{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE ViewPatterns, PatternGuards, TypeFamilies #-}
module Hint.Pattern(patternHint) where
import Hint.Type(DeclHint,Idea,modComments,firstDeclComments,ideaTo,toSSA,toRefactSrcSpan,suggest,suggestRemove,warn)
import Data.Generics.Uniplate.DataOnly
import Data.Function
import Data.List.Extra
import Data.Tuple
import Data.Maybe
import Data.Either
import Refact.Types hiding (RType(Pattern, Match), SrcSpan)
import Refact.Types qualified as R (RType(Pattern, Match), SrcSpan)
import GHC.Hs
import GHC.Types.SrcLoc
import GHC.Types.Name.Reader
import GHC.Types.Name.Occurrence
import GHC.Data.Bag
import GHC.Types.Basic hiding (Pattern)
import GHC.Data.Strict qualified
import GHC.Util
import Language.Haskell.GhclibParserEx.GHC.Hs.Pat
import Language.Haskell.GhclibParserEx.GHC.Hs.Expr
import Language.Haskell.GhclibParserEx.GHC.Utils.Outputable
import Language.Haskell.GhclibParserEx.GHC.Types.Name.Reader
patternHint :: DeclHint
patternHint :: DeclHint
patternHint Scope
_scope ModuleEx
modu LHsDecl GhcPs
x =
((Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)
-> [Idea])
-> [(Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)]
-> [Idea]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (((String -> Pattern -> [Refactoring SrcSpan] -> Idea)
-> Pattern -> [Idea])
-> (String -> Pattern -> [Refactoring SrcSpan] -> Idea, Pattern)
-> [Idea]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (String -> Pattern -> [Refactoring SrcSpan] -> Idea)
-> Pattern -> [Idea]
hints ((String -> Pattern -> [Refactoring SrcSpan] -> Idea, Pattern)
-> [Idea])
-> ((Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)
-> (String -> Pattern -> [Refactoring SrcSpan] -> Idea, Pattern))
-> (Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)
-> [Idea]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)
-> (String -> Pattern -> [Refactoring SrcSpan] -> Idea, Pattern)
forall a b. (a, b) -> (b, a)
swap) (LHsDecl GhcPs
-> [(Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)]
asPattern LHsDecl GhcPs
x) [Idea] -> [Idea] -> [Idea]
forall a. [a] -> [a] -> [a]
++
(GenLocated SrcSpanAnnA (Pat GhcPs) -> [Idea])
-> [GenLocated SrcSpanAnnA (Pat GhcPs)] -> [Idea]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Bool -> Bool -> LPat GhcPs -> [Idea]
patHint Bool
strict Bool
False) [LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
p | PatBind XPatBind GhcPs GhcPs
_ LPat GhcPs
p GRHSs GhcPs (LHsExpr GhcPs)
_ <- GenLocated SrcSpanAnnA (HsDecl GhcPs) -> [HsBind GhcPs]
forall from to. Biplate from to => from -> [to]
universeBi LHsDecl GhcPs
GenLocated SrcSpanAnnA (HsDecl GhcPs)
x :: [HsBind GhcPs]] [Idea] -> [Idea] -> [Idea]
forall a. [a] -> [a] -> [a]
++
(GenLocated SrcSpanAnnA (Pat GhcPs) -> [Idea])
-> [GenLocated SrcSpanAnnA (Pat GhcPs)] -> [Idea]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Bool -> Bool -> LPat GhcPs -> [Idea]
patHint Bool
strict Bool
True) (GenLocated SrcSpanAnnA (HsDecl GhcPs)
-> [GenLocated SrcSpanAnnA (Pat GhcPs)]
forall from to. Biplate from to => from -> [to]
universeBi (GenLocated SrcSpanAnnA (HsDecl GhcPs)
-> [GenLocated SrcSpanAnnA (Pat GhcPs)])
-> GenLocated SrcSpanAnnA (HsDecl GhcPs)
-> [GenLocated SrcSpanAnnA (Pat GhcPs)]
forall a b. (a -> b) -> a -> b
$ (GenLocated SrcSpanAnnA (HsBind GhcPs)
-> GenLocated SrcSpanAnnA (HsBind GhcPs))
-> GenLocated SrcSpanAnnA (HsDecl GhcPs)
-> GenLocated SrcSpanAnnA (HsDecl GhcPs)
forall from to. Biplate from to => (to -> to) -> from -> from
transformBi LHsBind GhcPs -> LHsBind GhcPs
GenLocated SrcSpanAnnA (HsBind GhcPs)
-> GenLocated SrcSpanAnnA (HsBind GhcPs)
noPatBind LHsDecl GhcPs
GenLocated SrcSpanAnnA (HsDecl GhcPs)
x) [Idea] -> [Idea] -> [Idea]
forall a. [a] -> [a] -> [a]
++
(GenLocated SrcSpanAnnA (HsExpr GhcPs) -> [Idea])
-> [GenLocated SrcSpanAnnA (HsExpr GhcPs)] -> [Idea]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap LHsExpr GhcPs -> [Idea]
GenLocated SrcSpanAnnA (HsExpr GhcPs) -> [Idea]
expHint (GenLocated SrcSpanAnnA (HsDecl GhcPs)
-> [GenLocated SrcSpanAnnA (HsExpr GhcPs)]
forall from to. Biplate from to => from -> [to]
universeBi LHsDecl GhcPs
GenLocated SrcSpanAnnA (HsDecl GhcPs)
x)
where
exts :: [String]
exts = [String] -> [String]
forall a. Ord a => [a] -> [a]
nubOrd ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ ((LEpaComment, [String]) -> [String])
-> [(LEpaComment, [String])] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (LEpaComment, [String]) -> [String]
forall a b. (a, b) -> b
snd ([(LEpaComment, String)] -> [(LEpaComment, [String])]
languagePragmas (EpAnnComments -> [(LEpaComment, String)]
pragmas (ModuleEx -> EpAnnComments
modComments ModuleEx
modu) [(LEpaComment, String)]
-> [(LEpaComment, String)] -> [(LEpaComment, String)]
forall a. [a] -> [a] -> [a]
++ EpAnnComments -> [(LEpaComment, String)]
pragmas (ModuleEx -> EpAnnComments
firstDeclComments ModuleEx
modu)))
strict :: Bool
strict = String
"Strict" String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
exts
noPatBind :: LHsBind GhcPs -> LHsBind GhcPs
noPatBind :: LHsBind GhcPs -> LHsBind GhcPs
noPatBind (L SrcSpanAnnA
loc a :: HsBind GhcPs
a@PatBind{}) = SrcSpanAnnA
-> HsBind GhcPs -> GenLocated SrcSpanAnnA (HsBind GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
loc HsBind GhcPs
a{pat_lhs=noLocA (WildPat noExtField)}
noPatBind LHsBind GhcPs
x = LHsBind GhcPs
x
hints :: (String -> Pattern -> [Refactoring R.SrcSpan] -> Idea) -> Pattern -> [Idea]
hints :: (String -> Pattern -> [Refactoring SrcSpan] -> Idea)
-> Pattern -> [Idea]
hints String -> Pattern -> [Refactoring SrcSpan] -> Idea
gen (Pattern SrcSpan
l RType
rtype [LPat GhcPs]
pat (GRHSs XCGRHSs GhcPs (LHsExpr GhcPs)
_ [L SrcAnn NoEpAnns
_ (GRHS XCGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ [] GenLocated SrcSpanAnnA (HsExpr GhcPs)
bod)] HsLocalBinds GhcPs
bind))
| [GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
-> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [LGRHS GhcPs (LHsExpr GhcPs)]
[GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
guards Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
2 = [String -> Pattern -> [Refactoring SrcSpan] -> Idea
gen String
"Use guards" (SrcSpan
-> RType -> [LPat GhcPs] -> GRHSs GhcPs (LHsExpr GhcPs) -> Pattern
Pattern SrcSpan
l RType
rtype [LPat GhcPs]
pat (XCGRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> [LGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))]
-> HsLocalBinds GhcPs
-> GRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
forall p body.
XCGRHSs p body -> [LGRHS p body] -> HsLocalBinds p -> GRHSs p body
GRHSs XCGRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
EpAnnComments
emptyComments [LGRHS GhcPs (LHsExpr GhcPs)]
[LGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))]
guards HsLocalBinds GhcPs
bind)) [Refactoring SrcSpan
refactoring]]
where
rawGuards :: [(LHsExpr GhcPs, LHsExpr GhcPs)]
rawGuards :: [(LHsExpr GhcPs, LHsExpr GhcPs)]
rawGuards = LHsExpr GhcPs -> [(LHsExpr GhcPs, LHsExpr GhcPs)]
asGuards LHsExpr GhcPs
GenLocated SrcSpanAnnA (HsExpr GhcPs)
bod
mkGuard :: LHsExpr GhcPs -> (LHsExpr GhcPs -> GRHS GhcPs (LHsExpr GhcPs))
mkGuard :: LHsExpr GhcPs -> LHsExpr GhcPs -> GRHS GhcPs (LHsExpr GhcPs)
mkGuard LHsExpr GhcPs
a = XCGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> [GuardLStmt GhcPs]
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
forall p body.
XCGRHS p body -> [GuardLStmt p] -> body -> GRHS p body
GRHS XCGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
EpAnn GrhsAnn
forall ann. EpAnn ann
EpAnnNotUsed [StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
forall a an. a -> LocatedAn an a
noLocA (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))))
-> StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
forall a b. (a -> b) -> a -> b
$ XBodyStmt GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> SyntaxExpr GhcPs
-> SyntaxExpr GhcPs
-> StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
forall idL idR body.
XBodyStmt idL idR body
-> body -> SyntaxExpr idR -> SyntaxExpr idR -> StmtLR idL idR body
BodyStmt XBodyStmt GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
NoExtField
noExtField LHsExpr GhcPs
GenLocated SrcSpanAnnA (HsExpr GhcPs)
a SyntaxExpr GhcPs
forall (p :: Pass). IsPass p => SyntaxExpr (GhcPass p)
noSyntaxExpr SyntaxExpr GhcPs
forall (p :: Pass). IsPass p => SyntaxExpr (GhcPass p)
noSyntaxExpr]
guards :: [LGRHS GhcPs (LHsExpr GhcPs)]
guards :: [LGRHS GhcPs (LHsExpr GhcPs)]
guards = ((GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))))
-> [(GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))]
-> [GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
forall a b. (a -> b) -> [a] -> [b]
map (GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
forall a an. a -> LocatedAn an a
noLocA (GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))))
-> ((GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> (GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> (GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry LHsExpr GhcPs -> LHsExpr GhcPs -> GRHS GhcPs (LHsExpr GhcPs)
GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
mkGuard) [(LHsExpr GhcPs, LHsExpr GhcPs)]
[(GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))]
rawGuards
([GenLocated SrcSpanAnnA (HsExpr GhcPs)]
lhs, [GenLocated SrcSpanAnnA (HsExpr GhcPs)]
rhs) = [(GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))]
-> ([GenLocated SrcSpanAnnA (HsExpr GhcPs)],
[GenLocated SrcSpanAnnA (HsExpr GhcPs)])
forall a b. [(a, b)] -> ([a], [b])
unzip [(LHsExpr GhcPs, LHsExpr GhcPs)]
[(GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))]
rawGuards
mkTemplate :: String
-> [GenLocated (SrcSpanAnn' a) e]
-> [Either (GenLocated (SrcSpanAnn' a) e) (String, SrcSpan)]
mkTemplate String
c [GenLocated (SrcSpanAnn' a) e]
ps =
(GenLocated (SrcSpanAnn' a) e
-> Char -> Either (GenLocated (SrcSpanAnn' a) e) (String, SrcSpan))
-> [GenLocated (SrcSpanAnn' a) e]
-> String
-> [Either (GenLocated (SrcSpanAnn' a) e) (String, SrcSpan)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith GenLocated (SrcSpanAnn' a) e
-> Char -> Either (GenLocated (SrcSpanAnn' a) e) (String, SrcSpan)
checkLoc [GenLocated (SrcSpanAnn' a) e]
ps [Char
'1' .. Char
'9']
where
checkLoc :: GenLocated (SrcSpanAnn' a) e
-> Char -> Either (GenLocated (SrcSpanAnn' a) e) (String, SrcSpan)
checkLoc p :: GenLocated (SrcSpanAnn' a) e
p@(L SrcSpanAnn' a
l e
_) Char
v = if SrcSpanAnn' a -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnn' a
l SrcSpan -> SrcSpan -> Bool
forall a. Eq a => a -> a -> Bool
== SrcSpan
noSrcSpan then GenLocated (SrcSpanAnn' a) e
-> Either (GenLocated (SrcSpanAnn' a) e) (String, SrcSpan)
forall a b. a -> Either a b
Left GenLocated (SrcSpanAnn' a) e
p else (String, SrcSpan)
-> Either (GenLocated (SrcSpanAnn' a) e) (String, SrcSpan)
forall a b. b -> Either a b
Right (String
c String -> String -> String
forall a. [a] -> [a] -> [a]
++ [Char
v], GenLocated (SrcSpanAnn' a) e -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA GenLocated (SrcSpanAnn' a) e
p)
patSubts :: [Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, SrcSpan)]
patSubts =
case [LPat GhcPs]
pat of
[LPat GhcPs
p] -> [GenLocated SrcSpanAnnA (Pat GhcPs)
-> Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, SrcSpan)
forall a b. a -> Either a b
Left LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
p]
[LPat GhcPs]
ps -> String
-> [GenLocated SrcSpanAnnA (Pat GhcPs)]
-> [Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, SrcSpan)]
forall {a} {e}.
String
-> [GenLocated (SrcSpanAnn' a) e]
-> [Either (GenLocated (SrcSpanAnn' a) e) (String, SrcSpan)]
mkTemplate String
"p100" [LPat GhcPs]
[GenLocated SrcSpanAnnA (Pat GhcPs)]
ps
guardSubts :: [Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
guardSubts = String
-> [GenLocated SrcSpanAnnA (HsExpr GhcPs)]
-> [Either
(GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
forall {a} {e}.
String
-> [GenLocated (SrcSpanAnn' a) e]
-> [Either (GenLocated (SrcSpanAnn' a) e) (String, SrcSpan)]
mkTemplate String
"g100" [GenLocated SrcSpanAnnA (HsExpr GhcPs)]
lhs
exprSubts :: [Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
exprSubts = String
-> [GenLocated SrcSpanAnnA (HsExpr GhcPs)]
-> [Either
(GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
forall {a} {e}.
String
-> [GenLocated (SrcSpanAnn' a) e]
-> [Either (GenLocated (SrcSpanAnn' a) e) (String, SrcSpan)]
mkTemplate String
"e100" [GenLocated SrcSpanAnnA (HsExpr GhcPs)]
rhs
templateGuards :: [LocatedAn an (GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
templateGuards = (GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> LocatedAn
an (GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))))
-> [GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))]
-> [LocatedAn
an (GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
forall a b. (a -> b) -> [a] -> [b]
map GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> LocatedAn
an (GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
forall a an. a -> LocatedAn an a
noLocA ((Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)
-> Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)
-> GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> [Either
(GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
-> [Either
(GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
-> [GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (LHsExpr GhcPs -> LHsExpr GhcPs -> GRHS GhcPs (LHsExpr GhcPs)
GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
mkGuard (GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> (Either
(GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)
-> GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)
-> Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)
-> GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
forall {b}.
Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, b)
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
toString) [Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
guardSubts [Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
exprSubts)
toString :: Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, b)
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
toString (Left GenLocated SrcSpanAnnA (HsExpr GhcPs)
e) = GenLocated SrcSpanAnnA (HsExpr GhcPs)
e
toString (Right (String
v, b
_)) = String -> LHsExpr GhcPs
strToVar String
v
toString' :: Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, b)
-> GenLocated SrcSpanAnnA (Pat GhcPs)
toString' (Left GenLocated SrcSpanAnnA (Pat GhcPs)
e) = GenLocated SrcSpanAnnA (Pat GhcPs)
e
toString' (Right (String
v, b
_)) = String -> LPat GhcPs
strToPat String
v
template :: String
template = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"" (Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ Idea -> Maybe String
ideaTo (String -> Pattern -> [Refactoring SrcSpan] -> Idea
gen String
"" (SrcSpan
-> RType -> [LPat GhcPs] -> GRHSs GhcPs (LHsExpr GhcPs) -> Pattern
Pattern SrcSpan
l RType
rtype ((Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, SrcSpan)
-> GenLocated SrcSpanAnnA (Pat GhcPs))
-> [Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, SrcSpan)]
-> [GenLocated SrcSpanAnnA (Pat GhcPs)]
forall a b. (a -> b) -> [a] -> [b]
map Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, SrcSpan)
-> GenLocated SrcSpanAnnA (Pat GhcPs)
forall {b}.
Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, b)
-> GenLocated SrcSpanAnnA (Pat GhcPs)
toString' [Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, SrcSpan)]
patSubts) (XCGRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> [LGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))]
-> HsLocalBinds GhcPs
-> GRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
forall p body.
XCGRHSs p body -> [LGRHS p body] -> HsLocalBinds p -> GRHSs p body
GRHSs XCGRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
EpAnnComments
emptyComments [LGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))]
[GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
forall {an}.
[LocatedAn an (GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
templateGuards HsLocalBinds GhcPs
bind)) [])
f :: [Either a (String, R.SrcSpan)] -> [(String, R.SrcSpan)]
f :: forall a. [Either a (String, SrcSpan)] -> [(String, SrcSpan)]
f = [Either a (String, SrcSpan)] -> [(String, SrcSpan)]
forall a b. [Either a b] -> [b]
rights
refactoring :: Refactoring SrcSpan
refactoring = RType
-> SrcSpan -> [(String, SrcSpan)] -> String -> Refactoring SrcSpan
forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
rtype (SrcSpan -> SrcSpan
toRefactSrcSpan SrcSpan
l) ([Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, SrcSpan)]
-> [(String, SrcSpan)]
forall a. [Either a (String, SrcSpan)] -> [(String, SrcSpan)]
f [Either (GenLocated SrcSpanAnnA (Pat GhcPs)) (String, SrcSpan)]
patSubts [(String, SrcSpan)] -> [(String, SrcSpan)] -> [(String, SrcSpan)]
forall a. [a] -> [a] -> [a]
++ [Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
-> [(String, SrcSpan)]
forall a. [Either a (String, SrcSpan)] -> [(String, SrcSpan)]
f [Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
guardSubts [(String, SrcSpan)] -> [(String, SrcSpan)] -> [(String, SrcSpan)]
forall a. [a] -> [a] -> [a]
++ [Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
-> [(String, SrcSpan)]
forall a. [Either a (String, SrcSpan)] -> [(String, SrcSpan)]
f [Either (GenLocated SrcSpanAnnA (HsExpr GhcPs)) (String, SrcSpan)]
exprSubts) String
template
hints String -> Pattern -> [Refactoring SrcSpan] -> Idea
gen (Pattern SrcSpan
l RType
t [LPat GhcPs]
pats o :: GRHSs GhcPs (LHsExpr GhcPs)
o@(GRHSs XCGRHSs GhcPs (LHsExpr GhcPs)
_ [L SrcAnn NoEpAnns
_ (GRHS XCGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ [GuardLStmt GhcPs
test] GenLocated SrcSpanAnnA (HsExpr GhcPs)
bod)] HsLocalBinds GhcPs
bind))
| GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> String
forall a. Outputable a => a -> String
unsafePrettyPrint GuardLStmt GhcPs
GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
test String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"otherwise", String
"True"]
= [String -> Pattern -> [Refactoring SrcSpan] -> Idea
gen String
"Redundant guard" (SrcSpan
-> RType -> [LPat GhcPs] -> GRHSs GhcPs (LHsExpr GhcPs) -> Pattern
Pattern SrcSpan
l RType
t [LPat GhcPs]
pats GRHSs GhcPs (LHsExpr GhcPs)
o{grhssGRHSs=[noLocA (GRHS EpAnnNotUsed [] bod)]}) [RType -> SrcSpan -> Refactoring SrcSpan
forall a. RType -> a -> Refactoring a
Delete RType
Stmt (GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA GuardLStmt GhcPs
GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
test)]]
hints String -> Pattern -> [Refactoring SrcSpan] -> Idea
_ (Pattern SrcSpan
l RType
t [LPat GhcPs]
pats bod :: GRHSs GhcPs (LHsExpr GhcPs)
bod@(GRHSs XCGRHSs GhcPs (LHsExpr GhcPs)
_ [LGRHS GhcPs (LHsExpr GhcPs)]
_ HsLocalBinds GhcPs
binds)) | HsLocalBinds GhcPs -> Bool
f HsLocalBinds GhcPs
binds
= [String -> SrcSpan -> String -> [Refactoring SrcSpan] -> Idea
suggestRemove String
"Redundant where" SrcSpan
whereSpan String
"where" [ ]]
where
f :: HsLocalBinds GhcPs -> Bool
f :: HsLocalBinds GhcPs -> Bool
f (HsValBinds XHsValBinds GhcPs GhcPs
_ (ValBinds XValBinds GhcPs GhcPs
_ LHsBindsLR GhcPs GhcPs
bag [LSig GhcPs]
_)) = Bag (GenLocated SrcSpanAnnA (HsBind GhcPs)) -> Bool
forall a. Bag a -> Bool
isEmptyBag LHsBindsLR GhcPs GhcPs
Bag (GenLocated SrcSpanAnnA (HsBind GhcPs))
bag
f (HsIPBinds XHsIPBinds GhcPs GhcPs
_ (IPBinds XIPBinds GhcPs
_ [LIPBind GhcPs]
l)) = [GenLocated SrcSpanAnnA (IPBind GhcPs)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [LIPBind GhcPs]
[GenLocated SrcSpanAnnA (IPBind GhcPs)]
l
f HsLocalBinds GhcPs
_ = Bool
False
whereSpan :: SrcSpan
whereSpan = case SrcSpan
l of
UnhelpfulSpan UnhelpfulSpanReason
s -> UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan UnhelpfulSpanReason
s
RealSrcSpan RealSrcSpan
s Maybe BufSpan
_ ->
let end :: RealSrcLoc
end = RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
s
start :: RealSrcLoc
start = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
s) (RealSrcLoc -> Int
srcLocLine RealSrcLoc
end) (RealSrcLoc -> Int
srcLocCol RealSrcLoc
end Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
5)
in RealSrcSpan -> Maybe BufSpan -> SrcSpan
RealSrcSpan (RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan RealSrcLoc
start RealSrcLoc
end) Maybe BufSpan
forall a. Maybe a
GHC.Data.Strict.Nothing
hints String -> Pattern -> [Refactoring SrcSpan] -> Idea
gen (Pattern SrcSpan
l RType
t [LPat GhcPs]
pats o :: GRHSs GhcPs (LHsExpr GhcPs)
o@(GRHSs XCGRHSs GhcPs (LHsExpr GhcPs)
_ ([LGRHS GhcPs (LHsExpr GhcPs)]
-> Maybe
([GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))],
GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))))
[GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
-> Maybe
([GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))],
GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))))
forall a. [a] -> Maybe ([a], a)
unsnoc -> Just ([GenLocated
(SrcAnn NoEpAnns)
(GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
gs, L SrcAnn NoEpAnns
_ (GRHS XCGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ [GuardLStmt GhcPs
test] GenLocated SrcSpanAnnA (HsExpr GhcPs)
bod))) HsLocalBinds GhcPs
binds))
| GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> String
forall a. Outputable a => a -> String
unsafePrettyPrint GuardLStmt GhcPs
GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
test String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"True"
= let otherwise_ :: LocatedAn
an (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
otherwise_ = StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> LocatedAn
an (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
forall a an. a -> LocatedAn an a
noLocA (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> LocatedAn
an (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))))
-> StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> LocatedAn
an (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
forall a b. (a -> b) -> a -> b
$ XBodyStmt GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> SyntaxExpr GhcPs
-> SyntaxExpr GhcPs
-> StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
forall idL idR body.
XBodyStmt idL idR body
-> body -> SyntaxExpr idR -> SyntaxExpr idR -> StmtLR idL idR body
BodyStmt XBodyStmt GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
NoExtField
noExtField (String -> LHsExpr GhcPs
strToVar String
"otherwise") SyntaxExpr GhcPs
forall (p :: Pass). IsPass p => SyntaxExpr (GhcPass p)
noSyntaxExpr SyntaxExpr GhcPs
forall (p :: Pass). IsPass p => SyntaxExpr (GhcPass p)
noSyntaxExpr in
[String -> Pattern -> [Refactoring SrcSpan] -> Idea
gen String
"Use otherwise" (SrcSpan
-> RType -> [LPat GhcPs] -> GRHSs GhcPs (LHsExpr GhcPs) -> Pattern
Pattern SrcSpan
l RType
t [LPat GhcPs]
pats GRHSs GhcPs (LHsExpr GhcPs)
o{grhssGRHSs = gs ++ [noLocA (GRHS EpAnnNotUsed [otherwise_] bod)]}) [RType
-> SrcSpan -> [(String, SrcSpan)] -> String -> Refactoring SrcSpan
forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
Expr (GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA GuardLStmt GhcPs
GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
test) [] String
"otherwise"]]
hints String -> Pattern -> [Refactoring SrcSpan] -> Idea
_ Pattern
_ = []
asGuards :: LHsExpr GhcPs -> [(LHsExpr GhcPs, LHsExpr GhcPs)]
asGuards :: LHsExpr GhcPs -> [(LHsExpr GhcPs, LHsExpr GhcPs)]
asGuards (L SrcSpanAnnA
_ (HsPar XPar GhcPs
_ LHsToken "(" GhcPs
_ LHsExpr GhcPs
x LHsToken ")" GhcPs
_)) = LHsExpr GhcPs -> [(LHsExpr GhcPs, LHsExpr GhcPs)]
asGuards LHsExpr GhcPs
x
asGuards (L SrcSpanAnnA
_ (HsIf XIf GhcPs
_ LHsExpr GhcPs
a LHsExpr GhcPs
b LHsExpr GhcPs
c)) = (LHsExpr GhcPs
GenLocated SrcSpanAnnA (HsExpr GhcPs)
a, LHsExpr GhcPs
GenLocated SrcSpanAnnA (HsExpr GhcPs)
b) (GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> [(GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))]
-> [(GenLocated SrcSpanAnnA (HsExpr GhcPs),
GenLocated SrcSpanAnnA (HsExpr GhcPs))]
forall a. a -> [a] -> [a]
: LHsExpr GhcPs -> [(LHsExpr GhcPs, LHsExpr GhcPs)]
asGuards LHsExpr GhcPs
c
asGuards LHsExpr GhcPs
x = [(String -> LHsExpr GhcPs
strToVar String
"otherwise", LHsExpr GhcPs
x)]
data Pattern = Pattern SrcSpan R.RType [LPat GhcPs] (GRHSs GhcPs (LHsExpr GhcPs))
asPattern :: LHsDecl GhcPs -> [(Pattern, String -> Pattern -> [Refactoring R.SrcSpan] -> Idea)]
asPattern :: LHsDecl GhcPs
-> [(Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)]
asPattern (L SrcSpanAnnA
loc HsDecl GhcPs
x) = (HsBind GhcPs
-> [(Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)])
-> [HsBind GhcPs]
-> [(Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap HsBind GhcPs
-> [(Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)]
decl (HsDecl GhcPs -> [HsBind GhcPs]
forall from to. Biplate from to => from -> [to]
universeBi HsDecl GhcPs
x)
where
decl :: HsBind GhcPs -> [(Pattern, String -> Pattern -> [Refactoring R.SrcSpan] -> Idea)]
decl :: HsBind GhcPs
-> [(Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)]
decl o :: HsBind GhcPs
o@(PatBind XPatBind GhcPs GhcPs
_ LPat GhcPs
pat GRHSs GhcPs (LHsExpr GhcPs)
rhs) = [(SrcSpan
-> RType -> [LPat GhcPs] -> GRHSs GhcPs (LHsExpr GhcPs) -> Pattern
Pattern (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
loc) RType
Bind [LPat GhcPs
pat] GRHSs GhcPs (LHsExpr GhcPs)
rhs, \String
msg (Pattern SrcSpan
_ RType
_ [LPat GhcPs
pat] GRHSs GhcPs (LHsExpr GhcPs)
rhs) [Refactoring SrcSpan]
rs -> String
-> Located (HsBind GhcPs)
-> Located (HsBind GhcPs)
-> [Refactoring SrcSpan]
-> Idea
forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
msg (HsBind GhcPs -> Located (HsBind GhcPs)
forall e. e -> Located e
noLoc HsBind GhcPs
o :: Located (HsBind GhcPs)) (HsBind GhcPs -> Located (HsBind GhcPs)
forall e. e -> Located e
noLoc (XPatBind GhcPs GhcPs
-> LPat GhcPs -> GRHSs GhcPs (LHsExpr GhcPs) -> HsBind GhcPs
forall idL idR.
XPatBind idL idR
-> LPat idL -> GRHSs idR (LHsExpr idR) -> HsBindLR idL idR
PatBind XPatBind GhcPs GhcPs
EpAnn [AddEpAnn]
forall ann. EpAnn ann
EpAnnNotUsed LPat GhcPs
pat GRHSs GhcPs (LHsExpr GhcPs)
rhs) :: Located (HsBind GhcPs)) [Refactoring SrcSpan]
rs)]
decl (FunBind XFunBind GhcPs GhcPs
_ LIdP GhcPs
_ (MG XMG GhcPs (LHsExpr GhcPs)
_ (L SrcSpanAnnL
_ [GenLocated
SrcSpanAnnA (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
xs))) = (GenLocated
SrcSpanAnnA (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> (Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea))
-> [GenLocated
SrcSpanAnnA (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
-> [(Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)]
forall a b. (a -> b) -> [a] -> [b]
map LMatch GhcPs (LHsExpr GhcPs)
-> (Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)
GenLocated
SrcSpanAnnA (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> (Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)
match [GenLocated
SrcSpanAnnA (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
xs
decl HsBind GhcPs
_ = []
match :: LMatch GhcPs (LHsExpr GhcPs) -> (Pattern, String -> Pattern -> [Refactoring R.SrcSpan] -> Idea)
match :: LMatch GhcPs (LHsExpr GhcPs)
-> (Pattern, String -> Pattern -> [Refactoring SrcSpan] -> Idea)
match o :: LMatch GhcPs (LHsExpr GhcPs)
o@(L SrcSpanAnnA
loc (Match XCMatch GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ HsMatchContext GhcPs
ctx [LPat GhcPs]
pats GRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
grhss)) = (SrcSpan
-> RType -> [LPat GhcPs] -> GRHSs GhcPs (LHsExpr GhcPs) -> Pattern
Pattern (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
loc) RType
R.Match [LPat GhcPs]
pats GRHSs GhcPs (LHsExpr GhcPs)
GRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
grhss, \String
msg (Pattern SrcSpan
_ RType
_ [LPat GhcPs]
pats GRHSs GhcPs (LHsExpr GhcPs)
grhss) [Refactoring SrcSpan]
rs -> String
-> Located (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> Located (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> [Refactoring SrcSpan]
-> Idea
forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
msg (GenLocated
SrcSpanAnnA (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> Located (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
forall a e. LocatedAn a e -> Located e
reLoc LMatch GhcPs (LHsExpr GhcPs)
GenLocated
SrcSpanAnnA (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
o) (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> Located (Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
forall e. e -> Located e
noLoc (XCMatch GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> HsMatchContext GhcPs
-> [LPat GhcPs]
-> GRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
-> Match GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
forall p body.
XCMatch p body
-> HsMatchContext p -> [LPat p] -> GRHSs p body -> Match p body
Match XCMatch GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
EpAnn [AddEpAnn]
forall ann. EpAnn ann
EpAnnNotUsed HsMatchContext GhcPs
ctx [LPat GhcPs]
pats GRHSs GhcPs (LHsExpr GhcPs)
GRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
grhss) :: Located (Match GhcPs (LHsExpr GhcPs))) [Refactoring SrcSpan]
rs)
patHint :: Bool -> Bool -> LPat GhcPs -> [Idea]
patHint :: Bool -> Bool -> LPat GhcPs -> [Idea]
patHint Bool
_ Bool
_ o :: LPat GhcPs
o@(L SrcSpanAnnA
_ (ConPat XConPat GhcPs
_ XRec GhcPs (ConLikeP GhcPs)
name (PrefixCon [HsConPatTyArg (NoGhcTc GhcPs)]
_ [LPat GhcPs]
args)))
| [GenLocated SrcSpanAnnA (Pat GhcPs)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [LPat GhcPs]
[GenLocated SrcSpanAnnA (Pat GhcPs)]
args Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
3 Bool -> Bool -> Bool
&& (GenLocated SrcSpanAnnA (Pat GhcPs) -> Bool)
-> [GenLocated SrcSpanAnnA (Pat GhcPs)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all LPat GhcPs -> Bool
GenLocated SrcSpanAnnA (Pat GhcPs) -> Bool
isPWildcard [LPat GhcPs]
[GenLocated SrcSpanAnnA (Pat GhcPs)]
args =
let rec_fields :: HsRecFields GhcPs (LPat GhcPs)
rec_fields = [LHsRecField GhcPs (GenLocated SrcSpanAnnA (Pat GhcPs))]
-> Maybe (XRec GhcPs RecFieldsDotDot)
-> HsRecFields GhcPs (GenLocated SrcSpanAnnA (Pat GhcPs))
forall p arg.
[LHsRecField p arg]
-> Maybe (XRec p RecFieldsDotDot) -> HsRecFields p arg
HsRecFields [] Maybe (XRec GhcPs RecFieldsDotDot)
Maybe (GenLocated SrcSpan RecFieldsDotDot)
forall a. Maybe a
Nothing :: HsRecFields GhcPs (LPat GhcPs)
new :: LPat GhcPs
new = Pat GhcPs -> GenLocated SrcSpanAnnA (Pat GhcPs)
forall a an. a -> LocatedAn an a
noLocA (Pat GhcPs -> GenLocated SrcSpanAnnA (Pat GhcPs))
-> Pat GhcPs -> GenLocated SrcSpanAnnA (Pat GhcPs)
forall a b. (a -> b) -> a -> b
$ XConPat GhcPs
-> XRec GhcPs (ConLikeP GhcPs)
-> HsConDetails
(HsConPatTyArg (NoGhcTc GhcPs))
(LPat GhcPs)
(HsRecFields GhcPs (LPat GhcPs))
-> Pat GhcPs
forall p.
XConPat p -> XRec p (ConLikeP p) -> HsConPatDetails p -> Pat p
ConPat XConPat GhcPs
EpAnn [AddEpAnn]
forall ann. EpAnn ann
EpAnnNotUsed XRec GhcPs (ConLikeP GhcPs)
name (HsRecFields GhcPs (GenLocated SrcSpanAnnA (Pat GhcPs))
-> HsConDetails
(HsConPatTyArg GhcPs)
(GenLocated SrcSpanAnnA (Pat GhcPs))
(HsRecFields GhcPs (GenLocated SrcSpanAnnA (Pat GhcPs)))
forall tyarg arg rec. rec -> HsConDetails tyarg arg rec
RecCon HsRecFields GhcPs (GenLocated SrcSpanAnnA (Pat GhcPs))
rec_fields) :: LPat GhcPs
in
[String
-> Located (Pat GhcPs)
-> Located (Pat GhcPs)
-> [Refactoring SrcSpan]
-> Idea
forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
"Use record patterns" (GenLocated SrcSpanAnnA (Pat GhcPs) -> Located (Pat GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
o) (GenLocated SrcSpanAnnA (Pat GhcPs) -> Located (Pat GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
new) [RType
-> SrcSpan -> [(String, SrcSpan)] -> String -> Refactoring SrcSpan
forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
R.Pattern (GenLocated SrcSpanAnnA (Pat GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
o) [] (GenLocated SrcSpanAnnA (Pat GhcPs) -> String
forall a. Outputable a => a -> String
unsafePrettyPrint LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
new)]]
patHint Bool
_ Bool
_ o :: LPat GhcPs
o@(L SrcSpanAnnA
_ (VarPat XVarPat GhcPs
_ (L SrcSpanAnnN
_ RdrName
name)))
| OccName -> String
occNameString (RdrName -> OccName
rdrNameOcc RdrName
name) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"otherwise" =
[String
-> Located (Pat GhcPs)
-> Located (Pat GhcPs)
-> [Refactoring SrcSpan]
-> Idea
forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
warn String
"Used otherwise as a pattern" (GenLocated SrcSpanAnnA (Pat GhcPs) -> Located (Pat GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
o) (Pat GhcPs -> Located (Pat GhcPs)
forall e. e -> Located e
noLoc (XWildPat GhcPs -> Pat GhcPs
forall p. XWildPat p -> Pat p
WildPat XWildPat GhcPs
NoExtField
noExtField) :: Located (Pat GhcPs)) []]
patHint Bool
lang Bool
strict o :: LPat GhcPs
o@(L SrcSpanAnnA
_ (BangPat XBangPat GhcPs
_ pat :: LPat GhcPs
pat@(L SrcSpanAnnA
_ Pat GhcPs
x)))
| Bool
strict, Pat GhcPs -> Bool
f Pat GhcPs
x = [String
-> Located (Pat GhcPs)
-> Located (Pat GhcPs)
-> [Refactoring SrcSpan]
-> Idea
forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
warn String
"Redundant bang pattern" (GenLocated SrcSpanAnnA (Pat GhcPs) -> Located (Pat GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
o) (Pat GhcPs -> Located (Pat GhcPs)
forall e. e -> Located e
noLoc Pat GhcPs
x :: Located (Pat GhcPs)) [Refactoring SrcSpan
r]]
where
f :: Pat GhcPs -> Bool
f :: Pat GhcPs -> Bool
f (ParPat XParPat GhcPs
_ LHsToken "(" GhcPs
_ (L SrcSpanAnnA
_ Pat GhcPs
x) LHsToken ")" GhcPs
_) = Pat GhcPs -> Bool
f Pat GhcPs
x
f (AsPat XAsPat GhcPs
_ LIdP GhcPs
_ LHsToken "@" GhcPs
_ (L SrcSpanAnnA
_ Pat GhcPs
x)) = Pat GhcPs -> Bool
f Pat GhcPs
x
f LitPat {} = Bool
True
f NPat {} = Bool
True
f ConPat {} = Bool
True
f TuplePat {} = Bool
True
f ListPat {} = Bool
True
f (SigPat XSigPat GhcPs
_ (L SrcSpanAnnA
_ Pat GhcPs
p) HsPatSigType (NoGhcTc GhcPs)
_) = Pat GhcPs -> Bool
f Pat GhcPs
p
f Pat GhcPs
_ = Bool
False
r :: Refactoring SrcSpan
r = RType
-> SrcSpan -> [(String, SrcSpan)] -> String -> Refactoring SrcSpan
forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
R.Pattern (GenLocated SrcSpanAnnA (Pat GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
o) [(String
"x", GenLocated SrcSpanAnnA (Pat GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
pat)] String
"x"
patHint Bool
False Bool
_ o :: LPat GhcPs
o@(L SrcSpanAnnA
_ (LazyPat XLazyPat GhcPs
_ pat :: LPat GhcPs
pat@(L SrcSpanAnnA
_ Pat GhcPs
x)))
| Pat GhcPs -> Bool
f Pat GhcPs
x = [String
-> Located (Pat GhcPs)
-> Located (Pat GhcPs)
-> [Refactoring SrcSpan]
-> Idea
forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
warn String
"Redundant irrefutable pattern" (GenLocated SrcSpanAnnA (Pat GhcPs) -> Located (Pat GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
o) (Pat GhcPs -> Located (Pat GhcPs)
forall e. e -> Located e
noLoc Pat GhcPs
x :: Located (Pat GhcPs)) [Refactoring SrcSpan
r]]
where
f :: Pat GhcPs -> Bool
f :: Pat GhcPs -> Bool
f (ParPat XParPat GhcPs
_ LHsToken "(" GhcPs
_ (L SrcSpanAnnA
_ Pat GhcPs
x) LHsToken ")" GhcPs
_) = Pat GhcPs -> Bool
f Pat GhcPs
x
f (AsPat XAsPat GhcPs
_ LIdP GhcPs
_ LHsToken "@" GhcPs
_ (L SrcSpanAnnA
_ Pat GhcPs
x)) = Pat GhcPs -> Bool
f Pat GhcPs
x
f WildPat{} = Bool
True
f VarPat{} = Bool
True
f Pat GhcPs
_ = Bool
False
r :: Refactoring SrcSpan
r = RType
-> SrcSpan -> [(String, SrcSpan)] -> String -> Refactoring SrcSpan
forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
R.Pattern (GenLocated SrcSpanAnnA (Pat GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
o) [(String
"x", GenLocated SrcSpanAnnA (Pat GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
pat)] String
"x"
patHint Bool
_ Bool
_ o :: LPat GhcPs
o@(L SrcSpanAnnA
_ (AsPat XAsPat GhcPs
_ LIdP GhcPs
v LHsToken "@" GhcPs
_ (L SrcSpanAnnA
_ (WildPat XWildPat GhcPs
_)))) =
[String
-> Located (Pat GhcPs)
-> Located RdrName
-> [Refactoring SrcSpan]
-> Idea
forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
warn String
"Redundant as-pattern" (GenLocated SrcSpanAnnA (Pat GhcPs) -> Located (Pat GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
o) (GenLocated SrcSpanAnnN RdrName -> Located RdrName
forall a e. LocatedAn a e -> Located e
reLoc LIdP GhcPs
GenLocated SrcSpanAnnN RdrName
v) [RType
-> SrcSpan -> [(String, SrcSpan)] -> String -> Refactoring SrcSpan
forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
R.Pattern (GenLocated SrcSpanAnnA (Pat GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LPat GhcPs
GenLocated SrcSpanAnnA (Pat GhcPs)
o) [] (GenLocated SrcSpanAnnN RdrName -> String
rdrNameStr LIdP GhcPs
GenLocated SrcSpanAnnN RdrName
v)]]
patHint Bool
_ Bool
_ LPat GhcPs
_ = []
expHint :: LHsExpr GhcPs -> [Idea]
expHint :: LHsExpr GhcPs -> [Idea]
expHint o :: LHsExpr GhcPs
o@(L SrcSpanAnnA
_ (HsCase XCase GhcPs
_ LHsExpr GhcPs
_ (MG XMG GhcPs (LHsExpr GhcPs)
Origin
FromSource (L SrcSpanAnnL
_ [L SrcSpanAnnA
_ (Match XCMatch GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ HsMatchContext GhcPs
CaseAlt [L SrcSpanAnnA
_ (WildPat XWildPat GhcPs
_)] (GRHSs XCGRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ [L SrcAnn NoEpAnns
_ (GRHS XCGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ [] GenLocated SrcSpanAnnA (HsExpr GhcPs)
e)] (EmptyLocalBinds XEmptyLocalBinds GhcPs GhcPs
_))) ])))) =
[String
-> Located (HsExpr GhcPs)
-> Located (HsExpr GhcPs)
-> [Refactoring SrcSpan]
-> Idea
forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
"Redundant case" (GenLocated SrcSpanAnnA (HsExpr GhcPs) -> Located (HsExpr GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc LHsExpr GhcPs
GenLocated SrcSpanAnnA (HsExpr GhcPs)
o) (GenLocated SrcSpanAnnA (HsExpr GhcPs) -> Located (HsExpr GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc GenLocated SrcSpanAnnA (HsExpr GhcPs)
e) [Refactoring SrcSpan
r]]
where
r :: Refactoring SrcSpan
r = RType
-> SrcSpan -> [(String, SrcSpan)] -> String -> Refactoring SrcSpan
forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
Expr (GenLocated SrcSpanAnnA (HsExpr GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LHsExpr GhcPs
GenLocated SrcSpanAnnA (HsExpr GhcPs)
o) [(String
"x", GenLocated SrcSpanAnnA (HsExpr GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA GenLocated SrcSpanAnnA (HsExpr GhcPs)
e)] String
"x"
expHint o :: LHsExpr GhcPs
o@(L SrcSpanAnnA
_ (HsCase XCase GhcPs
_ (L SrcSpanAnnA
_ (HsVar XVar GhcPs
_ (L SrcSpanAnnN
_ RdrName
x))) (MG XMG GhcPs (LHsExpr GhcPs)
Origin
FromSource (L SrcSpanAnnL
_ [L SrcSpanAnnA
_ (Match XCMatch GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ HsMatchContext GhcPs
CaseAlt [L SrcSpanAnnA
_ (VarPat XVarPat GhcPs
_ (L SrcSpanAnnN
_ RdrName
y))] (GRHSs XCGRHSs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ [L SrcAnn NoEpAnns
_ (GRHS XCGRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ [] GenLocated SrcSpanAnnA (HsExpr GhcPs)
e)] (EmptyLocalBinds XEmptyLocalBinds GhcPs GhcPs
_))) ]))))
| RdrName -> String
occNameStr RdrName
x String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== RdrName -> String
occNameStr RdrName
y =
[String
-> Located (HsExpr GhcPs)
-> Located (HsExpr GhcPs)
-> [Refactoring SrcSpan]
-> Idea
forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
"Redundant case" (GenLocated SrcSpanAnnA (HsExpr GhcPs) -> Located (HsExpr GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc LHsExpr GhcPs
GenLocated SrcSpanAnnA (HsExpr GhcPs)
o) (GenLocated SrcSpanAnnA (HsExpr GhcPs) -> Located (HsExpr GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc GenLocated SrcSpanAnnA (HsExpr GhcPs)
e) [Refactoring SrcSpan
r]]
where
r :: Refactoring SrcSpan
r = RType
-> SrcSpan -> [(String, SrcSpan)] -> String -> Refactoring SrcSpan
forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
Expr (GenLocated SrcSpanAnnA (HsExpr GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LHsExpr GhcPs
GenLocated SrcSpanAnnA (HsExpr GhcPs)
o) [(String
"x", GenLocated SrcSpanAnnA (HsExpr GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA GenLocated SrcSpanAnnA (HsExpr GhcPs)
e)] String
"x"
expHint LHsExpr GhcPs
_ = []