From 5f630eb0aa3e4872e9eb870349cf50b4360930b5 Mon Sep 17 00:00:00 2001 From: Phil de Joux <philderbeast@gmail.com> Date: Tue, 11 Jul 2023 07:49:15 -0400 Subject: [PATCH] Follow hlint suggestion: move brackets to avoid $ --- .hlint.yaml | 1 - Cabal/src/Distribution/Compat/ResponseFile.hs | 2 +- Cabal/src/Distribution/Compat/Time.hs | 2 +- Cabal/src/Distribution/ReadE.hs | 2 +- Cabal/src/Distribution/Simple/Build.hs | 2 +- Cabal/src/Distribution/Simple/Haddock.hs | 17 +++++++---------- Cabal/src/Distribution/Utils/Json.hs | 2 +- .../src/Distribution/Solver/Modular/Linking.hs | 6 +++--- .../src/Distribution/Solver/Modular/Message.hs | 2 +- cabal-install/src/Distribution/Client/CmdRun.hs | 13 +++++++------ .../src/Distribution/Client/GenBounds.hs | 2 +- .../src/Distribution/Client/Install.hs | 2 +- cabal-install/src/Distribution/Client/List.hs | 12 ++++-------- .../Distribution/Client/ProjectPlanOutput.hs | 3 ++- .../src/Distribution/Client/ProjectPlanning.hs | 4 ++-- cabal-install/src/Distribution/Client/Utils.hs | 2 +- generics-sop-lens.hs | 4 ++-- 17 files changed, 36 insertions(+), 42 deletions(-) diff --git a/.hlint.yaml b/.hlint.yaml index 65b1c7492b..49c81e1f07 100644 --- a/.hlint.yaml +++ b/.hlint.yaml @@ -12,7 +12,6 @@ - ignore: {name: "Missing NOINLINE pragma"} # 1 hint - ignore: {name: "Monoid law, left identity"} # 3 hints - ignore: {name: "Monoid law, right identity"} # 3 hints -- ignore: {name: "Move brackets to avoid $"} # 25 hints - ignore: {name: "Move guards forward"} # 4 hints - ignore: {name: "Redundant $"} # 125 hints - ignore: {name: "Redundant $!"} # 4 hints diff --git a/Cabal/src/Distribution/Compat/ResponseFile.hs b/Cabal/src/Distribution/Compat/ResponseFile.hs index fb9d330963..c03207fed5 100644 --- a/Cabal/src/Distribution/Compat/ResponseFile.hs +++ b/Cabal/src/Distribution/Compat/ResponseFile.hs @@ -76,7 +76,7 @@ expandResponse = go recursionLimit "." | otherwise = const $ hPutStrLn stderr "Error: response file recursion limit exceeded." >> exitFailure expand :: Int -> FilePath -> String -> IO [String] - expand n dir arg@('@' : f) = readRecursively n (dir </> f) `catchIOError` (const $ print "?" >> return [arg]) + expand n dir arg@('@' : f) = readRecursively n (dir </> f) `catchIOError` const (print "?" >> return [arg]) expand _n _dir x = return [x] readRecursively :: Int -> FilePath -> IO [String] diff --git a/Cabal/src/Distribution/Compat/Time.hs b/Cabal/src/Distribution/Compat/Time.hs index 168c2d919b..9727690bf1 100644 --- a/Cabal/src/Distribution/Compat/Time.hs +++ b/Cabal/src/Distribution/Compat/Time.hs @@ -155,7 +155,7 @@ posixSecondsToModTime s = posixTimeToModTime :: POSIXTime -> ModTime posixTimeToModTime p = ModTime $ - (ceiling $ p * 1e7) -- 100 ns precision + ceiling (p * 1e7) -- 100 ns precision + (secToUnixEpoch * windowsTick) -- | Return age of given file in days. diff --git a/Cabal/src/Distribution/ReadE.hs b/Cabal/src/Distribution/ReadE.hs index 072dee9904..d7a64b8d07 100644 --- a/Cabal/src/Distribution/ReadE.hs +++ b/Cabal/src/Distribution/ReadE.hs @@ -55,7 +55,7 @@ runParsecFromString p txt = parsecToReadE :: (String -> ErrorMsg) -> ParsecParser a -> ReadE a parsecToReadE err p = ReadE $ \txt -> - (const $ err txt) `Bi.first` runParsecFromString p txt + const (err txt) `Bi.first` runParsecFromString p txt parsecToReadEErr :: (Parsec.ParseError -> ErrorMsg) -> ParsecParser a -> ReadE a parsecToReadEErr err p = diff --git a/Cabal/src/Distribution/Simple/Build.hs b/Cabal/src/Distribution/Simple/Build.hs index c2e421045b..25a0af6db3 100644 --- a/Cabal/src/Distribution/Simple/Build.hs +++ b/Cabal/src/Distribution/Simple/Build.hs @@ -857,7 +857,7 @@ testSuiteLibV09AsLibAndExe { hsSourceDirs = [unsafeMakeSymbolicPath testDir] , targetBuildDepends = testLibDep - : (targetBuildDepends $ testBuildInfo test) + : targetBuildDepends (testBuildInfo test) } } -- \| The stub executable needs a new 'ComponentLocalBuildInfo' diff --git a/Cabal/src/Distribution/Simple/Haddock.hs b/Cabal/src/Distribution/Simple/Haddock.hs index 8e90f6f6dd..04e9613083 100644 --- a/Cabal/src/Distribution/Simple/Haddock.hs +++ b/Cabal/src/Distribution/Simple/Haddock.hs @@ -395,7 +395,7 @@ haddock pkg_descr lbi suffixes flags' = do return $ PackageIndex.insert ipi index CFLib flib -> - ( when (flag haddockForeignLibs) $ do + when (flag haddockForeignLibs) (do withTempDirectoryEx verbosity tmpFileOpts (buildDir lbi') "tmp" $ \tmp -> do smsg @@ -409,12 +409,11 @@ haddock pkg_descr lbi suffixes flags' = do version flib let libArgs' = commonArgs `mappend` flibArgs - runHaddock verbosity tmpFileOpts comp platform haddockProg True libArgs' - ) + runHaddock verbosity tmpFileOpts comp platform haddockProg True libArgs') >> return index - CExe _ -> (when (flag haddockExecutables) $ smsg >> doExe component) >> return index - CTest _ -> (when (flag haddockTestSuites) $ smsg >> doExe component) >> return index - CBench _ -> (when (flag haddockBenchmarks) $ smsg >> doExe component) >> return index + CExe _ -> when (flag haddockExecutables) (smsg >> doExe component) >> return index + CTest _ -> when (flag haddockTestSuites) (smsg >> doExe component) >> return index + CBench _ -> when (flag haddockBenchmarks) (smsg >> doExe component) >> return index for_ (extraDocFiles pkg_descr) $ \fpath -> do files <- matchDirFileGlob verbosity (specVersion pkg_descr) "." fpath @@ -937,8 +936,7 @@ renderPureArgs version comp platform args = renderInterface :: (FilePath, Maybe FilePath, Maybe FilePath, Visibility) -> String renderInterface (i, html, hypsrc, visibility) = "--read-interface=" - ++ ( intercalate "," $ - concat + ++ intercalate "," (concat [ [fromMaybe "" html] , -- only render hypsrc path if html path -- is given and hyperlinked-source is @@ -962,8 +960,7 @@ renderPureArgs version comp platform args = ] else [] , [i] - ] - ) + ]) bool a b c = if c then a else b isVersion major minor = version >= mkVersion [major, minor] diff --git a/Cabal/src/Distribution/Utils/Json.hs b/Cabal/src/Distribution/Utils/Json.hs index 873e60631a..4f8bea52cb 100644 --- a/Cabal/src/Distribution/Utils/Json.hs +++ b/Cabal/src/Distribution/Utils/Json.hs @@ -39,7 +39,7 @@ renderJson json = toLazyByteString (go json) go (JsonObject attrs) = surround "{" "}" $ mconcat $ intersperse "," $ map render attrs where - render (k, v) = (surround "\"" "\"" $ stringUtf8 (escape k)) <> ":" <> go v + render (k, v) = surround "\"" "\"" (stringUtf8 (escape k)) <> ":" <> go v go (JsonString s) = surround "\"" "\"" $ stringUtf8 (escape s) surround :: Builder -> Builder -> Builder -> Builder diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/Linking.hs b/cabal-install-solver/src/Distribution/Solver/Modular/Linking.hs index eb3c98a8ac..3e4e2de3ee 100644 --- a/cabal-install-solver/src/Distribution/Solver/Modular/Linking.hs +++ b/cabal-install-solver/src/Distribution/Solver/Modular/Linking.hs @@ -85,11 +85,11 @@ validateLinking index = (`runReader` initVS) . go go :: Tree d c -> Validate (Tree d c) go (PChoice qpn rdm gr cs) = - PChoice qpn rdm gr <$> (W.traverseWithKey (goP qpn) $ fmap go cs) + PChoice qpn rdm gr <$> W.traverseWithKey (goP qpn) (fmap go cs) go (FChoice qfn rdm gr t m d cs) = - FChoice qfn rdm gr t m d <$> (W.traverseWithKey (goF qfn) $ fmap go cs) + FChoice qfn rdm gr t m d <$> W.traverseWithKey (goF qfn) (fmap go cs) go (SChoice qsn rdm gr t cs) = - SChoice qsn rdm gr t <$> (W.traverseWithKey (goS qsn) $ fmap go cs) + SChoice qsn rdm gr t <$> W.traverseWithKey (goS qsn) (fmap go cs) -- For the other nodes we just recurse go (GoalChoice rdm cs) = GoalChoice rdm <$> T.traverse go cs diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs b/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs index eade1c3a1a..d802079d04 100644 --- a/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs +++ b/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs @@ -66,7 +66,7 @@ showMessages = go 0 go !l (Step (Next (Goal (P _ ) gr)) (Step (TryP qpn' i) ms@(Step Enter (Step (Next _) _)))) = (atLevel l $ "trying: " ++ showQPNPOpt qpn' i ++ showGR gr) (go l ms) go !l (Step (Next (Goal (P qpn) gr)) (Step (Failure _c UnknownPackage) ms)) = - (atLevel l $ "unknown package: " ++ showQPN qpn ++ showGR gr) $ go l ms + atLevel l ("unknown package: " ++ showQPN qpn ++ showGR gr) $ go l ms -- standard display go !l (Step Enter ms) = go (l+1) ms go !l (Step Leave ms) = go (l-1) ms diff --git a/cabal-install/src/Distribution/Client/CmdRun.hs b/cabal-install/src/Distribution/Client/CmdRun.hs index cf9338e82d..8d25932422 100644 --- a/cabal-install/src/Distribution/Client/CmdRun.hs +++ b/cabal-install/src/Distribution/Client/CmdRun.hs @@ -514,12 +514,13 @@ renderRunProblem (TargetProblemMatchesMultiple targetSelector targets) = ++ " which includes \n" ++ unlines ( (\(label, xs) -> "- " ++ label ++ ": " ++ renderListPretty xs) - <$> ( zip ["executables", "test-suites", "benchmarks"] $ - filter (not . null) . map removeDuplicates $ - map (componentNameRaw . availableTargetComponentName) - <$> (flip filterTargetsKind $ targets) - <$> [ExeKind, TestKind, BenchKind] - ) + <$> zip + ["executables", "test-suites", "benchmarks"] + ( filter (not . null) . map removeDuplicates $ + map (componentNameRaw . availableTargetComponentName) + <$> (flip filterTargetsKind $ targets) + <$> [ExeKind, TestKind, BenchKind] + ) ) where removeDuplicates = catMaybes . map safeHead . group . sort diff --git a/cabal-install/src/Distribution/Client/GenBounds.hs b/cabal-install/src/Distribution/Client/GenBounds.hs index e3584ab8cd..ab69bb55ef 100644 --- a/cabal-install/src/Distribution/Client/GenBounds.hs +++ b/cabal-install/src/Distribution/Client/GenBounds.hs @@ -104,7 +104,7 @@ pvpize v = showBounds :: Package pkg => Int -> pkg -> String showBounds padTo p = unwords $ - (padAfter padTo $ unPackageName $ packageName p) + padAfter padTo (unPackageName $ packageName p) : -- TODO: use normaliseVersionRange map showInterval (asVersionIntervals $ pvpize $ packageVersion p) diff --git a/cabal-install/src/Distribution/Client/Install.hs b/cabal-install/src/Distribution/Client/Install.hs index 93ad8e5ae2..a7eed14fbb 100644 --- a/cabal-install/src/Distribution/Client/Install.hs +++ b/cabal-install/src/Distribution/Client/Install.hs @@ -1790,7 +1790,7 @@ installLocalTarballPackage distDirExists <- doesDirectoryExist distDirPath when ( distDirExists - && (not $ distDirPath `equalFilePath` distDirPathNew) + && not (distDirPath `equalFilePath` distDirPathNew) ) $ do -- NB: we need to handle the case when 'distDirPathNew' is a diff --git a/cabal-install/src/Distribution/Client/List.hs b/cabal-install/src/Distribution/Client/List.hs index ef9285bf39..55f5f34c89 100644 --- a/cabal-install/src/Distribution/Client/List.hs +++ b/cabal-install/src/Distribution/Client/List.hs @@ -431,8 +431,7 @@ showPackageSummaryInfo pkginfo = renderStyle (style{lineLength = 80, ribbonsPerLine = 1}) $ char '*' <+> pretty (pkgName pkginfo) - $+$ ( nest 4 $ - vcat + $+$ nest 4 (vcat [ maybeShowST (synopsis pkginfo) "Synopsis:" reflowParagraphs , text "Default available version:" <+> case selectedSourcePkg pkginfo of @@ -450,8 +449,7 @@ showPackageSummaryInfo pkginfo = versions , maybeShowST (homepage pkginfo) "Homepage:" text , text "License: " <+> either pretty pretty (license pkginfo) - ] - ) + ]) $+$ text "" where maybeShowST l s f @@ -466,8 +464,7 @@ showPackageDetailedInfo pkginfo = <<>> maybe Disp.empty (\v -> char '-' Disp.<> pretty v) (selectedVersion pkginfo) <+> text (replicate (16 - length (prettyShow (pkgName pkginfo))) ' ') <<>> parens pkgkind - $+$ ( nest 4 $ - vcat + $+$ nest 4 (vcat [ entryST "Synopsis" synopsis hideIfNull reflowParagraphs , entry "Versions available" @@ -501,8 +498,7 @@ showPackageDetailedInfo pkginfo = , if not (hasLib pkginfo) then mempty else text "Modules:" $+$ nest 4 (vcat (map pretty . sort . modules $ pkginfo)) - ] - ) + ]) $+$ text "" where entry fname field cond format = case cond (field pkginfo) of diff --git a/cabal-install/src/Distribution/Client/ProjectPlanOutput.hs b/cabal-install/src/Distribution/Client/ProjectPlanOutput.hs index 57aa77af89..018ea89552 100644 --- a/cabal-install/src/Distribution/Client/ProjectPlanOutput.hs +++ b/cabal-install/src/Distribution/Client/ProjectPlanOutput.hs @@ -193,7 +193,8 @@ encodePlanAsJson distDirLayout elaboratedInstallPlan elaboratedSharedConfig = let components = J.object $ [ comp2str c - J..= ( J.object $ + J..= J.object + ( [ "depends" J..= map (jdisplay . confInstId) (map fst ldeps) , "exe-depends" J..= map (jdisplay . confInstId) edeps ] diff --git a/cabal-install/src/Distribution/Client/ProjectPlanning.hs b/cabal-install/src/Distribution/Client/ProjectPlanning.hs index a67a66a0e5..28066513de 100644 --- a/cabal-install/src/Distribution/Client/ProjectPlanning.hs +++ b/cabal-install/src/Distribution/Client/ProjectPlanning.hs @@ -414,7 +414,7 @@ rebuildProjectConfig let fetchCompiler = do -- have to create the cache directory before configuring the compiler liftIO $ createDirectoryIfMissingVerbose verbosity True distProjectCacheDirectory - (compiler, Platform arch os, _) <- configureCompiler verbosity distDirLayout ((fst $ PD.ignoreConditions projectConfigSkeleton) <> cliConfig) + (compiler, Platform arch os, _) <- configureCompiler verbosity distDirLayout (fst (PD.ignoreConditions projectConfigSkeleton) <> cliConfig) pure (os, arch, compilerInfo compiler) projectConfig <- instantiateProjectConfigSkeletonFetchingCompiler fetchCompiler mempty projectConfigSkeleton @@ -4545,7 +4545,7 @@ packageHashInputs Set.fromList ( map confInstId - ( (map fst $ compLibDependencies comp) + ( map fst (compLibDependencies comp) ++ compExeDependencies comp ) ) diff --git a/cabal-install/src/Distribution/Client/Utils.hs b/cabal-install/src/Distribution/Client/Utils.hs index f7a51bf8c4..6a744fca3b 100644 --- a/cabal-install/src/Distribution/Client/Utils.hs +++ b/cabal-install/src/Distribution/Client/Utils.hs @@ -229,7 +229,7 @@ logDirChange _ Nothing m = m logDirChange l (Just d) m = do l $ "cabal: Entering directory '" ++ d ++ "'\n" m - `Exception.finally` (l $ "cabal: Leaving directory '" ++ d ++ "'\n") + `Exception.finally` l ("cabal: Leaving directory '" ++ d ++ "'\n") -- The number of processors is not going to change during the duration of the -- program, so unsafePerformIO is safe here. diff --git a/generics-sop-lens.hs b/generics-sop-lens.hs index 457c4dabae..3c3b484b72 100644 --- a/generics-sop-lens.hs +++ b/generics-sop-lens.hs @@ -64,13 +64,13 @@ genericClassyLenses p = case gdatatypeInfo p of , " " ++ dn' ++ " :: Lens' a " ++ dn , "" ]] ++ - (hcollapse $ hcmap (Proxy :: Proxy Typeable) deriveCls fis) ++ + hcollapse (hcmap (Proxy :: Proxy Typeable) deriveCls fis) ++ [[ "" , "instance Has" ++ dn ++ " " ++ dn ++ " where" , " " ++ dn' ++ " = id" , " {-# INLINE " ++ dn' ++ " #-}" ]] ++ - (hcollapse $ hcmap (Proxy :: Proxy Typeable) deriveInst fis) + hcollapse (hcmap (Proxy :: Proxy Typeable) deriveInst fis) where dn' = case dn of [] -> [] -- GitLab