Skip to content

Commit c884ad9

Browse files
authored
Merge pull request #1226 from peterwicksstringfield/easy_hlint_fixes
Easy hlint fixes
2 parents b1d912a + 3938faa commit c884ad9

File tree

38 files changed

+64
-113
lines changed

38 files changed

+64
-113
lines changed

GenChangelogs.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -33,4 +33,4 @@ main = do
3333
forM_ prsAfterLastTag $ \SimplePullRequest{..} ->
3434
putStrLn $ T.unpack $ "- " <> simplePullRequestTitle <>
3535
"\n([#" <> T.pack (show $ unIssueNumber simplePullRequestNumber) <> ")](" <> getUrl simplePullRequestHtmlUrl <> ")" <>
36-
" by @" <> (untagName (simpleUserLogin simplePullRequestUser))
36+
" by @" <> untagName (simpleUserLogin simplePullRequestUser)

exe/Main.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ main = withUtf8 $ do
1616

1717
let withExamples =
1818
case args of
19-
LspMode (LspArguments{..}) -> argsExamplePlugin
20-
_ -> False
19+
LspMode LspArguments{..} -> argsExamplePlugin
20+
_ -> False
2121

2222
defaultMain args (idePlugins withExamples)

exe/Wrapper.hs

+2-3
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,7 @@ launchHaskellLanguageServer LspArguments{..} = do
7373
hPutStrLn stderr $ showProgramVersionOfInterest programsOfInterest
7474
hPutStrLn stderr ""
7575
-- Get the ghc version -- this might fail!
76-
hPutStrLn stderr $ "Consulting the cradle to get project GHC version..."
76+
hPutStrLn stderr "Consulting the cradle to get project GHC version..."
7777
ghcVersion <- getRuntimeGhcVersion' cradle
7878
hPutStrLn stderr $ "Project GHC version: " ++ ghcVersion
7979

@@ -136,12 +136,11 @@ getRuntimeGhcVersion' cradle = do
136136
-- of the project that may or may not be accurate.
137137
findLocalCradle :: FilePath -> IO (Cradle Void)
138138
findLocalCradle fp = do
139-
cradleConf <- (findCradle defaultLoadingOptions) fp
139+
cradleConf <- findCradle defaultLoadingOptions fp
140140
crdl <- case cradleConf of
141141
Just yaml -> do
142142
hPutStrLn stderr $ "Found \"" ++ yaml ++ "\" for \"" ++ fp ++ "\""
143143
loadCradle yaml
144144
Nothing -> loadImplicitCradle fp
145145
hPutStrLn stderr $ "Module \"" ++ fp ++ "\" is loaded by Cradle: " ++ show crdl
146146
return crdl
147-

ghcide/test/src/Development/IDE/Test.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -168,7 +168,7 @@ checkDiagnosticsForDoc :: TextDocumentIdentifier -> [(DiagnosticSeverity, Cursor
168168
checkDiagnosticsForDoc TextDocumentIdentifier {_uri} expected obtained = do
169169
let expected' = Map.fromList [(nuri, map (\(ds, c, t) -> (ds, c, t, Nothing)) expected)]
170170
nuri = toNormalizedUri _uri
171-
expectDiagnosticsWithTags' (return $ (_uri, List obtained)) expected'
171+
expectDiagnosticsWithTags' (return (_uri, List obtained)) expected'
172172

173173
canonicalizeUri :: Uri -> IO Uri
174174
canonicalizeUri uri = filePathToUri <$> canonicalizePath (fromJust (uriToFilePath uri))

hie-compat/src-ghc86/Compat/HieBin.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -97,7 +97,7 @@ writeHieFile hie_file_path hiefile = do
9797
-- hieVersion and the GHC version used to generate this file
9898
mapM_ (putByte bh0) hieMagic
9999
putBinLine bh0 $ BSC.pack $ show hieVersion
100-
putBinLine bh0 $ ghcVersion
100+
putBinLine bh0 ghcVersion
101101

102102
-- remember where the dictionary pointer will go
103103
dict_p_p <- tellBin bh0
@@ -297,7 +297,7 @@ getSymbolTable bh ncu = do
297297
getSymTabName :: SymbolTable -> BinHandle -> IO Name
298298
getSymTabName st bh = do
299299
i :: Word32 <- get bh
300-
return $ st A.! (fromIntegral i)
300+
return $ st A.! fromIntegral i
301301

302302
putName :: HieSymbolTable -> BinHandle -> Name -> IO ()
303303
putName (HieSymbolTable next ref) bh name = do

hie-compat/src-ghc86/Compat/HieDebug.hs

+5-6
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-
22
Functions to validate and check .hie file ASTs generated by GHC.
33
-}
4-
{-# LANGUAGE StandaloneDeriving #-}
54
{-# LANGUAGE OverloadedStrings #-}
65
{-# LANGUAGE FlexibleContexts #-}
76
module Compat.HieDebug where
@@ -22,10 +21,10 @@ import Data.Function ( on )
2221
import Data.List ( sortOn )
2322
import Data.Foldable ( toList )
2423

25-
ppHies :: Outputable a => (HieASTs a) -> SDoc
24+
ppHies :: Outputable a => HieASTs a -> SDoc
2625
ppHies (HieASTs asts) = M.foldrWithKey go "" asts
2726
where
28-
go k a rest = vcat $
27+
go k a rest = vcat
2928
[ "File: " <> ppr k
3029
, ppHie a
3130
, rest
@@ -112,9 +111,9 @@ validAst (Node _ span children) = do
112111
]
113112
checkContainment [] = return ()
114113
checkContainment (x:xs)
115-
| span `containsSpan` (nodeSpan x) = checkContainment xs
114+
| span `containsSpan` nodeSpan x = checkContainment xs
116115
| otherwise = Left $ hsep
117-
[ ppr $ span
116+
[ ppr span
118117
, "does not contain"
119118
, ppr $ nodeSpan x
120119
]
@@ -139,7 +138,7 @@ validateScopes asts = M.foldrWithKey (\k a b -> valid k a ++ b) [] refMap
139138
[] -> []
140139
_ -> if any (`scopeContainsSpan` sp) scopes
141140
then []
142-
else return $ hsep $
141+
else return $ hsep
143142
[ "Name", ppr n, "at position", ppr sp
144143
, "doesn't occur in calculated scope", ppr scopes]
145144
| otherwise = []

hie-compat/src-ghc86/Compat/HieTypes.hs

+10-11
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@ For more information see https://gitlab.haskell.org/ghc/ghc/wikis/hie-files
55
-}
66
{-# LANGUAGE DeriveTraversable #-}
77
{-# LANGUAGE DeriveDataTypeable #-}
8-
{-# LANGUAGE TypeSynonymInstances #-}
98
{-# LANGUAGE FlexibleInstances #-}
109
{-# LANGUAGE ScopedTypeVariables #-}
1110
{-# OPTIONS_GHC -Wno-orphans #-}
@@ -168,7 +167,7 @@ data HieType a
168167
type HieTypeFlat = HieType TypeIndex
169168

170169
-- | Roughly isomorphic to the original core 'Type'.
171-
newtype HieTypeFix = Roll (HieType (HieTypeFix))
170+
newtype HieTypeFix = Roll (HieType HieTypeFix)
172171

173172
instance Binary (HieType TypeIndex) where
174173
put_ bh (HTyVarTy n) = do
@@ -200,7 +199,7 @@ instance Binary (HieType TypeIndex) where
200199
put_ bh (HCastTy a) = do
201200
putByte bh 7
202201
put_ bh a
203-
put_ bh (HCoercionTy) = putByte bh 8
202+
put_ bh HCoercionTy = putByte bh 8
204203

205204
get bh = do
206205
(t :: Word8) <- get bh
@@ -228,7 +227,7 @@ instance Binary (HieArgs TypeIndex) where
228227

229228
-- | Mapping from filepaths (represented using 'FastString') to the
230229
-- corresponding AST
231-
newtype HieASTs a = HieASTs { getAsts :: (M.Map FastString (HieAST a)) }
230+
newtype HieASTs a = HieASTs { getAsts :: M.Map FastString (HieAST a) }
232231
deriving (Functor, Foldable, Traversable)
233232

234233
instance Binary (HieASTs TypeIndex) where
@@ -276,9 +275,9 @@ instance Binary (NodeInfo TypeIndex) where
276275
put_ bh $ nodeType ni
277276
put_ bh $ M.toList $ nodeIdentifiers ni
278277
get bh = NodeInfo
279-
<$> fmap (S.fromDistinctAscList) (get bh)
278+
<$> fmap S.fromDistinctAscList (get bh)
280279
<*> get bh
281-
<*> fmap (M.fromList) (get bh)
280+
<*> fmap M.fromList (get bh)
282281

283282
type Identifier = Either ModuleName Name
284283

@@ -309,7 +308,7 @@ instance Binary (IdentifierDetails TypeIndex) where
309308
put_ bh $ S.toAscList $ identInfo dets
310309
get bh = IdentifierDetails
311310
<$> get bh
312-
<*> fmap (S.fromDistinctAscList) (get bh)
311+
<*> fmap S.fromDistinctAscList (get bh)
313312

314313

315314
-- | Different contexts under which identifiers exist
@@ -419,7 +418,7 @@ data IEType
419418

420419
instance Binary IEType where
421420
put_ bh b = putByte bh (fromIntegral (fromEnum b))
422-
get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
421+
get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
423422

424423

425424
data RecFieldContext
@@ -431,7 +430,7 @@ data RecFieldContext
431430

432431
instance Binary RecFieldContext where
433432
put_ bh b = putByte bh (fromIntegral (fromEnum b))
434-
get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
433+
get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
435434

436435

437436
data BindType
@@ -441,7 +440,7 @@ data BindType
441440

442441
instance Binary BindType where
443442
put_ bh b = putByte bh (fromIntegral (fromEnum b))
444-
get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
443+
get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
445444

446445

447446
data DeclType
@@ -456,7 +455,7 @@ data DeclType
456455

457456
instance Binary DeclType where
458457
put_ bh b = putByte bh (fromIntegral (fromEnum b))
459-
get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
458+
get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
460459

461460

462461
data Scope

hie-compat/src-ghc86/Compat/HieUtils.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -62,11 +62,11 @@ resolveVisibility kind ty_args
6262
ts' = go (extendTvSubst env tv t) res ts
6363

6464
go env (FunTy _ res) (t:ts) -- No type-class args in tycon apps
65-
= (True,t) : (go env res ts)
65+
= (True,t) : go env res ts
6666

6767
go env (TyVarTy tv) ts
6868
| Just ki <- lookupTyVar env tv = go env ki ts
69-
go env kind (t:ts) = (True, t) : (go env kind ts) -- Ill-kinded
69+
go env kind (t:ts) = (True, t) : go env kind ts -- Ill-kinded
7070

7171
foldType :: (HieType a -> a) -> HieTypeFix -> a
7272
foldType f (Roll t) = f $ fmap (foldType f) t
@@ -114,7 +114,7 @@ compressTypes
114114
-> (HieASTs TypeIndex, A.Array TypeIndex HieTypeFlat)
115115
compressTypes asts = (a, arr)
116116
where
117-
(a, (HTS _ m i)) = flip runState initialHTS $
117+
(a, HTS _ m i) = flip runState initialHTS $
118118
for asts $ \typ -> do
119119
i <- getTypeIndex typ
120120
return i

hls-plugin-api/src/Ide/Types.hs

-1
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
{-# LANGUAGE GADTs #-}
2-
{-# LANGUAGE OverloadedStrings #-}
32
{-# LANGUAGE ScopedTypeVariables #-}
43

54
module Ide.Types

install/src/Cabal.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ getGhcPathOfOrThrowError versionNumber =
4646

4747
cabalInstallHls :: VersionNumber -> [String] -> Action ()
4848
cabalInstallHls versionNumber args = do
49-
localBin <- liftIO $ getInstallDir
49+
localBin <- liftIO getInstallDir
5050
cabalVersion <- getCabalVersion args
5151
ghcPath <- getGhcPathOfOrThrowError versionNumber
5252

install/src/HlsInstall.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ defaultMain = do
3838
let args = [verbosityArg (shakeVerbosity shakeOptionsRules)]
3939

4040
phony "show-options" $ do
41-
putNormal $ "Options:"
41+
putNormal "Options:"
4242
putNormal $ " Verbosity level: " ++ show (shakeVerbosity shakeOptionsRules)
4343

4444
want ["short-help"]
@@ -51,7 +51,7 @@ defaultMain = do
5151
phony "data" $ do
5252
need ["show-options"]
5353
need ["check"]
54-
liftIO $ putStrLn "Generation of hoogle data files is disabled for now."
54+
liftIO $ putStrLn "Generation of hoogle data files is disabled for now."
5555
-- if isRunFromStack then stackBuildData args else cabalBuildData args
5656

5757
forM_
@@ -90,7 +90,7 @@ defaultMain = do
9090
need ["icu-macos-fix-build"]
9191

9292
phony "icu-macos-fix-install" (command_ [] "brew" ["install", "icu4c"])
93-
phony "icu-macos-fix-build" $ mapM_ (flip buildIcuMacosFix $ args) versions
93+
phony "icu-macos-fix-build" $ mapM_ (flip buildIcuMacosFix args) versions
9494

9595

9696
buildIcuMacosFix :: VersionNumber -> [String] -> Action ()

plugins/default/src/Ide/Plugin/Example.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -128,7 +128,7 @@ codeLens _lf ideState plId CodeLensParams{_textDocument=TextDocumentIdentifier u
128128
-- edit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing
129129
range = Range (Position 3 0) (Position 4 0)
130130
let cmdParams = AddTodoParams uri "do abc"
131-
cmd <- mkLspCommand plId "codelens.todo" title (Just [(toJSON cmdParams)])
131+
cmd <- mkLspCommand plId "codelens.todo" title (Just [toJSON cmdParams])
132132
pure $ Right $ List [ CodeLens range (Just cmd) Nothing ]
133133
Nothing -> pure $ Right $ List []
134134

plugins/default/src/Ide/Plugin/Floskell.hs

-3
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,5 @@
1-
{-# LANGUAGE RecordWildCards #-}
21
{-# LANGUAGE OverloadedStrings #-}
32
{-# LANGUAGE ScopedTypeVariables #-}
4-
{-# LANGUAGE TypeApplications #-}
5-
{-# LANGUAGE ViewPatterns #-}
63

74
module Ide.Plugin.Floskell
85
(

plugins/default/src/Ide/Plugin/Fourmolu.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
1+
{-# LANGUAGE DisambiguateRecordFields #-}
12
{-# LANGUAGE LambdaCase #-}
23
{-# LANGUAGE OverloadedStrings #-}
34
{-# LANGUAGE PackageImports #-}
4-
{-# LANGUAGE RecordWildCards #-}
55
{-# LANGUAGE TypeApplications #-}
66

77
module Ide.Plugin.Fourmolu (

plugins/default/src/Ide/Plugin/Ormolu.hs

-1
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE OverloadedStrings #-}
22
{-# LANGUAGE PackageImports #-}
3-
{-# LANGUAGE RecordWildCards #-}
43
{-# LANGUAGE ScopedTypeVariables #-}
54
{-# LANGUAGE TypeApplications #-}
65

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs

-1
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
{-# LANGUAGE ExtendedDefaultRules #-}
55
{-# LANGUAGE FlexibleContexts #-}
66
{-# LANGUAGE FlexibleInstances #-}
7-
{-# LANGUAGE ImplicitParams #-}
87
{-# LANGUAGE NamedFieldPuns #-}
98
{-# LANGUAGE OverloadedStrings #-}
109
{-# LANGUAGE RankNTypes #-}

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Parse/Option.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -30,4 +30,4 @@ langOptions = runParser (many space *> languageOpts <* many space)
3030
-- >>> runParser languageOpts ":set -XBinaryLiterals -XOverloadedStrings"
3131
-- Right ["BinaryLiterals","OverloadedStrings"]
3232
languageOpts :: Parser Char [[Char]]
33-
languageOpts = string ":set" *> many (many space *> string "-X" *> (many letterChar))
33+
languageOpts = string ":set" *> many (many space *> string "-X" *> many letterChar)

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Util.hs

-1
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE ImplicitParams #-}
21
{-# LANGUAGE ScopedTypeVariables #-}
32
{-# LANGUAGE NoMonomorphismRestriction #-}
43
{-# OPTIONS_GHC -Wno-orphans #-}

plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs

+3-5
Original file line numberDiff line numberDiff line change
@@ -3,13 +3,11 @@
33
{-# LANGUAGE DeriveGeneric #-}
44
{-# LANGUAGE DerivingStrategies #-}
55
{-# LANGUAGE DuplicateRecordFields #-}
6-
{-# LANGUAGE LambdaCase #-}
76
{-# LANGUAGE NamedFieldPuns #-}
87
{-# LANGUAGE OverloadedStrings #-}
98
{-# LANGUAGE RecordWildCards #-}
109
{-# LANGUAGE ScopedTypeVariables #-}
1110
{-# LANGUAGE TypeFamilies #-}
12-
{-# LANGUAGE ViewPatterns #-}
1311

1412
#include "ghc-api-version.h"
1513

@@ -189,10 +187,10 @@ minimalImportsRule = define $ \MinimalImports nfp -> do
189187

190188
-- | Use the ghc api to extract a minimal, explicit set of imports for this module
191189
extractMinimalImports ::
192-
Maybe (HscEnvEq) ->
193-
Maybe (TcModuleResult) ->
190+
Maybe HscEnvEq ->
191+
Maybe TcModuleResult ->
194192
IO ([LImportDecl GhcRn], Maybe [LImportDecl GhcRn])
195-
extractMinimalImports (Just (hsc)) (Just (TcModuleResult {..})) = do
193+
extractMinimalImports (Just hsc) (Just TcModuleResult {..}) = do
196194
-- extract the original imports and the typechecking environment
197195
let tcEnv = tmrTypechecked
198196
(_, imports, _, _) = tmrRenamed

plugins/hls-hlint-plugin/src/Ide/Plugin/Hlint.hs

-3
Original file line numberDiff line numberDiff line change
@@ -7,10 +7,7 @@
77
{-# LANGUAGE FlexibleInstances #-}
88
{-# LANGUAGE OverloadedStrings #-}
99
{-# LANGUAGE PackageImports #-}
10-
{-# LANGUAGE RecordWildCards #-}
11-
{-# LANGUAGE TupleSections #-}
1210
{-# LANGUAGE TypeFamilies #-}
13-
{-# LANGUAGE ViewPatterns #-}
1411

1512
module Ide.Plugin.Hlint
1613
(

0 commit comments

Comments
 (0)