Skip to content

Commit 5f630eb

Browse files
philderbeastulysses4ever
authored andcommitted
Follow hlint suggestion: move brackets to avoid $
1 parent a17f56c commit 5f630eb

File tree

17 files changed

+36
-42
lines changed

17 files changed

+36
-42
lines changed

.hlint.yaml

-1
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,6 @@
1212
- ignore: {name: "Missing NOINLINE pragma"} # 1 hint
1313
- ignore: {name: "Monoid law, left identity"} # 3 hints
1414
- ignore: {name: "Monoid law, right identity"} # 3 hints
15-
- ignore: {name: "Move brackets to avoid $"} # 25 hints
1615
- ignore: {name: "Move guards forward"} # 4 hints
1716
- ignore: {name: "Redundant $"} # 125 hints
1817
- ignore: {name: "Redundant $!"} # 4 hints

Cabal/src/Distribution/Compat/ResponseFile.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,7 @@ expandResponse = go recursionLimit "."
7676
| otherwise = const $ hPutStrLn stderr "Error: response file recursion limit exceeded." >> exitFailure
7777

7878
expand :: Int -> FilePath -> String -> IO [String]
79-
expand n dir arg@('@' : f) = readRecursively n (dir </> f) `catchIOError` (const $ print "?" >> return [arg])
79+
expand n dir arg@('@' : f) = readRecursively n (dir </> f) `catchIOError` const (print "?" >> return [arg])
8080
expand _n _dir x = return [x]
8181

8282
readRecursively :: Int -> FilePath -> IO [String]

Cabal/src/Distribution/Compat/Time.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -155,7 +155,7 @@ posixSecondsToModTime s =
155155
posixTimeToModTime :: POSIXTime -> ModTime
156156
posixTimeToModTime p =
157157
ModTime $
158-
(ceiling $ p * 1e7) -- 100 ns precision
158+
ceiling (p * 1e7) -- 100 ns precision
159159
+ (secToUnixEpoch * windowsTick)
160160

161161
-- | Return age of given file in days.

Cabal/src/Distribution/ReadE.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ runParsecFromString p txt =
5555

5656
parsecToReadE :: (String -> ErrorMsg) -> ParsecParser a -> ReadE a
5757
parsecToReadE err p = ReadE $ \txt ->
58-
(const $ err txt) `Bi.first` runParsecFromString p txt
58+
const (err txt) `Bi.first` runParsecFromString p txt
5959

6060
parsecToReadEErr :: (Parsec.ParseError -> ErrorMsg) -> ParsecParser a -> ReadE a
6161
parsecToReadEErr err p =

Cabal/src/Distribution/Simple/Build.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -857,7 +857,7 @@ testSuiteLibV09AsLibAndExe
857857
{ hsSourceDirs = [unsafeMakeSymbolicPath testDir]
858858
, targetBuildDepends =
859859
testLibDep
860-
: (targetBuildDepends $ testBuildInfo test)
860+
: targetBuildDepends (testBuildInfo test)
861861
}
862862
}
863863
-- \| The stub executable needs a new 'ComponentLocalBuildInfo'

Cabal/src/Distribution/Simple/Haddock.hs

+7-10
Original file line numberDiff line numberDiff line change
@@ -395,7 +395,7 @@ haddock pkg_descr lbi suffixes flags' = do
395395

396396
return $ PackageIndex.insert ipi index
397397
CFLib flib ->
398-
( when (flag haddockForeignLibs) $ do
398+
when (flag haddockForeignLibs) (do
399399
withTempDirectoryEx verbosity tmpFileOpts (buildDir lbi') "tmp" $
400400
\tmp -> do
401401
smsg
@@ -409,12 +409,11 @@ haddock pkg_descr lbi suffixes flags' = do
409409
version
410410
flib
411411
let libArgs' = commonArgs `mappend` flibArgs
412-
runHaddock verbosity tmpFileOpts comp platform haddockProg True libArgs'
413-
)
412+
runHaddock verbosity tmpFileOpts comp platform haddockProg True libArgs')
414413
>> return index
415-
CExe _ -> (when (flag haddockExecutables) $ smsg >> doExe component) >> return index
416-
CTest _ -> (when (flag haddockTestSuites) $ smsg >> doExe component) >> return index
417-
CBench _ -> (when (flag haddockBenchmarks) $ smsg >> doExe component) >> return index
414+
CExe _ -> when (flag haddockExecutables) (smsg >> doExe component) >> return index
415+
CTest _ -> when (flag haddockTestSuites) (smsg >> doExe component) >> return index
416+
CBench _ -> when (flag haddockBenchmarks) (smsg >> doExe component) >> return index
418417

419418
for_ (extraDocFiles pkg_descr) $ \fpath -> do
420419
files <- matchDirFileGlob verbosity (specVersion pkg_descr) "." fpath
@@ -937,8 +936,7 @@ renderPureArgs version comp platform args =
937936
renderInterface :: (FilePath, Maybe FilePath, Maybe FilePath, Visibility) -> String
938937
renderInterface (i, html, hypsrc, visibility) =
939938
"--read-interface="
940-
++ ( intercalate "," $
941-
concat
939+
++ intercalate "," (concat
942940
[ [fromMaybe "" html]
943941
, -- only render hypsrc path if html path
944942
-- is given and hyperlinked-source is
@@ -962,8 +960,7 @@ renderPureArgs version comp platform args =
962960
]
963961
else []
964962
, [i]
965-
]
966-
)
963+
])
967964

968965
bool a b c = if c then a else b
969966
isVersion major minor = version >= mkVersion [major, minor]

Cabal/src/Distribution/Utils/Json.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@ renderJson json = toLazyByteString (go json)
3939
go (JsonObject attrs) =
4040
surround "{" "}" $ mconcat $ intersperse "," $ map render attrs
4141
where
42-
render (k, v) = (surround "\"" "\"" $ stringUtf8 (escape k)) <> ":" <> go v
42+
render (k, v) = surround "\"" "\"" (stringUtf8 (escape k)) <> ":" <> go v
4343
go (JsonString s) = surround "\"" "\"" $ stringUtf8 (escape s)
4444

4545
surround :: Builder -> Builder -> Builder -> Builder

cabal-install-solver/src/Distribution/Solver/Modular/Linking.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -85,11 +85,11 @@ validateLinking index = (`runReader` initVS) . go
8585
go :: Tree d c -> Validate (Tree d c)
8686

8787
go (PChoice qpn rdm gr cs) =
88-
PChoice qpn rdm gr <$> (W.traverseWithKey (goP qpn) $ fmap go cs)
88+
PChoice qpn rdm gr <$> W.traverseWithKey (goP qpn) (fmap go cs)
8989
go (FChoice qfn rdm gr t m d cs) =
90-
FChoice qfn rdm gr t m d <$> (W.traverseWithKey (goF qfn) $ fmap go cs)
90+
FChoice qfn rdm gr t m d <$> W.traverseWithKey (goF qfn) (fmap go cs)
9191
go (SChoice qsn rdm gr t cs) =
92-
SChoice qsn rdm gr t <$> (W.traverseWithKey (goS qsn) $ fmap go cs)
92+
SChoice qsn rdm gr t <$> W.traverseWithKey (goS qsn) (fmap go cs)
9393

9494
-- For the other nodes we just recurse
9595
go (GoalChoice rdm cs) = GoalChoice rdm <$> T.traverse go cs

cabal-install-solver/src/Distribution/Solver/Modular/Message.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ showMessages = go 0
6666
go !l (Step (Next (Goal (P _ ) gr)) (Step (TryP qpn' i) ms@(Step Enter (Step (Next _) _)))) =
6767
(atLevel l $ "trying: " ++ showQPNPOpt qpn' i ++ showGR gr) (go l ms)
6868
go !l (Step (Next (Goal (P qpn) gr)) (Step (Failure _c UnknownPackage) ms)) =
69-
(atLevel l $ "unknown package: " ++ showQPN qpn ++ showGR gr) $ go l ms
69+
atLevel l ("unknown package: " ++ showQPN qpn ++ showGR gr) $ go l ms
7070
-- standard display
7171
go !l (Step Enter ms) = go (l+1) ms
7272
go !l (Step Leave ms) = go (l-1) ms

cabal-install/src/Distribution/Client/CmdRun.hs

+7-6
Original file line numberDiff line numberDiff line change
@@ -514,12 +514,13 @@ renderRunProblem (TargetProblemMatchesMultiple targetSelector targets) =
514514
++ " which includes \n"
515515
++ unlines
516516
( (\(label, xs) -> "- " ++ label ++ ": " ++ renderListPretty xs)
517-
<$> ( zip ["executables", "test-suites", "benchmarks"] $
518-
filter (not . null) . map removeDuplicates $
519-
map (componentNameRaw . availableTargetComponentName)
520-
<$> (flip filterTargetsKind $ targets)
521-
<$> [ExeKind, TestKind, BenchKind]
522-
)
517+
<$> zip
518+
["executables", "test-suites", "benchmarks"]
519+
( filter (not . null) . map removeDuplicates $
520+
map (componentNameRaw . availableTargetComponentName)
521+
<$> (flip filterTargetsKind $ targets)
522+
<$> [ExeKind, TestKind, BenchKind]
523+
)
523524
)
524525
where
525526
removeDuplicates = catMaybes . map safeHead . group . sort

cabal-install/src/Distribution/Client/GenBounds.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,7 @@ pvpize v =
104104
showBounds :: Package pkg => Int -> pkg -> String
105105
showBounds padTo p =
106106
unwords $
107-
(padAfter padTo $ unPackageName $ packageName p)
107+
padAfter padTo (unPackageName $ packageName p)
108108
:
109109
-- TODO: use normaliseVersionRange
110110
map showInterval (asVersionIntervals $ pvpize $ packageVersion p)

cabal-install/src/Distribution/Client/Install.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -1790,7 +1790,7 @@ installLocalTarballPackage
17901790
distDirExists <- doesDirectoryExist distDirPath
17911791
when
17921792
( distDirExists
1793-
&& (not $ distDirPath `equalFilePath` distDirPathNew)
1793+
&& not (distDirPath `equalFilePath` distDirPathNew)
17941794
)
17951795
$ do
17961796
-- NB: we need to handle the case when 'distDirPathNew' is a

cabal-install/src/Distribution/Client/List.hs

+4-8
Original file line numberDiff line numberDiff line change
@@ -431,8 +431,7 @@ showPackageSummaryInfo pkginfo =
431431
renderStyle (style{lineLength = 80, ribbonsPerLine = 1}) $
432432
char '*'
433433
<+> pretty (pkgName pkginfo)
434-
$+$ ( nest 4 $
435-
vcat
434+
$+$ nest 4 (vcat
436435
[ maybeShowST (synopsis pkginfo) "Synopsis:" reflowParagraphs
437436
, text "Default available version:"
438437
<+> case selectedSourcePkg pkginfo of
@@ -450,8 +449,7 @@ showPackageSummaryInfo pkginfo =
450449
versions
451450
, maybeShowST (homepage pkginfo) "Homepage:" text
452451
, text "License: " <+> either pretty pretty (license pkginfo)
453-
]
454-
)
452+
])
455453
$+$ text ""
456454
where
457455
maybeShowST l s f
@@ -466,8 +464,7 @@ showPackageDetailedInfo pkginfo =
466464
<<>> maybe Disp.empty (\v -> char '-' Disp.<> pretty v) (selectedVersion pkginfo)
467465
<+> text (replicate (16 - length (prettyShow (pkgName pkginfo))) ' ')
468466
<<>> parens pkgkind
469-
$+$ ( nest 4 $
470-
vcat
467+
$+$ nest 4 (vcat
471468
[ entryST "Synopsis" synopsis hideIfNull reflowParagraphs
472469
, entry
473470
"Versions available"
@@ -501,8 +498,7 @@ showPackageDetailedInfo pkginfo =
501498
, if not (hasLib pkginfo)
502499
then mempty
503500
else text "Modules:" $+$ nest 4 (vcat (map pretty . sort . modules $ pkginfo))
504-
]
505-
)
501+
])
506502
$+$ text ""
507503
where
508504
entry fname field cond format = case cond (field pkginfo) of

cabal-install/src/Distribution/Client/ProjectPlanOutput.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -193,7 +193,8 @@ encodePlanAsJson distDirLayout elaboratedInstallPlan elaboratedSharedConfig =
193193
let components =
194194
J.object $
195195
[ comp2str c
196-
J..= ( J.object $
196+
J..= J.object
197+
(
197198
[ "depends" J..= map (jdisplay . confInstId) (map fst ldeps)
198199
, "exe-depends" J..= map (jdisplay . confInstId) edeps
199200
]

cabal-install/src/Distribution/Client/ProjectPlanning.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -414,7 +414,7 @@ rebuildProjectConfig
414414
let fetchCompiler = do
415415
-- have to create the cache directory before configuring the compiler
416416
liftIO $ createDirectoryIfMissingVerbose verbosity True distProjectCacheDirectory
417-
(compiler, Platform arch os, _) <- configureCompiler verbosity distDirLayout ((fst $ PD.ignoreConditions projectConfigSkeleton) <> cliConfig)
417+
(compiler, Platform arch os, _) <- configureCompiler verbosity distDirLayout (fst (PD.ignoreConditions projectConfigSkeleton) <> cliConfig)
418418
pure (os, arch, compilerInfo compiler)
419419

420420
projectConfig <- instantiateProjectConfigSkeletonFetchingCompiler fetchCompiler mempty projectConfigSkeleton
@@ -4545,7 +4545,7 @@ packageHashInputs
45454545
Set.fromList
45464546
( map
45474547
confInstId
4548-
( (map fst $ compLibDependencies comp)
4548+
( map fst (compLibDependencies comp)
45494549
++ compExeDependencies comp
45504550
)
45514551
)

cabal-install/src/Distribution/Client/Utils.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -229,7 +229,7 @@ logDirChange _ Nothing m = m
229229
logDirChange l (Just d) m = do
230230
l $ "cabal: Entering directory '" ++ d ++ "'\n"
231231
m
232-
`Exception.finally` (l $ "cabal: Leaving directory '" ++ d ++ "'\n")
232+
`Exception.finally` l ("cabal: Leaving directory '" ++ d ++ "'\n")
233233

234234
-- The number of processors is not going to change during the duration of the
235235
-- program, so unsafePerformIO is safe here.

generics-sop-lens.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -64,13 +64,13 @@ genericClassyLenses p = case gdatatypeInfo p of
6464
, " " ++ dn' ++ " :: Lens' a " ++ dn
6565
, ""
6666
]] ++
67-
(hcollapse $ hcmap (Proxy :: Proxy Typeable) deriveCls fis) ++
67+
hcollapse (hcmap (Proxy :: Proxy Typeable) deriveCls fis) ++
6868
[[ ""
6969
, "instance Has" ++ dn ++ " " ++ dn ++ " where"
7070
, " " ++ dn' ++ " = id"
7171
, " {-# INLINE " ++ dn' ++ " #-}"
7272
]] ++
73-
(hcollapse $ hcmap (Proxy :: Proxy Typeable) deriveInst fis)
73+
hcollapse (hcmap (Proxy :: Proxy Typeable) deriveInst fis)
7474
where
7575
dn' = case dn of
7676
[] -> []

0 commit comments

Comments
 (0)