Skip to content

Commit 78f510e

Browse files
jhrcekmergify[bot]
andauthored
Fix most hlint warnings in ghcide (#3975)
* Fix most hlint warnings in ghcide * stylish-haskell --------- Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent b5a8063 commit 78f510e

File tree

16 files changed

+51
-51
lines changed

16 files changed

+51
-51
lines changed

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -534,7 +534,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
534534
-- compilation but these are the true source of
535535
-- information.
536536
new_deps = fmap (\(df, targets) -> RawComponentInfo (homeUnitId_ df) df targets cfp opts dep_info) newTargetDfs
537-
all_deps = new_deps `NE.appendList` maybe [] id oldDeps
537+
all_deps = new_deps `NE.appendList` fromMaybe [] oldDeps
538538
-- Get all the unit-ids for things in this component
539539
_inplace = map rawComponentUnitId $ NE.toList all_deps
540540

@@ -594,7 +594,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
594594
void $ modifyVar' fileToFlags $
595595
Map.insert hieYaml this_flags_map
596596
void $ modifyVar' filesMap $
597-
flip HM.union (HM.fromList (zip (map fst $ concatMap toFlagsMap all_targets) (repeat hieYaml)))
597+
flip HM.union (HM.fromList (map ((,hieYaml) . fst) $ concatMap toFlagsMap all_targets))
598598

599599
void $ extendKnownTargets all_targets
600600

@@ -685,7 +685,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
685685
-- again.
686686
modifyVar_ fileToFlags (const (return Map.empty))
687687
-- Keep the same name cache
688-
modifyVar_ hscEnvs (return . Map.adjust (\_ -> []) hieYaml )
688+
modifyVar_ hscEnvs (return . Map.adjust (const []) hieYaml )
689689
consultCradle hieYaml cfp
690690
else return (opts, Map.keys old_di)
691691
Nothing -> consultCradle hieYaml cfp

ghcide/session-loader/Development/IDE/Session/Implicit.hs

Lines changed: 12 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -3,26 +3,27 @@ module Development.IDE.Session.Implicit
33
) where
44

55

6-
import Control.Applicative ((<|>))
6+
import Control.Applicative ((<|>))
7+
import Control.Exception (handleJust)
78
import Control.Monad
8-
import Control.Monad.Trans.Maybe
99
import Control.Monad.IO.Class
10-
import Control.Exception (handleJust)
10+
import Control.Monad.Trans.Maybe
1111
import Data.Bifunctor
12+
import Data.Functor ((<&>))
1213
import Data.Maybe
1314
import Data.Void
15+
import System.Directory hiding (findFile)
1416
import System.FilePath
15-
import System.Directory hiding (findFile)
1617
import System.IO.Error
1718

18-
import Colog.Core (LogAction (..), WithSeverity (..))
19-
import HIE.Bios.Cradle (getCradle, defaultCradle)
19+
import Colog.Core (LogAction (..), WithSeverity (..))
2020
import HIE.Bios.Config
21-
import HIE.Bios.Types hiding (ActionName(..))
21+
import HIE.Bios.Cradle (defaultCradle, getCradle)
22+
import HIE.Bios.Types hiding (ActionName (..))
2223

23-
import Hie.Locate
2424
import Hie.Cabal.Parser
25-
import qualified Hie.Yaml as Implicit
25+
import Hie.Locate
26+
import qualified Hie.Yaml as Implicit
2627

2728
loadImplicitCradle :: Show a => LogAction IO (WithSeverity Log) -> FilePath -> IO (Cradle a)
2829
loadImplicitCradle l wfile = do
@@ -50,11 +51,11 @@ inferCradleTree start_dir =
5051
<|> (cabalExecutable >> cabalConfigDir start_dir >>= \dir -> cabalWorkDir dir >> pure (simpleCabalCradle dir))
5152
<|> (stackExecutable >> stackConfigDir start_dir >>= \dir -> stackWorkDir dir >> stackCradle dir)
5253
-- If we have a cabal.project OR we have a .cabal and dist-newstyle, prefer cabal
53-
<|> (cabalExecutable >> (cabalConfigDir start_dir <|> cabalFileAndWorkDir) >>= pure . simpleCabalCradle)
54+
<|> (cabalExecutable >> (cabalConfigDir start_dir <|> cabalFileAndWorkDir) <&> simpleCabalCradle)
5455
-- If we have a stack.yaml, use stack
5556
<|> (stackExecutable >> stackConfigDir start_dir >>= stackCradle)
5657
-- If we have a cabal file, use cabal
57-
<|> (cabalExecutable >> cabalFileDir start_dir >>= pure . simpleCabalCradle)
58+
<|> (cabalExecutable >> cabalFileDir start_dir <&> simpleCabalCradle)
5859

5960
where
6061
maybeItsBios = (\wdir -> (Bios (Program $ wdir </> ".hie-bios") Nothing Nothing, wdir)) <$> biosWorkDir start_dir

ghcide/src/Development/IDE/Core/Compile.hs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -297,8 +297,8 @@ captureSplicesAndDeps TypecheckHelpers{..} env k = do
297297
#endif
298298

299299
| n <- concatMap (uniqDSetToList . bcoFreeNames) $ bc_bcos bcos
300-
, Just mod <- [nameModule_maybe n] -- Names from other modules
301300
, not (isWiredInName n) -- Exclude wired-in names
301+
, Just mod <- [nameModule_maybe n] -- Names from other modules
302302
, moduleUnitId mod `elem` home_unit_ids -- Only care about stuff from the home package set
303303
]
304304
home_unit_ids =
@@ -340,7 +340,7 @@ captureSplicesAndDeps TypecheckHelpers{..} env k = do
340340
#else
341341
{- load it -}
342342
; fv_hvs <- loadDecls (hscInterp hsc_env') hsc_env' srcspan bcos
343-
; let hval = (expectJust "hscCompileCoreExpr'" $ lookup (idName binding_id) fv_hvs)
343+
; let hval = expectJust "hscCompileCoreExpr'" $ lookup (idName binding_id) fv_hvs
344344
#endif
345345

346346
; modifyIORef' var (flip extendModuleEnvList [(mi_module $ hm_iface hm, linkableHash lb) | lb <- lbs, let hm = linkableHomeMod lb])
@@ -595,7 +595,7 @@ mkHiFileResultCompile se session' tcm simplified_guts = catchErrs $ do
595595
-- SYB is slow but fine given that this is only used for testing
596596
noUnfoldings = everywhere $ mkT $ \v -> if isId v
597597
then
598-
let v' = if isOtherUnfolding (realIdUnfolding v) then (setIdUnfolding v noUnfolding) else v
598+
let v' = if isOtherUnfolding (realIdUnfolding v) then setIdUnfolding v noUnfolding else v
599599
in setIdOccInfo v' noOccInfo
600600
else v
601601
isOtherUnfolding (OtherCon _) = True
@@ -1256,9 +1256,9 @@ parseHeader
12561256
-> FilePath -- ^ the filename (for source locations)
12571257
-> Util.StringBuffer -- ^ Haskell module source text (full Unicode is supported)
12581258
#if MIN_VERSION_ghc(9,5,0)
1259-
-> ExceptT [FileDiagnostic] m ([FileDiagnostic], Located(HsModule GhcPs))
1259+
-> ExceptT [FileDiagnostic] m ([FileDiagnostic], Located (HsModule GhcPs))
12601260
#else
1261-
-> ExceptT [FileDiagnostic] m ([FileDiagnostic], Located(HsModule))
1261+
-> ExceptT [FileDiagnostic] m ([FileDiagnostic], Located HsModule)
12621262
#endif
12631263
parseHeader dflags filename contents = do
12641264
let loc = mkRealSrcLoc (Util.mkFastString filename) 1 1
@@ -1748,19 +1748,19 @@ pathToModuleName = mkModuleName . map rep
17481748
17491749
- CPP clauses should be placed at the end of the imports section. The clauses
17501750
should be ordered by the GHC version they target from earlier to later versions,
1751-
with negative if clauses coming before positive if clauses of the same
1752-
version. (If you think about which GHC version a clause activates for this
1751+
with negative if clauses coming before positive if clauses of the same
1752+
version. (If you think about which GHC version a clause activates for this
17531753
should make sense `!MIN_VERSION_GHC(9,0,0)` refers to 8.10 and lower which is
1754-
a earlier version than `MIN_VERSION_GHC(9,0,0)` which refers to versions 9.0
1754+
a earlier version than `MIN_VERSION_GHC(9,0,0)` which refers to versions 9.0
17551755
and later). In addition there should be a space before and after each CPP
17561756
clause.
17571757
1758-
- In if clauses that use `&&` and depend on more than one statement, the
1758+
- In if clauses that use `&&` and depend on more than one statement, the
17591759
positive statement should come before the negative statement. In addition the
17601760
clause should come after the single positive clause for that GHC version.
17611761
1762-
- There shouldn't be multiple identical CPP statements. The use of odd or even
1762+
- There shouldn't be multiple identical CPP statements. The use of odd or even
17631763
GHC numbers is identical, with the only preference being to use what is
1764-
already there. (i.e. (`MIN_VERSION_GHC(9,2,0)` and `MIN_VERSION_GHC(9,1,0)`
1764+
already there. (i.e. (`MIN_VERSION_GHC(9,2,0)` and `MIN_VERSION_GHC(9,1,0)`
17651765
are functionally equivalent)
17661766
-}

ghcide/src/Development/IDE/Core/FileStore.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -265,7 +265,7 @@ registerFileWatches globs = do
265265
-- our purposes.
266266
registration = LSP.TRegistration { _id ="globalFileWatches"
267267
, _method = LSP.SMethod_WorkspaceDidChangeWatchedFiles
268-
, _registerOptions = Just $ regOptions}
268+
, _registerOptions = Just regOptions}
269269
regOptions =
270270
DidChangeWatchedFilesRegistrationOptions { _watchers = watchers }
271271
-- See Note [File existence cache and LSP file watchers] for why this exists, and the choice of watch kind

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -372,7 +372,7 @@ getLocatedImportsRule recorder =
372372
let import_dirs = deps env_eq
373373
let dflags = hsc_dflags env
374374
isImplicitCradle = isNothing $ envImportPaths env_eq
375-
dflags' <- return $ if isImplicitCradle
375+
let dflags' = if isImplicitCradle
376376
then addRelativeImport file (moduleName $ ms_mod ms) dflags
377377
else dflags
378378
opt <- getIdeOptions
@@ -538,7 +538,7 @@ reportImportCyclesRule recorder =
538538
let cycles = mapMaybe (cycleErrorInFile fileId) (toList errs)
539539
-- Convert cycles of files into cycles of module names
540540
forM cycles $ \(imp, files) -> do
541-
modNames <- forM files $
541+
modNames <- forM files $
542542
getModuleName . idToPath depPathIdMap
543543
pure $ toDiag imp $ sort modNames
544544
where cycleErrorInFile f (PartOfCycle imp fs)
@@ -701,7 +701,7 @@ dependencyInfoForFiles fs = do
701701
-- 'extendModSummaryNoDeps'.
702702
-- This may have to change in the future.
703703
map extendModSummaryNoDeps $
704-
(catMaybes mss)
704+
catMaybes mss
705705
#endif
706706
pure (fingerprintToBS $ Util.fingerprintFingerprints $ map (maybe fingerprint0 msrFingerprint) msrs, processDependencyInformation rawDepInfo bm mg)
707707

@@ -1170,7 +1170,7 @@ getLinkableType f = use_ NeedsCompilation f
11701170
-- needsCompilationRule :: Rules ()
11711171
needsCompilationRule :: NormalizedFilePath -> Action (IdeResultNoDiagnosticsEarlyCutoff (Maybe LinkableType))
11721172
needsCompilationRule file
1173-
| "boot" `isSuffixOf` (fromNormalizedFilePath file) =
1173+
| "boot" `isSuffixOf` fromNormalizedFilePath file =
11741174
pure (Just $ encodeLinkableType Nothing, Just Nothing)
11751175
needsCompilationRule file = do
11761176
graph <- useNoFile GetModuleGraph

ghcide/src/Development/IDE/Core/Shake.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -189,7 +189,7 @@ import Development.IDE.GHC.Compat (mkSplitUniqSupply,
189189
data Log
190190
= LogCreateHieDbExportsMapStart
191191
| LogCreateHieDbExportsMapFinish !Int
192-
| LogBuildSessionRestart !String ![DelayedActionInternal] !(KeySet) !Seconds !(Maybe FilePath)
192+
| LogBuildSessionRestart !String ![DelayedActionInternal] !KeySet !Seconds !(Maybe FilePath)
193193
| LogBuildSessionRestartTakingTooLong !Seconds
194194
| LogDelayedAction !(DelayedAction ()) !Seconds
195195
| LogBuildSessionFinish !(Maybe SomeException)
@@ -1276,7 +1276,7 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
12761276
liftIO $ tag "count" (show $ Prelude.length newDiags)
12771277
liftIO $ tag "key" (show k)
12781278
LSP.sendNotification SMethod_TextDocumentPublishDiagnostics $
1279-
LSP.PublishDiagnosticsParams (fromNormalizedUri uri') (fmap fromIntegral ver) ( newDiags)
1279+
LSP.PublishDiagnosticsParams (fromNormalizedUri uri') (fmap fromIntegral ver) newDiags
12801280
return action
12811281
where
12821282
diagsFromRule :: Diagnostic -> Diagnostic

ghcide/src/Development/IDE/GHC/Compat/Outputable.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -137,11 +137,11 @@ pprNoLocMsgEnvelope (MsgEnvelope { errMsgDiagnostic = e
137137
= sdocWithContext $ \_ctx ->
138138
withErrStyle unqual $
139139
#if MIN_VERSION_ghc(9,7,0)
140-
(formatBulleted e)
140+
formatBulleted e
141141
#elif MIN_VERSION_ghc(9,3,0)
142-
(formatBulleted _ctx $ e)
142+
formatBulleted _ctx $ e
143143
#else
144-
(formatBulleted _ctx $ Error.renderDiagnostic e)
144+
formatBulleted _ctx $ Error.renderDiagnostic e
145145
#endif
146146

147147

ghcide/src/Development/IDE/GHC/Compat/Units.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
1-
{-# LANGUAGE CPP #-}
2-
{-# LANGUAGE PatternSynonyms #-}
1+
{-# LANGUAGE CPP #-}
32

43
-- | Compat module for 'UnitState' and 'UnitInfo'.
54
module Development.IDE.GHC.Compat.Units (

ghcide/src/Development/IDE/GHC/CoreFile.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -124,7 +124,7 @@ codeGutsToCoreFile hash CgGuts{..} = CoreFile (map (toIfaceTopBind1 cg_module) $
124124
-- | Implicit binds can be generated from the interface and are not tidied,
125125
-- so we must filter them out
126126
isNotImplictBind :: CoreBind -> Bool
127-
isNotImplictBind bind = any (not . isImplicitId) $ bindBindings bind
127+
isNotImplictBind bind = not . all isImplicitId $ bindBindings bind
128128

129129
bindBindings :: CoreBind -> [Var]
130130
bindBindings (NonRec b _) = [b]
@@ -189,7 +189,7 @@ tcTopIfaceBindings1 :: IORef TypeEnv -> [TopIfaceBinding IfaceId]
189189
-> IfL [CoreBind]
190190
tcTopIfaceBindings1 ty_var ver_decls
191191
= do
192-
int <- mapM (traverse $ tcIfaceId) ver_decls
192+
int <- mapM (traverse tcIfaceId) ver_decls
193193
let all_ids = concatMap toList int
194194
liftIO $ modifyIORef ty_var (flip extendTypeEnvList $ map AnId all_ids)
195195
extendIfaceIdEnv all_ids $ mapM tc_iface_bindings int
@@ -212,7 +212,7 @@ tc_iface_bindings (TopIfaceNonRec v e) = do
212212
e' <- tcIfaceExpr e
213213
pure $ NonRec v e'
214214
tc_iface_bindings (TopIfaceRec vs) = do
215-
vs' <- traverse (\(v, e) -> (,) <$> pure v <*> tcIfaceExpr e) vs
215+
vs' <- traverse (\(v, e) -> (v,) <$> tcIfaceExpr e) vs
216216
pure $ Rec vs'
217217

218218
-- | Prefixes that can occur in a GHC OccName

ghcide/src/Development/IDE/GHC/Orphans.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -98,7 +98,7 @@ instance Ord FastString where
9898
instance NFData (SrcSpanAnn' a) where
9999
rnf = rwhnf
100100

101-
instance Bifunctor (GenLocated) where
101+
instance Bifunctor GenLocated where
102102
bimap f g (L l x) = L (f l) (g x)
103103

104104
deriving instance Functor SrcSpanAnn'

ghcide/src/Development/IDE/GHC/Util.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -168,7 +168,7 @@ cgGutsToCoreModule safeMode guts modDetails = CoreModule
168168
-- Will produce an 8 byte unreadable ByteString.
169169
fingerprintToBS :: Fingerprint -> BS.ByteString
170170
fingerprintToBS (Fingerprint a b) = BS.unsafeCreate 8 $ \ptr -> do
171-
ptr' <- pure $ castPtr ptr
171+
let ptr' = castPtr ptr
172172
pokeElemOff ptr' 0 a
173173
pokeElemOff ptr' 1 b
174174

ghcide/src/Development/IDE/Import/FindImports.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -23,9 +23,9 @@ import Development.IDE.Types.Location
2323
-- standard imports
2424
import Control.Monad.Extra
2525
import Control.Monad.IO.Class
26-
import Data.List (isSuffixOf, find)
27-
import qualified Data.Set as S
26+
import Data.List (find, isSuffixOf)
2827
import Data.Maybe
28+
import qualified Data.Set as S
2929
import System.FilePath
3030

3131
-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]
@@ -93,7 +93,7 @@ locateModuleFile import_dirss exts targetFor isSource modName = do
9393
Nothing ->
9494
case find (\(_ , _, reexports) -> S.member modName reexports) import_dirss of
9595
Just (uid,_,_) -> pure $ LocateFoundReexport uid
96-
Nothing -> pure $ LocateNotFound
96+
Nothing -> pure LocateNotFound
9797
Just (uid,file) -> pure $ LocateFoundFile uid file
9898
where
9999
go (uid, candidate) = fmap ((uid,) <$>) $ targetFor modName candidate

ghcide/src/Development/IDE/LSP/LanguageServer.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -110,7 +110,7 @@ runLanguageServer recorder options inH outH defaultConfig parseConfig onConfigCh
110110
-- TODO: magic string
111111
, LSP.configSection = "haskell"
112112
, LSP.doInitialize = doInitialize
113-
, LSP.staticHandlers = (const staticHandlers)
113+
, LSP.staticHandlers = const staticHandlers
114114
, LSP.interpretHandler = interpretHandler
115115
, LSP.options = modifyOptions options
116116
}

ghcide/src/Development/IDE/LSP/Outline.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -274,7 +274,7 @@ hsConDeclsBinders cons
274274
get_flds_h98 _ = []
275275

276276
get_flds_gadt :: HsConDeclGADTDetails GhcPs
277-
-> ([LFieldOcc GhcPs])
277+
-> [LFieldOcc GhcPs]
278278
#if MIN_VERSION_ghc(9,3,0)
279279
get_flds_gadt (RecConGADT flds _) = get_flds (reLoc flds)
280280
#else
@@ -283,7 +283,7 @@ hsConDeclsBinders cons
283283
get_flds_gadt _ = []
284284

285285
get_flds :: Located [LConDeclField GhcPs]
286-
-> ([LFieldOcc GhcPs])
286+
-> [LFieldOcc GhcPs]
287287
get_flds flds = concatMap (cd_fld_names . unLoc) (unLoc flds)
288288

289289

ghcide/src/Development/IDE/Plugin/Completions/Logic.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -704,7 +704,7 @@ getCompletions
704704
pn = showForSnippet name
705705
ty = showForSnippet <$> typ
706706
thisModName = Local $ nameSrcSpan name
707-
dets = NameDetails <$> (nameModule_maybe name) <*> pure (nameOccName name)
707+
dets = NameDetails <$> nameModule_maybe name <*> pure (nameOccName name)
708708

709709
-- When record-dot-syntax completions are available, we return them exclusively.
710710
-- They are only available when we write i.e. `myrecord.` with OverloadedRecordDot enabled.
@@ -762,7 +762,7 @@ uniqueCompl candidate unique =
762762
EQ ->
763763
-- preserve completions for duplicate record fields where the only difference is in the type
764764
-- remove redundant completions with less type info than the previous
765-
if (isLocalCompletion unique)
765+
if isLocalCompletion unique
766766
-- filter global completions when we already have a local one
767767
|| not(isLocalCompletion candidate) && isLocalCompletion unique
768768
then EQ

ghcide/src/Development/IDE/Plugin/TypeLenses.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -183,7 +183,7 @@ codeLensResolveProvider ideState pId lens@CodeLens{_range} uri TypeLensesResolve
183183

184184
generateLensCommand :: PluginId -> Uri -> T.Text -> TextEdit -> Command
185185
generateLensCommand pId uri title edit =
186-
let wEdit = WorkspaceEdit (Just $ Map.singleton uri $ [edit]) Nothing Nothing
186+
let wEdit = WorkspaceEdit (Just $ Map.singleton uri [edit]) Nothing Nothing
187187
in mkLspCommand pId (CommandId typeLensCommandId) title (Just [toJSON wEdit])
188188

189189
-- Since the lenses are created with diagnostics, and since the globalTypeSig

0 commit comments

Comments
 (0)