Skip to content

Commit 6576637

Browse files
Hlint fixes.
1 parent 4d431e9 commit 6576637

File tree

36 files changed

+119
-164
lines changed

36 files changed

+119
-164
lines changed

GenChangelogs.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ main = do
2424

2525
prs <- github' $ pullRequestsForR "haskell" "haskell-language-server" stateClosed FetchAll
2626
let prsAfterLastTag = either (error . show)
27-
(foldMap (\pr -> if inRange pr then [pr] else []))
27+
(foldMap (\pr -> [pr | inRange pr]))
2828
prs
2929
inRange pr
3030
| Just mergedDate <- simplePullRequestMergedAt pr = mergedDate > lastDate

ghcide/.hlint.yaml

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,6 @@
1111
- ignore: {name: "Redundant do"}
1212
- ignore: {name: "Avoid lambda"}
1313
- ignore: {name: "Use newtype instead of data"}
14-
- ignore: {name: "Use fromMaybe"}
1514
- ignore: {name: "Use unless"}
1615
- ignore: {name: "Move brackets to avoid $"}
1716
- ignore: {name: "Eta reduce"}
@@ -25,6 +24,16 @@
2524
- ignore: {name: "Use uncurry"}
2625
- ignore: {name: "Avoid lambda using `infix`"}
2726

27+
# We are using the "redundant" return/pure to assign a name. We do not want to
28+
# delete it. In particular, this is not an improvement:
29+
# Found:
30+
# do options <- somethingComplicated
31+
# pure options
32+
# Perhaps:
33+
# do somethingComplicated
34+
- ignore: {name: "Redundant return"}
35+
- ignore: {name: "Redundant pure"}
36+
2837
# Off by default hints we like
2938
- warn: {name: Use module export list}
3039

@@ -107,7 +116,7 @@
107116
# Things that are unsafe in Haskell base library
108117
- {name: unsafeInterleaveIO, within: []}
109118
- {name: unsafeDupablePerformIO, within: []}
110-
- {name: unsafeCoerce, within: []}
119+
- {name: unsafeCoerce, within: [Ide.Plugin.Eval.Code]}
111120
# Things that are a bit dangerous in the GHC API
112121
- {name: nameModule, within: []}
113122

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -120,7 +120,7 @@ setInitialDynFlags = do
120120
hPutStrLn stderr $ "Couldn't load cradle for libdir: " ++ show (err,dir,hieYaml,cradle)
121121
pure Nothing
122122
CradleNone -> do
123-
hPutStrLn stderr $ "Couldn't load cradle (CradleNone)"
123+
hPutStrLn stderr "Couldn't load cradle (CradleNone)"
124124
pure Nothing
125125
dynFlags <- mapM dynFlagsForPrinting libdir
126126
mapM_ setUnsafeGlobalDynFlags dynFlags

ghcide/src/Development/IDE/Spans/AtPoint.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -158,7 +158,7 @@ documentHighlight hf rf pos = pure highlights
158158
ns = concat $ pointCommand hf pos (rights . M.keys . nodeIdentifiers . nodeInfo)
159159
highlights = do
160160
n <- ns
161-
ref <- maybe [] id (M.lookup (Right n) rf)
161+
ref <- fromMaybe [] (M.lookup (Right n) rf)
162162
pure $ makeHighlight ref
163163
makeHighlight (sp,dets) =
164164
DocumentHighlight (realSrcSpanToRange sp) (Just $ highlightType $ identInfo dets)
@@ -266,12 +266,12 @@ typeLocationsAtPoint hiedb lookupModule _ideOptions pos (HAR _ ast _ _ hieKind)
266266
HQualTy a b -> getTypes [a,b]
267267
HCastTy a -> getTypes [a]
268268
_ -> []
269-
in fmap nubOrd $ concatMapM (fmap (maybe [] id) . nameToLocation hiedb lookupModule) (getTypes ts)
269+
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation hiedb lookupModule) (getTypes ts)
270270
HieFresh ->
271271
let ts = concat $ pointCommand ast pos getts
272272
getts x = nodeType ni ++ (mapMaybe identType $ M.elems $ nodeIdentifiers ni)
273273
where ni = nodeInfo x
274-
in fmap nubOrd $ concatMapM (fmap (maybe [] id) . nameToLocation hiedb lookupModule) (getTypes ts)
274+
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation hiedb lookupModule) (getTypes ts)
275275

276276
namesInType :: Type -> [Name]
277277
namesInType (TyVarTy n) = [Var.varName n]

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,7 @@ clientSupportsDocumentChanges caps =
135135
WorkspaceEditClientCapabilities mDc _ _ <- _workspaceEdit wCaps
136136
mDc
137137
in
138-
fromMaybe False supports
138+
Just True == supports
139139

140140
-- ---------------------------------------------------------------------
141141

@@ -214,7 +214,7 @@ allLspCmdIds' pid mp = mkPlugin (allLspCmdIds pid) (Just . pluginCommands)
214214

215215

216216
allLspCmdIds :: T.Text -> [(PluginId, [PluginCommand ideState])] -> [T.Text]
217-
allLspCmdIds pid commands = concat $ map go commands
217+
allLspCmdIds pid commands = concatMap go commands
218218
where
219219
go (plid, cmds) = map (mkLspCmdId pid plid . commandId) cmds
220220

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-# LANGUAGE GADTs #-}
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE ScopedTypeVariables #-}
4-
{-# LANGUAGE TupleSections #-}
54
{-# LANGUAGE FlexibleContexts #-}
65
{-# LANGUAGE PolyKinds #-}
76
{-# LANGUAGE ViewPatterns #-}

install/src/Cabal.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,7 @@ getProjectFile ver = do
9696
else "cabal.project"
9797

9898
checkCabal_ :: [String] -> Action ()
99-
checkCabal_ args = checkCabal args >> return ()
99+
checkCabal_ args = void $ checkCabal args
100100

101101
-- | check `cabal` has the required version
102102
checkCabal :: [String] -> Action String

install/src/Env.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,7 @@ findInstalledGhcs = do
5454
-- sort by version to make it coherent with getHlsVersions
5555
$ sortBy (comparing fst)
5656
-- nub by version. knownGhcs takes precedence.
57-
$ nubBy ((==) `on` fst)
57+
$ nubOrdBy (compare `on` fst)
5858
-- filter out stack provided GHCs (assuming that stack programs path is the default one in linux)
5959
$ filter (not . isInfixOf ".stack" . snd) (knownGhcs ++ availableGhcs)
6060

install/src/Print.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ printInStars = liftIO . putStrLn . embedInStars
2525

2626
-- | Trim whitespace of both ends of a string
2727
trim :: String -> String
28-
trim = dropWhileEnd isSpace . dropWhile isSpace
28+
trim = trimEnd . trimStart
2929

3030
-- | Trim the whitespace of the stdout of a command
3131
trimmedStdout :: Stdout String -> String

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -93,7 +93,7 @@ provider ideState typ contents fp fo = withIndefiniteProgress title Cancellable
9393

9494
convertDynFlags :: DynFlags -> IO [DynOption]
9595
convertDynFlags df =
96-
let pp = if null p then [] else ["-pgmF=" <> p]
96+
let pp = ["-pgmF=" <> p | not (null p)]
9797
p = D.sPgm_F $ D.settings df
9898
pm = map (("-fplugin=" <>) . moduleNameString) $ D.pluginModNames df
9999
ex = map showExtension $ S.toList $ D.extensionFlags df

0 commit comments

Comments
 (0)