Skip to content

Commit 0067b7d

Browse files
Eliminate redundant brackets.
1 parent b1d912a commit 0067b7d

File tree

17 files changed

+43
-47
lines changed

17 files changed

+43
-47
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

+1-2
Original file line numberDiff line numberDiff line change
@@ -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-

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -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

+2-2
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ import Data.Function ( on )
2222
import Data.List ( sortOn )
2323
import Data.Foldable ( toList )
2424

25-
ppHies :: Outputable a => (HieASTs a) -> SDoc
25+
ppHies :: Outputable a => HieASTs a -> SDoc
2626
ppHies (HieASTs asts) = M.foldrWithKey go "" asts
2727
where
2828
go k a rest = vcat $
@@ -112,7 +112,7 @@ validAst (Node _ span children) = do
112112
]
113113
checkContainment [] = return ()
114114
checkContainment (x:xs)
115-
| span `containsSpan` (nodeSpan x) = checkContainment xs
115+
| span `containsSpan` nodeSpan x = checkContainment xs
116116
| otherwise = Left $ hsep
117117
[ ppr $ span
118118
, "does not contain"

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

+10-10
Original file line numberDiff line numberDiff line change
@@ -168,7 +168,7 @@ data HieType a
168168
type HieTypeFlat = HieType TypeIndex
169169

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

173173
instance Binary (HieType TypeIndex) where
174174
put_ bh (HTyVarTy n) = do
@@ -200,7 +200,7 @@ instance Binary (HieType TypeIndex) where
200200
put_ bh (HCastTy a) = do
201201
putByte bh 7
202202
put_ bh a
203-
put_ bh (HCoercionTy) = putByte bh 8
203+
put_ bh HCoercionTy = putByte bh 8
204204

205205
get bh = do
206206
(t :: Word8) <- get bh
@@ -228,7 +228,7 @@ instance Binary (HieArgs TypeIndex) where
228228

229229
-- | Mapping from filepaths (represented using 'FastString') to the
230230
-- corresponding AST
231-
newtype HieASTs a = HieASTs { getAsts :: (M.Map FastString (HieAST a)) }
231+
newtype HieASTs a = HieASTs { getAsts :: M.Map FastString (HieAST a) }
232232
deriving (Functor, Foldable, Traversable)
233233

234234
instance Binary (HieASTs TypeIndex) where
@@ -276,9 +276,9 @@ instance Binary (NodeInfo TypeIndex) where
276276
put_ bh $ nodeType ni
277277
put_ bh $ M.toList $ nodeIdentifiers ni
278278
get bh = NodeInfo
279-
<$> fmap (S.fromDistinctAscList) (get bh)
279+
<$> fmap S.fromDistinctAscList (get bh)
280280
<*> get bh
281-
<*> fmap (M.fromList) (get bh)
281+
<*> fmap M.fromList (get bh)
282282

283283
type Identifier = Either ModuleName Name
284284

@@ -309,7 +309,7 @@ instance Binary (IdentifierDetails TypeIndex) where
309309
put_ bh $ S.toAscList $ identInfo dets
310310
get bh = IdentifierDetails
311311
<$> get bh
312-
<*> fmap (S.fromDistinctAscList) (get bh)
312+
<*> fmap S.fromDistinctAscList (get bh)
313313

314314

315315
-- | Different contexts under which identifiers exist
@@ -419,7 +419,7 @@ data IEType
419419

420420
instance Binary IEType where
421421
put_ bh b = putByte bh (fromIntegral (fromEnum b))
422-
get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
422+
get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
423423

424424

425425
data RecFieldContext
@@ -431,7 +431,7 @@ data RecFieldContext
431431

432432
instance Binary RecFieldContext where
433433
put_ bh b = putByte bh (fromIntegral (fromEnum b))
434-
get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
434+
get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
435435

436436

437437
data BindType
@@ -441,7 +441,7 @@ data BindType
441441

442442
instance Binary BindType where
443443
put_ bh b = putByte bh (fromIntegral (fromEnum b))
444-
get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
444+
get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
445445

446446

447447
data DeclType
@@ -456,7 +456,7 @@ data DeclType
456456

457457
instance Binary DeclType where
458458
put_ bh b = putByte bh (fromIntegral (fromEnum b))
459-
get bh = do x <- getByte bh; pure $! (toEnum (fromIntegral x))
459+
get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
460460

461461

462462
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

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/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-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -189,10 +189,10 @@ minimalImportsRule = define $ \MinimalImports nfp -> do
189189

190190
-- | Use the ghc api to extract a minimal, explicit set of imports for this module
191191
extractMinimalImports ::
192-
Maybe (HscEnvEq) ->
193-
Maybe (TcModuleResult) ->
192+
Maybe HscEnvEq ->
193+
Maybe TcModuleResult ->
194194
IO ([LImportDecl GhcRn], Maybe [LImportDecl GhcRn])
195-
extractMinimalImports (Just (hsc)) (Just (TcModuleResult {..})) = do
195+
extractMinimalImports (Just hsc) (Just TcModuleResult {..}) = do
196196
-- extract the original imports and the typechecking environment
197197
let tcEnv = tmrTypechecked
198198
(_, imports, _, _) = tmrRenamed

plugins/hls-retrie-plugin/src/Ide/Plugin/Retrie.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -227,7 +227,7 @@ suggestBindRewrites ::
227227
GHC.Module ->
228228
HsBindLR GhcRn GhcRn ->
229229
[(T.Text, CodeActionKind, RunRetrieParams)]
230-
suggestBindRewrites originatingFile pos ms_mod (FunBind {fun_id = L l' rdrName})
230+
suggestBindRewrites originatingFile pos ms_mod FunBind {fun_id = L l' rdrName}
231231
| pos `isInsideSrcSpan` l' =
232232
let pprName = prettyPrint rdrName
233233
pprNameText = T.pack pprName
@@ -253,7 +253,7 @@ suggestTypeRewrites ::
253253
GHC.Module ->
254254
TyClDecl pass ->
255255
[(T.Text, CodeActionKind, RunRetrieParams)]
256-
suggestTypeRewrites originatingFile ms_mod (SynDecl {tcdLName = L _ rdrName}) =
256+
suggestTypeRewrites originatingFile ms_mod SynDecl {tcdLName = L _ rdrName} =
257257
let pprName = prettyPrint rdrName
258258
pprNameText = T.pack pprName
259259
unfoldRewrite restrictToOriginatingFile =
@@ -273,7 +273,7 @@ suggestRuleRewrites ::
273273
GHC.Module ->
274274
LRuleDecls pass ->
275275
[(T.Text, CodeActionKind, RunRetrieParams)]
276-
suggestRuleRewrites originatingFile pos ms_mod (L _ (HsRules {rds_rules})) =
276+
suggestRuleRewrites originatingFile pos ms_mod (L _ HsRules {rds_rules}) =
277277
concat
278278
[ [ forwardRewrite ruleName True
279279
, forwardRewrite ruleName False

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

+2-3
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ mkTyName :: Type -> String
2222
mkTyName (tcSplitFunTys -> ([a@(isFunTy -> False)], b))
2323
= "f" ++ mkTyName a ++ mkTyName b
2424
-- eg. mkTyName (a -> b -> C) = "f_C"
25-
mkTyName (tcSplitFunTys -> ((_:_), b))
25+
mkTyName (tcSplitFunTys -> (_:_, b))
2626
= "f_" ++ mkTyName b
2727
-- eg. mkTyName (Either A B) = "eab"
2828
mkTyName (splitTyConApp_maybe -> Just (c, args))
@@ -31,7 +31,7 @@ mkTyName (splitTyConApp_maybe -> Just (c, args))
3131
mkTyName (getTyVar_maybe -> Just tv)
3232
= occNameString $ occName tv
3333
-- eg. mkTyName (forall x. y) = "y"
34-
mkTyName (tcSplitSigmaTy -> ((_:_), _, t))
34+
mkTyName (tcSplitSigmaTy -> (_:_, _, t))
3535
= mkTyName t
3636
mkTyName _ = "x"
3737

@@ -90,4 +90,3 @@ mkManyGoodNames hy args =
9090
-- | Which names are in scope?
9191
getInScope :: Map OccName a -> [OccName]
9292
getInScope = M.keys
93-

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

+4-5
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ instance Show Class where
7777
data TacticState = TacticState
7878
{ ts_skolems :: !(Set TyVar)
7979
-- ^ The known skolems.
80-
, ts_unifier :: !(TCvSubst)
80+
, ts_unifier :: !TCvSubst
8181
-- ^ The current substitution of univars.
8282
, ts_used_vals :: !(Set OccName)
8383
-- ^ Set of values used by tactics.
@@ -236,10 +236,10 @@ overProvenance f (HyInfo prv ty) = HyInfo (f prv) ty
236236
-- | The current bindings and goal for a hole to be filled by refinery.
237237
data Judgement' a = Judgement
238238
{ _jHypothesis :: !(Map OccName (HyInfo a))
239-
, _jBlacklistDestruct :: !(Bool)
240-
, _jWhitelistSplit :: !(Bool)
239+
, _jBlacklistDestruct :: !Bool
240+
, _jWhitelistSplit :: !Bool
241241
, _jIsTopHole :: !Bool
242-
, _jGoal :: !(a)
242+
, _jGoal :: !a
243243
}
244244
deriving stock (Eq, Generic, Functor, Show)
245245

@@ -364,4 +364,3 @@ data RunTacticResults = RunTacticResults
364364
, rtr_extract :: LHsExpr GhcPs
365365
, rtr_other_solns :: [(Trace, LHsExpr GhcPs)]
366366
} deriving Show
367-

src/Ide/Version.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ showProgramVersionOfInterest ProgramsOfInterest {..} =
4949
]
5050
where
5151
showVersionWithDefault :: Maybe Version -> String
52-
showVersionWithDefault = maybe ("Not found") showVersion
52+
showVersionWithDefault = maybe "Not found" showVersion
5353

5454
findProgramVersions :: IO ProgramsOfInterest
5555
findProgramVersions = ProgramsOfInterest

test/functional/Completion.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -298,7 +298,7 @@ snippetTests = testGroup "snippets" [
298298
, testCase "respects lsp configuration" $ runSession hlsCommand fullCaps "test/testdata/completion" $ do
299299
doc <- openDoc "Completion.hs" "haskell"
300300

301-
let config = object [ "haskell" .= (object ["completionSnippetsOn" .= False])]
301+
let config = object [ "haskell" .= object ["completionSnippetsOn" .= False]]
302302

303303
sendNotification WorkspaceDidChangeConfiguration
304304
(DidChangeConfigurationParams config)

test/functional/FunctionalCodeAction.hs

+5-5
Original file line numberDiff line numberDiff line change
@@ -370,7 +370,7 @@ redundantImportTests = testGroup "redundant import code actions" [
370370
CACommand cmd : _ <- getAllCodeActions doc
371371
executeCommand cmd
372372
contents <- documentContents doc
373-
liftIO $ (T.lines contents) @?=
373+
liftIO $ T.lines contents @?=
374374
[ "{-# OPTIONS_GHC -Wunused-imports #-}"
375375
, "module MultipleImports where"
376376
, "import Data.Maybe"
@@ -435,7 +435,7 @@ signatureTests = testGroup "missing top level signature code actions" [
435435
_ <- waitForDiagnosticsFromSource doc "typecheck"
436436
cas <- map fromAction <$> getAllCodeActions doc
437437

438-
liftIO $ "add signature: main :: IO ()" `elem` (map (^. L.title) cas) @? "Contains code action"
438+
liftIO $ "add signature: main :: IO ()" `elem` map (^. L.title) cas @? "Contains code action"
439439

440440
executeCodeAction $ head cas
441441

@@ -449,7 +449,7 @@ signatureTests = testGroup "missing top level signature code actions" [
449449
, " return ()"
450450
]
451451

452-
liftIO $ (T.lines contents) @?= expected
452+
liftIO $ T.lines contents @?= expected
453453
]
454454

455455
missingPragmaTests :: TestTree
@@ -487,7 +487,7 @@ missingPragmaTests = testGroup "missing pragma warning code actions" [
487487
, " deriving (Generic,Functor,Traversable)"
488488
]
489489

490-
liftIO $ (T.lines contents) @?= expected
490+
liftIO $ T.lines contents @?= expected
491491

492492
, testCase "Adds TypeApplications pragma" $ do
493493
runSession hlsCommand fullCaps "test/testdata/addPragmas" $ do
@@ -511,7 +511,7 @@ missingPragmaTests = testGroup "missing pragma warning code actions" [
511511
, "foo = id @a"
512512
]
513513

514-
liftIO $ (T.lines contents) @?= expected
514+
liftIO $ T.lines contents @?= expected
515515
]
516516

517517
unusedTermTests :: TestTree

test/functional/Tactic.hs

+2-3
Original file line numberDiff line numberDiff line change
@@ -154,7 +154,7 @@ goldenTest input line col tc occ =
154154
doc <- openDoc input "haskell"
155155
_ <- waitForDiagnostics
156156
actions <- getCodeActions doc $ pointRange line col
157-
Just (CACodeAction (CodeAction {_command = Just c}))
157+
Just (CACodeAction CodeAction {_command = Just c})
158158
<- pure $ find ((== Just (tacticTitle tc occ)) . codeActionTitle) actions
159159
executeCommand c
160160
_resp :: ApplyWorkspaceEditRequest <- skipManyTill anyMessage message
@@ -174,7 +174,7 @@ expectFail input line col tc occ =
174174
doc <- openDoc input "haskell"
175175
_ <- waitForDiagnostics
176176
actions <- getCodeActions doc $ pointRange line col
177-
Just (CACodeAction (CodeAction {_command = Just c}))
177+
Just (CACodeAction CodeAction {_command = Just c})
178178
<- pure $ find ((== Just (tacticTitle tc occ)) . codeActionTitle) actions
179179
resp <- executeCommandWithResp c
180180
liftIO $ unless (isLeft $ _result resp) $
@@ -190,4 +190,3 @@ executeCommandWithResp cmd = do
190190
let args = decode $ encode $ fromJust $ cmd ^. arguments
191191
execParams = ExecuteCommandParams (cmd ^. command) args Nothing
192192
request WorkspaceExecuteCommand execParams
193-

0 commit comments

Comments
 (0)