1# hlint configuration file
2# ==================================
3
4# The hlint tool is mainly automatic, but some hints/restrictions can be specified here.
5
6- package:
7    name: base
8    modules:
9    - import Prelude
10    - import Control.Arrow
11    - import Control.Exception
12    - import Control.Monad
13    - import Control.Monad.Trans.State
14    - import qualified Data.Foldable
15    - import Data.Foldable(asum, sequenceA_, traverse_, for_)
16    - import Data.Traversable(traverse, for)
17    - import Control.Applicative
18    - import Data.Bifunctor
19    - import Data.Function
20    - import Data.Int
21    - import Data.Char
22    - import Data.List as Data.List
23    - import Data.List as X
24    - import Data.Maybe
25    - import Data.Monoid
26    - import System.IO
27    - import Control.Concurrent.Chan
28    - import System.Mem.Weak
29    - import Control.Exception.Base
30    - import System.Exit
31    - import Data.Either
32    - import Numeric
33
34    - import IO as System.IO
35    - import List as Data.List
36    - import Maybe as Data.Maybe
37    - import Monad as Control.Monad
38    - import Char as Data.Char
39    - import Language.Haskell.TH as TH
40
41- package:
42    name: lens
43    modules:
44    - import Control.Lens
45    - import Control.Lens.Operators
46    - import Control.Monad.Reader
47
48- package:
49    name: attoparsec
50    modules:
51    - import Data.Attoparsec.Text
52    - import Data.Attoparsec.ByteString
53
54- package:
55    name: codeworld-api
56    modules:
57    - import CodeWorld
58
59- group:
60    name: default
61    enabled: true
62    imports:
63    - package base
64    rules:
65
66    # I/O
67
68    - warn: {lhs: putStrLn (show x), rhs: print x}
69    - warn: {lhs: putStr (x ++ "\n"), rhs: putStrLn x}
70    - warn: {lhs: putStr (x ++ y ++ "\n"), rhs: putStrLn (x ++ y)}
71    - warn: {lhs: mapM_ putChar, rhs: putStr}
72    - warn: {lhs: hGetChar stdin, rhs: getChar}
73    - warn: {lhs: hGetLine stdin, rhs: getLine}
74    - warn: {lhs: hGetContents stdin, rhs: getContents}
75    - warn: {lhs: hPutChar stdout, rhs: putChar}
76    - warn: {lhs: hPutStr stdout, rhs: putStr}
77    - warn: {lhs: hPutStrLn stdout, rhs: putStrLn}
78    - warn: {lhs: hPrint stdout, rhs: print}
79    - warn: {lhs: hWaitForInput a 0, rhs: hReady a}
80    - warn: {lhs: hPutStrLn a (show b), rhs: hPrint a b}
81    - warn: {lhs: hIsEOF stdin, rhs: isEOF}
82    - warn: {lhs: withFile f WriteMode (\h -> hPutStr h x), rhs: writeFile f x}
83    - warn: {lhs: withFile f WriteMode (\h -> hPutStrLn h x), rhs: writeFile f (x ++ "\n")}
84    - warn: {lhs: withFile f AppendMode (\h -> hPutStr h x), rhs: appendFile f x}
85    - warn: {lhs: withFile f AppendMode (\h -> hPutStrLn h x), rhs: appendFile f (x ++ "\n")}
86
87    # EXIT
88
89    - warn: {lhs: exitWith ExitSuccess, rhs: exitSuccess}
90
91    # ORD
92
93    - warn: {lhs: not (a == b), rhs: a /= b, note: incorrect if either value is NaN}
94    - warn: {lhs: not (a /= b), rhs: a == b, note: incorrect if either value is NaN}
95    - warn: {lhs: not (a >  b), rhs: a <= b, note: incorrect if either value is NaN}
96    - warn: {lhs: not (a >= b), rhs: a <  b, note: incorrect if either value is NaN}
97    - warn: {lhs: not (a <  b), rhs: a >= b, note: incorrect if either value is NaN}
98    - warn: {lhs: not (a <= b), rhs: a >  b, note: incorrect if either value is NaN}
99    - warn: {lhs: compare x y /= GT, rhs: x <= y}
100    - warn: {lhs: compare x y == LT, rhs: x < y}
101    - warn: {lhs: compare x y /= LT, rhs: x >= y}
102    - warn: {lhs: compare x y == GT, rhs: x > y}
103    - warn: {lhs: compare x y == EQ, rhs: x == y}
104    - warn: {lhs: compare x y /= EQ, rhs: x /= y}
105    - warn: {lhs: head (sort x), rhs: minimum x}
106    - warn: {lhs: last (sort x), rhs: maximum x}
107    - warn: {lhs: head (sortBy f x), rhs: minimumBy f x, side: isCompare f}
108    - warn: {lhs: last (sortBy f x), rhs: maximumBy f x, side: isCompare f}
109    - warn: {lhs: reverse (sortBy f x), rhs: sortBy (flip f) x, name: Avoid reverse, side: isCompare f, note: Stabilizes sort order}
110    - warn: {lhs: sortBy (flip (comparing f)), rhs: sortOn (Down . f)}
111    - warn: {lhs: sortBy (comparing f), rhs: sortOn f, side: notEq f fst && notEq f snd}
112    - warn: {lhs: reverse (sortOn f x), rhs: sortOn (Data.Ord.Down . f) x, name: Avoid reverse, note: Stabilizes sort order}
113    # This suggestion likely costs performance, see https://github.com/ndmitchell/hlint/issues/669#issuecomment-607154496
114    # - warn: {lhs: reverse (sort x), rhs: sortOn Data.Ord.Down x, name: Avoid reverse, note: Stabilizes sort order}
115    - hint: {lhs: flip (g `on` h), rhs: flip g `on` h, name: Move flip}
116    - hint: {lhs: (f `on` g) `on` h, rhs: f `on` (g . h), name: Fuse on/on}
117
118
119    # READ/SHOW
120
121    - warn: {lhs: showsPrec 0 x "", rhs: show x}
122    - warn: {lhs: readsPrec 0, rhs: reads}
123    - warn: {lhs: showsPrec 0, rhs: shows}
124    - hint: {lhs: showIntAtBase 16 intToDigit, rhs: showHex}
125    - hint: {lhs: showIntAtBase 8 intToDigit, rhs: showOct}
126
127    # LIST
128
129    - warn: {lhs: concat (map f x), rhs: concatMap f x}
130    - warn: {lhs: concat (fmap f x), rhs: concatMap f x}
131    - hint: {lhs: "concat [a, b]", rhs: a ++ b}
132    - hint: {lhs: map f (map g x), rhs: map (f . g) x, name: Use map once}
133    - hint: {lhs: concatMap f (map g x), rhs: concatMap (f . g) x, name: Fuse concatMap/map}
134    - hint: {lhs: x !! 0, rhs: head x}
135    - warn: {lhs: take n (repeat x), rhs: replicate n x}
136    - warn: {lhs: map f (replicate n x), rhs: replicate n (f x)}
137    - warn: {lhs: map f (repeat x), rhs: repeat (f x)}
138    - warn: {lhs: "cycle [x]", rhs: repeat x}
139    - warn: {lhs: head (reverse x), rhs: last x}
140    - warn: {lhs: head (drop n x), rhs: x !! n, side: isNat n}
141    - warn: {lhs: head (drop n x), rhs: x !! max 0 n, side: not (isNat n) && not (isNeg n)}
142    - warn: {lhs: reverse (init x), rhs: tail (reverse x)}
143    - warn: {lhs: reverse (tail (reverse x)), rhs: init x, note: IncreasesLaziness}
144    - warn: {lhs: reverse (reverse x), rhs: x, note: IncreasesLaziness, name: Avoid reverse}
145    - warn: {lhs: isPrefixOf (reverse x) (reverse y), rhs: isSuffixOf x y}
146    - warn: {lhs: "foldr (++) []", rhs: concat}
147    - warn: {lhs: foldr (++) "", rhs: concat}
148    - warn: {lhs: "foldr ((++) . f) []", rhs: concatMap f}
149    - warn: {lhs: foldr ((++) . f) "", rhs: concatMap f}
150    - warn: {lhs: "foldl (++) []", rhs: concat, note: IncreasesLaziness}
151    - warn: {lhs: foldl (++) "", rhs: concat, note: IncreasesLaziness}
152    - warn: {lhs: foldl f (head x) (tail x), rhs: foldl1 f x}
153    - warn: {lhs: foldr f (last x) (init x), rhs: foldr1 f x}
154    - warn: {lhs: "foldr (\\c a -> x : a) []", rhs: "map (\\c -> x)"}
155    - warn: {lhs: foldr (.) id l z, rhs: foldr ($) z l}
156    - warn: {lhs: span (not . p), rhs: break p}
157    - warn: {lhs: break (not . p), rhs: span p}
158    - warn: {lhs: "(takeWhile p x, dropWhile p x)", rhs: span p x, note: DecreasesLaziness}
159    - warn: {lhs: fst (span p x), rhs: takeWhile p x}
160    - warn: {lhs: snd (span p x), rhs: dropWhile p x}
161    - warn: {lhs: fst (break p x), rhs: takeWhile (not . p) x}
162    - warn: {lhs: snd (break p x), rhs: dropWhile (not . p) x}
163    - warn: {lhs: "(take n x, drop n x)", rhs: splitAt n x, note: DecreasesLaziness}
164    - warn: {lhs: fst (splitAt p x), rhs: take p x}
165    - warn: {lhs: snd (splitAt p x), rhs: drop p x}
166    - warn: {lhs: concatMap (++ "\n"), rhs: unlines}
167    - warn: {lhs: map id, rhs: id}
168    - warn: {lhs: concatMap id, rhs: concat}
169    - warn: {lhs: or (map p x), rhs: any p x}
170    - warn: {lhs: and (map p x), rhs: all p x}
171    - warn: {lhs: any f (map g x), rhs: any (f . g) x}
172    - warn: {lhs: all f (map g x), rhs: all (f . g) x}
173    - warn: {lhs: "zipWith (,)", rhs: zip}
174    - warn: {lhs: "zipWith3 (,,)", rhs: zip3}
175    - hint: {lhs: map fst &&& map snd, rhs: unzip}
176    - hint: {lhs: length x == 0, rhs: null x, note: IncreasesLaziness}
177    - hint: {lhs: 0 == length x, rhs: null x, note: IncreasesLaziness}
178    - hint: {lhs: length x < 1, rhs: null x, note: IncreasesLaziness}
179    - hint: {lhs: 1 > length x, rhs: null x, note: IncreasesLaziness}
180    - hint: {lhs: length x <= 0, rhs: null x, note: IncreasesLaziness}
181    - hint: {lhs: 0 >= length x, rhs: null x, note: IncreasesLaziness}
182    - hint: {lhs: "x == []", rhs: null x}
183    - hint: {lhs: "[] == x", rhs: null x}
184    - hint: {lhs: all (const False), rhs: "null"}
185    - hint: {lhs: any (const True) x, rhs: not (null x), name: Use null}
186    - hint: {lhs: length x /= 0, rhs: not (null x), note: IncreasesLaziness, name: Use null}
187    - hint: {lhs: 0 /= length x, rhs: not (null x), note: IncreasesLaziness, name: Use null}
188    - hint: {lhs: "\\x -> [x]", rhs: "(:[])", name: "Use :"}
189    - hint: {lhs: map f (zip x y), rhs: zipWith (curry f) x y, side: not (isApp f)}
190    - hint: {lhs: "map f (fromMaybe [] x)", rhs: "maybe [] (map f) x"}
191    - warn: {lhs: not (elem x y), rhs: notElem x y}
192    - hint: {lhs: foldr f z (map g x), rhs: foldr (f . g) z x, name: Fuse foldr/map}
193    - warn: {lhs: "x ++ concatMap (' ':) y", rhs: "unwords (x:y)"}
194    - warn: {lhs: intercalate " ", rhs: unwords}
195    - hint: {lhs: concat (intersperse x y), rhs: intercalate x y, side: notEq x " "}
196    - hint: {lhs: concat (intersperse " " x), rhs: unwords x}
197    - warn: {lhs: null (concat x), rhs: all null x}
198    - warn: {lhs: null (filter f x), rhs: not (any f x), name: Use any}
199    - warn: {lhs: "filter f x == []", rhs: not (any f x), name: Use any}
200    - warn: {lhs: "filter f x /= []", rhs: any f x}
201    - warn: {lhs: any id, rhs: or}
202    - warn: {lhs: all id, rhs: and}
203    - warn: {lhs: any (not . f) x, rhs: not (all f x), name: Hoist not}
204    - warn: {lhs: all (not . f) x, rhs: not (any f x), name: Hoist not}
205    - warn: {lhs: any ((==) a), rhs: elem a, note: ValidInstance Eq a}
206    - warn: {lhs: any (== a), rhs: elem a}
207    - warn: {lhs: any (a ==), rhs: elem a, note: ValidInstance Eq a}
208    - warn: {lhs: all ((/=) a), rhs: notElem a, note: ValidInstance Eq a}
209    - warn: {lhs: all (/= a), rhs: notElem a, note: ValidInstance Eq a}
210    - warn: {lhs: all (a /=), rhs: notElem a, note: ValidInstance Eq a}
211    - warn: {lhs: elem True, rhs: or}
212    - warn: {lhs: notElem False, rhs: and}
213    - warn: {lhs: True `elem` l, rhs: or l}
214    - warn: {lhs: False `notElem` l, rhs: and l}
215    - warn: {lhs: findIndex ((==) a), rhs: elemIndex a}
216    - warn: {lhs: findIndex (a ==), rhs: elemIndex a}
217    - warn: {lhs: findIndex (== a), rhs: elemIndex a}
218    - warn: {lhs: findIndices ((==) a), rhs: elemIndices a}
219    - warn: {lhs: findIndices (a ==), rhs: elemIndices a}
220    - warn: {lhs: findIndices (== a), rhs: elemIndices a}
221    - warn: {lhs: "lookup b (zip l [0..])", rhs: elemIndex b l}
222    - hint: {lhs: "elem x [y]", rhs: x == y, note: ValidInstance Eq a}
223    - hint: {lhs: "notElem x [y]", rhs: x /= y, note: ValidInstance Eq a}
224    - hint: {lhs: length x >= 0, rhs: "True", name: Length always non-negative}
225    - hint: {lhs: 0 <= length x, rhs: "True", name: Length always non-negative}
226    - hint: {lhs: length x > 0, rhs: not (null x), note: IncreasesLaziness, name: Use null}
227    - hint: {lhs: 0 < length x, rhs: not (null x), note: IncreasesLaziness, name: Use null}
228    - hint: {lhs: length x >= 1, rhs: not (null x), note: IncreasesLaziness, name: Use null}
229    - hint: {lhs: 1 <= length x, rhs: not (null x), note: IncreasesLaziness, name: Use null}
230    - warn: {lhs: take i x, rhs: "[]", side: isNegZero i, name: Take on a non-positive}
231    - warn: {lhs: drop i x, rhs: x, side: isNegZero i, name: Drop on a non-positive}
232    - warn: {lhs: last (scanl f z x), rhs: foldl f z x}
233    - warn: {lhs: head (scanr f z x), rhs: foldr f z x}
234    - warn: {lhs: iterate id, rhs: repeat}
235    - warn: {lhs: zipWith f (repeat x), rhs: map (f x)}
236    - warn: {lhs: zipWith f y (repeat z), rhs: map (`f` z) y}
237    - warn: {lhs: listToMaybe (filter p x), rhs: find p x}
238    - warn: {lhs: zip (take n x) (take n y), rhs: take n (zip x y)}
239    - warn: {lhs: zip (take n x) (take m y), rhs: take (min n m) (zip x y), side: notEq n m, note: [IncreasesLaziness, DecreasesLaziness], name: Redundant take}
240
241    # MONOIDS
242
243    - warn: {lhs: mempty <> x, rhs: x, name: "Monoid law, left identity"}
244    - warn: {lhs: mempty `mappend` x, rhs: x, name: "Monoid law, left identity"}
245    - warn: {lhs: x <> mempty, rhs: x, name: "Monoid law, right identity"}
246    - warn: {lhs: x `mappend` mempty, rhs: x, name: "Monoid law, right identity"}
247    - warn: {lhs: foldr (<>) mempty, rhs: Data.Foldable.fold}
248    - warn: {lhs: foldr mappend mempty, rhs: Data.Foldable.fold}
249    - warn: {lhs: mempty x, rhs: mempty, name: Evaluate}
250    - warn: {lhs: x `mempty` y, rhs: mempty, name: Evaluate, note: "Make sure you didn't mean to use mappend instead of mempty"}
251
252    # TRAVERSABLES
253
254    - warn: {lhs: traverse pure, rhs: pure, name: "Traversable law"}
255    - warn: {lhs: traverse (pure . f) x, rhs: pure (fmap f x), name: "Traversable law"}
256    - warn: {lhs: sequenceA (map f x), rhs: traverse f x}
257    - warn: {lhs: sequenceA (fmap f x), rhs: traverse f x}
258    - warn: {lhs: sequenceA_ (map f x), rhs: traverse_ f x}
259    - warn: {lhs: sequenceA_ (fmap f x), rhs: traverse_ f x}
260    - warn: {lhs: foldMap id, rhs: fold}
261    - warn: {lhs: fold (fmap f x), rhs: foldMap f x}
262    - warn: {lhs: fold (map f x), rhs: foldMap f x}
263    - warn: {lhs: foldMap f (fmap g x), rhs: foldMap (f . g) x, name: Fuse foldMap/fmap}
264    - warn: {lhs: foldMap f (map g x), rhs: foldMap (f . g) x, name: Fuse foldMap/map}
265
266    # BY
267
268    - warn: {lhs: deleteBy (==), rhs: delete}
269    - warn: {lhs: groupBy (==), rhs: group}
270    - warn: {lhs: insertBy compare, rhs: insert}
271    - warn: {lhs: intersectBy (==), rhs: intersect}
272    - warn: {lhs: maximumBy compare, rhs: maximum}
273    - warn: {lhs: minimumBy compare, rhs: minimum}
274    - warn: {lhs: nubBy (==), rhs: nub}
275    - warn: {lhs: sortBy compare, rhs: sort}
276    - warn: {lhs: unionBy (==), rhs: union}
277
278    # FOLDS
279
280    - warn: {lhs: foldr  (>>) (return ()), rhs: sequence_}
281    - warn: {lhs: foldr  (&&) True, rhs: and}
282    - warn: {lhs: foldl  (&&) True, rhs: and, note: IncreasesLaziness}
283    - warn: {lhs: foldr1 (&&) , rhs: and, note: "RemovesError on `[]`"}
284    - warn: {lhs: foldl1 (&&) , rhs: and, note: "RemovesError on `[]`"}
285    - warn: {lhs: foldr  (||) False, rhs: or}
286    - warn: {lhs: foldl  (||) False, rhs: or, note: IncreasesLaziness}
287    - warn: {lhs: foldr1 (||) , rhs: or, note: "RemovesError on `[]`"}
288    - warn: {lhs: foldl1 (||) , rhs: or, note: "RemovesError on `[]`"}
289    - warn: {lhs: foldl  (+) 0, rhs: sum}
290    - warn: {lhs: foldr  (+) 0, rhs: sum}
291    - warn: {lhs: foldl1 (+)  , rhs: sum, note: "RemovesError on `[]`"}
292    - warn: {lhs: foldr1 (+)  , rhs: sum, note: "RemovesError on `[]`"}
293    - warn: {lhs: foldl  (*) 1, rhs: product}
294    - warn: {lhs: foldr  (*) 1, rhs: product}
295    - warn: {lhs: foldl1 (*)  , rhs: product, note: "RemovesError on `[]`"}
296    - warn: {lhs: foldr1 (*)  , rhs: product, note: "RemovesError on `[]`"}
297    - warn: {lhs: foldl1 max  , rhs: maximum}
298    - warn: {lhs: foldr1 max  , rhs: maximum}
299    - warn: {lhs: foldl1 min  , rhs: minimum}
300    - warn: {lhs: foldr1 min  , rhs: minimum}
301    - warn: {lhs: foldr mplus mzero, rhs: msum}
302
303    # FUNCTION
304
305    - warn: {lhs: \x -> x, rhs: id}
306    - warn: {lhs: \x y -> x, rhs: const}
307    - warn: {lhs: curry fst, rhs: const}
308    - warn: {lhs: curry snd, rhs: \_ x -> x, note: "Alternatively, use const id"}
309    - warn: {lhs: flip const, rhs: \_ x -> x, note: "Alternatively, use const id"}
310    - warn: {lhs: "\\(x,y) -> y", rhs: snd}
311    - warn: {lhs: "\\(x,y) -> x", rhs: fst}
312    - hint: {lhs: "\\x y -> f (x,y)", rhs: curry f}
313    - hint: {lhs: "\\(x,y) -> f x y", rhs: uncurry f, note: IncreasesLaziness}
314    - warn: {lhs: f (fst p) (snd p), rhs: uncurry f p}
315    - warn: {lhs: "uncurry (\\x y -> z)", rhs: "\\(x,y) -> z"}
316    - warn: {lhs: "curry (\\(x,y) -> z)", rhs: "\\x y -> z"}
317    - warn: {lhs: uncurry (curry f), rhs: f}
318    - warn: {lhs: curry (uncurry f), rhs: f}
319    - warn: {lhs: "uncurry f (a, b)", rhs: f a b}
320    - warn: {lhs: ($) (f x), rhs: f x, name: Redundant $}
321    - warn: {lhs: (f $), rhs: f, name: Redundant $}
322    - warn: {lhs: (& f), rhs: f, name: Redundant &}
323    - hint: {lhs: \x -> y, rhs: const y, side: isAtom y && not (isWildcard y)}
324        # If any isWildcard recursively then x may be used but not mentioned explicitly
325    - warn: {lhs: flip f x y, rhs: f y x, side: isApp original && isAtom y}
326    - warn: {lhs: id x, rhs: x}
327    - warn: {lhs: id . x, rhs: x, name: Redundant id}
328    - warn: {lhs: x . id, rhs: x, name: Redundant id}
329    - warn: {lhs: "((,) x)", rhs: "(_noParen_ x,)", name: Use tuple-section, note: RequiresExtension TupleSections}
330    - warn: {lhs: "flip (,) x", rhs: "(,_noParen_ x)", name: Use tuple-section, note: RequiresExtension TupleSections}
331    - warn: {lhs: flip (flip f), rhs: f, note: DecreasesLaziness}
332    - warn: {lhs: flip f <*> g, rhs: f =<< g, name: Redundant flip}
333    - warn: {lhs: g <**> flip f, rhs: g >>= f, name: Redundant flip}
334    - warn: {lhs: flip f =<< g, rhs: f <*> g, name: Redundant flip}
335    - warn: {lhs: g >>= flip f, rhs: g Control.Applicative.<**> f, name: Redundant flip}
336
337    # CHAR
338
339    - warn: {lhs: a >= 'a' && a <= 'z', rhs: isAsciiLower a}
340    - warn: {lhs: a >= 'A' && a <= 'Z', rhs: isAsciiUpper a}
341    - warn: {lhs: a >= '0' && a <= '9', rhs: isDigit a}
342    - warn: {lhs: a >= '0' && a <= '7', rhs: isOctDigit a}
343    - warn: {lhs: isLower a || isUpper a, rhs: isAlpha a}
344    - warn: {lhs: isUpper a || isLower a, rhs: isAlpha a}
345
346    # BOOL
347
348    - warn: {lhs: x == True, rhs: x, name: Redundant ==}
349    - hint: {lhs: x == False, rhs: not x, name: Redundant ==}
350    - warn: {lhs: True == a, rhs: a, name: Redundant ==}
351    - hint: {lhs: False == a, rhs: not a, name: Redundant ==}
352    - warn: {lhs: a /= True, rhs: not a, name: Redundant /=}
353    - hint: {lhs: a /= False, rhs: a, name: Redundant /=}
354    - warn: {lhs: True /= a, rhs: not a, name: Redundant /=}
355    - hint: {lhs: False /= a, rhs: a, name: Redundant /=}
356    - warn: {lhs: if a then x else x, rhs: x, note: IncreasesLaziness, name: Redundant if}
357    - warn: {lhs: if a then True else False, rhs: a, name: Redundant if}
358    - warn: {lhs: if a then False else True, rhs: not a, name: Redundant if}
359    - warn: {lhs: if a then t else (if b then t else f), rhs: if a || b then t else f, name: Redundant if}
360    - warn: {lhs: if a then (if b then t else f) else f, rhs: if a && b then t else f, name: Redundant if}
361    - warn: {lhs: if x then True else y, rhs: x || y, side: notEq y False, name: Redundant if}
362    - warn: {lhs: if x then y else False, rhs: x && y, side: notEq y True, name: Redundant if}
363    - warn: {lhs: if | b -> t | otherwise -> f, rhs: if b then t else f, name: Redundant multi-way if}
364    - hint: {lhs: "case a of {True -> t; False -> f}", rhs: if a then t else f, name: Use if}
365    - hint: {lhs: "case a of {False -> f; True -> t}", rhs: if a then t else f, name: Use if}
366    - hint: {lhs: "case a of {True -> t; _ -> f}", rhs: if a then t else f, name: Use if}
367    - hint: {lhs: "case a of {False -> f; _ -> t}", rhs: if a then t else f, name: Use if}
368    - hint: {lhs: "if c then (True, x) else (False, x)", rhs: "(c, x)", note: IncreasesLaziness, name: Redundant if}
369    - hint: {lhs: "if c then (False, x) else (True, x)", rhs: "(not c, x)", note: IncreasesLaziness, name: Redundant if}
370    - hint: {lhs: "or [x, y]", rhs: x || y}
371    - hint: {lhs: "or [x, y, z]", rhs: x || y || z}
372    - hint: {lhs: "and [x, y]", rhs: x && y}
373    - hint: {lhs: "and [x, y, z]", rhs: x && y && z}
374    - warn: {lhs: if x then False else y, rhs: not x && y, side: notEq y True, name: Redundant if}
375    - warn: {lhs: if x then y else True, rhs: not x || y, side: notEq y False, name: Redundant if}
376    - warn: {lhs: not (not x), rhs: x, name: Redundant not}
377
378    # ARROW
379
380    - warn: {lhs: id *** g, rhs: second g}
381    - warn: {lhs: f *** id, rhs: first f}
382    - ignore: {lhs: zip (map f x) (map g x), rhs: map (f Control.Arrow.&&& g) x}
383    - ignore: {lhs: "\\x -> (f x, g x)", rhs: f Control.Arrow.&&& g}
384    - hint: {lhs: "(fst x, snd x)", rhs:  x, note: DecreasesLaziness, name: Redundant pair}
385
386    # BIFUNCTOR
387
388    - warn: {lhs: bimap id g, rhs: second g}
389    - warn: {lhs: bimap f id, rhs: first f}
390    - warn: {lhs: first id, rhs: id}
391    - warn: {lhs: second id, rhs: id}
392    - warn: {lhs: bimap id id, rhs: id}
393    - warn: {lhs: first f (second g x), rhs: bimap f g x}
394    - warn: {lhs: second g (first f x), rhs: bimap f g x}
395    - warn: {lhs: first f (first g x), rhs: first (f . g) x}
396    - warn: {lhs: second f (second g x), rhs: second (f . g) x}
397    - warn: {lhs: bimap f h (bimap g i x), rhs: bimap (f . g) (h . i) x}
398    - warn: {lhs: first f (bimap g h x), rhs: bimap (f . g) h x}
399    - warn: {lhs: second g (bimap f h x), rhs: bimap f (g . h) x}
400    - warn: {lhs: bimap f h (first g x), rhs: bimap (f . g) h x}
401    - warn: {lhs: bimap f g (second h x), rhs: bimap f (g . h) x}
402    - hint: {lhs: "\\(x,y) -> (f x, g y)", rhs: Data.Bifunctor.bimap f g, note: IncreasesLaziness}
403    - hint: {lhs: "\\(x,y) -> (f x,y)", rhs: Data.Bifunctor.first f, note: IncreasesLaziness}
404    - hint: {lhs: "\\(x,y) -> (x,f y)", rhs: Data.Bifunctor.second f, note: IncreasesLaziness}
405    - hint: {lhs: "(f (fst x), g (snd x))", rhs: Data.Bifunctor.bimap f g x}
406    - hint: {lhs: "(f (fst x), snd x)", rhs: Data.Bifunctor.first f x}
407    - hint: {lhs: "(fst x, g (snd x))", rhs: Data.Bifunctor.second g x}
408
409    # FUNCTOR
410
411    - warn: {lhs: fmap f (fmap g x), rhs: fmap (f . g) x, name: Functor law}
412    - warn: {lhs: f <$> g <$> x, rhs: f . g <$> x, name: Functor law}
413    - warn: {lhs: fmap id, rhs: id, name: Functor law}
414    - warn: {lhs: id <$> x, rhs: x, name: Functor law}
415    - hint: {lhs: fmap f $ x, rhs: f <$> x, side: isApp x || isAtom x}
416    - hint: {lhs: \x -> a <$> b x, rhs: fmap a . b}
417    - hint: {lhs: x *> pure y, rhs: x Data.Functor.$> y}
418    - hint: {lhs: x *> return y, rhs: x Data.Functor.$> y}
419    - hint: {lhs: pure x <* y, rhs: x Data.Functor.<$ y}
420    - hint: {lhs: return x <* y, rhs: x Data.Functor.<$ y}
421    - hint: {lhs: const x <$> y, rhs: x <$ y}
422    - hint: {lhs: pure x <$> y, rhs: x <$ y}
423    - hint: {lhs: return x <$> y, rhs: x <$ y}
424    - hint: {lhs: x <&> const y, rhs: x Data.Functor.$> y}
425    - hint: {lhs: x <&> pure y, rhs: x Data.Functor.$> y}
426    - hint: {lhs: x <&> return y, rhs: x Data.Functor.$> y}
427
428    # APPLICATIVE
429
430    - hint: {lhs: return x <*> y, rhs: x <$> y}
431    - hint: {lhs: pure x <*> y, rhs: x <$> y}
432    - warn: {lhs: x <* pure y, rhs: x}
433    - warn: {lhs: pure x *> y, rhs: "y"}
434
435    # MONAD
436
437    - warn: {lhs: return a >>= f, rhs: f a, name: "Monad law, left identity"}
438    - warn: {lhs: f =<< return a, rhs: f a, name: "Monad law, left identity"}
439    - warn: {lhs: m >>= return, rhs: m, name: "Monad law, right identity"}
440    - warn: {lhs: return =<< m, rhs: m, name: "Monad law, right identity"}
441    - warn: {lhs: liftM, rhs: fmap}
442    - warn: {lhs: liftA, rhs: fmap}
443    - hint: {lhs: m >>= return . f, rhs: m Data.Functor.<&> f}
444    - hint: {lhs: return . f =<< m, rhs: f <$> m}
445    - warn: {lhs: fmap f x >>= g, rhs: x >>= g . f}
446    - warn: {lhs: f <$> x >>= g, rhs: x >>= g . f}
447    - warn: {lhs: x Data.Functor.<&> f >>= g, rhs: x >>= g . f}
448    - warn: {lhs: g =<< fmap f x, rhs: g . f =<< x}
449    - warn: {lhs: g =<< f <$> x, rhs: g . f =<< x}
450    - warn: {lhs: g =<< (x Data.Functor.<&> f), rhs: g . f =<< x}
451    - warn: {lhs: if x then y else return (), rhs: Control.Monad.when x $ _noParen_ y, side: not (isAtom y)}
452    - warn: {lhs: if x then y else return (), rhs: Control.Monad.when x y, side: isAtom y}
453    - warn: {lhs: if x then return () else y, rhs: Control.Monad.unless x $ _noParen_ y, side: isAtom y}
454    - warn: {lhs: if x then return () else y, rhs: Control.Monad.unless x y, side: isAtom y}
455    - warn: {lhs: sequence (map f x), rhs: mapM f x}
456    - warn: {lhs: sequence_ (map f x), rhs: mapM_ f x}
457    - warn: {lhs: sequence (fmap f x), rhs: mapM f x}
458    - warn: {lhs: sequence_ (fmap f x), rhs: mapM_ f x}
459    - hint: {lhs: flip mapM, rhs: Control.Monad.forM}
460    - hint: {lhs: flip mapM_, rhs: Control.Monad.forM_}
461    - hint: {lhs: flip forM, rhs: mapM}
462    - hint: {lhs: flip forM_, rhs: mapM_}
463    - warn: {lhs: when (not x), rhs: unless x}
464    - warn: {lhs: unless (not x), rhs: when x}
465    - warn: {lhs: x >>= id, rhs: Control.Monad.join x}
466    - warn: {lhs: id =<< x, rhs: Control.Monad.join x}
467    - warn: {lhs: id =<< x, rhs: Control.Monad.join x}
468    - warn: {lhs: id =<< x, rhs: Control.Monad.join x}
469    - hint: {lhs: join (f <$> x), rhs: f =<< x}
470    - hint: {lhs: join (fmap f x), rhs: f =<< x}
471    - hint: {lhs: a >> return (), rhs: Control.Monad.void a, side: isAtom a || isApp a}
472    - warn: {lhs: fmap (const ()), rhs: Control.Monad.void}
473    - warn: {lhs: const () <$> x, rhs: Control.Monad.void x}
474    - warn: {lhs: () <$ x, rhs: Control.Monad.void x}
475    - warn: {lhs: flip (>=>), rhs: (<=<)}
476    - warn: {lhs: flip (<=<), rhs: (>=>)}
477    - warn: {lhs: flip (>>=), rhs: (=<<)}
478    - warn: {lhs: flip (=<<), rhs: (>>=)}
479    - hint: {lhs: \x -> f x >>= g, rhs: f Control.Monad.>=> g}
480    - hint: {lhs: \x -> f =<< g x, rhs: f Control.Monad.<=< g}
481    - hint: {lhs: (>>= f) . g, rhs: f Control.Monad.<=< g}
482    - hint: {lhs: (f =<<) . g, rhs: f Control.Monad.<=< g}
483    - warn: {lhs: a >> forever a, rhs: forever a}
484    - hint: {lhs: liftM2 id, rhs: ap}
485    - warn: {lhs: liftA2 f (return x), rhs: fmap (f x)}
486    - warn: {lhs: liftM2 f (pure x), rhs: fmap (f x)}
487    - warn: {lhs: liftM2 f (return x), rhs: fmap (f x)}
488    - warn: {lhs: fmap f (return x), rhs: return (f x)}
489    - warn: {lhs: f <$> return x, rhs: return (f x)}
490    - warn: {lhs: mapM (uncurry f) (zip l m), rhs: zipWithM f l m}
491    - warn: {lhs: mapM_ (void . f), rhs: mapM_ f}
492    - warn: {lhs: forM_ x (void . f), rhs: forM_ x f}
493    - warn: {lhs: a >>= \_ -> b, rhs: a >> b}
494    - warn: {lhs: m <* return x, rhs: m}
495    - warn: {lhs: return x *> m, rhs: m}
496    - warn: {lhs: pure x >> m, rhs: m}
497    - warn: {lhs: return x >> m, rhs: m}
498
499    # STATE MONAD
500
501    - warn: {lhs: fst (runState x y), rhs: evalState x y}
502    - warn: {lhs: snd (runState x y), rhs: execState x y}
503
504    # MONAD LIST
505
506    - warn: {lhs: fmap unzip (mapM f x), rhs: Control.Monad.mapAndUnzipM f x}
507    - warn: {lhs: sequence (zipWith f x y), rhs: Control.Monad.zipWithM f x y}
508    - warn: {lhs: sequence_ (zipWith f x y), rhs: Control.Monad.zipWithM_ f x y}
509    - warn: {lhs: sequence (replicate n x), rhs: Control.Monad.replicateM n x}
510    - warn: {lhs: sequence_ (replicate n x), rhs: Control.Monad.replicateM_ n x}
511    - warn: {lhs: sequenceA (zipWith f x y), rhs: Control.Monad.zipWithM f x y}
512    - warn: {lhs: sequenceA_ (zipWith f x y), rhs: Control.Monad.zipWithM_ f x y}
513    - warn: {lhs: sequenceA (replicate n x), rhs: Control.Monad.replicateM n x}
514    - warn: {lhs: sequenceA_ (replicate n x), rhs: Control.Monad.replicateM_ n x}
515    - warn: {lhs: mapM f (replicate n x), rhs: Control.Monad.replicateM n (f x)}
516    - warn: {lhs: mapM_ f (replicate n x), rhs: Control.Monad.replicateM_ n (f x)}
517    - warn: {lhs: mapM f (map g x), rhs: mapM (f . g) x, name: Fuse mapM/map}
518    - warn: {lhs: mapM_ f (map g x), rhs: mapM_ (f . g) x, name: Fuse mapM_/map}
519    - warn: {lhs: traverse f (map g x), rhs: traverse (f . g) x, name: Fuse traverse/map}
520    - warn: {lhs: traverse_ f (map g x), rhs: traverse_ (f . g) x, name: Fuse traverse_/map}
521    - warn: {lhs: mapM id, rhs: sequence}
522    - warn: {lhs: mapM_ id, rhs: sequence_}
523
524    # APPLICATIVE / TRAVERSABLE
525
526    - warn: {lhs: flip traverse, rhs: for}
527    - warn: {lhs: flip for, rhs: traverse}
528    - warn: {lhs: flip traverse_, rhs: for_}
529    - warn: {lhs: flip for_, rhs: traverse_}
530    - warn: {lhs: foldr (*>) (pure ()), rhs: sequenceA_}
531    - warn: {lhs: foldr (<|>) empty, rhs: asum}
532    - warn: {lhs: liftA2 (flip ($)), rhs: (<**>)}
533    - warn: {lhs: liftA2 f (pure x), rhs: fmap (f x)}
534    - warn: {lhs: fmap f (pure x), rhs: pure (f x)}
535    - warn: {lhs: f <$> pure x, rhs: pure (f x)}
536    - warn: {lhs: Just <$> a <|> pure Nothing, rhs: optional a}
537    - hint: {lhs: m >>= pure . f, rhs: m Data.Functor.<&> f}
538    - hint: {lhs: pure . f =<< m, rhs: f <$> m}
539    - warn: {lhs: empty <|> x, rhs: x, name: "Alternative law, left identity"}
540    - warn: {lhs: x <|> empty, rhs: x, name: "Alternative law, right identity"}
541    - warn: {lhs: traverse id, rhs: sequenceA}
542    - warn: {lhs: traverse_ id, rhs: sequenceA_}
543
544
545    # LIST COMP
546
547    - hint: {lhs: "if b then [x] else []", rhs: "[x | b]", name: Use list comprehension}
548    - hint: {lhs: "if b then [] else [x]", rhs: "[x | not b]", name: Use list comprehension}
549    - hint: {lhs: "[x | x <- y]", rhs: "y", side: isVar x, name: Redundant list comprehension}
550
551    # SEQ
552
553    - warn: {lhs: seq x x, rhs: x, name: Redundant seq}
554    - warn: {lhs: join seq, rhs: id, name: Redundant seq}
555    - warn: {lhs: id $! x, rhs: x, name: Redundant $!}
556    - warn: {lhs: seq x y, rhs: "y", side: isWHNF x, name: Redundant seq}
557    - warn: {lhs: f $! x, rhs: f x, side: isWHNF x, name: Redundant $!}
558    - warn: {lhs: evaluate x, rhs: return x, side: isWHNF x, name: Redundant evaluate}
559    - warn: {lhs: seq (rnf x) (), rhs: rnf x, name: Redundant seq}
560
561    # TUPLE
562
563    - warn: {lhs: fst (unzip x), rhs: map fst x}
564    - warn: {lhs: snd (unzip x), rhs: map snd x}
565    - hint: {lhs: "\\x y -> (x, y)", rhs: "(,)"}
566    - hint: {lhs: "\\x y z -> (x, y, z)", rhs: "(,,)"}
567
568    # MAYBE
569
570    - warn: {lhs: maybe x id, rhs: Data.Maybe.fromMaybe x}
571    - warn: {lhs: maybe Nothing Just, rhs: id, name: Redundant maybe}
572    - warn: {lhs: maybe False (const True), rhs: Data.Maybe.isJust}
573    - warn: {lhs: maybe True (const False), rhs: Data.Maybe.isNothing}
574    - warn: {lhs: maybe False (x ==), rhs: (Just x ==)}
575    - warn: {lhs: maybe True (x /=), rhs: (Just x /=)}
576    - warn: {lhs: maybe False (== x), rhs: (Just x ==), note: ValidInstance Eq x}
577    - warn: {lhs: maybe True (/= x), rhs: (Just x /=), note: ValidInstance Eq x}
578    # The following two hints seem to be somewhat unwelcome, e.g.
579    # https://github.com/ndmitchell/hlint/issues/1177
580    - ignore: {lhs: fromMaybe False x, rhs: Just True == x} # Eta expanded, see https://github.com/ndmitchell/hlint/issues/970#issuecomment-643645053
581    - ignore: {lhs: fromMaybe True x, rhs: Just False /= x}
582    - warn: {lhs: not (isNothing x), rhs: isJust x}
583    - warn: {lhs: not (isJust x), rhs: isNothing x}
584    - warn: {lhs: "maybe [] (:[])", rhs: maybeToList}
585    - warn: {lhs: catMaybes (map f x), rhs: mapMaybe f x}
586    - warn: {lhs: catMaybes (fmap f x), rhs: mapMaybe f x}
587    - hint: {lhs: case x of Nothing -> y; Just a -> a , rhs: Data.Maybe.fromMaybe y x, side: isAtom y, name: Replace case with fromMaybe}
588    - hint: {lhs: case x of Just a -> a; Nothing -> y, rhs: Data.Maybe.fromMaybe y x, side: isAtom y, name: Replace case with fromMaybe}
589    - hint: {lhs: case x of Nothing -> y; Just a -> f a , rhs: maybe y f x, side: isAtom y && isAtom f, name: Replace case with maybe}
590    - hint: {lhs: case x of Just a -> f a; Nothing -> y, rhs: maybe y f x, side: isAtom y && isAtom f, name: Replace case with maybe}
591    - warn: {lhs: if isNothing x then y else f (fromJust x), rhs: maybe y f x}
592    - warn: {lhs: if isJust x then f (fromJust x) else y, rhs: maybe y f x}
593    - warn: {lhs: maybe Nothing (Just . f), rhs: fmap f}
594    - hint: {lhs: map fromJust (filter isJust x), rhs:  Data.Maybe.catMaybes x}
595    - warn: {lhs: x == Nothing , rhs:  isNothing x}
596    - warn: {lhs: Nothing == x , rhs:  isNothing x}
597    - warn: {lhs: x /= Nothing , rhs:  Data.Maybe.isJust x}
598    - warn: {lhs: Nothing /= x , rhs:  Data.Maybe.isJust x}
599    - warn: {lhs: concatMap (maybeToList . f), rhs: Data.Maybe.mapMaybe f}
600    - warn: {lhs: concatMap maybeToList, rhs: catMaybes}
601    - warn: {lhs: maybe n Just x, rhs: x Control.Applicative.<|> n}
602    - warn: {lhs: if isNothing x then y else fromJust x, rhs: fromMaybe y x}
603    - warn: {lhs: if isJust x then fromJust x else y, rhs: fromMaybe y x}
604    - warn: {lhs: isJust x && (fromJust x == y), rhs: x == Just y}
605    - warn: {lhs: mapMaybe f (map g x), rhs: mapMaybe (f . g) x, name: Fuse mapMaybe/map}
606    - warn: {lhs: fromMaybe a (fmap f x), rhs: maybe a f x}
607    - warn: {lhs: fromMaybe a (f <$> x), rhs: maybe a f x}
608    - warn: {lhs: mapMaybe id, rhs: catMaybes}
609    - hint: {lhs: "[x | Just x <- a]", rhs: Data.Maybe.catMaybes a}
610    - hint: {lhs: case m of Nothing -> Nothing; Just x -> x, rhs: Control.Monad.join m}
611    - hint: {lhs: maybe Nothing id, rhs: join}
612    - hint: {lhs: maybe Nothing f x, rhs: f =<< x}
613    - warn: {lhs: maybe x f (fmap g y), rhs: maybe x (f . g) y, name: Redundant fmap}
614    - warn: {lhs: isJust (fmap f x), rhs: isJust x}
615    - warn: {lhs: isNothing (fmap f x), rhs: isNothing x}
616    - warn: {lhs: fromJust (fmap f x), rhs: f (fromJust x), note: IncreasesLaziness}
617    - warn: {lhs: mapMaybe f (fmap g x), rhs: mapMaybe (f . g) x, name: Redundant fmap}
618    - warn: {lhs: catMaybes (nub x), rhs: nub (catMaybes x), name: Move nub out}
619    - warn: {lhs: lefts (nub x), rhs: nub (lefts x), name: Move nub out}
620    - warn: {lhs: rights (nub x), rhs: nub (rights x), name: Move nub out}
621    - warn: {lhs: catMaybes (reverse x), rhs: reverse (catMaybes x), name: Move reverse out}
622    - warn: {lhs: lefts (reverse x), rhs: reverse (lefts x), name: Move reverse out}
623    - warn: {lhs: rights (reverse x), rhs: reverse (rights x), name: Move reverse out}
624    - warn: {lhs: catMaybes (sort x), rhs: sort (catMaybes x), name: Move sort out}
625    - warn: {lhs: lefts (sort x), rhs: sort (lefts x), name: Move sort out}
626    - warn: {lhs: rights (sort x), rhs: sort (rights x), name: Move sort out}
627    - warn: {lhs: catMaybes (nubOrd x), rhs: nubOrd (catMaybes x), name: Move nubOrd out}
628    - warn: {lhs: lefts (nubOrd x), rhs: nubOrd (lefts x), name: Move nubOrd out}
629    - warn: {lhs: rights (nubOrd x), rhs: nubOrd (rights x), name: Move nubOrd out}
630
631    # EITHER
632
633    - warn: {lhs: "[a | Left a <- a]", rhs: lefts a}
634    - warn: {lhs: "[a | Right a <- a]", rhs: rights a}
635    - warn: {lhs: either Left (Right . f), rhs: fmap f}
636    - warn: {lhs: either f g (fmap h x), rhs: either f (g . h) x, name: Redundant fmap}
637    - warn: {lhs: isLeft (fmap f x), rhs: isLeft x}
638    - warn: {lhs: isRight (fmap f x), rhs: isRight x}
639    - warn: {lhs: fromLeft x (fmap f y), rhs: fromLeft x y}
640    - warn: {lhs: fromRight x (fmap f y), rhs: either (const x) f y}
641    - warn: {lhs: either (const x) id, rhs: fromRight x}
642    - warn: {lhs: either id (const x), rhs: fromLeft x}
643
644    # INFIX
645
646    - hint: {lhs: elem x y, rhs: x `elem` y, side: not (isInfixApp original) && not (isParen result), name: Use infix}
647    - hint: {lhs: notElem x y, rhs: x `notElem` y, side: not (isInfixApp original) && not (isParen result), name: Use infix}
648    - hint: {lhs: isInfixOf x y, rhs: x `isInfixOf` y, side: not (isInfixApp original) && not (isParen result), name: Use infix}
649    - hint: {lhs: isSuffixOf x y, rhs: x `isSuffixOf` y, side: not (isInfixApp original) && not (isParen result), name: Use infix}
650    - hint: {lhs: isPrefixOf x y, rhs: x `isPrefixOf` y, side: not (isInfixApp original) && not (isParen result), name: Use infix}
651    - hint: {lhs: union x y, rhs: x `union` y, side: not (isInfixApp original) && not (isParen result), name: Use infix}
652    - hint: {lhs: intersect x y, rhs: x `intersect` y, side: not (isInfixApp original) && not (isParen result), name: Use infix}
653
654    # MATHS
655
656    - warn: {lhs: fromIntegral x, rhs: x, side: isLitInt x, name: Redundant fromIntegral}
657    - warn: {lhs: fromInteger x, rhs: x, side: isLitInt x, name: Redundant fromInteger}
658    - hint: {lhs: x + negate y, rhs: x - y}
659    - hint: {lhs: 0 - x, rhs: negate x}
660    - warn: {lhs: negate (negate x), rhs: x, name: Redundant negate}
661    - hint: {lhs: log y / log x, rhs: logBase x y}
662    - hint: {lhs: sin x / cos x, rhs: tan x}
663    - hint: {lhs: rem n 2 == 0, rhs: even n}
664    - hint: {lhs: 0 == rem n 2, rhs: even n}
665    - hint: {lhs: rem n 2 /= 0, rhs: odd n}
666    - hint: {lhs: 0 /= rem n 2, rhs: odd n}
667    - hint: {lhs: mod n 2 == 0, rhs: even n}
668    - hint: {lhs: 0 == mod n 2, rhs: even n}
669    - hint: {lhs: mod n 2 /= 0, rhs: odd n}
670    - hint: {lhs: 0 /= mod n 2, rhs: odd n}
671    - hint: {lhs: not (even x), rhs: odd x}
672    - hint: {lhs: not (odd x), rhs: even x}
673    - hint: {lhs: x ** 0.5, rhs: sqrt x}
674    - hint: {lhs: x ^ 0, rhs: "1", name: Use 1}
675    - hint: {lhs: round (x - 0.5), rhs: floor x}
676
677    # CONCURRENT
678
679    - hint: {lhs: mapM_ (writeChan a), rhs: writeList2Chan a}
680    - error: {lhs: atomically (readTVar x), rhs: readTVarIO x}
681    - error: {lhs: atomically (newTVar x), rhs: newTVarIO x}
682    - error: {lhs: atomically (newTMVar x), rhs: newTMVarIO x}
683    - error: {lhs: atomically newEmptyTMVar, rhs: newEmptyTMVarIO}
684
685    # TYPEABLE
686
687    - hint: {lhs: "typeOf (a :: b)", rhs: "typeRep (Proxy :: Proxy b)"}
688
689    # EXCEPTION
690
691    - hint: {lhs: flip Control.Exception.catch, rhs: handle}
692    - hint: {lhs: flip handle, rhs: Control.Exception.catch}
693    - hint: {lhs: flip (catchJust p), rhs: handleJust p}
694    - hint: {lhs: flip (handleJust p), rhs: catchJust p}
695    - hint: {lhs: Control.Exception.bracket b (const a) (const t), rhs: Control.Exception.bracket_ b a t}
696    - hint: {lhs: Control.Exception.bracket (openFile x y) hClose, rhs: withFile x y}
697    - hint: {lhs: Control.Exception.bracket (openBinaryFile x y) hClose, rhs: withBinaryFile x y}
698    - hint: {lhs: throw (ErrorCall a), rhs: error a}
699    - warn: {lhs: toException NonTermination, rhs: nonTermination}
700    - warn: {lhs: toException NestedAtomically, rhs: nestedAtomically}
701
702    # IOREF
703
704    - hint: {lhs: modifyIORef r (const x), rhs: writeIORef r x}
705    - hint: {lhs: modifyIORef r (\v -> x), rhs: writeIORef r x}
706
707    # STOREABLE/PTR
708
709    - hint: {lhs: castPtr nullPtr, rhs: nullPtr}
710    - hint: {lhs: castPtr (castPtr x), rhs: castPtr x}
711    - hint: {lhs: plusPtr (castPtr x), rhs: plusPtr x}
712    - hint: {lhs: minusPtr (castPtr x), rhs: minusPtr x}
713    - hint: {lhs: minusPtr x (castPtr y), rhs: minusPtr x y}
714    - hint: {lhs: peekByteOff (castPtr x), rhs: peekByteOff x}
715    - hint: {lhs: pokeByteOff (castPtr x), rhs: pokeByteOff x}
716
717    # WEAK POINTERS
718
719    - warn: {lhs: mkWeak a a b, rhs: mkWeakPtr a b}
720    - warn: {lhs: "mkWeak a (a, b) c", rhs: mkWeakPair a b c}
721
722    # FOLDABLE
723
724    - warn: {lhs: case m of Nothing -> return (); Just x -> f x, rhs: Data.Foldable.forM_ m f}
725    - warn: {lhs: case m of Just x -> f x; Nothing -> return (), rhs: Data.Foldable.forM_ m f}
726    - warn: {lhs: case m of Just x -> f x; _ -> return (), rhs: Data.Foldable.forM_ m f}
727    - warn: {lhs: when (isJust m) (f (fromJust m)), rhs: Data.Foldable.forM_ m f}
728
729    # STATE MONAD
730
731    - warn: {lhs: f <$> Control.Monad.State.get, rhs: gets f}
732    - warn: {lhs: fmap f  Control.Monad.State.get, rhs: gets f}
733    - warn: {lhs: f <$> Control.Monad.State.gets g, rhs: gets (f . g)}
734    - warn: {lhs: fmap f (Control.Monad.State.gets g), rhs: gets (f . g)}
735    - warn: {lhs: f <$> Control.Monad.Reader.ask, rhs: asks f}
736    - warn: {lhs: fmap f Control.Monad.Reader.ask, rhs: asks f}
737    - warn: {lhs: f <$> Control.Monad.Reader.asks g, rhs: asks (f . g)}
738    - warn: {lhs: fmap f (Control.Monad.Reader.asks g), rhs: asks (f . g)}
739    - warn: {lhs: fst (runState m s), rhs: evalState m s}
740    - warn: {lhs: snd (runState m s), rhs: execState m s}
741
742    # EVALUATE
743
744    - warn: {lhs: True && x, rhs: x, name: Evaluate}
745    - warn: {lhs: False && x, rhs: "False", name: Evaluate}
746    - warn: {lhs: True || x, rhs: "True", name: Evaluate}
747    - warn: {lhs: False || x, rhs: x, name: Evaluate}
748    - warn: {lhs: not True, rhs: "False", name: Evaluate}
749    - warn: {lhs: not False, rhs: "True", name: Evaluate}
750    - warn: {lhs: Nothing >>= k, rhs: Nothing, name: Evaluate}
751    - warn: {lhs: k =<< Nothing, rhs: Nothing, name: Evaluate}
752    - warn: {lhs: either f g (Left x), rhs: f x, name: Evaluate}
753    - warn: {lhs: either f g (Right y), rhs: g y, name: Evaluate}
754    - warn: {lhs: "fst (x,y)", rhs: x, name: Evaluate}
755    - warn: {lhs: "snd (x,y)", rhs: "y", name: Evaluate}
756    - warn: {lhs: "init [x]", rhs: "[]", name: Evaluate}
757    - warn: {lhs: "null [x]", rhs: "False", name: Evaluate}
758    - warn: {lhs: "null []", rhs: "True", name: Evaluate}
759    - warn: {lhs: "length []", rhs: "0", name: Evaluate}
760    - warn: {lhs: "foldl f z []", rhs: z, name: Evaluate}
761    - warn: {lhs: "foldr f z []", rhs: z, name: Evaluate}
762    - warn: {lhs: "foldr1 f [x]", rhs: x, name: Evaluate}
763    - warn: {lhs: "scanr f z []", rhs: "[z]", name: Evaluate}
764    - warn: {lhs: "scanr1 f []", rhs: "[]", name: Evaluate}
765    - warn: {lhs: "scanr1 f [x]", rhs: "[x]", name: Evaluate}
766    - warn: {lhs: "take n []", rhs: "[]", note: IncreasesLaziness, name: Evaluate}
767    - warn: {lhs: "drop n []", rhs: "[]", note: IncreasesLaziness, name: Evaluate}
768    - warn: {lhs: "takeWhile p []", rhs: "[]", name: Evaluate}
769    - warn: {lhs: "dropWhile p []", rhs: "[]", name: Evaluate}
770    - warn: {lhs: "span p []", rhs: "([],[])", name: Evaluate}
771    - warn: {lhs: lines "", rhs: "[]", name: Evaluate}
772    - warn: {lhs: "unwords []", rhs: "\"\"", name: Evaluate}
773    - warn: {lhs: x - 0, rhs: x, name: Evaluate}
774    - warn: {lhs: x * 1, rhs: x, name: Evaluate}
775    - warn: {lhs: x / 1, rhs: x, name: Evaluate}
776    - warn: {lhs: "concat [a]", rhs: a, name: Evaluate}
777    - warn: {lhs: "concat []", rhs: "[]", name: Evaluate}
778    - warn: {lhs: "zip [] []", rhs: "[]", name: Evaluate}
779    - warn: {lhs: const x y, rhs: x, name: Evaluate}
780    - warn: {lhs: any (const False), rhs: const False, note: IncreasesLaziness, name: Evaluate}
781    - warn: {lhs: all (const True), rhs: const True, note: IncreasesLaziness, name: Evaluate}
782    - warn: {lhs: "[] ++ x", rhs: x, name: Evaluate}
783    - warn: {lhs: "x ++ []", rhs: x, name: Evaluate}
784
785    # FOLDABLE + TUPLES
786
787    - warn: {lhs: "foldr   f z (x,b)", rhs: f b z, name: Using foldr on tuple}
788    - warn: {lhs: "foldr'  f z (x,b)", rhs: f b z, name: Using foldr' on tuple}
789    - warn: {lhs: "foldl   f z (x,b)", rhs: f z b, name: Using foldl on tuple}
790    - warn: {lhs: "foldl'  f z (x,b)", rhs: f z b, name: Using foldl' on tuple}
791    - warn: {lhs: "foldMap f   (x,b)", rhs: f b, name: Using foldMap on tuple}
792    - warn: {lhs: "foldr1  f   (x,b)", rhs: b, name: Using foldr1 on tuple}
793    - warn: {lhs: "foldl1  f   (x,b)", rhs: b, name: Using foldl1 on tuple}
794    - warn: {lhs: "elem    e   (x,b)", rhs: e == b, name: Using elem on tuple}
795    - warn: {lhs: "fold        (x,b)", rhs: b, name: Using fold on tuple}
796    - warn: {lhs: "toList      (x,b)", rhs: b, name: Using toList on tuple}
797    - warn: {lhs: "maximum     (x,b)", rhs: b, name: Using maximum on tuple}
798    - warn: {lhs: "minimum     (x,b)", rhs: b, name: Using minimum on tuple}
799    - warn: {lhs: "sum         (x,b)", rhs: b, name: Using sum on tuple}
800    - warn: {lhs: "product     (x,b)", rhs: b, name: Using product on tuple}
801    - warn: {lhs: "concat      (x,b)", rhs: b, name: Using concat on tuple}
802    - warn: {lhs: "and         (x,b)", rhs: b, name: Using and on tuple}
803    - warn: {lhs: "or          (x,b)", rhs: b, name: Using or on tuple}
804    - warn: {lhs: "any     f   (x,b)", rhs: f b, name: Using any on tuple}
805    - warn: {lhs: "all     f   (x,b)", rhs: f b, name: Using all on tuple}
806
807    - warn: {lhs: "foldr   f z (x,y,b)", rhs: f b z, name: Using foldr on tuple}
808    - warn: {lhs: "foldr'  f z (x,y,b)", rhs: f b z, name: Using foldr' on tuple}
809    - warn: {lhs: "foldl   f z (x,y,b)", rhs: f z b, name: Using foldl on tuple}
810    - warn: {lhs: "foldl'  f z (x,y,b)", rhs: f z b, name: Using foldl' on tuple}
811    - warn: {lhs: "foldMap f   (x,y,b)", rhs: f b, name: Using foldMap on tuple}
812    - warn: {lhs: "foldr1  f   (x,y,b)", rhs: b, name: Using foldr1 on tuple}
813    - warn: {lhs: "foldl1  f   (x,y,b)", rhs: b, name: Using foldl1 on tuple}
814    - warn: {lhs: "elem    e   (x,y,b)", rhs: e == b, name: Using elem on tuple}
815    - warn: {lhs: "fold        (x,y,b)", rhs: b, name: Using fold on tuple}
816    - warn: {lhs: "toList      (x,y,b)", rhs: b, name: Using toList on tuple}
817    - warn: {lhs: "maximum     (x,y,b)", rhs: b, name: Using maximum on tuple}
818    - warn: {lhs: "minimum     (x,y,b)", rhs: b, name: Using minimum on tuple}
819    - warn: {lhs: "sum         (x,y,b)", rhs: b, name: Using sum on tuple}
820    - warn: {lhs: "product     (x,y,b)", rhs: b, name: Using product on tuple}
821    - warn: {lhs: "concat      (x,y,b)", rhs: b, name: Using concat on tuple}
822    - warn: {lhs: "and         (x,y,b)", rhs: b, name: Using and on tuple}
823    - warn: {lhs: "or          (x,y,b)", rhs: b, name: Using or on tuple}
824    - warn: {lhs: "any     f   (x,y,b)", rhs: f b, name: Using any on tuple}
825    - warn: {lhs: "all     f   (x,y,b)", rhs: f b, name: Using all on tuple}
826
827    - warn: {lhs: null x  , rhs: "False", side: isTuple x, name: Using null on tuple}
828    - warn: {lhs: length x, rhs: "1"    , side: isTuple x, name: Using length on tuple}
829
830    # MAP
831
832    - warn: {lhs: "Data.Map.fromList []", rhs: Data.Map.empty}
833    - warn: {lhs: "Data.Map.Lazy.fromList []", rhs: Data.Map.Lazy.empty}
834    - warn: {lhs: "Data.Map.Strict.fromList []", rhs: Data.Map.Strict.empty}
835
836    # TEMPLATE HASKELL
837
838    - hint: {lhs: "TH.varE 'a", rhs: "[|a|]", name: Use TH quotation brackets}
839
840- group:
841    name: lens
842    enabled: true
843    imports:
844    - package base
845    - package lens
846    rules:
847    - warn: {lhs: "(a ^. b) ^. c", rhs: "a ^. (b . c)"}
848    - warn: {lhs: "fromJust (a ^? b)", rhs: "a ^?! b"}
849    - warn: {lhs: "a .~ Just b", rhs: "a ?~ b"}
850    - warn: {lhs: "(mapped %~ b) a", rhs: "a <&> b"}
851    - warn: {lhs: "((mapped . b) %~ c) a", rhs: "a <&> b %~ c"}
852    - warn: {lhs: "(mapped .~ b) a", rhs: "b <$ a"}
853    - warn: {lhs: "ask <&> (^. a)", rhs: "view a"}
854    - warn: {lhs: "view a <&> (^. b)", rhs: "view (a . b)"}
855
856    # `at` pitfalls:
857
858    - warn: {lhs: "Control.Lens.at a . Control.Lens._Just", rhs: "Control.Lens.ix a"}
859    - error: {lhs: "Control.Lens.has (Control.Lens.at a)", rhs: "True"}
860    - error: {lhs: "Control.Lens.has (a . Control.Lens.at b)", rhs: "Control.Lens.has a"}
861    - error: {lhs: "Control.Lens.nullOf (Control.Lens.at a)", rhs: "False"}
862    - error: {lhs: "Control.Lens.nullOf (a . Control.Lens.at b)", rhs: "Control.Lens.nullOf a"}
863
864- group:
865    name: use-lens
866    enabled: false
867    imports:
868    - package base
869    - package lens
870    rules:
871    - warn: {lhs: "either Just (const Nothing)", rhs: preview _Left}
872    - warn: {lhs: "either (const Nothing) Just", rhs: preview _Right}
873
874- group:
875    name: attoparsec
876    enabled: true
877    imports:
878    - package base
879    - package attoparsec
880    rules:
881    - warn: {lhs: Data.Attoparsec.Text.option Nothing (Just <$> p),       rhs: optional p}
882    - warn: {lhs: Data.Attoparsec.ByteString.option Nothing (Just <$> p), rhs: optional p}
883
884- group:
885    name: generalise
886    enabled: false
887    imports:
888    - package base
889    rules:
890    - warn: {lhs: map, rhs: fmap}
891    - warn: {lhs: a ++ b, rhs: a <> b}
892    - warn: {lhs: "sequence [a]", rhs: "pure <$> a"}
893    - warn: {lhs: "x /= []", rhs: not (null x), name: Use null}
894    - warn: {lhs: "[] /= x", rhs: not (null x), name: Use null}
895    - warn: {lhs: "maybe []", rhs: foldMap}
896
897- group:
898    name: generalise-for-conciseness
899    enabled: false
900    imports:
901    - package base
902    rules:
903    - warn: {lhs: maybe mempty, rhs: foldMap}
904    - warn: {lhs: maybe False, rhs: any}
905    - warn: {lhs: maybe True, rhs: all}
906    - warn: {lhs: either (const mempty), rhs: foldMap}
907    - warn: {lhs: either mempty, rhs: foldMap}
908    - warn: {lhs: either (const False), rhs: any}
909    - warn: {lhs: either (const True), rhs: all}
910    - warn: {lhs: Data.Maybe.fromMaybe mempty, rhs: Data.Foldable.fold}
911    - warn: {lhs: Data.Maybe.fromMaybe 0, rhs: sum}
912    - warn: {lhs: Data.Maybe.fromMaybe 1, rhs: product}
913    - warn: {lhs: Data.Maybe.fromMaybe empty, rhs: Data.Foldable.asum}
914    - warn: {lhs: Data.Maybe.fromMaybe mzero, rhs: Data.Foldable.msum}
915    - warn: {lhs: Data.Either.fromRight mempty, rhs: Data.Foldable.fold}
916    - warn: {lhs: Data.Either.fromRight False, rhs: or}
917    - warn: {lhs: Data.Either.fromRight True, rhs: and}
918    - warn: {lhs: Data.Either.fromRight 0, rhs: sum}
919    - warn: {lhs: Data.Either.fromRight 1, rhs: product}
920    - warn: {lhs: Data.Either.fromRight empty, rhs: Data.Foldable.asum}
921    - warn: {lhs: Data.Either.fromRight mzero, rhs: Data.Foldable.msum}
922    - warn: {lhs: if f x then Just x else Nothing, rhs: mfilter f (Just x)}
923    - hint: {lhs: maybe (pure ()), rhs: traverse_, note: IncreasesLaziness}
924    - hint: {lhs: fromMaybe (pure ()), rhs: sequenceA_, note: IncreasesLaziness}
925    - hint: {lhs: fromRight (pure ()), rhs: sequenceA_, note: IncreasesLaziness}
926    - hint: {lhs: "[fst x, snd x]", rhs: Data.Bifoldable.biList x}
927    - hint: {lhs: "\\(x, y) -> [x, y]", rhs: Data.Bifoldable.biList, note: IncreasesLaziness}
928    - hint: {lhs: const mempty, rhs: mempty}
929    - hint: {lhs: \x -> mempty, rhs: mempty, name: Redundant lambda}
930
931# hints that use the 'extra' library
932- group:
933    name: extra
934    enabled: false
935    rules:
936    - warn: {lhs: fmap concat (forM a b), rhs: concatForM a b}
937    - warn: {lhs: concat <$> forM a b, rhs: concatForM a b}
938    - warn: {lhs: fmap concat (forM_ a b), rhs: concatForM_ a b}
939    - warn: {lhs: concat <$> forM_ a b, rhs: concatForM_ a b}
940    - warn: {lhs: "maybe (pure ()) b a", rhs: "whenJust a b"}
941    - warn: {lhs: "maybe (return ()) b a", rhs: "whenJust a b"}
942    - warn: {lhs: "maybeM (pure ()) b a", rhs: "whenJustM a b"}
943    - warn: {lhs: "maybeM (return ()) b a", rhs: "whenJustM a b"}
944    - warn: {lhs: "if a then Just <$> b else pure Nothing", rhs: "whenMaybe a b"}
945    - warn: {lhs: "maybe a b =<< c", rhs: "maybeM a b c"}
946    - warn: {lhs: "maybeM a pure x", rhs: "fromMaybeM a b"}
947    - warn: {lhs: "maybeM a return x", rhs: "fromMaybeM a b"}
948    - warn: {lhs: "either a b =<< c", rhs: "eitherM a b c"}
949    - warn: {lhs: "fold1M a b >> return ()", rhs: "fold1M_ a b"}
950    - warn: {lhs: "fold1M a b >> pure ()", rhs: "fold1M_ a b"}
951    - warn: {lhs: "flip concatMapM", rhs: "concatForM"}
952    - warn: {lhs: "liftM mconcat (mapM a b)", rhs: "mconcatMapM a b"}
953    - warn: {lhs: "ifM a b (return ())", rhs: "whenM a b"}
954    - warn: {lhs: "ifM a (return ()) b", rhs: "unlessM a b"}
955    - warn: {lhs: "ifM a (return True) b", rhs: "(||^) a b"}
956    - warn: {lhs: "ifM a b (return False)", rhs: "(&&^) a b"}
957    - warn: {lhs: "anyM id", rhs: "orM"}
958    - warn: {lhs: "allM id", rhs: "andM"}
959    - warn: {lhs: "either id id", rhs: "fromEither"}
960    - warn: {lhs: "either (const Nothing) Just", rhs: "eitherToMaybe"}
961    - warn: {lhs: "either (Left . a) Right", rhs: "mapLeft a"}
962    - warn: {lhs: "atomicModifyIORef a (\\ v -> (b v, ()))", rhs: "atomicModifyIORef_ a b"}
963    - warn: {lhs: "atomicModifyIORef' a (\\ v -> (b v, ()))", rhs: "atomicModifyIORef'_ a b"}
964    - warn: {lhs: "null (intersect a b)", rhs: "disjoint a b"}
965    - warn: {lhs: "[minBound .. maxBound]", rhs: "enumerate"}
966    - warn: {lhs: "zipWithFrom (,)", rhs: "zipFrom"}
967    - warn: {lhs: "zip [i..]", rhs: "zipFrom i"}
968    - warn: {lhs: "zipWith f [i..]", rhs: "zipWithFrom f i"}
969    - warn: {lhs: "dropWhile isSpace", rhs: "trimStart"}
970    - warn: {lhs: "dropWhileEnd isSpace", rhs: "trimEnd"}
971    - warn: {lhs: "trimEnd (trimStart a)", rhs: "trim a"}
972    - warn: {lhs: "map toLower", rhs: "lower"}
973    - warn: {lhs: "map toUpper", rhs: "upper"}
974    - warn: {lhs: "mergeBy compare", rhs: "merge"}
975    - warn: {lhs: "breakEnd (not . a)", rhs: "spanEnd a"}
976    - warn: {lhs: "spanEnd (not . a)", rhs: "breakEnd a"}
977    - warn: {lhs: "mconcat (map a b)", rhs: "mconcatMap a b"}
978    - warn: {lhs: "fromMaybe b (stripPrefix a b)", rhs: "dropPrefix a b"}
979    - warn: {lhs: "fromMaybe b (stripSuffix a b)", rhs: "dropSuffix a b"}
980    - warn: {lhs: "nubSortBy compare", rhs: "nubSort"}
981    - warn: {lhs: "nubSortBy (compare `on` a)", rhs: "nubSortOn a"}
982    - warn: {lhs: "nubOrdBy compare", rhs: "nubOrd"}
983    - warn: {lhs: "\\a -> (a, a)", rhs: "dupe"}
984    - warn: {lhs: "showFFloat (Just a) b \"\"", rhs: "showDP a b"}
985    - warn: {lhs: "readFileEncoding utf8", rhs: "readFileUTF8"}
986    - warn: {lhs: "withFile a ReadMode hGetContents'", rhs: "readFile' a"}
987    - warn: {lhs: "readFileEncoding' utf8", rhs: "readFileUTF8'"}
988    - warn: {lhs: "withBinaryFile a ReadMode hGetContents'", rhs: "readFileBinary' a"}
989    - warn: {lhs: "writeFileEncoding utf8", rhs: "writeFileUTF8"}
990    - warn: {lhs: "head $ x ++ [y]", rhs: "headDef y x"}
991    - warn: {lhs: "last $ x : y", rhs: "lastDef x y"}
992    - warn: {lhs: "drop 1", rhs: "drop1"}
993    - warn: {lhs: "dropEnd 1", rhs: "dropEnd1"}
994
995# hints that will be enabled in future
996- group:
997    name: future
998    enabled: false
999    rules:
1000    - warn: {lhs: return, rhs: pure}
1001
1002- group:
1003    name: dollar
1004    enabled: false
1005    imports:
1006    - package base
1007    rules:
1008    - warn: {lhs: a $ b $ c, rhs: a . b $ c}
1009
1010- group:
1011    # These hints are same if all matched functions are monomorphic, or polymorphic, but don't have adhoc polymorphism
1012    name: monomorphic
1013    enabled: false
1014    imports:
1015    - package base
1016    rules:
1017    - warn: {lhs: if c then f x else f y, rhs: f (if c then x else y), note: IncreasesLaziness, name: Too strict if}
1018    - hint: {lhs: maybe (f x) (f . g), rhs: f . maybe x g, note: IncreasesLaziness, name: Too strict maybe}
1019    - hint: {lhs: maybe (f x) f y, rhs: f (Data.Maybe.fromMaybe x y), note: IncreasesLaziness, name: Too strict maybe}
1020
1021- group:
1022    name: codeworld
1023    enabled: false
1024    imports:
1025    - package base
1026    - package codeworld-api
1027    rules:
1028    - warn: {lhs: "pictures []", rhs: blank, name: Evaluate}
1029    - warn: {lhs: "pictures [ p ]", rhs: p, name: Evaluate}
1030    - warn: {lhs: "pictures [ p, q ]", rhs: p & q, name: Evaluate}
1031    - hint: {lhs: foldl1 (&), rhs: pictures}
1032    - hint: {lhs: foldl (&) blank, rhs: pictures}
1033    - hint: {lhs: foldl' (&) blank, rhs: pictures}
1034    - hint: {lhs: foldr' (&) blank, rhs: pictures}
1035    - hint: {lhs: foldr (&) blank, rhs: pictures}
1036    - hint: {lhs: foldr1 (&), rhs: pictures}
1037    - hint: {lhs: scaled x x, rhs: dilated x}
1038    - hint: {lhs: scaledPoint x x, rhs: dilatedPoint x}
1039    - warn: {lhs: "brighter (- a)", rhs: "duller a"}
1040    - warn: {lhs: "lighter (- a)", rhs: "darker a"}
1041    - warn: {lhs: "duller (- a)", rhs: "brighter a"}
1042    - warn: {lhs: "darker (- a)", rhs: "lighter a"}
1043    - warn: {lhs: translated x y (translated u v p), rhs: translated (x + u) (y + v) p, name: Use translated once}
1044
1045- group:
1046    name: teaching
1047    enabled: false
1048    imports:
1049    - package base
1050    rules:
1051    - hint: {lhs: "x /= []", rhs: not (null x), name: Use null}
1052    - hint: {lhs: "[] /= x", rhs: not (null x), name: Use null}
1053    - hint: {lhs: "not (x || y)", rhs: "not x && not y", name: Apply De Morgan law}
1054    - hint: {lhs: "not (x && y)", rhs: "not x || not y", name: Apply De Morgan law}
1055    - hint: {lhs: "[ f x | x <- l ]", rhs: map f l}
1056    - hint: {lhs: "[ x | x <- l, p x ]", rhs: filter p l}
1057    - warn: {lhs: foldr f c (reverse x), rhs: foldl (flip f) c x, name: Use left fold instead of right fold}
1058    - warn: {lhs: foldr1 f (reverse x), rhs: foldl1 (flip f) x, name: Use left fold instead of right fold}
1059    - warn: {lhs: foldl f c (reverse x), rhs: foldr (flip f) c x, note: IncreasesLaziness, name: Use right fold instead of left fold}
1060    - warn: {lhs: foldl1 f (reverse x), rhs: foldr1 (flip f) x, note: IncreasesLaziness, name: Use right fold instead of left fold}
1061    - warn: {lhs: foldr' f c (reverse x), rhs: foldl' (flip f) c x, name: Use left fold instead of right fold}
1062    - warn: {lhs: foldl' f c (reverse x), rhs: foldr (flip f) c x, note: IncreasesLaziness, name: Use right fold instead of left fold}
1063
1064- group:
1065    # used for tests, enabled when testing this file
1066    name: testing
1067    enabled: false
1068    rules:
1069    - warn: {lhs: "[issue766| |]", rhs: "mempty", name: "Use mempty"}
1070
1071# <TEST>
1072# yes = concat . map f -- concatMap f
1073# yes = foo . bar . concat . map f . baz . bar -- concatMap f . baz . bar
1074# yes = map f (map g x) -- map (f . g) x
1075# yes = concat.map (\x->if x==e then l' else [x]) -- concatMap (\x->if x==e then l' else [x])
1076# yes = f x where f x = concat . map head -- concatMap head
1077# yes = concat . map f . g -- concatMap f . g
1078# yes = concat $ map f x -- concatMap f x
1079# yes = map f x & concat -- concatMap f x
1080# yes = "test" ++ concatMap (' ':) ["of","this"] -- unwords ("test":["of","this"])
1081# yes = if f a then True else b -- f a || b
1082# yes = not (a == b) -- a /= b
1083# yes = not (a /= b) -- a == b
1084# yes = not . (a ==) -- (a /=)
1085# yes = not . (== a) -- (/= a)
1086# yes = not . (a /=) -- (a ==)
1087# yes = not . (/= a) -- (== a)
1088# yes = if a then 1 else if b then 1 else 2 -- if a || b then 1 else 2
1089# no  = if a then 1 else if b then 3 else 2
1090# yes = a >>= return . bob -- a Data.Functor.<&> bob
1091# yes = return . bob =<< a -- bob <$> a
1092# yes = m alice >>= pure . b -- m alice Data.Functor.<&> b
1093# yes = pure .b =<< m alice -- b <$> m alice
1094# yes = asciiCI "hi" *> pure Hi -- asciiCI "hi" Data.Functor.$> Hi
1095# yes = asciiCI "bye" *> return Bye -- asciiCI "bye" Data.Functor.$> Bye
1096# yes = pure x <* y -- x Data.Functor.<$ y
1097# yes = return x <* y -- x Data.Functor.<$ y
1098# yes = const x <$> y -- x <$ y
1099# yes = pure alice <$> [1, 2] -- alice <$ [1, 2]
1100# yes = return alice <$> "Bob" -- alice <$ "Bob"
1101# yes = Just a <&> const b -- Just a Data.Functor.$> b
1102# yes = [a,b] <&> pure c -- [a,b] Data.Functor.$> c
1103# yes = Hi <&> return bye -- Hi Data.Functor.$> bye
1104# yes = (x !! 0) + (x !! 2) -- head x
1105# yes = if b < 42 then [a] else [] -- [a | b < 42]
1106# no  = take n (foo xs) == "hello"
1107# yes = head (reverse xs) -- last xs
1108# yes = reverse xs `isPrefixOf` reverse ys -- isSuffixOf xs ys
1109# no = putStrLn $ show (length xs) ++ "Test"
1110# yes = ftable ++ map (\ (c, x) -> (toUpper c, urlEncode x)) ftable -- Data.Bifunctor.bimap toUpper urlEncode
1111# yes = map (\(a,b) -> a) xs -- fst
1112# yes = map (\(a,_) -> a) xs -- fst
1113# yes = readFile $ args !! 0 -- head args
1114# yes = if Debug `elem` opts then ["--debug"] else [] -- ["--debug" | Debug `elem` opts]
1115# yes = if nullPS s then return False else if headPS s /= '\n' then return False else alter_input tailPS >> return True \
1116#     -- if nullPS s || (headPS s /= '\n') then return False else alter_input tailPS >> return True
1117# yes = if foo then do stuff; moreStuff; lastOfTheStuff else return () \
1118#     -- Control.Monad.when foo $ do stuff ; moreStuff ; lastOfTheStuff
1119# yes = if foo then stuff else return () -- Control.Monad.when foo stuff
1120# yes = foo $ \(a, b) -> (a, y + b) -- Data.Bifunctor.second ((+) y)
1121# no  = foo $ \(a, b) -> (a, a + b)
1122# yes = map (uncurry (+)) $ zip [1 .. 5] [6 .. 10] -- zipWith (curry (uncurry (+))) [1 .. 5] [6 .. 10]
1123# yes = curry (uncurry (+)) -- (+)
1124# yes = fst foo .= snd foo -- uncurry (.=) foo
1125# yes = fst foo `_ba__'r''` snd foo -- uncurry _ba__'r'' foo
1126# no = do iter <- textBufferGetTextIter tb ; textBufferSelectRange tb iter iter
1127# no = flip f x $ \y -> y*y+y
1128# no = \x -> f x (g x)
1129# no = foo (\ v -> f v . g)
1130# yes = concat . intersperse " " -- unwords
1131# yes = Prelude.concat $ intersperse " " xs -- unwords xs
1132# yes = concat $ Data.List.intersperse " " xs -- unwords xs
1133# yes = if a then True else False -- a
1134# yes = if x then true else False -- x && true
1135# yes = elem x y -- x `elem` y
1136# yes = foo (elem x y) -- x `elem` y
1137# no  = x `elem` y
1138# no  = elem 1 [] : []
1139# yes = a & (mapped . b) %~ c -- a <&> b %~ c
1140# test a = foo (\x -> True) -- const True
1141# test a = foo (\_ -> True) -- const True
1142# test a = foo (\x -> x) -- id
1143# h a = flip f x (y z) -- f (y z) x
1144# h a = flip f x $ y z
1145# yes x = case x of {True -> a ; False -> b} -- if x then a else b
1146# yes x = case x of {False -> a ; _ -> b} -- if x then b else a
1147# no = const . ok . toResponse $ "saved"
1148# yes = case x z of Nothing -> y; Just pat -> pat -- Data.Maybe.fromMaybe y (x z)
1149# yes = if p then s else return () -- Control.Monad.when p s
1150# warn = a $$$$ b $$$$ c ==> a . b $$$$$ c
1151# yes = when (not . null $ asdf) -- unless (null asdf)
1152# yes = (foo . bar . when) (not . null $ asdf) -- (foo . bar) (unless (null asdf))
1153# yes = id 1 -- 1
1154# yes = case concat (map f x) of [] -> [] -- concatMap f x
1155# yes = [v | v <- xs] -- xs
1156# no  = [Left x | Left x <- xs]
1157# when p s = if p then s else return ()
1158# no = x ^^ 18.5
1159# instance Arrow (->) where first f = f *** id
1160# yes = fromInteger 12 -- 12
1161# import Prelude hiding (catch); no = catch
1162# import Control.Exception as E; no = E.catch
1163# main = do f; putStrLn $ show x -- print x
1164# main = map (writer,) $ map arcObj $ filter (rdfPredEq (Res dctreferences)) ts -- map ((writer,) . arcObj) (filter (rdfPredEq (Res dctreferences)) ts)
1165# h x y = return $! (x, y) -- return (x, y)
1166# h x y = return $! x
1167# getInt = do { x <- readIO "0"; return $! (x :: Int) }
1168# foo = evaluate [12] -- return [12]
1169# test = \ a -> f a >>= \ b -> return (a, b)
1170# fooer input = catMaybes . map Just $ input -- mapMaybe Just
1171# yes = mapMaybe id -- catMaybes
1172# foo = magic . isLeft $ fmap f x -- magic (isLeft x)
1173# foo = (bar . baz . magic . isRight) (fmap f x) -- (bar . baz . magic) (isRight x)
1174# main = print $ map (\_->5) [2,3,5] -- const 5
1175# main = head $ drop n x -- x !! max 0 n
1176# main = head $ drop (-3) x -- x
1177# main = head $ drop 2 x -- x !! 2
1178# main = foo . bar . baz . head $ drop 2 x -- (foo . bar . baz) (x !! 2)
1179# main = drop 0 x -- x
1180# main = take 0 x -- []
1181# main = take (-5) x -- []
1182# main = take (-y) x
1183# main = take 4 x
1184# main = let (first, rest) = (takeWhile p l, dropWhile p l) in rest -- span p l
1185# main = let (first, rest) = (take n l, drop n l) in rest -- splitAt n l
1186# main = fst (splitAt n l) -- take n l
1187# main = snd $ splitAt n l -- drop n l
1188# main = map $ \ d -> ([| $d |], [| $d |])
1189# pairs (x:xs) = map (x,) xs ++ pairs xs
1190# {-# ANN foo "HLint: ignore" #-};foo = map f (map g x) -- @Ignore ???
1191# {-# HLINT ignore foo #-};foo = map f (map g x) -- @Ignore ???
1192# yes = fmap lines $ abc 123 -- lines <$> abc 123
1193# no = fmap lines $ abc $ def 123
1194# test = foo . not . not -- id
1195# test = map (not . not) xs -- id
1196# used = not . not . any (`notElem` special) . fst . derives -- any (`notElem` special) . fst . derives
1197# test = foo . id . map -- map
1198# test = food id xs
1199# yes = baz baz >> return () -- Control.Monad.void (baz baz)
1200# no = foo >>= bar >>= something >>= elsee >> return ()
1201# no = f (#) x
1202# data Pair = P {a :: !Int}; foo = return $! P{a=undefined}
1203# data Pair = P {a :: !Int}; foo = return $! P undefined
1204# foo = return $! Just undefined -- return (Just undefined)
1205# foo = return $! (a,b) -- return (a,b)
1206# foo = return $! 1
1207# foo = return $! "test"
1208# bar = [x | (x,_) <- pts]
1209# return' x = x `seq` return x
1210# foo = last (sortBy (compare `on` fst) xs) -- maximumBy (compare `on` fst) xs
1211# g = \ f -> parseFile f >>= (\ cu -> return (f, cu))
1212# foo = bar $ \(x,y) -> x x y
1213# foo = (\x -> f x >>= g) -- f Control.Monad.>=> g
1214# foo = (\f -> h f >>= g) -- h Control.Monad.>=> g
1215# foo = (\f -> h f >>= f)
1216# foo = bar $ \x -> [x,y]
1217# foo = bar $ \x -> [z,y] -- const [z,y]
1218# f condition tChar tBool = if condition then _monoField tChar else _monoField tBool
1219# foo = maybe Bar{..} id -- Data.Maybe.fromMaybe Bar{..}
1220# foo = (\a -> Foo {..}) 1
1221# foo = zipWith SymInfo [0 ..] (repeat ty) -- map (`SymInfo` ty) [0 ..]
1222# foo = zipWith (SymInfo q) [0 ..] (repeat ty) -- map (( \ x_ -> SymInfo q x_ ty)) [0 .. ] @NoRefactor
1223# f rec = rec
1224# mean x = fst $ foldl (\(m, n) x' -> (m+(x'-m)/(n+1),n+1)) (0,0) x
1225# {-# LANGUAGE TypeApplications #-} \
1226# foo = id @Int
1227# {-# LANGUAGE TypeApplications #-} \
1228# foo = const @_ @SomeException
1229# foo = id 12 -- 12
1230# yes = foldr (\ curr acc -> (+ 1) curr : acc) [] -- map (\ curr -> (+ 1) curr)
1231# yes = foldr (\ curr acc -> curr + curr : acc) [] -- map (\ curr -> curr + curr)
1232# no = foo $ (,) x $ do {this is a test; and another test}
1233# no = sequence (return x)
1234# no = sequenceA (pure a)
1235# yes = zipWith func xs ys & sequenceA -- Control.Monad.zipWithM func xs ys
1236# {-# LANGUAGE QuasiQuotes #-}; no = f (\url -> [hamlet|foo @{url}|])
1237# yes = f ((,) x) -- (x,)
1238# yes = f ((,) (2 + 3)) -- (2 + 3,)
1239# instance Class X where method = map f (map g x) -- map (f . g) x
1240# instance Eq X where x == y = compare x y == EQ
1241# issue1055 = map f ((sort . map g) xs)
1242# issue1049 = True `elem` xs -- or xs
1243# issue1049 = elem True -- or
1244# issue1062 = bar (\(f, x) -> baz () () . f $ x) -- uncurry ((.) (baz () ()))
1245# issue1058 n = [] ++ issue1058 (n+1) -- issue1058 (n+1)
1246# issue1183 = (a >= 'a') && a <= 'z' -- isAsciiLower a
1247# issue1183 = (a >= 'a') && (a <= 'z') -- isAsciiLower a
1248# issue1218 = uncurry (zipWith g) $ (a, b) -- zipWith g a b
1249
1250# import Language.Haskell.TH\
1251# yes = varE 'foo -- [|foo|]
1252# import Prelude \
1253# yes = flip mapM -- Control.Monad.forM
1254# import Control.Monad \
1255# yes = flip mapM -- forM
1256# import Control.Monad(forM) \
1257# yes = flip mapM -- forM
1258# import Control.Monad(forM_) \
1259# yes = flip mapM -- Control.Monad.forM
1260# import qualified Control.Monad \
1261# yes = flip mapM -- Control.Monad.forM
1262# import qualified Control.Monad as CM \
1263# yes = flip mapM -- CM.forM
1264# import qualified Control.Monad as CM(forM,filterM) \
1265# yes = flip mapM -- CM.forM
1266# import Control.Monad as CM(forM,filterM) \
1267# yes = flip mapM -- forM
1268# import Control.Monad hiding (forM) \
1269# yes = flip mapM -- Control.Monad.forM
1270# import Control.Monad hiding (filterM) \
1271# yes = flip mapM -- forM
1272# import qualified Data.Text.Lazy as DTL \
1273# main = DTL.concat $ map (`DTL.snoc` '-') [DTL.pack "one", DTL.pack "two", DTL.pack "three"]
1274# import Text.Blaze.Html5.Attributes as A \
1275# main = A.id (stringValue id')
1276# import Prelude((==)) \
1277# import qualified Prelude as P \
1278# main = P.length xs == 0 -- P.null xs
1279# main = hello .~ Just 12 -- hello ?~ 12
1280# foo = liftIO $ window `on` deleteEvent $ do a; b
1281# no = sort <$> f input `shouldBe` sort <$> x
1282# sortBy (comparing length) -- sortOn length
1283# myJoin = on $ child ^. ChildParentId ==. parent ^. ParentId
1284# foo = typeOf (undefined :: Foo Int) -- typeRep (Proxy :: Proxy (Foo Int))
1285# foo = typeOf (undefined :: a) -- typeRep (Proxy :: Proxy a)
1286# {-# RULES "Id-fmap-id" forall (x :: Id a). fmap id x = x #-}
1287# import Data.Map (fromList) \
1288# fromList [] -- Data.Map.empty
1289# import Data.Map.Lazy (fromList) \
1290# fromList [] -- Data.Map.Lazy.empty
1291# import Data.Map.Strict (fromList) \
1292# fromList [] -- Data.Map.Strict.empty
1293# test953 = for [] $ \n -> bar n >>= \case {Just n  -> pure (); Nothing -> baz n}
1294# f = map (flip (,) "a") "123" -- (,"a")
1295# test1196 = map (flip (,) (+ 1)) "123" -- (,(+ 1))
1296# f = map ((,) "a") "123" -- ("a",)
1297# test1196 = map ((,) (+ 1)) "123" -- ((+ 1),)
1298# test979 = flip Map.traverseWithKey blocks \k v -> lots_of_code_goes_here
1299# infixl 4 <*! \
1300# test993 = f =<< g <$> x <*! y
1301# {-# LANGUAGE QuasiQuotes #-} \
1302# test = [issue766| |] -- mempty
1303# {-# LANGUAGE QuasiQuotes #-} \
1304# test = [issue766| x |]
1305# </TEST>
1306