Skip to content

Commit b64caa7

Browse files
Eliminate redundant $.
1 parent 0067b7d commit b64caa7

File tree

12 files changed

+19
-22
lines changed

12 files changed

+19
-22
lines changed

exe/Wrapper.hs

Lines changed: 1 addition & 1 deletion
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

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

Lines changed: 1 addition & 1 deletion
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

Lines changed: 1 addition & 1 deletion
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

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ import Data.Foldable ( toList )
2525
ppHies :: Outputable a => HieASTs a -> SDoc
2626
ppHies (HieASTs asts) = M.foldrWithKey go "" asts
2727
where
28-
go k a rest = vcat $
28+
go k a rest = vcat
2929
[ "File: " <> ppr k
3030
, ppHie a
3131
, rest
@@ -114,7 +114,7 @@ validAst (Node _ span children) = do
114114
checkContainment (x:xs)
115115
| span `containsSpan` nodeSpan x = checkContainment xs
116116
| otherwise = Left $ hsep
117-
[ ppr $ span
117+
[ ppr span
118118
, "does not contain"
119119
, ppr $ nodeSpan x
120120
]
@@ -139,7 +139,7 @@ validateScopes asts = M.foldrWithKey (\k a b -> valid k a ++ b) [] refMap
139139
[] -> []
140140
_ -> if any (`scopeContainsSpan` sp) scopes
141141
then []
142-
else return $ hsep $
142+
else return $ hsep
143143
[ "Name", ppr n, "at position", ppr sp
144144
, "doesn't occur in calculated scope", ppr scopes]
145145
| otherwise = []

install/src/Cabal.hs

Lines changed: 1 addition & 1 deletion
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

Lines changed: 3 additions & 3 deletions
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/hls-retrie-plugin/src/Ide/Plugin/Retrie.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -121,7 +121,7 @@ runRetrieCmd lsp state RunRetrieParams{originatingFile = uri, ..} =
121121
nfp <- MaybeT $ return $ uriToNormalizedFilePath $ toNormalizedUri uri
122122
(session, _) <- MaybeT $
123123
runAction "Retrie.GhcSessionDeps" state $
124-
useWithStale GhcSessionDeps $
124+
useWithStale GhcSessionDeps
125125
nfp
126126
(ms, binds, _, _, _) <- MaybeT $ runAction "Retrie.getBinds" state $ getBinds nfp
127127
let importRewrites = concatMap (extractImports ms binds) rewrites

plugins/tactics/src/Ide/Plugin/Tactic/CodeGen.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -178,7 +178,7 @@ destructLambdaCase' f jdg = do
178178
let g = jGoal jdg
179179
case splitFunTy_maybe (unCType g) of
180180
Just (arg, _) | isAlgType arg ->
181-
fmap (fmap noLoc $ lambdaCase) <$>
181+
fmap (fmap noLoc lambdaCase) <$>
182182
destructMatches f Nothing (CType arg) jdg
183183
_ -> throwError $ GoalMismatch "destructLambdaCase'" g
184184

@@ -214,7 +214,7 @@ mkCon dcon (fmap unLoc -> args)
214214
, (lhs : rhs : args') <- args =
215215
noLoc $ foldl' (@@) (op lhs (coerceName dcon_name) rhs) args'
216216
| otherwise =
217-
noLoc $ foldl' (@@) (bvar' $ occName $ dcon_name) args
217+
noLoc $ foldl' (@@) (bvar' $ occName dcon_name) args
218218
where
219219
dcon_name = dataConName dcon
220220

@@ -259,4 +259,3 @@ infixCall s = flip op (fromString s)
259259
-- | Like '(@@)', but uses a dollar instead of parentheses.
260260
appDollar :: HsExpr GhcPs -> HsExpr GhcPs -> HsExpr GhcPs
261261
appDollar = infixCall "$"
262-

plugins/tactics/src/Ide/Plugin/Tactic/Context.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -89,8 +89,7 @@ getFunBindId _ = []
8989

9090

9191
getCurrentDefinitions :: MonadReader Context m => m [(OccName, CType)]
92-
getCurrentDefinitions = asks $ ctxDefiningFuncs
92+
getCurrentDefinitions = asks ctxDefiningFuncs
9393

9494
getModuleHypothesis :: MonadReader Context m => m [(OccName, CType)]
9595
getModuleHypothesis = asks ctxModuleFuncs
96-

plugins/tactics/src/Ide/Plugin/Tactic/GHC.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -78,7 +78,7 @@ freshTyvars t = do
7878
reps <- fmap M.fromList
7979
$ for tvs $ \tv -> do
8080
uniq <- freshUnique
81-
pure $ (tv, setTyVarUnique tv uniq)
81+
pure (tv, setTyVarUnique tv uniq)
8282
pure $
8383
everywhere
8484
(mkT $ \tv ->
@@ -153,4 +153,4 @@ dataConExTys :: DataCon -> [TyCoVar]
153153
dataConExTys = DataCon.dataConExTyCoVars
154154
#else
155155
dataConExTys = DataCon.dataConExTyVars
156-
#endif
156+
#endif

plugins/tactics/src/Ide/Plugin/Tactic/Machinery.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,7 @@ runTactic ctx jdg t =
9292
. flip runReader ctx
9393
. unExtractM
9494
$ runTacticT t jdg tacticState of
95-
(errs, []) -> Left $ take 50 $ errs
95+
(errs, []) -> Left $ take 50 errs
9696
(_, fmap assoc23 -> solns) -> do
9797
let sorted =
9898
flip sortBy solns $ comparing $ \((_, ext), (jdg, holes)) ->
@@ -174,7 +174,7 @@ scoreSolution ext TacticState{..} holes
174174
, Penalize $ S.size ts_unused_top_vals
175175
, Penalize $ S.size ts_intro_vals
176176
, Reward $ S.size ts_used_vals
177-
, Penalize $ ts_recursion_count
177+
, Penalize ts_recursion_count
178178
, Penalize $ solutionSize ext
179179
)
180180

@@ -251,4 +251,3 @@ requireConcreteHole m = do
251251
case S.size $ vars S.\\ skolems of
252252
0 -> m
253253
_ -> throwError TooPolymorphic
254-

src/Ide/Version.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -67,7 +67,7 @@ findVersionOf tool =
6767
Just path ->
6868
readProcessWithExitCode path ["--numeric-version"] "" >>= \case
6969
(ExitSuccess, sout, _) -> pure $ consumeParser myVersionParser sout
70-
_ -> pure $ Nothing
70+
_ -> pure Nothing
7171
where
7272
myVersionParser = do
7373
skipSpaces

0 commit comments

Comments
 (0)