Skip to content

Commit a5531c3

Browse files
authored
Merge pull request #11196 from cabalism/hlint/section
HLint: use section and use tuple section
2 parents 65599b7 + 55fa641 commit a5531c3

File tree

32 files changed

+68
-49
lines changed

32 files changed

+68
-49
lines changed

.hlint.yaml

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@
2828
- ignore: {name: "Use ++"} # 4 hints
2929
- ignore: {name: "Use :"} # 28 hints
3030
- ignore: {name: "Use <$"} # 2 hints
31-
- ignore: {name: "Use <$>"} # 89 hints
31+
- ignore: {name: "Use <$>"} # 87 hints
3232
- ignore: {name: "Use <&>"} # 16 hints
3333
- ignore: {name: "Use <=<"} # 4 hints
3434
- ignore: {name: "Use =<<"} # 7 hints
@@ -56,8 +56,6 @@
5656
- ignore: {name: "Use record patterns"} # 16 hints
5757
- ignore: {name: "Use replicateM_"} # 2 hints
5858
- ignore: {name: "Use rights"} # 2 hints
59-
- ignore: {name: "Use section"} # 18 hints
60-
- ignore: {name: "Use tuple-section"} # 28 hints
6159
- ignore: {name: "Use typeRep"} # 2 hints
6260
- ignore: {name: "Use unless"} # 23 hints
6361
- ignore: {name: "Use unwords"} # 8 hints

Cabal-syntax/src/Distribution/Compat/Lens.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE RankNTypes #-}
2+
{-# LANGUAGE TupleSections #-}
23

34
-- | This module provides very basic lens functionality, without extra dependencies.
45
--
@@ -154,7 +155,7 @@ lens sa sbt afb s = sbt s <$> afb (sa s)
154155
-------------------------------------------------------------------------------
155156

156157
_1 :: Lens (a, c) (b, c) a b
157-
_1 f (a, c) = flip (,) c <$> f a
158+
_1 f (a, c) = (,c) <$> f a
158159

159160
_2 :: Lens (c, a) (c, b) a b
160161
_2 f (c, a) = (,) c <$> f a

Cabal-syntax/src/Distribution/Types/Flag.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# LANGUAGE DeriveDataTypeable #-}
22
{-# LANGUAGE DeriveGeneric #-}
33
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4+
{-# LANGUAGE TupleSections #-}
45

56
module Distribution.Types.Flag
67
( -- * Package flag
@@ -170,7 +171,7 @@ mkFlagAssignment :: [(FlagName, Bool)] -> FlagAssignment
170171
mkFlagAssignment =
171172
FlagAssignment
172173
. Map.fromListWith (flip combineFlagValues)
173-
. fmap (fmap (\b -> (1, b)))
174+
. fmap (fmap (1,))
174175

175176
-- | Deconstruct a 'FlagAssignment' into a list of flag/value pairs.
176177
--

Cabal/src/Distribution/Backpack/ReadyComponent.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE PatternGuards #-}
2+
{-# LANGUAGE TupleSections #-}
23
{-# LANGUAGE TypeFamilies #-}
34

45
-- | See <https://github.com/ezyang/ghc-proposals/blob/backpack/proposals/0000-backpack.rst>
@@ -210,7 +211,7 @@ instance Functor InstM where
210211
in (f x, s')
211212

212213
instance Applicative InstM where
213-
pure a = InstM $ \s -> (a, s)
214+
pure a = InstM (a,)
214215
InstM f <*> InstM x = InstM $ \s ->
215216
let (f', s') = f s
216217
(x', s'') = x s'

Cabal/src/Distribution/PackageDescription/Check.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1060,7 +1060,7 @@ checkMissingDocs dgs esgs edgs efgs = do
10601060
-> [FilePath] -- Actuals.
10611061
-> [PackageCheck]
10621062
checkDoc b ds as =
1063-
let fds = map ("." </>) $ filter (flip notElem as) ds
1063+
let fds = map ("." </>) $ filter (`notElem` as) ds
10641064
in if null fds
10651065
then []
10661066
else
@@ -1075,7 +1075,7 @@ checkMissingDocs dgs esgs edgs efgs = do
10751075
-> [FilePath] -- Actuals.
10761076
-> [PackageCheck]
10771077
checkDocMove b field ds as =
1078-
let fds = filter (flip elem as) ds
1078+
let fds = filter (`elem` as) ds
10791079
in if null fds
10801080
then []
10811081
else

Cabal/src/Distribution/PackageDescription/Check/Conditional.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE ScopedTypeVariables #-}
2+
{-# LANGUAGE TupleSections #-}
23

34
-- |
45
-- Module : Distribution.PackageDescription.Check.Conditional
@@ -245,7 +246,7 @@ checkDuplicateModules pkg =
245246
libMap =
246247
foldCondTree
247248
Map.empty
248-
(\(_, v) -> Map.fromListWith sumPair . map (\x -> (x, (1, 1))) $ getModules v)
249+
(\(_, v) -> Map.fromListWith sumPair . map (,(1, 1)) $ getModules v)
249250
(Map.unionWith mergePair) -- if a module may occur in nonexclusive branches count it twice strictly and once loosely.
250251
(Map.unionWith maxPair) -- a module occurs the max of times it might appear in exclusive branches
251252
t

Cabal/src/Distribution/PackageDescription/Check/Target.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -79,7 +79,7 @@ checkLibrary
7979
checkP
8080
( not $
8181
all
82-
(flip elem (explicitLibModules lib))
82+
(`elem` explicitLibModules lib)
8383
(libModulesAutogen lib)
8484
)
8585
(PackageBuildImpossible AutogenNotExposed)
@@ -172,7 +172,7 @@ checkExecutable
172172
-- Alas exeModules ad exeModulesAutogen (exported from
173173
-- Distribution.Types.Executable) take `Executable` as a parameter.
174174
checkP
175-
(not $ all (flip elem (exeModules exe)) (exeModulesAutogen exe))
175+
(not $ all (`elem` exeModules exe) (exeModulesAutogen exe))
176176
(PackageBuildImpossible $ AutogenNoOther cet)
177177
checkP
178178
( not $
@@ -218,7 +218,7 @@ checkTestSuite
218218
checkP
219219
( not $
220220
all
221-
(flip elem (testModules ts))
221+
(`elem` testModules ts)
222222
(testModulesAutogen ts)
223223
)
224224
(PackageBuildImpossible $ AutogenNoOther cet)
@@ -280,7 +280,7 @@ checkBenchmark
280280
checkP
281281
( not $
282282
all
283-
(flip elem (benchmarkModules bm))
283+
(`elem` benchmarkModules bm)
284284
(benchmarkModulesAutogen bm)
285285
)
286286
(PackageBuildImpossible $ AutogenNoOther cet)

Cabal/src/Distribution/Simple/Build.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -240,7 +240,7 @@ build_setupHooks
240240
, SetupHooks.targetInfo = target
241241
}
242242
for_ mbPostBuild ($ postBuildInputs)
243-
return (maybe index (Index.insert `flip` index) mb_ipi)
243+
return (maybe index (`Index.insert` index) mb_ipi)
244244

245245
return ()
246246
where
@@ -616,7 +616,7 @@ generateCode
616616
-> IO (SymbolicPath Pkg (Dir Source), [ModuleName.ModuleName])
617617
generateCode codeGens nm pdesc bi lbi clbi verbosity = do
618618
when (not . null $ codeGens) $ createDirectoryIfMissingVerbose verbosity True $ i tgtDir
619-
(\x -> (tgtDir, x)) . concat <$> mapM go codeGens
619+
(tgtDir,) . concat <$> mapM go codeGens
620620
where
621621
allLibs = (maybe id (:) $ library pdesc) (subLibraries pdesc)
622622
dependencyLibs = filter (const True) allLibs -- intersect with componentPackageDeps of clbi

Cabal/src/Distribution/Simple/BuildPaths.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# LANGUAGE DataKinds #-}
22
{-# LANGUAGE FlexibleContexts #-}
33
{-# LANGUAGE RankNTypes #-}
4+
{-# LANGUAGE TupleSections #-}
45

56
-----------------------------------------------------------------------------
67

@@ -321,7 +322,7 @@ getSourceFiles
321322
-> [ModuleName.ModuleName]
322323
-> IO [(ModuleName.ModuleName, SymbolicPathX allowAbsolute Pkg File)]
323324
getSourceFiles verbosity mbWorkDir dirs modules = for modules $ \m ->
324-
fmap ((,) m) $
325+
fmap (m,) $
325326
findFileCwdWithExtension
326327
mbWorkDir
327328
builtinHaskellSuffixes

Cabal/src/Distribution/Simple/BuildTarget.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE DuplicateRecordFields #-}
44
{-# LANGUAGE FlexibleContexts #-}
55
{-# LANGUAGE RankNTypes #-}
6+
{-# LANGUAGE TupleSections #-}
67

78
-----------------------------------------------------------------------------
89

@@ -229,12 +230,12 @@ readUserBuildTarget targetstr =
229230

230231
tokens :: CabalParsing m => m (String, Maybe (String, Maybe String))
231232
tokens =
232-
(\s -> (s, Nothing)) <$> parsecHaskellString
233+
(,Nothing) <$> parsecHaskellString
233234
<|> (,) <$> token <*> P.optional (P.char ':' *> tokens2)
234235

235236
tokens2 :: CabalParsing m => m (String, Maybe String)
236237
tokens2 =
237-
(\s -> (s, Nothing)) <$> parsecHaskellString
238+
(,Nothing) <$> parsecHaskellString
238239
<|> (,) <$> token <*> P.optional (P.char ':' *> (parsecHaskellString <|> token))
239240

240241
token :: CabalParsing m => m String

0 commit comments

Comments
 (0)