Skip to content

Commit bcaaf8b

Browse files
committed
Reduce usage of partial functions
1 parent 8a8f59b commit bcaaf8b

File tree

7 files changed

+34
-56
lines changed

7 files changed

+34
-56
lines changed

.hlint.yaml

+2-21
Original file line numberDiff line numberDiff line change
@@ -64,8 +64,6 @@
6464
- Ide.Types
6565
- Test.Hls
6666
- Test.Hls.Command
67-
- Wingman.Debug
68-
- Wingman.Types
6967
- AutoTupleSpec
7068
- name: unsafeInterleaveIO
7169
within:
@@ -76,7 +74,6 @@
7674
- Ide.Plugin.Eval.Code
7775
- Development.IDE.Core.Compile
7876
- Development.IDE.Types.Shake
79-
- Wingman.Judgements.SYB
8077
- Ide.Plugin.Properties
8178

8279
# Things that are a bit dangerous in the GHC API
@@ -105,17 +102,13 @@
105102
- Ide.Plugin.CallHierarchy.Internal
106103
- Ide.Plugin.Eval.Code
107104
- Ide.Plugin.Eval.Util
108-
- Ide.Plugin.Floskell
109105
- Ide.Plugin.ModuleName
110106
- Ide.Plugin.Class.ExactPrint
111107
- TExpectedActual
112108
- TRigidType
113109
- TRigidType2
114110
- RightToLeftFixities
115111
- Typeclass
116-
- Wingman.Judgements
117-
- Wingman.Machinery
118-
- Wingman.Tactics
119112
- CompletionTests #Previously part of GHCIDE Main tests
120113
- DiagnosticTests #Previously part of GHCIDE Main tests
121114
- FindDefinitionAndHoverTests #Previously part of GHCIDE Main tests
@@ -149,7 +142,6 @@
149142
- Main
150143
- Development.IDE.Spans.Common
151144
- Ide.PluginUtils
152-
- Wingman.Metaprogramming.Parser
153145
- Development.Benchmark.Rules
154146
- ErrorGivenPartialSignature
155147
- IfaceTests #Previously part of GHCIDE Main tests
@@ -171,8 +163,6 @@
171163
- Development.IDE.Plugin.Completions.Logic
172164
- Development.IDE.Spans.Documentation
173165
- TErrorGivenPartialSignature
174-
- Wingman.CaseSplit
175-
- Wingman.Simplify
176166
- InitializeResponseTests #Previously part of GHCIDE Main tests
177167
- PositionMappingTests #Previously part of GHCIDE Main tests
178168

@@ -185,31 +175,23 @@
185175
within: []
186176

187177
- name: Data.Foldable.foldr1
188-
within:
189-
- Wingman.Tactics
178+
within: []
190179

191180
- name: Data.Maybe.fromJust
192181
within:
193182
- Experiments
194183
- Main
195-
- MultipleImports
196184
- Progress
197-
- Utils
198185
- Development.IDE.Core.Compile
199186
- Development.IDE.Core.Rules
200187
- Development.IDE.Core.Shake
201-
- Development.IDE.Plugin.Completions
202-
- Development.IDE.Plugin.CodeAction.ExactPrint
203-
- Development.IDE.Plugin.CodeAction
204188
- Development.IDE.Test
205189
- Development.IDE.Graph.Internal.Profile
206190
- Development.IDE.Graph.Internal.Rules
207-
- Ide.Plugin.Class
208191
- CodeLensTests #Previously part of GHCIDE Main tests
209192

210193
- name: "Data.Map.!"
211-
within:
212-
- Wingman.LanguageServer
194+
within: []
213195

214196
- name: "Data.IntMap.!"
215197
within: []
@@ -250,7 +232,6 @@
250232
- Development.IDE.Graph.Internal.Database
251233
- Development.IDE.GHC.Util
252234
- Development.IDE.Plugin.CodeAction.Util
253-
- Wingman.Debug
254235

255236
# We really do not want novel usages of restricted functions, and mere
256237
# Warning is not enough to prevent those consistently; you need a build failure.

ghcide/test/exe/FindDefinitionAndHoverTests.hs

-2
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,4 @@
11

2-
{-# LANGUAGE MultiWayIf #-}
3-
42
module FindDefinitionAndHoverTests (tests) where
53

64
import Control.Monad

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,7 @@ asStmts (Property t _ _) =
8585
myExecStmt :: String -> ExecOptions -> Ghc (Either String (Maybe String))
8686
myExecStmt stmt opts = do
8787
(temp, purge) <- liftIO newTempFile
88-
evalPrint <- head <$> runDecls ("evalPrint x = P.writeFile "<> show temp <> " (P.show x)")
88+
evalPrint <- head <$> runDecls ("evalPrint x = P.writeFile " <> show temp <> " (P.show x)")
8989
modifySession $ \hsc -> hsc {hsc_IC = setInteractivePrintName (hsc_IC hsc) evalPrint}
9090
result <- execStmt stmt opts >>= \case
9191
ExecComplete (Left err) _ -> pure $ Left $ show err

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -122,7 +122,7 @@ commentsToSections isLHS Comments {..} =
122122
in case parseMaybe lineGroupP $ NE.toList lcs of
123123
Nothing -> mempty
124124
Just (mls, rs) ->
125-
( maybe mempty (uncurry Map.singleton) ((theRan,) <$> mls)
125+
( maybe mempty (Map.singleton theRan) mls
126126
, -- orders setup sections in ascending order
127127
if null rs
128128
then mempty

plugins/hls-floskell-plugin/src/Ide/Plugin/Floskell.hs

+4-2
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module Ide.Plugin.Floskell
88

99
import Control.Monad.Except (throwError)
1010
import Control.Monad.IO.Class
11+
import Data.List (find)
1112
import qualified Data.Text as T
1213
import qualified Data.Text.Lazy as TL
1314
import Development.IDE hiding (pluginHandlers)
@@ -53,7 +54,8 @@ findConfigOrDefault file = do
5354
case mbConf of
5455
Just confFile -> readAppConfig confFile
5556
Nothing ->
56-
let gibiansky = head (filter (\s -> styleName s == "gibiansky") styles)
57-
in pure $ defaultAppConfig { appStyle = gibiansky }
57+
pure $ case find (\s -> styleName s == "gibiansky") styles of
58+
Just gibiansky -> defaultAppConfig { appStyle = gibiansky }
59+
Nothing -> defaultAppConfig
5860

5961
-- ---------------------------------------------------------------------

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs

+20-21
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,6 @@ import GHC (AddEpAnn (Ad
7575
EpAnn (..),
7676
EpaLocation (..),
7777
LEpaComment)
78-
import GHC.Exts (fromList)
7978
import qualified GHC.LanguageExtensions as Lang
8079
import Ide.Logger hiding
8180
(group)
@@ -189,18 +188,18 @@ extendImportHandler :: CommandFunction IdeState ExtendImport
189188
extendImportHandler ideState _ edit@ExtendImport {..} = ExceptT $ do
190189
res <- liftIO $ runMaybeT $ extendImportHandler' ideState edit
191190
whenJust res $ \(nfp, wedit@WorkspaceEdit {_changes}) -> do
192-
let (_, head -> TextEdit {_range}) = fromJust $ _changes >>= listToMaybe . M.toList
193-
srcSpan = rangeToSrcSpan nfp _range
194-
LSP.sendNotification SMethod_WindowShowMessage $
195-
ShowMessageParams MessageType_Info $
196-
"Import "
197-
<> maybe ("" <> newThing) (\x -> "" <> x <> " (" <> newThing <> ")") thingParent
198-
<> "’ from "
199-
<> importName
200-
<> " (at "
201-
<> printOutputable srcSpan
202-
<> ")"
203-
void $ LSP.sendRequest SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wedit) (\_ -> pure ())
191+
whenJust (listToMaybe =<< listToMaybe . M.elems =<< _changes) $ \TextEdit {_range} -> do
192+
let srcSpan = rangeToSrcSpan nfp _range
193+
LSP.sendNotification SMethod_WindowShowMessage $
194+
ShowMessageParams MessageType_Info $
195+
"Import "
196+
<> maybe ("" <> newThing) (\x -> "" <> x <> " (" <> newThing <> ")") thingParent
197+
<> "’ from "
198+
<> importName
199+
<> " (at "
200+
<> printOutputable srcSpan
201+
<> ")"
202+
void $ LSP.sendRequest SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wedit) (\_ -> pure ())
204203
return $ Right $ InR Null
205204

206205
extendImportHandler' :: IdeState -> ExtendImport -> MaybeT IO (NormalizedFilePath, WorkspaceEdit)
@@ -223,8 +222,7 @@ extendImportHandler' ideState ExtendImport {..}
223222
case existingImport of
224223
Just imp -> do
225224
fmap (nfp,) $ liftEither $
226-
rewriteToWEdit df doc
227-
$
225+
rewriteToWEdit df doc $
228226
extendImport (T.unpack <$> thingParent) (T.unpack newThing) (makeDeltaAst imp)
229227

230228
Nothing -> do
@@ -235,7 +233,7 @@ extendImportHandler' ideState ExtendImport {..}
235233
Nothing -> newThing
236234
Just p -> p <> "(" <> newThing <> ")"
237235
t <- liftMaybe $ snd <$> newImportToEdit n ps (fromMaybe "" contents)
238-
return (nfp, WorkspaceEdit {_changes=Just (GHC.Exts.fromList [(doc, [t])]), _documentChanges=Nothing, _changeAnnotations=Nothing})
236+
return (nfp, WorkspaceEdit {_changes=Just (M.singleton doc [t]), _documentChanges=Nothing, _changeAnnotations=Nothing})
239237
| otherwise =
240238
mzero
241239

@@ -609,7 +607,7 @@ suggestDeleteUnusedBinding
609607
let maybeIdx = findIndex (\(L _ id) -> isSameName id name) lnames
610608
in case maybeIdx of
611609
Nothing -> Nothing
612-
Just _ | length lnames == 1 -> Just (getLoc $ reLoc $ head lnames, True)
610+
Just _ | [lname] <- lnames -> Just (getLoc $ reLoc lname, True)
613611
Just idx ->
614612
let targetLname = getLoc $ reLoc $ lnames !! idx
615613
startLoc = srcSpanStart targetLname
@@ -1052,7 +1050,7 @@ suggestImportDisambiguation df (Just txt) ps fileContents diag@Diagnostic {..}
10521050
parensed =
10531051
"(" `T.isPrefixOf` T.strip (textInRange _range txt)
10541052
-- > removeAllDuplicates [1, 1, 2, 3, 2] = [3]
1055-
removeAllDuplicates = map head . filter ((==1) <$> length) . group . sort
1053+
removeAllDuplicates = map NE.head . filter ((==1) . length) . NE.group . sort
10561054
hasDuplicate xs = length xs /= length (S.fromList xs)
10571055
suggestions symbol mods local
10581056
| hasDuplicate mods = case mapM toModuleTarget (removeAllDuplicates mods) of
@@ -1290,7 +1288,7 @@ suggestImplicitParameter (L _ HsModule {hsmodDecls}) Diagnostic {_message, _rang
12901288
| otherwise = []
12911289

12921290
findTypeSignatureName :: T.Text -> Maybe T.Text
1293-
findTypeSignatureName t = matchRegexUnifySpaces t "([^ ]+) :: " <&> head
1291+
findTypeSignatureName t = matchRegexUnifySpaces t "([^ ]+) :: " >>= listToMaybe
12941292

12951293
-- | Suggests a constraint for a type signature with any number of existing constraints.
12961294
suggestFunctionConstraint :: DynFlags -> ParsedSource -> Diagnostic -> T.Text -> [(T.Text, Rewrite)]
@@ -1378,7 +1376,8 @@ removeRedundantConstraints df (makeDeltaAst -> L _ HsModule {hsmodDecls}) Diagno
13781376
& take 2
13791377
& mapMaybe ((`matchRegexUnifySpaces` "Redundant constraints?: (.+)") . T.strip)
13801378
& listToMaybe
1381-
<&> (head >>> parseConstraints)
1379+
>>= listToMaybe
1380+
<&> parseConstraints
13821381

13831382
formatConstraints :: [T.Text] -> T.Text
13841383
formatConstraints [] = ""
@@ -1658,7 +1657,7 @@ findPositionAfterModuleName ps hsmodName' = do
16581657
#endif
16591658
EpAnn _ annsModule _ -> do
16601659
-- Find the first 'where'
1661-
whereLocation <- fmap NE.head . NE.nonEmpty . mapMaybe filterWhere . am_main $ annsModule
1660+
whereLocation <- listToMaybe . mapMaybe filterWhere $ am_main annsModule
16621661
epaLocationToLine whereLocation
16631662
EpAnnNotUsed -> Nothing
16641663
filterWhere (AddEpAnn AnnWhere loc) = Just loc

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs

+6-8
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ import Development.IDE.Plugin.CodeAction.Util
3737
import Control.Lens (_head, _last, over)
3838
import Data.Bifunctor (first)
3939
import Data.Default (Default (..))
40-
import Data.Maybe (fromJust, fromMaybe,
40+
import Data.Maybe (fromMaybe,
4141
mapMaybe)
4242
import GHC (AddEpAnn (..),
4343
AnnContext (..),
@@ -82,15 +82,13 @@ rewriteToEdit :: HasCallStack =>
8282
Either String [TextEdit]
8383
rewriteToEdit dflags
8484
(Rewrite dst f) = do
85-
(ast, _ , _) <- runTransformT
86-
$ do
85+
(ast, _ , _) <- runTransformT $ do
8786
ast <- f dflags
8887
pure $ traceAst "REWRITE_result" $ resetEntryDP ast
89-
let editMap =
90-
[ TextEdit (fromJust $ srcSpanToRange dst) $
91-
T.pack $ exactPrint ast
92-
]
93-
pure editMap
88+
let edits = case srcSpanToRange dst of
89+
Just range -> [ TextEdit range $ T.pack $ exactPrint ast ]
90+
Nothing -> []
91+
pure edits
9492

9593
-- | Convert a 'Rewrite' into a 'WorkspaceEdit'
9694
rewriteToWEdit :: DynFlags

0 commit comments

Comments
 (0)