Skip to content

Latest commit

 

History

History
15592 lines (15549 loc) · 137 KB

hints.md

File metadata and controls

15592 lines (15549 loc) · 137 KB

Summary of Hints

This page is auto-generated from hlint --generate-summary.

Builtin Bracket

Hint Name Hint Severity
Redundant section Example: issue970 = (f x +) (g x)
Found: (f x +) (g x)
Suggestion: f x + (g x)
Suggestion
Redundant bracket Example: main = 1; {-# ANN module (1 + (2)) #-}
Found: (2)
Suggestion: 2
Warning
Redundant bracket Example: yes = (foo . bar x) <$> baz q
Found: (foo . bar x) <$> baz q
Suggestion: foo . bar x <$> baz q
Suggestion
Redundant $ Example: no = f $ [1,2..5]
Found: f $ [1, 2 .. 5]
Suggestion: f [1, 2 .. 5]
Suggestion
Move brackets to avoid $ Example: yes = (a b $ c d) ++ e
Found: (a b $ c d) ++ e
Suggestion: a b (c d) ++ e
Suggestion

Builtin Comment

Hint Name Hint Severity
Use pragma syntax Example: {- NOINLINE Y -}
Found: {- NOINLINE Y -}
Suggestion: {-# NOINLINE Y #-}
Suggestion
Fix pragma markup Example: {- MISSING HASH #-}
Found: {- MISSING HASH #-}
Suggestion: {-# MISSING HASH #-}
Suggestion

Builtin Export

Hint Name Hint Severity
Use module export list Example: module Foo where foo = 1
Found: module Foo where
Suggestion:
module Foo (
        module Foo
    ) where
Does not support refactoring.
Ignore
Use explicit module export list Example: module Foo(module Foo, foo) where foo = 1
Found:
module Foo (
        module Foo, foo
    ) where
Suggestion:
module Foo (
         ... , foo
    ) where
Does not support refactoring.
Ignore

Builtin Extensions

Hint Name Hint Severity
Unused LANGUAGE pragma Example:
{-# LANGUAGE TypeData #-} 
data T = MkT
Found: {-# LANGUAGE TypeData #-}
Suggestion: Perhaps you should remove it.
Warning

Builtin Fixities

Hint Name Hint Severity
Redundant bracket due to operator fixities Example: yes = (a >>= f) >>= g
Found: (a >>= f) >>= g
Suggestion: a >>= f >>= g
Ignore

Builtin Import

Hint Name Hint Severity
Use fewer imports Example:
import A (foo) 
import A (bar) 
import A (baz)
Found:
import A ( foo )
import A ( bar )
import A ( baz )
Suggestion:
import A ( foo, bar, baz )
Warning
Redundant as Example: import qualified A as A
Found: import qualified A as A
Suggestion: import qualified A
Suggestion

Builtin Lambda

Hint Name Hint Severity
Use tuple-section Example: yes = blah (\ x -> (y, x, z+q))
Found: \ x -> (y, x, z + q)
Suggestion: (y,, z + q)
Does not support refactoring.
Suggestion
Use section Example: f = bar (flip Foo.bar x)
Found: (flip Foo.bar x)
Suggestion: (`Foo.bar` x)
Suggestion
Use lambda-case Example: foo = bar (\x -> case x of Y z | z > 0 -> z)
Found: \ x -> case x of Y z | z > 0 -> z
Suggestion: \case Y z | z > 0 -> z
Does not support refactoring.
Suggestion
Use lambda Example: foo = bar (\x -> case x of [y, z] -> z)
Found: \ x -> case x of [y, z] -> z
Suggestion: \ [y, z] -> z
Suggestion
Redundant lambda Example: f = \x -> x + x
Found: f = \ x -> x + x
Suggestion: f x = x + x
Warning
Eta reduce Example: foo a b c = bar (flux ++ quux) c where flux = a
Found: foo a b c = bar (flux ++ quux) c
Suggestion: foo a b = bar (flux ++ quux)
Warning
Collapse lambdas Example: f = foo (\x -> \y -> \z -> x x y y z z)
Found: \ x -> \ y -> \ z -> x x y y z z
Suggestion: \ x y z -> x x y y z z
Suggestion
Avoid lambda using `infix` Example: f = a b (\x -> c x d)
Found: (\ x -> c x d)
Suggestion: (`c` d)
Suggestion
Avoid lambda Example: baz = bar (\x -> (x +))
Found: \ x -> (x +)
Suggestion: (+)
Warning
Avoid lambda Example: yes = map (\f -> dataDir f) dataFiles
Found: (\ f -> dataDir f)
Suggestion: (dataDir )
Suggestion

Builtin List

Hint Name Hint Severity
Use list literal pattern Example: yes (1:2:[]) = 1
Found: (1 : 2 : [])
Suggestion: [1, 2]
Suggestion
Use list literal Example: yes = [1] : [2] : [3] : [4] : [5] : []
Found: [1] : [2] : [3] : [4] : [5] : []
Suggestion: [[1], [2], [3], [4], [5]]
Suggestion
Use String Example: yes = y :: [Char] -> a
Found: [Char] -> a
Suggestion: String -> a
Ignore
Use : Example: foo = [a b] ++ xs
Found: [a b] ++ xs
Suggestion: a b : xs
Suggestion
Short-circuited list comprehension Example:
{-# LANGUAGE MonadComprehensions #-}
foo = [x | False, x <- [1 .. 10]]
Found: [x | False, x <- [1 .. 10]]
Suggestion: []
Suggestion
Redundant True guards Example: foo = [myexpr | True, a]
Found: [myexpr | True, a]
Suggestion: [myexpr | a]
Suggestion
Move map inside list comprehension Example: issue1039 = foo (map f [1 | _ <- []])
Found: map f [1 | _ <- []]
Suggestion: [f 1 | _ <- []]
Suggestion
Move guards forward Example: foo = [x + 1 | x <- [1..10], let q = even 1, q]
Found: [x + 1 | x <- [1 .. 10], let q = even 1, q]
Suggestion: [x + 1 | let q = even 1, q, x <- [1 .. 10]]
Suggestion

Builtin ListRec

Hint Name Hint Severity
Use map Example: f a (x:xs) b = x + a + b : f a xs b ; f a [] b = []
Found:
f a (x : xs) b = x + a + b : f a xs b
f a [] b = []
Suggestion: f a xs b = map (\ x -> x + a + b) xs
Warning
Use foldr Example: foos [] x = x; foos (y:ys) x = foo y $ foos ys x
Found:
foos [] x = x
foos (y : ys) x = foo y $ foos ys x
Suggestion: foos ys x = foldr foo x ys
Suggestion
Use foldl Example: f [] y = y; f (x : xs) y = let z = g x y in f xs z
Found:
f [] y = y
f (x : xs) y = let z = g x y in f xs z
Suggestion: f xs y = foldl (flip g) y xs
Suggestion
Use foldM Example: f (x:xs) a = a + x >>= \fax -> f xs fax ; f [] a = pure a
Found:
f (x : xs) a = a + x >>= \ fax -> f xs fax
f [] a = pure a
Suggestion: f xs a = foldM (+) a xs
Suggestion

Builtin Monad

Hint Name Hint Severity
Use mapM_ Example: yes = mapM async ds >>= mapM wait >> return ()
Found: mapM async ds >>= mapM wait
Suggestion: mapM async ds >>= mapM_ wait
Warning
Use let Example: yes = do x <- return $ y + z; foo x
Found: x <- return $ y + z
Suggestion: let x = y + z
Suggestion
Use join Example: yes = do x <- bar; x
Found:
do x <- bar
   x
Suggestion: do join bar
Warning
Use forM_ Example: main = void (forM f xs)
Found: void (forM f xs)
Suggestion: forM_ f xs
Warning
Use foldM_ Example: folder f a xs = foldM f a xs >>= \_ -> return ()
Found: foldM f a xs
Suggestion: foldM_ f a xs
Warning
Use <$> Example: yes = do x <- bar; return (f $ g x)
Found:
do x <- bar
   return (f $ g x)
Suggestion: do f . g <$> bar
Warning
Redundant void Example: main = void (forM_ f xs)
Found: void (forM_ f xs)
Suggestion: forM_ f xs
Warning
Redundant variable capture Example: main = do _ <- forM_ f xs; bar
Found: _ <- forM_ f xs
Suggestion: forM_ f xs
Warning
Redundant return Example: main = do a; when b c; return ()
Found:
do a
   when b c
   return ()
Suggestion:
do a
   when b c
Warning
Redundant do Example: main = do f a $ sleep 10
Found: do
Suggestion: Perhaps you should remove it.
Ignore

Builtin Naming

Hint Name Hint Severity
Use camelCase Example: cast_foo = 1
Found: cast_foo = ...
Suggestion: castFoo = ...
Does not support refactoring.
Suggestion

Builtin Negation

Hint Name Hint Severity
Parenthesize unary negation Example: yes = -x `mod` y
Found: - x `mod` y
Suggestion: - (x `mod` y)
Suggestion

Builtin NewType

Hint Name Hint Severity
Use newtype instead of data Example: data instance Foo Int = Bar {field :: Bool}
Found: data instance Foo Int = Bar {field :: Bool}
Suggestion: newtype instance Foo Int = Bar {field :: Bool}
Does not support refactoring.
Suggestion
Use DerivingStrategies Example: newtype instance Foo Int = Bar {field :: Bool} deriving Show
Found:
newtype instance Foo Int
  = Bar {field :: Bool}
  deriving Show
Suggestion:
Does not support refactoring.
Ignore

Builtin NumLiteral

Hint Name Hint Severity
Use underscore Example:
{-# LANGUAGE NumericUnderscores #-} 
3.14159265359
Found: 3.14159265359
Suggestion: 3.141_592_653_59
Suggestion

Builtin Pattern

Hint Name Hint Severity
Used otherwise as a pattern Example: foo otherwise = 1
Found: otherwise
Suggestion: _
Does not support refactoring.
Warning
Use record patterns Example: foo (Bar _ _ _ _) = x
Found: Bar _ _ _ _
Suggestion: Bar {}
Suggestion
Use otherwise Example: foo x | a = b | True = d
Found:
foo x
  | a = b
  | True = d
Suggestion:
foo x
  | a = b
  | otherwise = d
Suggestion
Use guards Example: foo x = yes x x where yes x y = if a then b else if c then d else e
Found: yes x y = if a then b else if c then d else e
Suggestion:
yes x y
  | a = b
  | c = d
  | otherwise = e
Suggestion
Redundant where Example: foo x = x + x where
Found: where
Suggestion: Perhaps you should remove it.
Does not support refactoring.
Suggestion
Redundant irrefutable pattern Example: foo ~x = y
Found: ~x
Suggestion: x
Warning
Redundant guard Example: foo x | otherwise = y
Found: foo x | otherwise = y
Suggestion: foo x = y
Suggestion
Redundant case Example: foo = case v of v -> x
Found: case v of v -> x
Suggestion: x
Suggestion
Redundant bang pattern Example: {-# LANGUAGE BangPatterns #-}; l !(() :: ()) = x
Found: !(() :: ())
Suggestion: (() :: ())
Warning
Redundant as-pattern Example: foo x@_ = x
Found: x@_
Suggestion: x
Warning

Builtin Pragma

Hint Name Hint Severity
Use fewer LANGUAGE pragmas Example:
{-# LANGUAGE RebindableSyntax #-} 
{-# LANGUAGE EmptyCase, RebindableSyntax #-}
Found:
{-# LANGUAGE EmptyCase, RebindableSyntax #-}
{-# LANGUAGE RebindableSyntax #-}
Suggestion: {-# LANGUAGE EmptyCase, RebindableSyntax #-}
Warning
Use LANGUAGE pragmas Example: {-# OPTIONS_GHC -cpp -w #-}
Found:
{-# OPTIONS_GHC -cpp -w #-}
Suggestion:
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -w #-}
Warning

Builtin Unsafe

Hint Name Hint Severity
Missing NOINLINE pragma Example: entries = unsafePerformIO . baz $ x
Found: entries = unsafePerformIO . baz $ x
Suggestion:
{-# NOINLINE entries #-}
entries = unsafePerformIO . baz $ x
Warning

Configured hints

Hint Name Hint Severity
Use print LHS: putStrLn (show x)
RHS: print x
Warning
Use putStrLn LHS: putStr (x ++ "\n")
RHS: putStrLn x
Warning
Use putStrLn LHS: putStr (x ++ y ++ "\n")
RHS: putStrLn (x ++ y)
Warning
Use putStr LHS: mapM_ putChar
RHS: putStr
Warning
Use getChar LHS: hGetChar stdin
RHS: getChar
Warning
Use getLine LHS: hGetLine stdin
RHS: getLine
Warning
Use getContents LHS: hGetContents stdin
RHS: getContents
Warning
Use putChar LHS: hPutChar stdout
RHS: putChar
Warning
Use putStr LHS: hPutStr stdout
RHS: putStr
Warning
Use putStrLn LHS: hPutStrLn stdout
RHS: putStrLn
Warning
Use print LHS: hPrint stdout
RHS: print
Warning
Use hReady LHS: hWaitForInput a 0
RHS: hReady a
Warning
Use hPrint LHS: hPutStrLn a (show b)
RHS: hPrint a b
Warning
Use isEOF LHS: hIsEOF stdin
RHS: isEOF
Warning
Use writeFile LHS: withFile f WriteMode (\ h -> hPutStr h x)
RHS: writeFile f x
Warning
Use writeFile LHS: withFile f WriteMode (\ h -> hPutStrLn h x)
RHS: writeFile f (x ++ "\n")
Warning
Use appendFile LHS: withFile f AppendMode (\ h -> hPutStr h x)
RHS: appendFile f x
Warning
Use appendFile LHS: withFile f AppendMode (\ h -> hPutStrLn h x)
RHS: appendFile f (x ++ "\n")
Warning
Use exitSuccess LHS: exitWith ExitSuccess
RHS: exitSuccess
Warning
Use /= LHS: not (a == b)
RHS: a /= b
Warning
Use == LHS: not (a /= b)
RHS: a == b
Warning
Use <= LHS: not (a > b)
RHS: a <= b
Warning
Use < LHS: not (a >= b)
RHS: a < b
Warning
Use >= LHS: not (a < b)
RHS: a >= b
Warning
Use > LHS: not (a <= b)
RHS: a > b
Warning
Use <= LHS: compare x y /= GT
RHS: x <= y
Warning
Use < LHS: compare x y == LT
RHS: x < y
Warning
Use >= LHS: compare x y /= LT
RHS: x >= y
Warning
Use > LHS: compare x y == GT
RHS: x > y
Warning
Redundant compare LHS: compare x y == EQ
RHS: x == y
Warning
Redundant compare LHS: compare x y /= EQ
RHS: x /= y
Warning
Use minimum LHS: head (sort x)
RHS: minimum x
Warning
Use maximum LHS: last (sort x)
RHS: maximum x
Warning
Use minimumBy LHS: head (sortBy f x)
RHS: minimumBy f x
Warning
Use maximumBy LHS: last (sortBy f x)
RHS: maximumBy f x
Warning
Avoid reverse LHS: reverse (sortBy f x)
RHS: sortBy (flip f) x
Warning
Use Down LHS: sortBy (flip (comparing f))
RHS: sortBy (comparing (Data.Ord.Down . f))
Warning
Avoid reverse LHS: reverse (sortOn f x)
RHS: sortOn (Data.Ord.Down . f) x
Warning
Avoid reverse LHS: reverse (sort x)
RHS: sortBy (comparing Data.Ord.Down) x
Warning
Move flip LHS: flip (g `on` h)
RHS: flip g `on` h
Suggestion
Fuse on/on LHS: (f `on` g) `on` h
RHS: f `on` (g . h)
Suggestion
Use max LHS: if a >= b then a else b
RHS: max a b
Warning
Use min LHS: if a >= b then b else a
RHS: min a b
Warning
Use max LHS: if a > b then a else b
RHS: max a b
Warning
Use min LHS: if a > b then b else a
RHS: min a b
Warning
Use min LHS: if a <= b then a else b
RHS: min a b
Warning
Use max LHS: if a <= b then b else a
RHS: max a b
Warning
Use min LHS: if a < b then a else b
RHS: min a b
Warning
Use max LHS: if a < b then b else a
RHS: max a b
Warning
Use max LHS: maximum [a, b]
RHS: max a b
Warning
Use min LHS: minimum [a, b]
RHS: min a b
Warning
Use show LHS: showsPrec 0 x ""
RHS: show x
Warning
Use show LHS: showsPrec 0 x []
RHS: show x
Warning
Use reads LHS: readsPrec 0
RHS: reads
Warning
Use shows LHS: showsPrec 0
RHS: shows
Warning
Use showHex LHS: showIntAtBase 16 intToDigit
RHS: showHex
Suggestion
Use showOct LHS: showIntAtBase 8 intToDigit
RHS: showOct
Suggestion
Use concatMap LHS: concat (map f x)
RHS: concatMap f x
Warning
Use concatMap LHS: concat (f <$> x)
RHS: concatMap f x
Warning
Use concatMap LHS: concat (x <&> f)
RHS: concatMap f x
Warning
Use concatMap LHS: concat (fmap f x)
RHS: concatMap f x
Warning
Use ++ LHS: concat [a, b]
RHS: a ++ b
Suggestion
Use map once LHS: map f (map g x)
RHS: map (f . g) x
Suggestion
Fuse concatMap/map LHS: concatMap f (map g x)
RHS: concatMap (f . g) x
Suggestion
Use head LHS: x !! 0
RHS: head x
Suggestion
Use replicate LHS: take n (repeat x)
RHS: replicate n x
Warning
Redundant map LHS: map f (replicate n x)
RHS: replicate n (f x)
Warning
Redundant map LHS: map f (repeat x)
RHS: repeat (f x)
Warning
Use cycle LHS: concatMap f (repeat x)
RHS: cycle (f x)
Warning
Use cycle LHS: concat (repeat x)
RHS: cycle x
Warning
Use repeat LHS: cycle [x]
RHS: repeat x
Warning
Use last LHS: head (reverse x)
RHS: last x
Warning
Use head LHS: last (reverse x)
RHS: head x
Warning
Use !! LHS: head (drop n x)
RHS: x !! n
Warning
Use !! LHS: head (drop n x)
RHS: x !! max 0 n
Warning
Use tail LHS: reverse (init x)
RHS: tail (reverse x)
Warning
Use init LHS: reverse (tail (reverse x))
RHS: init x
Warning
Avoid reverse LHS: reverse (reverse x)
RHS: x
Warning
Use isSuffixOf LHS: isPrefixOf (reverse x) (reverse y)
RHS: isSuffixOf x y
Warning
Use concat LHS: foldr (++) []
RHS: concat
Warning
Use concat LHS: foldr (++) ""
RHS: concat
Warning
Use concatMap LHS: foldr ((++) . f) []
RHS: concatMap f
Warning
Use concatMap LHS: foldr ((++) . f) ""
RHS: concatMap f
Warning
Use concat LHS: foldl (++) []
RHS: concat
Warning
Use concat LHS: foldl (++) ""
RHS: concat
Warning
Use foldl1 LHS: foldl f (head x) (tail x)
RHS: foldl1 f x
Warning
Use foldr1 LHS: foldr f (last x) (init x)
RHS: foldr1 f x
Warning
Use map LHS: foldr (\ c a -> x : a) []
RHS: map (\ c -> x)
Warning
Use $ LHS: foldr (.) id l z
RHS: foldr ($) z l
Warning
Use break LHS: span (not . p)
RHS: break p
Warning
Use span LHS: break (not . p)
RHS: span p
Warning
Use break LHS: span (notElem x)
RHS: break (elem x)
Warning
Use span LHS: break (notElem x)
RHS: span (elem x)
Warning
Use span LHS: (takeWhile p x, dropWhile p x)
RHS: span p x
Warning
Use takeWhile LHS: fst (span p x)
RHS: takeWhile p x
Warning
Use dropWhile LHS: snd (span p x)
RHS: dropWhile p x
Warning
Use takeWhile LHS: fst (break p x)
RHS: takeWhile (not . p) x
Warning
Use dropWhile LHS: snd (break p x)
RHS: dropWhile (not . p) x
Warning
Use splitAt LHS: (take n x, drop n x)
RHS: splitAt n x
Warning
Use take LHS: fst (splitAt p x)
RHS: take p x
Warning
Use drop LHS: snd (splitAt p x)
RHS: drop p x
Warning
Use unlines LHS: concatMap (++ "\n")
RHS: unlines
Warning
Redundant map LHS: map id
RHS: id
Warning
Use concat LHS: concatMap id
RHS: concat
Warning
Use any LHS: or (map p x)
RHS: any p x
Warning
Use all LHS: and (map p x)
RHS: all p x
Warning
Redundant map LHS: any f (map g x)
RHS: any (f . g) x
Warning
Redundant map LHS: all f (map g x)
RHS: all (f . g) x
Warning
Use zip LHS: zipWith (,)
RHS: zip
Warning
Use zip3 LHS: zipWith3 (,,)
RHS: zip3
Warning
Use unzip LHS: map fst &&& map snd
RHS: unzip
Suggestion
Use null LHS: length x == 0
RHS: null x
Suggestion
Use null LHS: 0 == length x
RHS: null x
Suggestion
Use null LHS: length x < 1
RHS: null x
Suggestion
Use null LHS: 1 > length x
RHS: null x
Suggestion
Use null LHS: length x <= 0
RHS: null x
Suggestion
Use null LHS: 0 >= length x
RHS: null x
Suggestion
Use null LHS: x == []
RHS: null x
Suggestion
Use null LHS: [] == x
RHS: null x
Suggestion
Use null LHS: all (const False)
RHS: null
Suggestion
Use null LHS: any (const True) x
RHS: not (null x)
Suggestion
Use null LHS: length x /= 0
RHS: not (null x)
Suggestion
Use null LHS: 0 /= length x
RHS: not (null x)
Suggestion
Use : LHS: \ x -> [x]
RHS: (: [])
Suggestion
Use zipWith LHS: map f (zip x y)
RHS: zipWith (curry f) x y
Suggestion
Use maybe LHS: map f (fromMaybe [] x)
RHS: maybe [] (map f) x
Suggestion
Use maybe LHS: concatMap f (fromMaybe [] x)
RHS: maybe [] (concatMap f) x
Suggestion
Use maybe LHS: concat (fromMaybe [] x)
RHS: maybe [] concat x
Suggestion
Use notElem LHS: not (elem x y)
RHS: notElem x y
Warning
Use elem LHS: not (notElem x y)
RHS: elem x y
Warning
Fuse foldr/map LHS: foldr f z (map g x)
RHS: foldr (f . g) z x
Suggestion
Use unwords LHS: x ++ concatMap (' ' :) y
RHS: unwords (x : y)
Warning
Use unwords LHS: intercalate " "
RHS: unwords
Warning
Use intercalate LHS: concat (intersperse x y)
RHS: intercalate x y
Suggestion
Use unwords LHS: concat (intersperse " " x)
RHS: unwords x
Suggestion
Use all LHS: null (concat x)
RHS: all null x
Warning
Use any LHS: null (filter f x)
RHS: not (any f x)
Warning
Use any LHS: filter f x == []
RHS: not (any f x)
Warning
Use any LHS: filter f x /= []
RHS: any f x
Warning
Use or LHS: any id
RHS: or
Warning
Use and LHS: all id
RHS: and
Warning
Hoist not LHS: any (not . f) x
RHS: not (all f x)
Warning
Hoist not LHS: all (not . f) x
RHS: not (any f x)
Warning
Use elem LHS: any ((==) a)
RHS: elem a
Warning
Use elem LHS: any (== a)
RHS: elem a
Warning
Use elem LHS: any (a ==)
RHS: elem a
Warning
Use notElem LHS: all ((/=) a)
RHS: notElem a
Warning
Use notElem LHS: all (/= a)
RHS: notElem a
Warning
Use notElem LHS: all (a /=)
RHS: notElem a
Warning
Use or LHS: elem True
RHS: or
Warning
Use and LHS: notElem False
RHS: and
Warning
Use or LHS: True `elem` l
RHS: or l
Warning
Use and LHS: False `notElem` l
RHS: and l
Warning
Use any LHS: elem False
RHS: any not
Warning
Use all LHS: notElem True
RHS: all not
Warning
Use any LHS: False `elem` l
RHS: any not l
Warning
Use all LHS: True `notElem` l
RHS: all not l
Warning
Use elemIndex LHS: findIndex ((==) a)
RHS: elemIndex a
Warning
Use elemIndex LHS: findIndex (a ==)
RHS: elemIndex a
Warning
Use elemIndex LHS: findIndex (== a)
RHS: elemIndex a
Warning
Use elemIndices LHS: findIndices ((==) a)
RHS: elemIndices a
Warning
Use elemIndices LHS: findIndices (a ==)
RHS: elemIndices a
Warning
Use elemIndices LHS: findIndices (== a)
RHS: elemIndices a
Warning
Use elemIndex LHS: lookup b (zip l [0 .. ])
RHS: elemIndex b l
Warning
Use == LHS: elem x [y]
RHS: x == y
Suggestion
Use /= LHS: notElem x [y]
RHS: x /= y
Suggestion
Use max LHS: length [1 .. n]
RHS: max 0 n
Suggestion
Length always non-negative LHS: length x >= 0
RHS: True
Suggestion
Length always non-negative LHS: 0 <= length x
RHS: True
Suggestion
Use null LHS: length x > 0
RHS: not (null x)
Suggestion
Use null LHS: 0 < length x
RHS: not (null x)
Suggestion
Use null LHS: length x >= 1
RHS: not (null x)
Suggestion
Use null LHS: 1 <= length x
RHS: not (null x)
Suggestion
Take on a non-positive LHS: take i x
RHS: []
Warning
Drop on a non-positive LHS: drop i x
RHS: x
Warning
Use foldl LHS: last (scanl f z x)
RHS: foldl f z x
Warning
Use foldr LHS: head (scanr f z x)
RHS: foldr f z x
Warning
Use take LHS: scanl (\ x _ -> a) b (replicate c d)
RHS: take c (iterate (\ x -> a) b)
Warning
Use iterate LHS: foldl (\ x _ -> a) b [1 .. c]
RHS: iterate (\ x -> a) b !! c
Warning
Use repeat LHS: iterate id
RHS: repeat
Warning
Use map LHS: zipWith f (repeat x)
RHS: map (f x)
Warning
Use map with tuple-section LHS: zip (repeat x)
RHS: map (_noParen_ x,)
Warning
Use map LHS: zipWith f y (repeat z)
RHS: map (`f` z) y
Warning
Use map with tuple-section LHS: zip y (repeat z)
RHS: map (, _noParen_ z) y
Warning
Use find LHS: listToMaybe (filter p x)
RHS: find p x
Warning
Redundant take LHS: zip (take n x) (take n y)
RHS: take n (zip x y)
Warning
Redundant take LHS: zip (take n x) (take m y)
RHS: take (min n m) (zip x y)
Warning
Monoid law, left identity LHS: mempty <> x
RHS: x
Warning
Monoid law, left identity LHS: mempty `mappend` x
RHS: x
Warning
Monoid law, right identity LHS: x <> mempty
RHS: x
Warning
Monoid law, right identity LHS: x `mappend` mempty
RHS: x
Warning
Use fold LHS: foldr (<>) mempty
RHS: Data.Foldable.fold
Warning
Use fold LHS: foldr mappend mempty
RHS: Data.Foldable.fold
Warning
Evaluate LHS: mempty x
RHS: mempty
Warning
Evaluate LHS: x `mempty` y
RHS: mempty
Warning
Traversable law LHS: traverse pure
RHS: pure
Warning
Traversable law LHS: traverse (pure . f) x
RHS: pure (fmap f x)
Warning
Use traverse LHS: sequenceA (map f x)
RHS: traverse f x
Warning
Use traverse LHS: sequenceA (f <$> x)
RHS: traverse f x
Warning
Use traverse LHS: sequenceA (x <&> f)
RHS: traverse f x
Warning
Use traverse LHS: sequenceA (fmap f x)
RHS: traverse f x
Warning
Use traverse_ LHS: sequenceA_ (map f x)
RHS: traverse_ f x
Warning
Use traverse_ LHS: sequenceA_ (f <$> x)
RHS: traverse_ f x
Warning
Use traverse_ LHS: sequenceA_ (x <&> f)
RHS: traverse_ f x
Warning
Use traverse_ LHS: sequenceA_ (fmap f x)
RHS: traverse_ f x
Warning
Use fold LHS: foldMap id
RHS: fold
Warning
Use foldMap LHS: fold (f <$> x)
RHS: foldMap f x
Warning
Use foldMap LHS: fold (x <&> f)
RHS: foldMap f x
Warning
Use foldMap LHS: fold (fmap f x)
RHS: foldMap f x
Warning
Use foldMap LHS: fold (map f x)
RHS: foldMap f x
Warning
Fuse foldMap/<$> LHS: foldMap f (g <$> x)
RHS: foldMap (f . g) x
Warning
Fuse foldMap/<&> LHS: foldMap f (x <&> g)
RHS: foldMap (f . g) x
Warning
Fuse foldMap/fmap LHS: foldMap f (fmap g x)
RHS: foldMap (f . g) x
Warning
Fuse foldMap/map LHS: foldMap f (map g x)
RHS: foldMap (f . g) x
Warning
Fuse traverse/fmap LHS: traverse f (fmap g x)
RHS: traverse (f . g) x
Warning
Fuse traverse/<$> LHS: traverse f (g <$> x)
RHS: traverse (f . g) x
Warning
Fuse traverse/<&> LHS: traverse f (x <&> g)
RHS: traverse (f . g) x
Warning
Fuse traverse_/fmap LHS: traverse_ f (fmap g x)
RHS: traverse_ (f . g) x
Warning
Fuse traverse_/<$> LHS: traverse_ f (g <$> x)
RHS: traverse_ (f . g) x
Warning
Fuse traverse_/<&> LHS: traverse_ f (x <&> g)
RHS: traverse_ (f . g) x
Warning
Use delete LHS: deleteBy (==)
RHS: delete
Warning
Use group LHS: groupBy (==)
RHS: group
Warning
Use insert LHS: insertBy compare
RHS: insert
Warning
Use intersect LHS: intersectBy (==)
RHS: intersect
Warning
Use maximum LHS: maximumBy compare
RHS: maximum
Warning
Use minimum LHS: minimumBy compare
RHS: minimum
Warning
Use nub LHS: nubBy (==)
RHS: nub
Warning
Use sort LHS: sortBy compare
RHS: sort
Warning
Use union LHS: unionBy (==)
RHS: union
Warning
Use sequence_ LHS: foldr (>>) (pure ())
RHS: sequence_
Warning
Use sequence_ LHS: foldr (>>) (return ())
RHS: sequence_
Warning
Use and LHS: foldr (&&) True
RHS: and
Warning
Use and LHS: foldl (&&) True
RHS: and
Warning
Use and LHS: foldr1 (&&)
RHS: and
Warning
Use and LHS: foldl1 (&&)
RHS: and
Warning
Use or LHS: foldr (||) False
RHS: or
Warning
Use or LHS: foldl (||) False
RHS: or
Warning
Use or LHS: foldr1 (||)
RHS: or
Warning
Use or LHS: foldl1 (||)
RHS: or
Warning
Use sum LHS: foldl (+) 0
RHS: sum
Warning
Use sum LHS: foldr (+) 0
RHS: sum
Warning
Use sum LHS: foldl1 (+)
RHS: sum
Warning
Use sum LHS: foldr1 (+)
RHS: sum
Warning
Use product LHS: foldl (*) 1
RHS: product
Warning
Use product LHS: foldr (*) 1
RHS: product
Warning
Use product LHS: foldl1 (*)
RHS: product
Warning
Use product LHS: foldr1 (*)
RHS: product
Warning
Use maximum LHS: foldl1 max
RHS: maximum
Warning
Use maximum LHS: foldr1 max
RHS: maximum
Warning
Use minimum LHS: foldl1 min
RHS: minimum
Warning
Use minimum LHS: foldr1 min
RHS: minimum
Warning
Use msum LHS: foldr mplus mzero
RHS: msum
Warning
Use id LHS: \ x -> x
RHS: id
Warning
Use const LHS: \ x y -> x
RHS: const
Warning
Use const LHS: curry fst
RHS: const
Warning
Redundant curry LHS: curry snd
RHS: \ _ x -> x
Warning
Redundant flip LHS: flip const
RHS: \ _ x -> x
Warning
Use snd LHS: \ (x, y) -> y
RHS: snd
Warning
Use fst LHS: \ (x, y) -> x
RHS: fst
Warning
Use curry LHS: \ x y -> f (x, y)
RHS: curry f
Suggestion
Use uncurry LHS: \ (x, y) -> f x y
RHS: uncurry f
Suggestion
Use uncurry LHS: f (fst p) (snd p)
RHS: uncurry f p
Warning
Redundant uncurry LHS: uncurry (\ x y -> z)
RHS: \ (x, y) -> z
Warning
Redundant curry LHS: curry (\ (x, y) -> z)
RHS: \ x y -> z
Warning
Redundant uncurry LHS: uncurry (curry f)
RHS: f
Warning
Redundant curry LHS: curry (uncurry f)
RHS: f
Warning
Redundant uncurry LHS: uncurry f (a, b)
RHS: f a b
Warning
Redundant $ LHS: ($) (f x)
RHS: f x
Warning
Redundant $ LHS: (f $)
RHS: f
Warning
Redundant & LHS: (& f)
RHS: f
Warning
Use const LHS: \ x -> y
RHS: const y
Suggestion
Redundant flip LHS: flip f x y
RHS: f y x
Warning
Redundant id LHS: id x
RHS: x
Warning
Redundant id LHS: id . x
RHS: x
Warning
Redundant id LHS: x . id
RHS: x
Warning
Use tuple-section LHS: ((,) x)
RHS: (_noParen_ x,)
Warning
Use tuple-section LHS: flip (,) x
RHS: (, _noParen_ x)
Warning
Redundant flip LHS: flip (flip f)
RHS: f
Warning
Redundant flip LHS: flip f <*> g
RHS: f =<< g
Warning
Redundant flip LHS: g <**> flip f
RHS: g >>= f
Warning
Redundant flip LHS: flip f =<< g
RHS: f <*> g
Warning
Redundant flip LHS: g >>= flip f
RHS: g Control.Applicative.<**> f
Warning
Use isAsciiLower LHS: a >= 'a' && a <= 'z'
RHS: isAsciiLower a
Warning
Use isAsciiLower LHS: 'a' <= a && a <= 'z'
RHS: isAsciiLower a
Warning
Use isAsciiUpper LHS: a >= 'A' && a <= 'Z'
RHS: isAsciiUpper a
Warning
Use isAsciiUpper LHS: 'A' <= a && a <= 'Z'
RHS: isAsciiUpper a
Warning
Use isDigit LHS: a >= '0' && a <= '9'
RHS: isDigit a
Warning
Use isDigit LHS: '0' <= a && a <= '9'
RHS: isDigit a
Warning
Use isOctDigit LHS: a >= '0' && a <= '7'
RHS: isOctDigit a
Warning
Use isOctDigit LHS: '0' <= a && a <= '7'
RHS: isOctDigit a
Warning
Use isAlpha LHS: isLower a || isUpper a
RHS: isAlpha a
Warning
Use isAlpha LHS: isUpper a || isLower a
RHS: isAlpha a
Warning
Redundant == LHS: x == True
RHS: x
Warning
Redundant == LHS: x == False
RHS: not x
Suggestion
Redundant == LHS: True == a
RHS: a
Warning
Redundant == LHS: False == a
RHS: not a
Suggestion
Redundant == LHS: (== True)
RHS: id
Suggestion
Redundant == LHS: (== False)
RHS: not
Suggestion
Redundant == LHS: (True ==)
RHS: id
Suggestion
Redundant == LHS: (False ==)
RHS: not
Suggestion
Redundant /= LHS: a /= True
RHS: not a
Warning
Redundant /= LHS: a /= False
RHS: a
Suggestion
Redundant /= LHS: True /= a
RHS: not a
Warning
Redundant /= LHS: False /= a
RHS: a
Suggestion
Redundant /= LHS: (/= True)
RHS: not
Suggestion
Redundant /= LHS: (/= False)
RHS: id
Suggestion
Redundant /= LHS: (True /=)
RHS: not
Suggestion
Redundant /= LHS: (False /=)
RHS: id
Suggestion
Redundant if LHS: if a then x else x
RHS: x
Warning
Redundant if LHS: if a then True else False
RHS: a
Warning
Redundant if LHS: if a then False else True
RHS: not a
Warning
Redundant if LHS: if a then t else (if b then t else f)
RHS: if a || b then t else f
Warning
Redundant if LHS: if a then (if b then t else f) else f
RHS: if a && b then t else f
Warning
Redundant if LHS: if x then True else y
RHS: x || y
Warning
Redundant if LHS: if x then y else False
RHS: x && y
Warning
Redundant multi-way if LHS:
if | b -> t
   | otherwise -> f
RHS: if b then t else f
Warning
Use if LHS:
case a of
  True -> t
  False -> f
RHS: if a then t else f
Suggestion
Use if LHS:
case a of
  False -> f
  True -> t
RHS: if a then t else f
Suggestion
Use if LHS:
case a of
  True -> t
  _ -> f
RHS: if a then t else f
Suggestion
Use if LHS:
case a of
  False -> f
  _ -> t
RHS: if a then t else f
Suggestion
Redundant if LHS: if c then (True, x) else (False, x)
RHS: (c, x)
Suggestion
Redundant if LHS: if c then (False, x) else (True, x)
RHS: (not c, x)
Suggestion
Use || LHS: or [x, y]
RHS: x || y
Suggestion
Use || LHS: or [x, y, z]
RHS: x || y || z
Suggestion
Use && LHS: and [x, y]
RHS: x && y
Suggestion
Use && LHS: and [x, y, z]
RHS: x && y && z
Suggestion
Redundant if LHS: if x then False else y
RHS: not x && y
Warning
Redundant if LHS: if x then y else True
RHS: not x || y
Warning
Redundant not LHS: not (not x)
RHS: x
Warning
Use second LHS: id *** g
RHS: second g
Warning
Use first LHS: f *** id
RHS: first f
Warning
Use &&& LHS: zip (map f x) (map g x)
RHS: map (f Control.Arrow.&&& g) x
Ignore
Use &&& LHS: \ x -> (f x, g x)
RHS: f Control.Arrow.&&& g
Ignore
Redundant pair LHS: (fst x, snd x)
RHS: x
Suggestion
Use second LHS: bimap id g
RHS: second g
Warning
Use first LHS: bimap f id
RHS: first f
Warning
Redundant first LHS: first id
RHS: id
Warning
Redundant second LHS: second id
RHS: id
Warning
Redundant bimap LHS: bimap id id
RHS: id
Warning
Use bimap LHS: first f (second g x)
RHS: bimap f g x
Warning
Use bimap LHS: second g (first f x)
RHS: bimap f g x
Warning
Redundant first LHS: first f (first g x)
RHS: first (f . g) x
Warning
Redundant second LHS: second f (second g x)
RHS: second (f . g) x
Warning
Redundant bimap LHS: bimap f h (bimap g i x)
RHS: bimap (f . g) (h . i) x
Warning
Redundant first LHS: first f (bimap g h x)
RHS: bimap (f . g) h x
Warning
Redundant second LHS: second g (bimap f h x)
RHS: bimap f (g . h) x
Warning
Redundant first LHS: bimap f h (first g x)
RHS: bimap (f . g) h x
Warning
Redundant second LHS: bimap f g (second h x)
RHS: bimap f (g . h) x
Warning
Use bimap LHS: \ (x, y) -> (f x, g y)
RHS: Data.Bifunctor.bimap f g
Suggestion
Use first LHS: \ (x, y) -> (f x, y)
RHS: Data.Bifunctor.first f
Suggestion
Use second LHS: \ (x, y) -> (x, f y)
RHS: Data.Bifunctor.second f
Suggestion
Use bimap LHS: (f (fst x), g (snd x))
RHS: Data.Bifunctor.bimap f g x
Suggestion
Use first LHS: (f (fst x), snd x)
RHS: Data.Bifunctor.first f x
Suggestion
Use second LHS: (fst x, g (snd x))
RHS: Data.Bifunctor.second g x
Suggestion
Functor law LHS: fmap f (fmap g x)
RHS: fmap (f . g) x
Warning
Functor law LHS: f <$> (g <$> x)
RHS: f . g <$> x
Warning
Functor law LHS: x <&> g <&> f
RHS: x <&> f . g
Warning
Functor law LHS: fmap id
RHS: id
Warning
Functor law LHS: id <$> x
RHS: x
Warning
Functor law LHS: x <&> id
RHS: x
Warning
Redundant <$> LHS: f <$> g <$> x
RHS: f . g <$> x
Warning
Use <$> LHS: fmap f $ x
RHS: f <$> x
Suggestion
Use fmap LHS: \ x -> a <$> b x
RHS: fmap a . b
Suggestion
Use fmap LHS: \ x -> b x <&> a
RHS: fmap a . b
Suggestion
Use $> LHS: x *> pure y
RHS: x Data.Functor.$> y
Suggestion
Use $> LHS: x *> return y
RHS: x Data.Functor.$> y
Suggestion
Use <$ LHS: pure x <* y
RHS: x Data.Functor.<$ y
Suggestion
Use <$ LHS: return x <* y
RHS: x Data.Functor.<$ y
Suggestion
Use <$ LHS: const x <$> y
RHS: x <$ y
Suggestion
Use <$ LHS: pure x <$> y
RHS: x <$ y
Suggestion
Use <$ LHS: return x <$> y
RHS: x <$ y
Suggestion
Use $> LHS: x <&> const y
RHS: x Data.Functor.$> y
Suggestion
Use $> LHS: x <&> pure y
RHS: x Data.Functor.$> y
Suggestion
Use $> LHS: x <&> return y
RHS: x Data.Functor.$> y
Suggestion
Using fmap on tuple LHS: fmap f (x, b)
RHS: (x, f b)
Warning
Using <$> on tuple LHS: f <$> (x, b)
RHS: (x, f b)
Warning
Using <&> on tuple LHS: (x, b) <&> f
RHS: (x, f b)
Warning
Using fmap on tuple LHS: fmap f (x, y, b)
RHS: (x, y, f b)
Warning
Using <$> on tuple LHS: f <$> (x, y, b)
RHS: (x, y, f b)
Warning
Using <&> on tuple LHS: (x, y, b) <&> f
RHS: (x, y, f b)
Warning
Use <$> LHS: pure x <*> y
RHS: x <$> y
Suggestion
Use <$> LHS: return x <*> y
RHS: x <$> y
Suggestion
Redundant <* LHS: x <* pure y
RHS: x
Warning
Redundant <* LHS: x <* return y
RHS: x
Warning
Redundant pure LHS: pure x *> y
RHS: y
Warning
Redundant return LHS: return x *> y
RHS: y
Warning
Monad law, left identity LHS: pure a >>= f
RHS: f a
Warning
Monad law, left identity LHS: return a >>= f
RHS: f a
Warning
Monad law, left identity LHS: f =<< pure a
RHS: f a
Warning
Monad law, left identity LHS: f =<< return a
RHS: f a
Warning
Monad law, right identity LHS: m >>= pure
RHS: m
Warning
Monad law, right identity LHS: m >>= return
RHS: m
Warning
Monad law, right identity LHS: pure =<< m
RHS: m
Warning
Monad law, right identity LHS: return =<< m
RHS: m
Warning
Use fmap LHS: liftM
RHS: fmap
Warning
Use fmap LHS: liftA
RHS: fmap
Warning
Use <&> LHS: m >>= pure . f
RHS: m Data.Functor.<&> f
Suggestion
Use <&> LHS: m >>= return . f
RHS: m Data.Functor.<&> f
Suggestion
Use <$> LHS: pure . f =<< m
RHS: f <$> m
Suggestion
Use <$> LHS: return . f =<< m
RHS: f <$> m
Suggestion
Redundant fmap LHS: fmap f x >>= g
RHS: x >>= g . f
Warning
Redundant <$> LHS: f <$> x >>= g
RHS: x >>= g . f
Warning
Redundant <&> LHS: x Data.Functor.<&> f >>= g
RHS: x >>= g . f
Warning
Redundant fmap LHS: g =<< fmap f x
RHS: g . f =<< x
Warning
Redundant <$> LHS: g =<< f <$> x
RHS: g . f =<< x
Warning
Redundant <&> LHS: g =<< (x Data.Functor.<&> f)
RHS: g . f =<< x
Warning
Use when LHS: if x then y else pure ()
RHS: Control.Monad.when x $ _noParen_ y
Warning
Use when LHS: if x then y else return ()
RHS: Control.Monad.when x $ _noParen_ y
Warning
Use when LHS: if x then y else pure ()
RHS: Control.Monad.when x y
Warning
Use when LHS: if x then y else return ()
RHS: Control.Monad.when x y
Warning
Use unless LHS: if x then pure () else y
RHS: Control.Monad.unless x $ _noParen_ y
Warning
Use unless LHS: if x then return () else y
RHS: Control.Monad.unless x $ _noParen_ y
Warning
Use unless LHS: if x then pure () else y
RHS: Control.Monad.unless x y
Warning
Use unless LHS: if x then return () else y
RHS: Control.Monad.unless x y
Warning
Use mapM LHS: sequence (map f x)
RHS: mapM f x
Warning
Use mapM_ LHS: sequence_ (map f x)
RHS: mapM_ f x
Warning
Use mapM LHS: sequence (f <$> x)
RHS: mapM f x
Warning
Use mapM LHS: sequence (x <&> f)
RHS: mapM f x
Warning
Use mapM LHS: sequence (fmap f x)
RHS: mapM f x
Warning
Use mapM_ LHS: sequence_ (f <$> x)
RHS: mapM_ f x
Warning
Use mapM_ LHS: sequence_ (x <&> f)
RHS: mapM_ f x
Warning
Use mapM_ LHS: sequence_ (fmap f x)
RHS: mapM_ f x
Warning
Use forM LHS: flip mapM
RHS: Control.Monad.forM
Suggestion
Use forM_ LHS: flip mapM_
RHS: Control.Monad.forM_
Suggestion
Use mapM LHS: flip forM
RHS: mapM
Suggestion
Use mapM_ LHS: flip forM_
RHS: mapM_
Suggestion
Use unless LHS: when (not x)
RHS: unless x
Warning
Use unless LHS: when (notElem x y)
RHS: unless (elem x y)
Warning
Use when LHS: unless (not x)
RHS: when x
Warning
Use when LHS: unless (notElem x y)
RHS: when (elem x y)
Warning
Use join LHS: x >>= id
RHS: Control.Monad.join x
Warning
Use join LHS: id =<< x
RHS: Control.Monad.join x
Warning
Use =<< LHS: join (f <$> x)
RHS: f =<< x
Suggestion
Use =<< LHS: join (x <&> f)
RHS: f =<< x
Suggestion
Use =<< LHS: join (fmap f x)
RHS: f =<< x
Suggestion
Use void LHS: a >> pure ()
RHS: Control.Monad.void a
Suggestion
Use void LHS: a >> return ()
RHS: Control.Monad.void a
Suggestion
Use void LHS: fmap (const ())
RHS: Control.Monad.void
Warning
Use void LHS: const () <$> x
RHS: Control.Monad.void x
Warning
Use void LHS: x <&> const ()
RHS: Control.Monad.void x
Warning
Use void LHS: () <$ x
RHS: Control.Monad.void x
Warning
Use <=< LHS: flip (>=>)
RHS: (<=<)
Warning
Use >=> LHS: flip (<=<)
RHS: (>=>)
Warning
Use =<< LHS: flip (>>=)
RHS: (=<<)
Warning
Use >>= LHS: flip (=<<)
RHS: (>>=)
Warning
Use >=> LHS: \ x -> f x >>= g
RHS: f Control.Monad.>=> g
Suggestion
Use <=< LHS: \ x -> f =<< g x
RHS: f Control.Monad.<=< g
Suggestion
Use <=< LHS: (>>= f) . g
RHS: f Control.Monad.<=< g
Suggestion
Use <=< LHS: (f =<<) . g
RHS: f Control.Monad.<=< g
Suggestion
Redundant >> LHS: a >> forever a
RHS: forever a
Warning
Use ap LHS: liftM2 id
RHS: ap
Suggestion
Use fmap LHS: liftM2 f (pure x)
RHS: fmap (f x)
Warning
Use fmap LHS: liftA2 f (return x)
RHS: fmap (f x)
Warning
Use fmap LHS: liftM2 f (pure x)
RHS: fmap (f x)
Warning
Use fmap LHS: liftM2 f (return x)
RHS: fmap (f x)
Warning
Redundant fmap LHS: fmap f (pure x)
RHS: pure (f x)
Warning
Redundant fmap LHS: fmap f (return x)
RHS: return (f x)
Warning
Redundant <$> LHS: f <$> pure x
RHS: pure (f x)
Warning
Redundant <&> LHS: pure x <&> f
RHS: pure (f x)
Warning
Redundant <$> LHS: f <$> return x
RHS: return (f x)
Warning
Redundant <&> LHS: return x <&> f
RHS: return (f x)
Warning
Use zipWithM LHS: mapM (uncurry f) (zip l m)
RHS: zipWithM f l m
Warning
Redundant void LHS: mapM_ (void . f)
RHS: mapM_ f
Warning
Redundant void LHS: forM_ x (void . f)
RHS: forM_ x f
Warning
Use >> LHS: a >>= \ _ -> b
RHS: a >> b
Warning
Redundant <* LHS: m <* pure x
RHS: m
Warning
Redundant <* LHS: m <* return x
RHS: m
Warning
Redundant pure LHS: pure x *> m
RHS: m
Warning
Redundant return LHS: return x *> m
RHS: m
Warning
Redundant pure LHS: pure x >> m
RHS: m
Warning
Redundant return LHS: return x >> m
RHS: m
Warning
Use replicateM LHS: forM [1 .. n] (const f)
RHS: replicateM n f
Warning
Use replicateM LHS: for [1 .. n] (const f)
RHS: replicateM n f
Warning
Use replicateM LHS: forM [1 .. n] (\ _ -> x)
RHS: replicateM n x
Warning
Use replicateM LHS: for [1 .. n] (\ _ -> x)
RHS: replicateM n x
Warning
Use evalState LHS: fst (runState x y)
RHS: evalState x y
Warning
Use execState LHS: snd (runState x y)
RHS: execState x y
Warning
Use mapAndUnzipM LHS: unzip <$> mapM f x
RHS: Control.Monad.mapAndUnzipM f x
Warning
Use mapAndUnzipM LHS: mapM f x <&> unzip
RHS: Control.Monad.mapAndUnzipM f x
Warning
Use mapAndUnzipM LHS: fmap unzip (mapM f x)
RHS: Control.Monad.mapAndUnzipM f x
Warning
Use zipWithM LHS: sequence (zipWith f x y)
RHS: Control.Monad.zipWithM f x y
Warning
Use zipWithM_ LHS: sequence_ (zipWith f x y)
RHS: Control.Monad.zipWithM_ f x y
Warning
Use replicateM LHS: sequence (replicate n x)
RHS: Control.Monad.replicateM n x
Warning
Use replicateM_ LHS: sequence_ (replicate n x)
RHS: Control.Monad.replicateM_ n x
Warning
Use zipWithM LHS: sequenceA (zipWith f x y)
RHS: Control.Monad.zipWithM f x y
Warning
Use zipWithM_ LHS: sequenceA_ (zipWith f x y)
RHS: Control.Monad.zipWithM_ f x y
Warning
Use replicateM LHS: sequenceA (replicate n x)
RHS: Control.Monad.replicateM n x
Warning
Use replicateM_ LHS: sequenceA_ (replicate n x)
RHS: Control.Monad.replicateM_ n x
Warning
Use replicateM LHS: mapM f (replicate n x)
RHS: Control.Monad.replicateM n (f x)
Warning
Use replicateM_ LHS: mapM_ f (replicate n x)
RHS: Control.Monad.replicateM_ n (f x)
Warning
Fuse mapM/map LHS: mapM f (map g x)
RHS: mapM (f . g) x
Warning
Fuse mapM_/map LHS: mapM_ f (map g x)
RHS: mapM_ (f . g) x
Warning
Fuse traverse/map LHS: traverse f (map g x)
RHS: traverse (f . g) x
Warning
Fuse traverse_/map LHS: traverse_ f (map g x)
RHS: traverse_ (f . g) x
Warning
Use sequence LHS: mapM id
RHS: sequence
Warning
Use sequence_ LHS: mapM_ id
RHS: sequence_
Warning
Use for LHS: flip traverse
RHS: for
Warning
Use traverse LHS: flip for
RHS: traverse
Warning
Use for_ LHS: flip traverse_
RHS: for_
Warning
Use traverse_ LHS: flip for_
RHS: traverse_
Warning
Use sequenceA_ LHS: foldr (*>) (pure ())
RHS: sequenceA_
Warning
Use sequence_ LHS: foldr (*>) (return ())
RHS: sequence_
Warning
Use asum LHS: foldr (<|>) empty
RHS: asum
Warning
Use <**> LHS: liftA2 (flip ($))
RHS: (<**>)
Warning
Use fmap LHS: liftA2 f (pure x)
RHS: fmap (f x)
Warning
Use fmap LHS: liftA2 f (return x)
RHS: fmap (f x)
Warning
Use optional LHS: Just <$> a <|> pure Nothing
RHS: optional a
Warning
Use optional LHS: Just <$> a <|> return Nothing
RHS: optional a
Warning
Alternative law, left identity LHS: empty <|> x
RHS: x
Warning
Alternative law, right identity LHS: x <|> empty
RHS: x
Warning
Use sequenceA LHS: traverse id
RHS: sequenceA
Warning
Use sequenceA_ LHS: traverse_ id
RHS: sequenceA_
Warning
Use list comprehension LHS: if b then [x] else []
RHS: [x | b]
Suggestion
Use list comprehension LHS: if b then [] else [x]
RHS: [x | not b]
Suggestion
Redundant list comprehension LHS: [x | x <- y]
RHS: y
Suggestion
Redundant list comprehension LHS: [f x | x <- [y]]
RHS: [f y]
Suggestion
Redundant seq LHS: seq x x
RHS: x
Warning
Redundant seq LHS: join seq
RHS: id
Warning
Redundant $! LHS: id $! x
RHS: x
Warning
Redundant seq LHS: seq x y
RHS: y
Warning
Redundant $! LHS: f $! x
RHS: f x
Warning
Redundant evaluate LHS: evaluate x
RHS: return x
Warning
Redundant seq LHS: seq (rnf x) ()
RHS: rnf x
Warning
Use map LHS: fst (unzip x)
RHS: map fst x
Warning
Use map LHS: snd (unzip x)
RHS: map snd x
Warning
Use (,) LHS: \ x y -> (x, y)
RHS: (,)
Suggestion
Use (,,) LHS: \ x y z -> (x, y, z)
RHS: (,,)
Suggestion
Evaluate LHS: (, b) a
RHS: (a, b)
Suggestion
Evaluate LHS: (a,) b
RHS: (a, b)
Suggestion
Avoid NonEmpty.unzip LHS: Data.List.NonEmpty.unzip
RHS: Data.Functor.unzip
Warning
Use fromMaybe LHS: maybe x id
RHS: Data.Maybe.fromMaybe x
Warning
Redundant maybe LHS: maybe Nothing Just
RHS: id
Warning
Use isJust LHS: maybe False (const True)
RHS: Data.Maybe.isJust
Warning
Use isNothing LHS: maybe True (const False)
RHS: Data.Maybe.isNothing
Warning
Use Just LHS: maybe False (x ==)
RHS: (Just x ==)
Warning
Use Just LHS: maybe True (x /=)
RHS: (Just x /=)
Warning
Use Just LHS: maybe False (== x)
RHS: (Just x ==)
Warning
Use Just LHS: maybe True (/= x)
RHS: (Just x /=)
Warning
Use Just LHS: fromMaybe False x
RHS: Just True == x
Ignore
Use Just LHS: fromMaybe True x
RHS: Just False /= x
Ignore
Use isJust LHS: not (isNothing x)
RHS: isJust x
Warning
Use isNothing LHS: not (isJust x)
RHS: isNothing x
Warning
Use maybeToList LHS: maybe [] (: [])
RHS: maybeToList
Warning
Use mapMaybe LHS: catMaybes (map f x)
RHS: mapMaybe f x
Warning
Use mapMaybe LHS: catMaybes (f <$> x)
RHS: mapMaybe f x
Warning
Use mapMaybe LHS: catMaybes (x <&> f)
RHS: mapMaybe f x
Warning
Use mapMaybe LHS: catMaybes (fmap f x)
RHS: mapMaybe f x
Warning
Replace case with fromMaybe LHS:
case x of
  Nothing -> y
  Just a -> a
RHS: Data.Maybe.fromMaybe y x
Suggestion
Replace case with fromMaybe LHS:
case x of
  Just a -> a
  Nothing -> y
RHS: Data.Maybe.fromMaybe y x
Suggestion
Replace case with maybe LHS:
case x of
  Nothing -> y
  Just a -> f a
RHS: maybe y f x
Suggestion
Replace case with maybe LHS:
case x of
  Just a -> f a
  Nothing -> y
RHS: maybe y f x
Suggestion
Use maybe LHS: if isNothing x then y else f (fromJust x)
RHS: maybe y f x
Warning
Use maybe LHS: if isJust x then f (fromJust x) else y
RHS: maybe y f x
Warning
Use fmap LHS: maybe Nothing (Just . f)
RHS: fmap f
Warning
Use catMaybes LHS: map fromJust (filter isJust x)
RHS: Data.Maybe.catMaybes x
Suggestion
Use mapMaybe LHS: filter isJust (map f x)
RHS: map Just (mapMaybe f x)
Suggestion
Use mapMaybe LHS: filter isJust (f <*> x)
RHS: map Just (mapMaybe f x)
Suggestion
Use mapMaybe LHS: filter isJust (x <&> f)
RHS: map Just (mapMaybe f x)
Suggestion
Use mapMaybe LHS: filter isJust (fmap f x)
RHS: map Just (mapMaybe f x)
Suggestion
Use isNothing LHS: x == Nothing
RHS: isNothing x
Warning
Use isNothing LHS: Nothing == x
RHS: isNothing x
Warning
Use isJust LHS: x /= Nothing
RHS: Data.Maybe.isJust x
Warning
Use isJust LHS: Nothing /= x
RHS: Data.Maybe.isJust x
Warning
Use mapMaybe LHS: concatMap (maybeToList . f)
RHS: Data.Maybe.mapMaybe f
Warning
Use catMaybes LHS: concatMap maybeToList
RHS: catMaybes
Warning
Use <|> LHS: maybe n Just x
RHS: x Control.Applicative.<|> n
Warning
Use fromMaybe LHS: if isNothing x then y else fromJust x
RHS: fromMaybe y x
Warning
Use fromMaybe LHS: if isJust x then fromJust x else y
RHS: fromMaybe y x
Warning
Use Just LHS: isJust x && (fromJust x == y)
RHS: x == Just y
Warning
Use Just LHS: isJust y && (x == fromJust y)
RHS: Just x == y
Warning
Fuse mapMaybe/map LHS: mapMaybe f (map g x)
RHS: mapMaybe (f . g) x
Warning
Use maybe LHS: fromMaybe a (fmap f x)
RHS: maybe a f x
Warning
Use maybe LHS: fromMaybe a (f <$> x)
RHS: maybe a f x
Warning
Use maybe LHS: fromMaybe a (x <&> f)
RHS: maybe a f x
Warning
Use catMaybes LHS: mapMaybe id
RHS: catMaybes
Warning
Use catMaybes LHS: [x | Just x <- a]
RHS: Data.Maybe.catMaybes a
Suggestion
Use join LHS:
case m of
  Nothing -> Nothing
  Just x -> x
RHS: Control.Monad.join m
Suggestion
Use join LHS: maybe Nothing id
RHS: join
Suggestion
Use =<< LHS: maybe Nothing f x
RHS: f =<< x
Suggestion
Redundant <$> LHS: maybe x f (g <$> y)
RHS: maybe x (f . g) y
Warning
Redundant <&> LHS: maybe x f (y <&> g)
RHS: maybe x (f . g) y
Warning
Redundant fmap LHS: maybe x f (fmap g y)
RHS: maybe x (f . g) y
Warning
Redundant <$> LHS: isJust (f <$> x)
RHS: isJust x
Warning
Redundant <&> LHS: isJust (x <&> f)
RHS: isJust x
Warning
Redundant fmap LHS: isJust (fmap f x)
RHS: isJust x
Warning
Redundant <$> LHS: isNothing (f <$> x)
RHS: isNothing x
Warning
Redundant <&> LHS: isNothing (x <&> f)
RHS: isNothing x
Warning
Redundant fmap LHS: isNothing (fmap f x)
RHS: isNothing x
Warning
Redundant <$> LHS: fromJust (f <$> x)
RHS: f (fromJust x)
Warning
Redundant <&> LHS: fromJust (x <&> f)
RHS: f (fromJust x)
Warning
Redundant fmap LHS: fromJust (fmap f x)
RHS: f (fromJust x)
Warning
Redundant <$> LHS: mapMaybe f (g <$> x)
RHS: mapMaybe (f . g) x
Warning
Redundant <&> LHS: mapMaybe f (x <&> g)
RHS: mapMaybe (f . g) x
Warning
Redundant fmap LHS: mapMaybe f (fmap g x)
RHS: mapMaybe (f . g) x
Warning
Move nub out LHS: catMaybes (nub x)
RHS: nub (catMaybes x)
Warning
Move nub out LHS: lefts (nub x)
RHS: nub (lefts x)
Warning
Move nub out LHS: rights (nub x)
RHS: nub (rights x)
Warning
Move reverse out LHS: catMaybes (reverse x)
RHS: reverse (catMaybes x)
Warning
Move reverse out LHS: lefts (reverse x)
RHS: reverse (lefts x)
Warning
Move reverse out LHS: rights (reverse x)
RHS: reverse (rights x)
Warning
Move sort out LHS: catMaybes (sort x)
RHS: sort (catMaybes x)
Warning
Move sort out LHS: lefts (sort x)
RHS: sort (lefts x)
Warning
Move sort out LHS: rights (sort x)
RHS: sort (rights x)
Warning
Move nubOrd out LHS: catMaybes (nubOrd x)
RHS: nubOrd (catMaybes x)
Warning
Move nubOrd out LHS: lefts (nubOrd x)
RHS: nubOrd (lefts x)
Warning
Move nubOrd out LHS: rights (nubOrd x)
RHS: nubOrd (rights x)
Warning
Move reverse out LHS: filter f (reverse x)
RHS: reverse (filter f x)
Warning
Use lefts LHS: [a | Left a <- b]
RHS: lefts b
Warning
Use rights LHS: [a | Right a <- b]
RHS: rights b
Warning
Use fmap LHS: either Left (Right . f)
RHS: fmap f
Warning
Redundant fmap LHS: either f g (fmap h x)
RHS: either f (g . h) x
Warning
Redundant <$> LHS: either f g (h <$> x)
RHS: either f (g . h) x
Warning
Redundant <&> LHS: either f g (x <&> h)
RHS: either f (g . h) x
Warning
Redundant fmap LHS: isLeft (fmap f x)
RHS: isLeft x
Warning
Redundant <$> LHS: isLeft (f <$> x)
RHS: isLeft x
Warning
Redundant <&> LHS: isLeft (x <&> f)
RHS: isLeft x
Warning
Redundant fmap LHS: isRight (fmap f x)
RHS: isRight x
Warning
Redundant <$> LHS: isRight (f <$> x)
RHS: isRight x
Warning
Redundant <&> LHS: isRight (x <&> f)
RHS: isRight x
Warning
Redundant fmap LHS: fromLeft x (fmap f y)
RHS: fromLeft x y
Warning
Redundant <$> LHS: fromLeft x (f <$> y)
RHS: fromLeft x y
Warning
Redundant <&> LHS: fromLeft x (y <&> f)
RHS: fromLeft x y
Warning
Use either LHS: fromRight x (fmap f y)
RHS: either (const x) f y
Warning
Use either LHS: fromRight x (f <$> y)
RHS: either (const x) f y
Warning
Use either LHS: fromRight x (y <&> f)
RHS: either (const x) f y
Warning
Use fromRight LHS: either (const x) id
RHS: fromRight x
Warning
Use fromLeft LHS: either id (const x)
RHS: fromLeft x
Warning
Use =<< LHS: either Left f x
RHS: f =<< x
Warning
Use infix LHS: elem x y
RHS: x `elem` y
Suggestion
Use infix LHS: notElem x y
RHS: x `notElem` y
Suggestion
Use infix LHS: isInfixOf x y
RHS: x `isInfixOf` y
Suggestion
Use infix LHS: isSuffixOf x y
RHS: x `isSuffixOf` y
Suggestion
Use infix LHS: isPrefixOf x y
RHS: x `isPrefixOf` y
Suggestion
Use infix LHS: union x y
RHS: x `union` y
Suggestion
Use infix LHS: intersect x y
RHS: x `intersect` y
Suggestion
Redundant fromIntegral LHS: fromIntegral x
RHS: x
Warning
Redundant fromInteger LHS: fromInteger x
RHS: x
Warning
Use - LHS: x + negate y
RHS: x - y
Suggestion
Use negate LHS: 0 - x
RHS: negate x
Suggestion
Redundant negate LHS: negate (negate x)
RHS: x
Warning
Use logBase LHS: log y / log x
RHS: logBase x y
Suggestion
Use tan LHS: sin x / cos x
RHS: tan x
Suggestion
Use even LHS: rem n 2 == 0
RHS: even n
Suggestion
Use even LHS: 0 == rem n 2
RHS: even n
Suggestion
Use odd LHS: rem n 2 /= 0
RHS: odd n
Suggestion
Use odd LHS: 0 /= rem n 2
RHS: odd n
Suggestion
Use even LHS: mod n 2 == 0
RHS: even n
Suggestion
Use even LHS: 0 == mod n 2
RHS: even n
Suggestion
Use odd LHS: mod n 2 /= 0
RHS: odd n
Suggestion
Use odd LHS: 0 /= mod n 2
RHS: odd n
Suggestion
Use odd LHS: not (even x)
RHS: odd x
Suggestion
Use even LHS: not (odd x)
RHS: even x
Suggestion
Use sqrt LHS: x ** 0.5
RHS: sqrt x
Suggestion
Use 1 LHS: x ^ 0
RHS: 1
Suggestion
Use floor LHS: round (x - 0.5)
RHS: floor x
Suggestion
Use writeList2Chan LHS: mapM_ (writeChan a)
RHS: writeList2Chan a
Suggestion
Use readTVarIO LHS: atomically (readTVar x)
RHS: readTVarIO x
Warning
Use newTVarIO LHS: atomically (newTVar x)
RHS: newTVarIO x
Warning
Use newTMVarIO LHS: atomically (newTMVar x)
RHS: newTMVarIO x
Warning
Use newEmptyTMVarIO LHS: atomically newEmptyTMVar
RHS: newEmptyTMVarIO
Warning
Use typeRep LHS: typeOf (a :: b)
RHS: typeRep (Proxy :: Proxy b)
Suggestion
Use handle LHS: flip Control.Exception.catch
RHS: handle
Suggestion
Use catch LHS: flip handle
RHS: Control.Exception.catch
Suggestion
Use handleJust LHS: flip (catchJust p)
RHS: handleJust p
Suggestion
Use catchJust LHS: flip (handleJust p)
RHS: catchJust p
Suggestion
Use bracket_ LHS: Control.Exception.bracket b (const a) (const t)
RHS: Control.Exception.bracket_ b a t
Suggestion
Use withFile LHS: Control.Exception.bracket (openFile x y) hClose
RHS: withFile x y
Suggestion
Use withBinaryFile LHS: Control.Exception.bracket (openBinaryFile x y) hClose
RHS: withBinaryFile x y
Suggestion
Use error LHS: throw (ErrorCall a)
RHS: error a
Suggestion
Use nonTermination LHS: toException NonTermination
RHS: nonTermination
Warning
Use nestedAtomically LHS: toException NestedAtomically
RHS: nestedAtomically
Warning
Use writeIORef LHS: modifyIORef r (const x)
RHS: writeIORef r x
Suggestion
Use writeIORef LHS: modifyIORef r (\ v -> x)
RHS: writeIORef r x
Suggestion
Redundant castPtr LHS: castPtr nullPtr
RHS: nullPtr
Suggestion
Redundant castPtr LHS: castPtr (castPtr x)
RHS: castPtr x
Suggestion
Redundant castPtr LHS: plusPtr (castPtr x)
RHS: plusPtr x
Suggestion
Redundant castPtr LHS: minusPtr (castPtr x)
RHS: minusPtr x
Suggestion
Redundant castPtr LHS: minusPtr x (castPtr y)
RHS: minusPtr x y
Suggestion
Redundant castPtr LHS: peekByteOff (castPtr x)
RHS: peekByteOff x
Suggestion
Redundant castPtr LHS: pokeByteOff (castPtr x)
RHS: pokeByteOff x
Suggestion
Use mkWeakPtr LHS: mkWeak a a b
RHS: mkWeakPtr a b
Warning
Use mkWeakPair LHS: mkWeak a (a, b) c
RHS: mkWeakPair a b c
Warning
Use for_ LHS:
case m of
  Nothing -> pure ()
  Just x -> f x
RHS: Data.Foldable.for_ m f
Warning
Use forM_ LHS:
case m of
  Nothing -> return ()
  Just x -> f x
RHS: Data.Foldable.forM_ m f
Warning
Use for_ LHS:
case m of
  Just x -> f x
  Nothing -> pure ()
RHS: Data.Foldable.for_ m f
Warning
Use forM_ LHS:
case m of
  Just x -> f x
  Nothing -> return ()
RHS: Data.Foldable.forM_ m f
Warning
Use for_ LHS:
case m of
  Just x -> f x
  _ -> pure ()
RHS: Data.Foldable.for_ m f
Warning
Use forM_ LHS:
case m of
  Just x -> f x
  _ -> return ()
RHS: Data.Foldable.forM_ m f
Warning
Use for_ LHS: when (isJust m) (f (fromJust m))
RHS: Data.Foldable.for_ m f
Warning
Fuse concatMap/fmap LHS: concatMap f (fmap g x)
RHS: concatMap (f . g) x
Suggestion
Fuse concatMap/<$> LHS: concatMap f (g <$> x)
RHS: concatMap (f . g) x
Suggestion
Fuse concatMap/<&> LHS: concatMap f (x <&> g)
RHS: concatMap (f . g) x
Suggestion
Use all LHS: null (concatMap f x)
RHS: all (null . f) x
Warning
Use any LHS: or (concat x)
RHS: any or x
Warning
Use any LHS: or (concatMap f x)
RHS: any (or . f) x
Warning
Use all LHS: and (concat x)
RHS: all and x
Warning
Use all LHS: and (concatMap f x)
RHS: all (and . f) x
Warning
Use any LHS: any f (concat x)
RHS: any (any f) x
Warning
Use any LHS: any f (concatMap g x)
RHS: any (any f . g) x
Warning
Use all LHS: all f (concat x)
RHS: all (all f) x
Warning
Use all LHS: all f (concatMap g x)
RHS: all (all f . g) x
Warning
Use foldMap LHS: fold (concatMap f x)
RHS: foldMap (fold . f) x
Warning
Use foldMap LHS: foldMap f (concatMap g x)
RHS: foldMap (foldMap f . g) x
Warning
Move catMaybes LHS: catMaybes (concatMap f x)
RHS: concatMap (catMaybes . f) x
Warning
Move catMaybes LHS: catMaybes (concat x)
RHS: concatMap catMaybes x
Warning
Move filter LHS: filter f (concatMap g x)
RHS: concatMap (filter f . g) x
Suggestion
Move filter LHS: filter f (concat x)
RHS: concatMap (filter f) x
Suggestion
Move mapMaybe LHS: mapMaybe f (concatMap g x)
RHS: concatMap (mapMaybe f . g) x
Warning
Move mapMaybe LHS: mapMaybe f (concat x)
RHS: concatMap (mapMaybe f) x
Warning
Use any LHS: or (fmap p x)
RHS: any p x
Warning
Use any LHS: or (p <$> x)
RHS: any p x
Warning
Use any LHS: or (x <&> p)
RHS: any p x
Warning
Use all LHS: and (fmap p x)
RHS: all p x
Warning
Use all LHS: and (p <$> x)
RHS: all p x
Warning
Use all LHS: and (x <&> p)
RHS: all p x
Warning
Redundant fmap LHS: any f (fmap g x)
RHS: any (f . g) x
Warning
Redundant <$> LHS: any f (g <$> x)
RHS: any (f . g) x
Warning
Redundant <&> LHS: any f (x <&> g)
RHS: any (f . g) x
Warning
Redundant fmap LHS: all f (fmap g x)
RHS: all (f . g) x
Warning
Redundant <$> LHS: all f (g <$> x)
RHS: all (f . g) x
Warning
Redundant <&> LHS: all f (x <&> g)
RHS: all (f . g) x
Warning
Fuse foldr/fmap LHS: foldr f z (fmap g x)
RHS: foldr (f . g) z x
Suggestion
Fuse foldr/<$> LHS: foldr f z (g <$> x)
RHS: foldr (f . g) z x
Suggestion
Fuse foldr/<&> LHS: foldr f z (x <&> g)
RHS: foldr (f . g) z x
Suggestion
Use gets LHS: f <$> Control.Monad.State.get
RHS: gets f
Warning
Use gets LHS: Control.Monad.State.get <&> f
RHS: gets f
Warning
Use gets LHS: fmap f Control.Monad.State.get
RHS: gets f
Warning
Redundant <$> LHS: f <$> Control.Monad.State.gets g
RHS: gets (f . g)
Warning
Redundant <&> LHS: Control.Monad.State.gets g <&> f
RHS: gets (f . g)
Warning
Redundant fmap LHS: fmap f (Control.Monad.State.gets g)
RHS: gets (f . g)
Warning
Use asks LHS: f <$> Control.Monad.Reader.ask
RHS: asks f
Warning
Use asks LHS: Control.Monad.Reader.ask <&> f
RHS: asks f
Warning
Use asks LHS: fmap f Control.Monad.Reader.ask
RHS: asks f
Warning
Redundant <$> LHS: f <$> Control.Monad.Reader.asks g
RHS: asks (f . g)
Warning
Redundant <&> LHS: Control.Monad.Reader.asks g <&> f
RHS: asks (f . g)
Warning
Redundant fmap LHS: fmap f (Control.Monad.Reader.asks g)
RHS: asks (f . g)
Warning
Use evalState LHS: fst (runState m s)
RHS: evalState m s
Warning
Use execState LHS: snd (runState m s)
RHS: execState m s
Warning
Evaluate LHS: True && x
RHS: x
Warning
Evaluate LHS: False && x
RHS: False
Warning
Evaluate LHS: True || x
RHS: True
Warning
Evaluate LHS: False || x
RHS: x
Warning
Evaluate LHS: not True
RHS: False
Warning
Evaluate LHS: not False
RHS: True
Warning
Evaluate LHS: Nothing >>= k
RHS: Nothing
Warning
Evaluate LHS: k =<< Nothing
RHS: Nothing
Warning
Evaluate LHS: either f g (Left x)
RHS: f x
Warning
Evaluate LHS: either f g (Right y)
RHS: g y
Warning
Evaluate LHS: fst (x, y)
RHS: x
Warning
Evaluate LHS: snd (x, y)
RHS: y
Warning
Evaluate LHS: fromJust (Just x)
RHS: x
Warning
Evaluate LHS: fromLeft y (Left x)
RHS: x
Warning
Evaluate LHS: fromLeft y (Right x)
RHS: y
Warning
Evaluate LHS: fromRight y (Right x)
RHS: x
Warning
Evaluate LHS: fromRight y (Left x)
RHS: y
Warning
Evaluate LHS: head [x]
RHS: x
Warning
Evaluate LHS: last [x]
RHS: x
Warning
Evaluate LHS: tail [x]
RHS: []
Warning
Evaluate LHS: init [x]
RHS: []
Warning
Evaluate LHS: null [x]
RHS: False
Warning
Evaluate LHS: null []
RHS: True
Warning
Evaluate LHS: null ""
RHS: True
Warning
Evaluate LHS: length []
RHS: 0
Warning
Evaluate LHS: length ""
RHS: 0
Warning
Evaluate LHS: foldl f z []
RHS: z
Warning
Evaluate LHS: foldr f z []
RHS: z
Warning
Evaluate LHS: foldr1 f [x]
RHS: x
Warning
Evaluate LHS: scanr f z []
RHS: [z]
Warning
Evaluate LHS: scanr1 f []
RHS: []
Warning
Evaluate LHS: scanr1 f [x]
RHS: [x]
Warning
Evaluate LHS: take n []
RHS: []
Warning
Evaluate LHS: take n ""
RHS: ""
Warning
Evaluate LHS: drop n []
RHS: []
Warning
Evaluate LHS: drop n ""
RHS: ""
Warning
Evaluate LHS: takeWhile p []
RHS: []
Warning
Evaluate LHS: takeWhile p ""
RHS: ""
Warning
Evaluate LHS: dropWhile p []
RHS: []
Warning
Evaluate LHS: dropWhile p ""
RHS: ""
Warning
Evaluate LHS: span p []
RHS: ([], [])
Warning
Evaluate LHS: span p ""
RHS: ("", "")
Warning
Evaluate LHS: lines ""
RHS: []
Warning
Evaluate LHS: lines []
RHS: []
Warning
Evaluate LHS: unwords []
RHS: ""
Warning
Evaluate LHS: x - 0
RHS: x
Warning
Evaluate LHS: x * 1
RHS: x
Warning
Evaluate LHS: x / 1
RHS: x
Warning
Evaluate LHS: concat [a]
RHS: a
Warning
Evaluate LHS: concat []
RHS: []
Warning
Evaluate LHS: concatMap f [a]
RHS: f a
Warning
Evaluate LHS: concatMap f []
RHS: []
Warning
Evaluate LHS: zip [] []
RHS: []
Warning
Evaluate LHS: const x y
RHS: x
Warning
Evaluate LHS: any (const False)
RHS: const False
Warning
Evaluate LHS: all (const True)
RHS: const True
Warning
Evaluate LHS: [] ++ x
RHS: x
Warning
Evaluate LHS: "" ++ x
RHS: x
Warning
Evaluate LHS: x ++ []
RHS: x
Warning
Evaluate LHS: x ++ ""
RHS: x
Warning
Evaluate LHS: all f [a]
RHS: f a
Warning
Evaluate LHS: all f []
RHS: True
Warning
Evaluate LHS: any f [a]
RHS: f a
Warning
Evaluate LHS: any f []
RHS: False
Warning
Evaluate LHS: maximum [a]
RHS: a
Warning
Evaluate LHS: minimum [a]
RHS: a
Warning
Evaluate LHS: map f []
RHS: []
Warning
Evaluate LHS: map f [a]
RHS: [f a]
Warning
Using foldr on tuple LHS: foldr f z (x, b)
RHS: f b z
Warning
Using foldr' on tuple LHS: foldr' f z (x, b)
RHS: f b z
Warning
Using foldl on tuple LHS: foldl f z (x, b)
RHS: f z b
Warning
Using foldl' on tuple LHS: foldl' f z (x, b)
RHS: f z b
Warning
Using foldMap on tuple LHS: foldMap f (x, b)
RHS: f b
Warning
Using foldr1 on tuple LHS: foldr1 f (x, b)
RHS: b
Warning
Using foldl1 on tuple LHS: foldl1 f (x, b)
RHS: b
Warning
Using elem on tuple LHS: elem e (x, b)
RHS: e == b
Warning
Using fold on tuple LHS: fold (x, b)
RHS: b
Warning
Using toList on tuple LHS: toList (x, b)
RHS: b
Warning
Using maximum on tuple LHS: maximum (x, b)
RHS: b
Warning
Using minimum on tuple LHS: minimum (x, b)
RHS: b
Warning
Using notElem on tuple LHS: notElem e (x, b)
RHS: e /= b
Warning
Using sum on tuple LHS: sum (x, b)
RHS: b
Warning
Using product on tuple LHS: product (x, b)
RHS: b
Warning
Using concat on tuple LHS: concat (x, b)
RHS: b
Warning
Using concatMap on tuple LHS: concatMap f (x, b)
RHS: f b
Warning
Using and on tuple LHS: and (x, b)
RHS: b
Warning
Using or on tuple LHS: or (x, b)
RHS: b
Warning
Using any on tuple LHS: any f (x, b)
RHS: f b
Warning
Using all on tuple LHS: all f (x, b)
RHS: f b
Warning
Using foldr on tuple LHS: foldr f z (x, y, b)
RHS: f b z
Warning
Using foldr' on tuple LHS: foldr' f z (x, y, b)
RHS: f b z
Warning
Using foldl on tuple LHS: foldl f z (x, y, b)
RHS: f z b
Warning
Using foldl' on tuple LHS: foldl' f z (x, y, b)
RHS: f z b
Warning
Using foldMap on tuple LHS: foldMap f (x, y, b)
RHS: f b
Warning
Using foldr1 on tuple LHS: foldr1 f (x, y, b)
RHS: b
Warning
Using foldl1 on tuple LHS: foldl1 f (x, y, b)
RHS: b
Warning
Using elem on tuple LHS: elem e (x, y, b)
RHS: e == b
Warning
Using fold on tuple LHS: fold (x, y, b)
RHS: b
Warning
Using toList on tuple LHS: toList (x, y, b)
RHS: b
Warning
Using maximum on tuple LHS: maximum (x, y, b)
RHS: b
Warning
Using minimum on tuple LHS: minimum (x, y, b)
RHS: b
Warning
Using notElem on tuple LHS: notElem e (x, y, b)
RHS: e /= b
Warning
Using sum on tuple LHS: sum (x, y, b)
RHS: b
Warning
Using product on tuple LHS: product (x, y, b)
RHS: b
Warning
Using concat on tuple LHS: concat (x, y, b)
RHS: b
Warning
Using concatMap on tuple LHS: concatMap f (x, y, b)
RHS: f b
Warning
Using and on tuple LHS: and (x, y, b)
RHS: b
Warning
Using or on tuple LHS: or (x, y, b)
RHS: b
Warning
Using any on tuple LHS: any f (x, y, b)
RHS: f b
Warning
Using all on tuple LHS: all f (x, y, b)
RHS: f b
Warning
Using null on tuple LHS: null x
RHS: False
Warning
Using length on tuple LHS: length x
RHS: 1
Warning
Use empty LHS: Data.Map.fromList []
RHS: Data.Map.empty
Warning
Use empty LHS: Data.Map.Lazy.fromList []
RHS: Data.Map.Lazy.empty
Warning
Use empty LHS: Data.Map.Strict.fromList []
RHS: Data.Map.Strict.empty
Warning
Redundant ^. LHS: (a ^. b) ^. c
RHS: a ^. (b . c)
Warning
Use ^?! LHS: fromJust (a ^? b)
RHS: a ^?! b
Warning
Use ?~ LHS: a .~ Just b
RHS: a ?~ b
Warning
Use <&> LHS: (mapped %~ b) a
RHS: a <&> b
Warning
Use <&> LHS: ((mapped . b) %~ c) a
RHS: a <&> b %~ c
Warning
Use <$ LHS: (mapped .~ b) a
RHS: b <$ a
Warning
Use view LHS: ask <&> (^. a)
RHS: view a
Warning
Redundant <&> LHS: view a <&> (^. b)
RHS: view (a . b)
Warning
Use ix LHS: Control.Lens.at a . Control.Lens._Just
RHS: Control.Lens.ix a
Warning
Use True LHS: Control.Lens.has (Control.Lens.at a)
RHS: True
Error
Redundant at LHS: Control.Lens.has (a . Control.Lens.at b)
RHS: Control.Lens.has a
Warning
Use False LHS: Control.Lens.nullOf (Control.Lens.at a)
RHS: False
Error
Redundant at LHS: Control.Lens.nullOf (a . Control.Lens.at b)
RHS: Control.Lens.nullOf a
Warning
Use optional LHS: Data.Attoparsec.Text.option Nothing (Just <$> p)
RHS: optional p
Warning
Use optional LHS: Data.Attoparsec.ByteString.option Nothing (Just <$> p)
RHS: optional p
Warning
Use return LHS: Test.QuickCheck.choose (x, x)
RHS: return x
Warning
Use return LHS: Test.QuickCheck.chooseInt (x, x)
RHS: return x
Warning
Use return LHS: Test.QuickCheck.chooseInteger (x, x)
RHS: return x
Warning
Use return LHS: Test.QuickCheck.chooseBoundedIntegral (x, x)
RHS: return x
Warning
Use return LHS: Test.QuickCheck.chooseEnum (x, x)
RHS: return x
Warning
Use oneof LHS: Control.Monad.join (Test.QuickCheck.elements l)
RHS: Test.QuickCheck.oneof l
Warning
Use return LHS: Test.QuickCheck.elements [x]
RHS: return x
Warning
Use return LHS: Test.QuickCheck.growingElements [x]
RHS: return x
Warning
Evaluate LHS: Test.QuickCheck.oneof [x]
RHS: x
Warning
Evaluate LHS: Test.QuickCheck.frequency [(a, x)]
RHS: x
Warning