diff --git a/.github/workflows/lint.yml b/.github/workflows/lint.yml new file mode 100644 index 0000000..982e41f --- /dev/null +++ b/.github/workflows/lint.yml @@ -0,0 +1,21 @@ +name: lint +on: + pull_request: + push: + branches: + - master + +jobs: + hlint: + runs-on: ubuntu-latest + steps: + - uses: actions/checkout@v4 + + - name: 'Set up HLint' + uses: haskell-actions/hlint-setup@v2 + + - name: 'Run HLint' + uses: haskell-actions/hlint-run@v2 + with: + path: src/ + fail-on: warning diff --git a/.hlint.yaml b/.hlint.yaml new file mode 100644 index 0000000..68f9a94 --- /dev/null +++ b/.hlint.yaml @@ -0,0 +1,67 @@ +# HLint configuration file +# https://github.com/ndmitchell/hlint +########################## +# Warnings currently triggered by your code + + +# Specify additional command line arguments +# +# - arguments: [--color, --cpp-simple, -XQuasiQuotes] + + +# Control which extensions/flags/modules/functions can be used +# +# - extensions: +# - default: false # all extension are banned by default +# - name: [PatternGuards, ViewPatterns] # only these listed extensions can be used +# - {name: CPP, within: CrossPlatform} # CPP can only be used in a given module +# +# - flags: +# - {name: -w, within: []} # -w is allowed nowhere +# +# - modules: +# - {name: [Data.Set, Data.HashSet], as: Set} # if you import Data.Set qualified, it must be as 'Set' +# - {name: Control.Arrow, within: []} # Certain modules are banned entirely +# +# - functions: +# - {name: unsafePerformIO, within: []} # unsafePerformIO can only appear in no modules + + +# Add custom hints for this project +# +# Will suggest replacing "wibbleMany [myvar]" with "wibbleOne myvar" +# - error: {lhs: "wibbleMany [x]", rhs: wibbleOne x} + +# The hints are named by the string they display in warning messages. +# For example, if you see a warning starting like +# +# Main.hs:116:51: Warning: Redundant == +# +# You can refer to that hint with `{name: Redundant ==}` (see below). + +# Turn on hints that are off by default +# +# Ban "module X(module X) where", to require a real export list +# - warn: {name: Use explicit module export list} +# +# Replace a $ b $ c with a . b $ c +# - group: {name: dollar, enabled: true} +# +# Generalise map to fmap, ++ to <> +# - group: {name: generalise, enabled: true} +# +# Warn on use of partial functions +# - group: {name: partial, enabled: true} + + +# Ignore some builtin hints +# - ignore: {name: Use let} +# - ignore: {name: Use const, within: SpecialModule} # Only within certain modules + + +# Define some custom infix operators +# - fixity: infixr 3 ~^#^~ + + +# To generate a suitable file for HLint do: +# $ hlint --default > .hlint.yaml diff --git a/src/Cornelis/Agda.hs b/src/Cornelis/Agda.hs index 28d9d8e..28da3e6 100644 --- a/src/Cornelis/Agda.hs +++ b/src/Cornelis/Agda.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE NumDecimals #-} + {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} diff --git a/src/Cornelis/Diff.hs b/src/Cornelis/Diff.hs index 4b574da..f66d66c 100644 --- a/src/Cornelis/Diff.hs +++ b/src/Cornelis/Diff.hs @@ -49,7 +49,7 @@ modifyDiff buf f = do -- | Reset the diff to an empty diff. resetDiff :: BufferNum -> Neovim CornelisEnv () -resetDiff buf = modifyDiff buf $ \_ -> (D.emptyDiff, ()) +resetDiff buf = modifyDiff buf $ const (D.emptyDiff, ()) -- | Add a buffer update (insertion or deletion) to the diff. -- The buffer update event coming from Vim is structured exactly how the diff-loc diff --git a/src/Cornelis/Goals.hs b/src/Cornelis/Goals.hs index 2267c56..4517845 100644 --- a/src/Cornelis/Goals.hs +++ b/src/Cornelis/Goals.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedLabels #-} + {-# LANGUAGE OverloadedStrings #-} module Cornelis.Goals where @@ -63,11 +63,9 @@ findGoal hunt = withAgda $ do prevGoal :: Neovim CornelisEnv () prevGoal = findGoal $ \pos goal -> - case pos > goal of - False -> Nothing - True -> Just $ ( p_line goal .-. p_line pos - , p_col goal .-. p_col pos -- TODO: This formula looks fishy - ) + (if pos > goal then Just ( p_line goal .-. p_line pos + , p_col goal .-. p_col pos -- TODO: This formula looks fishy + ) else Nothing) ------------------------------------------------------------------------------ @@ -75,11 +73,9 @@ prevGoal = nextGoal :: Neovim CornelisEnv () nextGoal = findGoal $ \pos goal -> - case pos < goal of - False -> Nothing - True -> Just $ Down ( p_line goal .-. p_line pos - , p_col goal .-. p_col pos - ) + (if pos < goal then Just $ Down ( p_line goal .-. p_line pos + , p_col goal .-. p_col pos + ) else Nothing) ------------------------------------------------------------------------------ -- | Uses highlighting extmarks to determine what a hole is; since the user @@ -89,7 +85,7 @@ getGoalAtCursor = do w <- nvim_get_current_win b <- window_get_buffer w p <- getWindowCursor w - fmap (b, ) $ getGoalAtPos b p + (b, ) <$> getGoalAtPos b p getGoalAtPos @@ -100,9 +96,7 @@ getGoalAtPos b p = do fmap (getFirst . fold) $ withBufferStuff b $ \bs -> do for (bs_ips bs) $ \ip -> do int <- getIpInterval b ip - pure $ case containsPoint int p of - False -> mempty - True -> pure $ ip { ip_intervalM = Identity int } + pure (if containsPoint int p then pure $ ip { ip_intervalM = Identity int } else mempty) ------------------------------------------------------------------------------ -- | Run a continuation on a goal at the current position in the current @@ -114,7 +108,7 @@ withGoalAtCursor f = getGoalAtCursor >>= \case (_, Nothing) -> do reportInfo "No goal at cursor" pure Nothing - (b, Just ip) -> fmap Just $ f b ip + (b, Just ip) -> (Just <$> f b ip) ------------------------------------------------------------------------------ -- | Run the first continuation on the goal at the current position, @@ -150,20 +144,20 @@ withGoalContentsOrPrompt prompt_str on_goal on_no_goal = getGoalAtCursor >>= \ca ------------------------------------------------------------------------------ -- | Get the contents of a goal. -getGoalContents_maybe :: Buffer -> InteractionPoint Identity -> Neovim CornelisEnv (Maybe Text) -getGoalContents_maybe b ip = do +getGoalContentsMaybe :: Buffer -> InteractionPoint Identity -> Neovim CornelisEnv (Maybe Text) +getGoalContentsMaybe b ip = do int <- getIpInterval b ip - iv <- fmap T.strip $ getBufferInterval b int + iv <- T.strip <$> getBufferInterval b int pure $ case iv of "?" -> Nothing -- Chop off {!, !} and trim any spaces. - _ -> Just $ T.strip $ T.dropEnd 2 $ T.drop 2 $ iv + _ -> Just $ T.strip $ T.dropEnd 2 $ T.drop 2 iv ------------------------------------------------------------------------------ -- | Like 'getGoalContents_maybe'. getGoalContents :: Buffer -> InteractionPoint Identity -> Neovim CornelisEnv Text -getGoalContents b ip = fromMaybe "" <$> getGoalContents_maybe b ip +getGoalContents b ip = fromMaybe "" <$> getGoalContentsMaybe b ip ------------------------------------------------------------------------------ diff --git a/src/Cornelis/Highlighting.hs b/src/Cornelis/Highlighting.hs index 40824e4..c880400 100644 --- a/src/Cornelis/Highlighting.hs +++ b/src/Cornelis/Highlighting.hs @@ -21,7 +21,7 @@ import Data.Functor ((<&>)) import Data.IntervalMap.FingerTree (IntervalMap) import qualified Data.IntervalMap.FingerTree as IM import qualified Data.Map as M -import Data.Maybe (listToMaybe, catMaybes) +import Data.Maybe (listToMaybe, catMaybes, mapMaybe) import qualified Data.Text as T import Data.Text.Encoding (encodeUtf8) import Data.Traversable (for) @@ -90,15 +90,13 @@ addHighlight b lis hl = do case Interval <$> lookupPoint lis (hl_start hl) <*> lookupPoint lis (hl_end hl) of - Just (int@(Interval start end)) -> do + Just int@(Interval start end) -> do ext <- setHighlight b int $ parseHighlightGroup hl - fmap (, ext) $ case isHole hl of - False -> pure mempty - True -> do - let vint = Interval start end - aint <- traverse (unvimify b) vint - pure $ maybe mempty (M.singleton aint) ext + (, ext) <$> (if isHole hl then (do + let vint = Interval start end + aint <- traverse (unvimify b) vint + pure $ maybe mempty (M.singleton aint) ext) else pure mempty) Nothing -> pure (mempty, Nothing) where -- Convert the first atom in a reply to a custom highlight @@ -114,10 +112,10 @@ addHighlight b lis hl = do -- TODO: Investigate whether is is possible/feasible to -- attach multiple HL groups to buffer locations. parseHighlightGroup :: Highlight -> Maybe HighlightGroup - parseHighlightGroup = listToMaybe . catMaybes . map atomToHlGroup . hl_atoms + parseHighlightGroup = listToMaybe . mapMaybe atomToHlGroup . hl_atoms isHole :: Highlight -> Bool - isHole = any (== "hole") . hl_atoms + isHole = elem "hole" . hl_atoms setHighlight :: Buffer @@ -143,8 +141,7 @@ setHighlight' b (Interval (Pos sl sc) (Pos el ec)) hl = do $ fmap (Just . coerce) $ nvim_buf_set_extmark b ns (from0 sl) (from0 sc) $ M.fromList - $ catMaybes - $ [ Just + $ catMaybes [ Just ( "end_line" , ObjectInt $ from0 el ) @@ -194,10 +191,10 @@ parseExtmark b } parseExtmark _ _ = pure Nothing -#if __GLASGOW_HASKELL__ <= 904 + hoistMaybe :: Applicative m => Maybe a -> MaybeT m a hoistMaybe = MaybeT . pure -#endif + getExtmarks :: Buffer -> AgdaPos -> Neovim CornelisEnv [ExtmarkStuff] @@ -212,7 +209,5 @@ getExtmarks b p = do marks <- fmap catMaybes $ traverse (parseExtmark b) $ V.toList res pure $ marks >>= \es -> - case containsPoint (es_interval es) p of - False -> mempty - True -> [es] + (if containsPoint (es_interval es) p then [es] else mempty) diff --git a/src/Cornelis/InfoWin.hs b/src/Cornelis/InfoWin.hs index 2fe5b8d..34b9ec5 100644 --- a/src/Cornelis/InfoWin.hs +++ b/src/Cornelis/InfoWin.hs @@ -70,12 +70,10 @@ showInfoWindow b doc = withBufferStuff b $ \bs -> do -- Check if the info win still exists, and if so, just modify it found <- fmap or $ for vis $ \(w, vb) -> do - case vb == iw_buffer ib of - False -> pure False - True -> do - writeInfoBuffer ns ib doc - resizeInfoWin w ib - pure True + (if vb == iw_buffer ib then (do + writeInfoBuffer ns ib doc + resizeInfoWin w ib + pure True) else pure False) -- Otherwise we need to rebuild it unless found $ do diff --git a/src/Cornelis/Offsets.hs b/src/Cornelis/Offsets.hs index 372ed25..d121c77 100644 --- a/src/Cornelis/Offsets.hs +++ b/src/Cornelis/Offsets.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DataKinds #-} -{-# LANGUAGE DerivingStrategies #-} + {-# LANGUAGE DerivingVia #-} {-# LANGUAGE RoleAnnotations #-} {-# LANGUAGE TypeFamilies #-} @@ -214,11 +214,11 @@ fromBytes t (Index i) | i < 0 = error $ "from bytes underflow" <> show (t, i) fromBytes _ (Index 0) = Index 0 fromBytes t (Index i) | Just (c, str) <- T.uncons t = let diff = BS.length $ encodeUtf8 $ T.singleton c - in case i - diff >= 0 of - True -> Index $ 1 + coerce (fromBytes str (Index (i - diff))) - -- We ran out of bytes in the middle of a multibyte character. Just - -- return the one we're on, and don't underflow! - False -> Index 0 + in if i - diff >= 0 + then Index $ 1 + coerce (fromBytes str (Index (i - diff))) + -- We ran out of bytes in the middle of a multibyte character. Just + -- return the one we're on, and don't underflow! + else Index 0 fromBytes t i = error $ "missing bytes: " <> show (t, i) addCol :: Pos e i j -> Offset e -> Pos e i j diff --git a/src/Cornelis/Pretty.hs b/src/Cornelis/Pretty.hs index 27fd266..1e6f7db 100644 --- a/src/Cornelis/Pretty.hs +++ b/src/Cornelis/Pretty.hs @@ -119,7 +119,7 @@ renderWithHlGroups = go [] 0 0 prettyType :: C.Type -> Doc HighlightGroup -prettyType (C.Type ty) = annotate CornelisType $ sep $ fmap pretty $ T.lines ty +prettyType (C.Type ty) = annotate CornelisType $ sep (pretty <$> T.lines ty) groupScopeSet :: [InScope] -> [[InScope]] @@ -149,7 +149,7 @@ prettyGoals (GoalSpecific _ scoped ty mhave mboundary mconstraints) = [ annotate CornelisTitle "Have:" <+> prettyType have | have <- maybeToList mhave ] <> - [ vcat $ fmap prettyInScopeSet $ groupScopeSet scoped + [ vcat (prettyInScopeSet <$> groupScopeSet scoped) ] <> [ section "Constraints" (fromMaybe [] mconstraints) pretty ] @@ -233,5 +233,5 @@ prettyGoal (GoalInfo name ty) = prettyError :: Message -> Doc HighlightGroup prettyError (Message msg) = - let (hdr, body) = fmap (T.drop 1) $ T.break (== '\n') msg in + let (hdr, body) = (T.drop 1 <$> T.break (== '\n') msg) in vcat [ annotate CornelisError (pretty hdr) , pretty body ] diff --git a/src/Cornelis/Types.hs b/src/Cornelis/Types.hs index 7f6c9bd..d9b6c47 100644 --- a/src/Cornelis/Types.hs +++ b/src/Cornelis/Types.hs @@ -9,6 +9,8 @@ {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wno-orphans #-} +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} +{-# HLINT ignore "Use camelCase" #-} module Cornelis.Types ( module Cornelis.Types @@ -207,7 +209,7 @@ ip_interval' :: InteractionPoint Identity -> AgdaInterval ip_interval' (InteractionPoint _ (Identity i)) = i sequenceInteractionPoint :: Applicative f => InteractionPoint f -> f (InteractionPoint Identity) -sequenceInteractionPoint (InteractionPoint n f) = InteractionPoint <$> pure n <*> fmap Identity f +sequenceInteractionPoint (InteractionPoint n f) = InteractionPoint n <$> fmap Identity f data NamedPoint = NamedPoint @@ -307,13 +309,13 @@ data DisplayInfo | UnknownDisplayInfo Value deriving (Eq, Ord, Show, Generic) -data TypeAux = TypeAux +newtype TypeAux = TypeAux { ta_expr :: Type } instance FromJSON TypeAux where parseJSON = withObject "TypeAux" $ \obj -> - (TypeAux . Type) <$> obj .: "expr" + TypeAux . Type <$> obj .: "expr" instance FromJSON DisplayInfo where parseJSON v = flip (withObject "DisplayInfo") v $ \obj -> diff --git a/src/Cornelis/Types/Agda.hs b/src/Cornelis/Types/Agda.hs index eec020f..c62e9c2 100644 --- a/src/Cornelis/Types/Agda.hs +++ b/src/Cornelis/Types/Agda.hs @@ -1,5 +1,7 @@ {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DataKinds #-} +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} +{-# HLINT ignore "Use camelCase" #-} module Cornelis.Types.Agda where diff --git a/src/Cornelis/Utils.hs b/src/Cornelis/Utils.hs index b032290..73f9adb 100644 --- a/src/Cornelis/Utils.hs +++ b/src/Cornelis/Utils.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DerivingVia #-} {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ViewPatterns #-} + {-# OPTIONS_GHC -Wno-orphans #-} @@ -49,17 +49,15 @@ savingCurrentWindow m = do windowsForBuffer :: Buffer -> Neovim env [Window] windowsForBuffer b = do - wins <- fmap V.toList $ vim_get_windows + wins <- V.toList <$> vim_get_windows fmap catMaybes $ for wins $ \w -> do wb <- window_get_buffer w - pure $ case wb == b of - False -> Nothing - True -> Just w + pure (if wb == b then Just w else Nothing) visibleBuffers :: Neovim env [(Window, Buffer)] visibleBuffers = do - wins <- fmap V.toList $ vim_get_windows - for wins $ \w -> fmap (w, ) $ window_get_buffer w + wins <- V.toList <$> vim_get_windows + for wins $ \w -> (w, ) <$> window_get_buffer w criticalFailure :: Text -> Neovim env a criticalFailure err = do diff --git a/src/Cornelis/Vim.hs b/src/Cornelis/Vim.hs index ad77ab1..8f203e3 100644 --- a/src/Cornelis/Vim.hs +++ b/src/Cornelis/Vim.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedLabels #-} + {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ViewPatterns #-} @@ -100,7 +100,7 @@ getBufferInterval b (Interval start end) = do Pos sl _ <- vimify b start Pos el _ <- vimify b end -- nvim_buf_get_lines is exclusive in its end line, thus the plus 1 - ls <- fmap toList $ nvim_buf_get_lines b (from0 sl) (from0 el + 1) False + ls <- toList <$> nvim_buf_get_lines b (from0 sl) (from0 el + 1) False pure $ T.unlines $ ls & _last %~ T.take (from1 (p_col end)) & _head %~ T.drop (from1 (p_col start)) diff --git a/src/Lib.hs b/src/Lib.hs index 66e0f05..76c5559 100644 --- a/src/Lib.hs +++ b/src/Lib.hs @@ -9,8 +9,7 @@ module Lib where import Control.Arrow ((&&&)) import Control.Concurrent.Chan.Unagi import Control.Lens -import Control.Monad (forever) -import Control.Monad (when) +import Control.Monad ( forever, when ) import Control.Monad.State.Class (gets) import Cornelis.Config (getConfig) import Cornelis.Debug (reportExceptions) @@ -55,7 +54,7 @@ respond b (DisplayInfo dp) = do -- Update the buffer's interaction points map respond b (InteractionPoints ips) = do let ips' = mapMaybe sequenceInteractionPoint ips - modifyBufferStuff b $ #bs_ips .~ (M.fromList $ fmap (ip_id &&& id) ips') + modifyBufferStuff b $ #bs_ips .~ M.fromList (fmap (ip_id &&& id) ips') -- Replace a function clause respond b (MakeCase mkcase) = do doMakeCase b mkcase @@ -89,9 +88,9 @@ respond b ClearHighlighting = do respond b (HighlightingInfo _remove hl) = do extmap <- highlightBuffer b hl modifyBufferStuff b $ \bs -> bs - & #bs_ip_exts <>~ M.compose extmap (fmap ip_interval' $ bs_ips $ bs) + & #bs_ip_exts <>~ M.compose extmap (ip_interval' <$> bs_ips bs) respond _ (RunningInfo _ x) = reportInfo x -respond _ (ClearRunningInfo) = reportInfo "" +respond _ ClearRunningInfo = reportInfo "" respond b (JumpToError _ pos) = do -- HACK(sandy): See #113. Agda reports error positions in sent messages -- relative to the *bytes* attached to the sent interval. But we can't easily @@ -104,7 +103,7 @@ respond b (JumpToError _ pos) = do case lookupPoint li pos of Nothing -> reportError "invalid error report from Agda" Just (Pos l c) -> do - ws <- fmap listToMaybe $ windowsForBuffer b + ws <- listToMaybe <$> windowsForBuffer b for_ ws $ flip window_set_cursor (fromOneIndexed (oneIndex l), fromZeroIndexed c) respond _ Status{} = pure () respond _ (Unknown k _) = reportError k @@ -116,8 +115,7 @@ doMakeCase b (RegularCase Function clauses ip) = do ins <- getIndent b (zeroIndex (p_line (iStart int))) replaceInterval b int $ T.unlines - $ fmap (T.replicate ins " " <>) - $ fmap replaceQuestion clauses + $ fmap ((T.replicate ins " " <>) . replaceQuestion) clauses -- TODO(sandy): It would be nice if Agda just gave us the bounds we're supposed to replace... doMakeCase b (RegularCase ExtendedLambda clauses ip) = do ws <- windowsForBuffer b diff --git a/src/Plugin.hs b/src/Plugin.hs index 89f2d0c..83ca126 100644 --- a/src/Plugin.hs +++ b/src/Plugin.hs @@ -2,12 +2,12 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ViewPatterns #-} + module Plugin where import Control.Lens -import Control.Monad ((>=>)) +import Control.Monad ((>=>), when) import Control.Monad.State.Class import Control.Monad.Trans import Cornelis.Agda (withCurrentBuffer, runIOTCM, withAgda, getAgda) @@ -65,7 +65,7 @@ gotoDefinition = withAgda $ do -- TODO(sandy): escape spaces vim_command $ "edit " <> ds_filepath ds b' <- window_get_buffer w - contents <- fmap (T.unlines . V.toList) $ buffer_get_lines b' 0 (-1) False + contents <- T.unlines . V.toList <$> buffer_get_lines b' 0 (-1) False let buffer_idx = toBytes contents $ zeroIndex $ ds_position ds -- TODO(sandy): use window_set_cursor instead? vim_command $ "keepjumps normal! " <> T.pack (show buffer_idx) <> "go" @@ -75,7 +75,7 @@ doLoad :: CommandArguments -> Neovim CornelisEnv () doLoad = const load atomicSwapIORef :: IORef a -> a -> IO a -atomicSwapIORef r x = atomicModifyIORef r (\y -> (x , y)) +atomicSwapIORef r x = atomicModifyIORef r (x,) load :: Neovim CornelisEnv () load = withAgda $ withCurrentBuffer $ \b -> do @@ -95,11 +95,11 @@ questionToMeta b = withBufferStuff b $ \bs -> do res <- fmap fold $ for (sortOn (Down . iStart . ip_interval') ips) $ \ip -> do int <- getIpInterval b ip - getGoalContents_maybe b ip >>= \case + getGoalContentsMaybe b ip >>= \case -- We only don't have a goal contents if we are a ? goal Nothing -> do replaceInterval b int "{! !}" - let int' = int { iEnd = (iStart int) `addCol` Offset 5 } + let int' = int { iEnd = iStart int `addCol` Offset 5 } void $ highlightInterval b int' CornelisHole modifyBufferStuff b $ #bs_ips %~ M.insert (ip_id ip) (ip & #ip_intervalM . #_Identity .~ int') @@ -108,9 +108,7 @@ questionToMeta b = withBufferStuff b $ \bs -> do Just _ -> pure $ Any False -- Force a save if we replaced any goals - case getAny res of - True -> load - False -> pure () + when (getAny res) load doAllGoals :: CommandArguments -> Neovim CornelisEnv () @@ -260,7 +258,7 @@ inferType :: Rewrite -> Neovim CornelisEnv () inferType mode = withAgda $ do cmd <- withGoalContentsOrPrompt "Infer type of what?" (\goal -> pure . Cmd_infer mode (ip_id goal) NoRange) - (\input -> pure $ Cmd_infer_toplevel mode input) + (pure . Cmd_infer_toplevel mode) runInteraction cmd @@ -313,7 +311,7 @@ doHelperFunc _ ms = withNormalizationMode ms $ \mode -> do doCaseSplit :: CommandArguments -> Neovim CornelisEnv () doCaseSplit _ = withAgda $ void $ withGoalAtCursor $ \b ip -> do - contents <- fmap T.strip $ getGoalContents b ip + contents <- T.strip <$> getGoalContents b ip thing <- bool (pure contents) (input @Text "Split on what?" Nothing Nothing) $ T.null contents @@ -337,15 +335,15 @@ goalWindow b = showInfoWindow b . prettyGoals computeModeCompletion :: String -> String -> Int -> Neovim env String computeModeCompletion _ _ _ = - pure $ unlines $ fmap show $ enumFromTo @ComputeMode minBound maxBound + pure $ unlines (show <$> enumFromTo @ComputeMode minBound maxBound) rewriteModeCompletion :: String -> String -> Int -> Neovim env String rewriteModeCompletion _ _ _ = - pure $ unlines $ fmap show $ enumFromTo @Rewrite minBound maxBound + pure $ unlines (show <$> enumFromTo @Rewrite minBound maxBound) debugCommandCompletion :: String -> String -> Int -> Neovim env String debugCommandCompletion _ _ _ = - pure $ unlines $ fmap show $ enumFromTo @DebugCommand minBound maxBound + pure $ unlines (show <$> enumFromTo @DebugCommand minBound maxBound) doDebug :: CommandArguments -> String -> Neovim CornelisEnv () @@ -358,7 +356,6 @@ doDebug _ str = Nothing -> vim_report_error $ T.pack $ "No matching debug command for " <> show str --- | The @on_bytes@ callback required by @nvim_buf_attach@. notifyEdit :: Text -- ^ the string "bytes" -> BufferNum -- ^ buffer handle diff --git a/test/PropertySpec.hs b/test/PropertySpec.hs index 3868f34..24b0d2d 100644 --- a/test/PropertySpec.hs +++ b/test/PropertySpec.hs @@ -46,7 +46,7 @@ spec = parallel $ do $ counterexample (show pn) $ counterexample (show $ strs !! rowidx) $ withVim (Seconds 1) $ \w b -> do - buffer_set_lines b 0 (-1) False $ V.fromList $ fmap T.pack $ strs + buffer_set_lines b 0 (-1) False $ V.fromList (T.pack <$> strs) setWindowCursor w pn ObjectInt row' <- vim_call_function "line" $ V.fromList [ObjectString "."] ObjectInt col' <- vim_call_function "virtcol" $ V.fromList [ObjectString "."] diff --git a/test/TestSpec.hs b/test/TestSpec.hs index b3ffa00..5b4e2ac 100644 --- a/test/TestSpec.hs +++ b/test/TestSpec.hs @@ -1,5 +1,5 @@ {-# LANGUAGE NumDecimals #-} -{-# LANGUAGE OverloadedLabels #-} + {-# LANGUAGE OverloadedStrings #-} module TestSpec where diff --git a/test/Utils.hs b/test/Utils.hs index 32323db..df9fa8f 100644 --- a/test/Utils.hs +++ b/test/Utils.hs @@ -1,6 +1,6 @@ {-# LANGUAGE NumDecimals #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ViewPatterns #-} + module Utils ( module Utils @@ -53,10 +53,10 @@ diff = ((filter (not . isCopy) . snd) .) . levenshtein @_ @_ @_ @Int differing :: Buffer -> Neovim env () -> Neovim env [Edit Text] differing b m = do - before <- fmap V.toList $ buffer_get_lines b 0 (-1) False + before <- V.toList <$> buffer_get_lines b 0 (-1) False m liftIO $ threadDelay 1e6 - after <- fmap V.toList $ buffer_get_lines b 0 (-1) False + after <- V.toList <$> buffer_get_lines b 0 (-1) False pure $ diff before after @@ -67,7 +67,7 @@ intervention b d m = do withVim :: Seconds -> (Window -> Buffer -> Neovim () ()) -> IO () withVim secs m = do - let withNeovimEmbedded f a = testWithEmbeddedNeovim f secs () a + let withNeovimEmbedded f = testWithEmbeddedNeovim f secs () withNeovimEmbedded Nothing $ do b <- nvim_create_buf False False w <- vim_get_current_window @@ -93,11 +93,11 @@ vimSpec -> (Window -> Buffer -> Neovim CornelisEnv ()) -> Spec vimSpec name secs fp m = do - let withNeovimEmbedded f a = testWithEmbeddedNeovim f secs () a + let withNeovimEmbedded f = testWithEmbeddedNeovim f secs () it name $ do withSystemTempFile "test.agda" $ \fp' h -> do hPutStr h $ "module " <> takeBaseName fp' <> " where\n" - hPutStr h =<< fmap (unlines . tail . lines) (readFile fp) + hPutStr h . unlines . tail . lines =<< readFile fp hFlush h withNeovimEmbedded Nothing $ do env <- cornelisInit