{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE ViewPatterns, PatternGuards, FlexibleContexts #-}
module Hint.List(listHint) where
import Control.Applicative
import Data.Generics.Uniplate.DataOnly
import Data.List.Extra
import Data.Maybe
import Prelude
import Hint.Type(DeclHint,Idea,suggest,ignore,substVars,toRefactSrcSpan,toSSA,modComments,firstDeclComments)
import Refact.Types hiding (SrcSpan)
import Refact.Types qualified as R
import GHC.Hs
import GHC.Types.SrcLoc
import GHC.Types.SourceText
import GHC.Types.Name.Reader
import GHC.Data.FastString
import GHC.Builtin.Types
import GHC.Util
import Language.Haskell.GhclibParserEx.GHC.Hs.Pat
import Language.Haskell.GhclibParserEx.GHC.Hs.Expr
import Language.Haskell.GhclibParserEx.GHC.Hs.Type
import Language.Haskell.GhclibParserEx.GHC.Hs.ExtendInstances
import Language.Haskell.GhclibParserEx.GHC.Utils.Outputable
import Language.Haskell.GhclibParserEx.GHC.Types.Name.Reader
listHint :: DeclHint
listHint :: DeclHint
listHint Scope
_ ModuleEx
modu = Bool -> LHsDecl GhcPs -> [Idea]
listDecl Bool
overloadedListsOn
where
exts :: [String]
exts = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a b. (a, b) -> b
snd ([(LEpaComment, String)] -> [(LEpaComment, [String])]
languagePragmas (EpAnnComments -> [(LEpaComment, String)]
pragmas (ModuleEx -> EpAnnComments
modComments ModuleEx
modu) forall a. [a] -> [a] -> [a]
++ EpAnnComments -> [(LEpaComment, String)]
pragmas (ModuleEx -> EpAnnComments
firstDeclComments ModuleEx
modu)))
overloadedListsOn :: Bool
overloadedListsOn = String
"OverloadedLists" forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
exts
listDecl :: Bool -> LHsDecl GhcPs -> [Idea]
listDecl :: Bool -> LHsDecl GhcPs -> [Idea]
listDecl Bool
overloadedListsOn LHsDecl GhcPs
x =
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Bool -> Bool -> LHsExpr GhcPs -> [Idea]
listExp Bool
overloadedListsOn Bool
False) (forall from to. Biplate from to => from -> [to]
childrenBi LHsDecl GhcPs
x) forall a. [a] -> [a] -> [a]
++
LHsDecl GhcPs -> [Idea]
stringType LHsDecl GhcPs
x forall a. [a] -> [a] -> [a]
++
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap XRec GhcPs (Pat GhcPs) -> [Idea]
listPat (forall from to. Biplate from to => from -> [to]
childrenBi LHsDecl GhcPs
x) forall a. [a] -> [a] -> [a]
++
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap LHsExpr GhcPs -> [Idea]
listComp (forall from to. Biplate from to => from -> [to]
universeBi LHsDecl GhcPs
x)
listComp :: LHsExpr GhcPs -> [Idea]
listComp :: LHsExpr GhcPs -> [Idea]
listComp o :: LHsExpr GhcPs
o@(L SrcSpanAnnA
_ (HsDo XDo GhcPs
_ HsDoFlavour
ListComp (L SrcSpanAnnL
_ [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
stmts))) =
LHsExpr GhcPs -> HsDoFlavour -> [ExprLStmt GhcPs] -> [Idea]
listCompCheckGuards LHsExpr GhcPs
o HsDoFlavour
ListComp [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
stmts
listComp o :: LHsExpr GhcPs
o@(L SrcSpanAnnA
_ (HsDo XDo GhcPs
_ HsDoFlavour
MonadComp (L SrcSpanAnnL
_ [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
stmts))) =
LHsExpr GhcPs -> HsDoFlavour -> [ExprLStmt GhcPs] -> [Idea]
listCompCheckGuards LHsExpr GhcPs
o HsDoFlavour
MonadComp [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
stmts
listComp (L SrcSpanAnnA
_ HsPar{}) = []
listComp o :: LHsExpr GhcPs
o@(forall a b. View a b => a -> b
view -> App2 GenLocated SrcSpanAnnA (HsExpr GhcPs)
mp GenLocated SrcSpanAnnA (HsExpr GhcPs)
f (L SrcSpanAnnA
_ (HsDo XDo GhcPs
_ HsDoFlavour
ListComp (L SrcSpanAnnL
_ [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
stmts)))) =
LHsExpr GhcPs
-> LHsExpr GhcPs
-> LHsExpr GhcPs
-> HsDoFlavour
-> [ExprLStmt GhcPs]
-> [Idea]
listCompCheckMap LHsExpr GhcPs
o GenLocated SrcSpanAnnA (HsExpr GhcPs)
mp GenLocated SrcSpanAnnA (HsExpr GhcPs)
f HsDoFlavour
ListComp [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
stmts
listComp o :: LHsExpr GhcPs
o@(forall a b. View a b => a -> b
view -> App2 GenLocated SrcSpanAnnA (HsExpr GhcPs)
mp GenLocated SrcSpanAnnA (HsExpr GhcPs)
f (L SrcSpanAnnA
_ (HsDo XDo GhcPs
_ HsDoFlavour
MonadComp (L SrcSpanAnnL
_ [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
stmts)))) =
LHsExpr GhcPs
-> LHsExpr GhcPs
-> LHsExpr GhcPs
-> HsDoFlavour
-> [ExprLStmt GhcPs]
-> [Idea]
listCompCheckMap LHsExpr GhcPs
o GenLocated SrcSpanAnnA (HsExpr GhcPs)
mp GenLocated SrcSpanAnnA (HsExpr GhcPs)
f HsDoFlavour
MonadComp [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
stmts
listComp LHsExpr GhcPs
_ = []
listCompCheckGuards :: LHsExpr GhcPs -> HsDoFlavour -> [ExprLStmt GhcPs] -> [Idea]
listCompCheckGuards :: LHsExpr GhcPs -> HsDoFlavour -> [ExprLStmt GhcPs] -> [Idea]
listCompCheckGuards LHsExpr GhcPs
o HsDoFlavour
ctx [ExprLStmt GhcPs]
stmts =
let revs :: [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
revs = forall a. [a] -> [a]
reverse [ExprLStmt GhcPs]
stmts
e :: GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
e@(L SrcSpanAnnA
_ LastStmt{}) = forall a. [a] -> a
head [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
revs
xs :: [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
xs = forall a. [a] -> [a]
reverse (forall a. [a] -> [a]
tail [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
revs) in
GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
-> [Idea]
list_comp_aux GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
e [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
xs
where
list_comp_aux :: GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
-> [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
-> [Idea]
list_comp_aux GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
e [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
xs
| String
"False" forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
cons = [forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
"Short-circuited list comprehension" (forall a e. LocatedAn a e -> Located e
reLoc LHsExpr GhcPs
o) (forall a e. LocatedAn a e -> Located e
reLoc forall {an}. LocatedAn an (HsExpr GhcPs)
o') (LHsExpr GhcPs -> LHsExpr GhcPs -> [Refactoring SrcSpan]
suggestExpr LHsExpr GhcPs
o forall {an}. LocatedAn an (HsExpr GhcPs)
o')]
| String
"True" forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
cons = [forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
"Redundant True guards" (forall a e. LocatedAn a e -> Located e
reLoc LHsExpr GhcPs
o) (forall a e. LocatedAn a e -> Located e
reLoc forall {an}. LocatedAn an (HsExpr GhcPs)
o2) (LHsExpr GhcPs -> LHsExpr GhcPs -> [Refactoring SrcSpan]
suggestExpr LHsExpr GhcPs
o forall {an}. LocatedAn an (HsExpr GhcPs)
o2)]
| Bool -> Bool
not (forall a. Data a => [a] -> [a] -> Bool
astListEq [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
xs [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
ys) = [forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
"Move guards forward" (forall a e. LocatedAn a e -> Located e
reLoc LHsExpr GhcPs
o) (forall a e. LocatedAn a e -> Located e
reLoc forall {an}. LocatedAn an (HsExpr GhcPs)
o3) (LHsExpr GhcPs -> LHsExpr GhcPs -> [Refactoring SrcSpan]
suggestExpr LHsExpr GhcPs
o forall {an}. LocatedAn an (HsExpr GhcPs)
o3)]
| Bool
otherwise = []
where
ys :: [ExprLStmt GhcPs]
ys = [ExprLStmt GhcPs] -> [ExprLStmt GhcPs]
moveGuardsForward [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
xs
o' :: LocatedAn an (HsExpr GhcPs)
o' = forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall p. XExplicitList p -> [LHsExpr p] -> HsExpr p
ExplicitList forall ann. EpAnn ann
EpAnnNotUsed []
o2 :: LocatedAn an (HsExpr GhcPs)
o2 = forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall p. XDo p -> HsDoFlavour -> XRec p [ExprLStmt p] -> HsExpr p
HsDo forall ann. EpAnn ann
EpAnnNotUsed HsDoFlavour
ctx (forall a an. a -> LocatedAn an a
noLocA (forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
/= forall a. a -> Maybe a
Just String
"True") forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExprLStmt GhcPs -> Maybe String
qualCon) [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
xs forall a. [a] -> [a] -> [a]
++ [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
e]))
o3 :: LocatedAn an (HsExpr GhcPs)
o3 = forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall p. XDo p -> HsDoFlavour -> XRec p [ExprLStmt p] -> HsExpr p
HsDo forall ann. EpAnn ann
EpAnnNotUsed HsDoFlavour
ctx (forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
ys forall a. [a] -> [a] -> [a]
++ [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
e])
cons :: [String]
cons = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ExprLStmt GhcPs -> Maybe String
qualCon [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
xs
qualCon :: ExprLStmt GhcPs -> Maybe String
qualCon :: ExprLStmt GhcPs -> Maybe String
qualCon (L SrcSpanAnnA
_ (BodyStmt XBodyStmt GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ (L SrcSpanAnnA
_ (HsVar XVar GhcPs
_ (L SrcSpanAnnN
_ RdrName
x))) SyntaxExpr GhcPs
_ SyntaxExpr GhcPs
_)) = forall a. a -> Maybe a
Just (RdrName -> String
occNameStr RdrName
x)
qualCon ExprLStmt GhcPs
_ = forall a. Maybe a
Nothing
listCompCheckMap ::
LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> HsDoFlavour -> [ExprLStmt GhcPs] -> [Idea]
listCompCheckMap :: LHsExpr GhcPs
-> LHsExpr GhcPs
-> LHsExpr GhcPs
-> HsDoFlavour
-> [ExprLStmt GhcPs]
-> [Idea]
listCompCheckMap LHsExpr GhcPs
o LHsExpr GhcPs
mp LHsExpr GhcPs
f HsDoFlavour
ctx [ExprLStmt GhcPs]
stmts | LHsExpr GhcPs -> String
varToStr LHsExpr GhcPs
mp forall a. Eq a => a -> a -> Bool
== String
"map" =
[forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
"Move map inside list comprehension" (forall a e. LocatedAn a e -> Located e
reLoc LHsExpr GhcPs
o) (forall a e. LocatedAn a e -> Located e
reLoc forall {an}. LocatedAn an (HsExpr GhcPs)
o2) (LHsExpr GhcPs -> LHsExpr GhcPs -> [Refactoring SrcSpan]
suggestExpr LHsExpr GhcPs
o forall {an}. LocatedAn an (HsExpr GhcPs)
o2)]
where
revs :: [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
revs = forall a. [a] -> [a]
reverse [ExprLStmt GhcPs]
stmts
L SrcSpanAnnA
_ (LastStmt XLastStmt GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))
_ GenLocated SrcSpanAnnA (HsExpr GhcPs)
body Maybe Bool
b SyntaxExpr GhcPs
s) = forall a. [a] -> a
head [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
revs
last :: LocatedAn
an (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
last = forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall idL idR body.
XLastStmt idL idR body
-> body -> Maybe Bool -> SyntaxExpr idR -> StmtLR idL idR body
LastStmt NoExtField
noExtField (forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall p. XApp p -> LHsExpr p -> LHsExpr p -> HsExpr p
HsApp forall ann. EpAnn ann
EpAnnNotUsed (LHsExpr GhcPs -> LHsExpr GhcPs
paren LHsExpr GhcPs
f) (LHsExpr GhcPs -> LHsExpr GhcPs
paren GenLocated SrcSpanAnnA (HsExpr GhcPs)
body)) Maybe Bool
b NoExtField
s
o2 :: LocatedAn an (HsExpr GhcPs)
o2 =forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall p. XDo p -> HsDoFlavour -> XRec p [ExprLStmt p] -> HsExpr p
HsDo forall ann. EpAnn ann
EpAnnNotUsed HsDoFlavour
ctx (forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse (forall a. [a] -> [a]
tail [GenLocated
SrcSpanAnnA
(StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
revs) forall a. [a] -> [a] -> [a]
++ [forall {an}.
LocatedAn
an (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))
last])
listCompCheckMap LHsExpr GhcPs
_ LHsExpr GhcPs
_ LHsExpr GhcPs
_ HsDoFlavour
_ [ExprLStmt GhcPs]
_ = []
suggestExpr :: LHsExpr GhcPs -> LHsExpr GhcPs -> [Refactoring R.SrcSpan]
suggestExpr :: LHsExpr GhcPs -> LHsExpr GhcPs -> [Refactoring SrcSpan]
suggestExpr LHsExpr GhcPs
o LHsExpr GhcPs
o2 = [forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
Expr (forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LHsExpr GhcPs
o) [] (forall a. Outputable a => a -> String
unsafePrettyPrint LHsExpr GhcPs
o2)]
moveGuardsForward :: [ExprLStmt GhcPs] -> [ExprLStmt GhcPs]
moveGuardsForward :: [ExprLStmt GhcPs] -> [ExprLStmt GhcPs]
moveGuardsForward = forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {l} {idL} {idR} {body}.
(Data l, Data (StmtLR idL idR body),
AllVars (GenLocated l (StmtLR idL idR body)),
AllVars (XRec idL (Pat idL))) =>
[GenLocated l (StmtLR idL idR body)]
-> [GenLocated l (StmtLR idL idR body)]
-> [GenLocated l (StmtLR idL idR body)]
f [] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse
where
f :: [GenLocated l (StmtLR idL idR body)]
-> [GenLocated l (StmtLR idL idR body)]
-> [GenLocated l (StmtLR idL idR body)]
f [GenLocated l (StmtLR idL idR body)]
guards (x :: GenLocated l (StmtLR idL idR body)
x@(L l
_ (BindStmt XBindStmt idL idR body
_ XRec idL (Pat idL)
p body
_)) : [GenLocated l (StmtLR idL idR body)]
xs) = forall a. [a] -> [a]
reverse [GenLocated l (StmtLR idL idR body)]
stop forall a. [a] -> [a] -> [a]
++ GenLocated l (StmtLR idL idR body)
x forall a. a -> [a] -> [a]
: [GenLocated l (StmtLR idL idR body)]
-> [GenLocated l (StmtLR idL idR body)]
-> [GenLocated l (StmtLR idL idR body)]
f [GenLocated l (StmtLR idL idR body)]
move [GenLocated l (StmtLR idL idR body)]
xs
where ([GenLocated l (StmtLR idL idR body)]
move, [GenLocated l (StmtLR idL idR body)]
stop) =
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any HsRecFields GhcPs (XRec GhcPs (Pat GhcPs)) -> Bool
hasPFieldsDotDot (forall from to. Biplate from to => from -> [to]
universeBi GenLocated l (StmtLR idL idR body)
x)
Bool -> Bool -> Bool
|| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any LHsFieldBind GhcPs (LFieldOcc GhcPs) (XRec GhcPs (Pat GhcPs))
-> Bool
isPFieldWildcard (forall from to. Biplate from to => from -> [to]
universeBi GenLocated l (StmtLR idL idR body)
x)
then forall a b. a -> b -> a
const Bool
False
else \GenLocated l (StmtLR idL idR body)
x ->
let pvs :: [String]
pvs = forall a. AllVars a => a -> [String]
pvars XRec idL (Pat idL)
p in
[String]
pvs forall a. Eq a => [a] -> [a] -> Bool
`disjoint` forall a. AllVars a => a -> [String]
varss GenLocated l (StmtLR idL idR body)
x Bool -> Bool -> Bool
&& String
"pun-right-hand-side" forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [String]
pvs
) [GenLocated l (StmtLR idL idR body)]
guards
f [GenLocated l (StmtLR idL idR body)]
guards (x :: GenLocated l (StmtLR idL idR body)
x@(L l
_ BodyStmt{}):[GenLocated l (StmtLR idL idR body)]
xs) = [GenLocated l (StmtLR idL idR body)]
-> [GenLocated l (StmtLR idL idR body)]
-> [GenLocated l (StmtLR idL idR body)]
f (GenLocated l (StmtLR idL idR body)
xforall a. a -> [a] -> [a]
:[GenLocated l (StmtLR idL idR body)]
guards) [GenLocated l (StmtLR idL idR body)]
xs
f [GenLocated l (StmtLR idL idR body)]
guards (x :: GenLocated l (StmtLR idL idR body)
x@(L l
_ LetStmt{}):[GenLocated l (StmtLR idL idR body)]
xs) = [GenLocated l (StmtLR idL idR body)]
-> [GenLocated l (StmtLR idL idR body)]
-> [GenLocated l (StmtLR idL idR body)]
f (GenLocated l (StmtLR idL idR body)
xforall a. a -> [a] -> [a]
:[GenLocated l (StmtLR idL idR body)]
guards) [GenLocated l (StmtLR idL idR body)]
xs
f [GenLocated l (StmtLR idL idR body)]
guards [GenLocated l (StmtLR idL idR body)]
xs = forall a. [a] -> [a]
reverse [GenLocated l (StmtLR idL idR body)]
guards forall a. [a] -> [a] -> [a]
++ [GenLocated l (StmtLR idL idR body)]
xs
listExp :: Bool -> Bool -> LHsExpr GhcPs -> [Idea]
listExp :: Bool -> Bool -> LHsExpr GhcPs -> [Idea]
listExp Bool
overloadedListsOn Bool
b (GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
fromParen -> GenLocated SrcSpanAnnA (HsExpr GhcPs)
x) =
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Idea]
res
then forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Bool -> Bool -> LHsExpr GhcPs -> [Idea]
listExp Bool
overloadedListsOn forall a b. (a -> b) -> a -> b
$ forall a. View a App2 => a -> Bool
isAppend GenLocated SrcSpanAnnA (HsExpr GhcPs)
x) forall a b. (a -> b) -> a -> b
$ forall on. Uniplate on => on -> [on]
children GenLocated SrcSpanAnnA (HsExpr GhcPs)
x
else [forall a. [a] -> a
head [Idea]
res]
where
res :: [Idea]
res = [forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
name (forall a e. LocatedAn a e -> Located e
reLoc GenLocated SrcSpanAnnA (HsExpr GhcPs)
x) (forall a e. LocatedAn a e -> Located e
reLoc GenLocated SrcSpanAnnA (HsExpr GhcPs)
x2) [Refactoring SrcSpan
r]
| (String
name, Bool
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> Maybe
(GenLocated SrcSpanAnnA (HsExpr GhcPs), [(String, SrcSpan)],
String)
f) <- Bool
-> [(String,
Bool
-> LHsExpr GhcPs
-> Maybe (LHsExpr GhcPs, [(String, SrcSpan)], String))]
checks Bool
overloadedListsOn
, Just (GenLocated SrcSpanAnnA (HsExpr GhcPs)
x2, [(String, SrcSpan)]
subts, String
temp) <- [Bool
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> Maybe
(GenLocated SrcSpanAnnA (HsExpr GhcPs), [(String, SrcSpan)],
String)
f Bool
b GenLocated SrcSpanAnnA (HsExpr GhcPs)
x]
, let r :: Refactoring SrcSpan
r = forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
Expr (forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA GenLocated SrcSpanAnnA (HsExpr GhcPs)
x) [(String, SrcSpan)]
subts String
temp ]
listPat :: LPat GhcPs -> [Idea]
listPat :: XRec GhcPs (Pat GhcPs) -> [Idea]
listPat XRec GhcPs (Pat GhcPs)
x = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Idea]
res then forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap XRec GhcPs (Pat GhcPs) -> [Idea]
listPat forall a b. (a -> b) -> a -> b
$ forall on. Uniplate on => on -> [on]
children XRec GhcPs (Pat GhcPs)
x else [forall a. [a] -> a
head [Idea]
res]
where res :: [Idea]
res = [forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
name (forall a e. LocatedAn a e -> Located e
reLoc XRec GhcPs (Pat GhcPs)
x) (forall a e. LocatedAn a e -> Located e
reLoc GenLocated SrcSpanAnnA (Pat GhcPs)
x2) [Refactoring SrcSpan
r]
| (String
name, GenLocated SrcSpanAnnA (Pat GhcPs)
-> Maybe
(GenLocated SrcSpanAnnA (Pat GhcPs), [(String, SrcSpan)], String)
f) <- [(String,
XRec GhcPs (Pat GhcPs)
-> Maybe (XRec GhcPs (Pat GhcPs), [(String, SrcSpan)], String))]
pchecks
, Just (GenLocated SrcSpanAnnA (Pat GhcPs)
x2, [(String, SrcSpan)]
subts, String
temp) <- [GenLocated SrcSpanAnnA (Pat GhcPs)
-> Maybe
(GenLocated SrcSpanAnnA (Pat GhcPs), [(String, SrcSpan)], String)
f XRec GhcPs (Pat GhcPs)
x]
, let r :: Refactoring SrcSpan
r = forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
Pattern (forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA XRec GhcPs (Pat GhcPs)
x) [(String, SrcSpan)]
subts String
temp ]
isAppend :: View a App2 => a -> Bool
isAppend :: forall a. View a App2 => a -> Bool
isAppend (forall a b. View a b => a -> b
view -> App2 GenLocated SrcSpanAnnA (HsExpr GhcPs)
op GenLocated SrcSpanAnnA (HsExpr GhcPs)
_ GenLocated SrcSpanAnnA (HsExpr GhcPs)
_) = LHsExpr GhcPs -> String
varToStr GenLocated SrcSpanAnnA (HsExpr GhcPs)
op forall a. Eq a => a -> a -> Bool
== String
"++"
isAppend a
_ = Bool
False
checks :: Bool -> [(String, Bool -> LHsExpr GhcPs -> Maybe (LHsExpr GhcPs, [(String, R.SrcSpan)], String))]
checks :: Bool
-> [(String,
Bool
-> LHsExpr GhcPs
-> Maybe (LHsExpr GhcPs, [(String, SrcSpan)], String))]
checks Bool
overloadedListsOn = let * :: a -> b -> (a, b)
(*) = (,) in forall a. [a] -> [a]
drop1
[ String
"Use string literal" forall a b. a -> b -> (a, b)
* forall p a.
p -> LHsExpr GhcPs -> Maybe (LHsExpr GhcPs, [a], String)
useString
, String
"Use :" forall a b. a -> b -> (a, b)
* forall a.
View a App2 =>
Bool -> a -> Maybe (LHsExpr GhcPs, [(String, SrcSpan)], String)
useCons
]
forall a. Semigroup a => a -> a -> a
<> [String
"Use list literal" forall a b. a -> b -> (a, b)
* forall p.
p
-> LHsExpr GhcPs
-> Maybe (LHsExpr GhcPs, [(String, SrcSpan)], String)
useList | Bool -> Bool
not Bool
overloadedListsOn ]
pchecks :: [(String, LPat GhcPs -> Maybe (LPat GhcPs, [(String, R.SrcSpan)], String))]
pchecks :: [(String,
XRec GhcPs (Pat GhcPs)
-> Maybe (XRec GhcPs (Pat GhcPs), [(String, SrcSpan)], String))]
pchecks = let * :: a -> b -> (a, b)
(*) = (,) in forall a. [a] -> [a]
drop1
[ String
"Use string literal pattern" forall a b. a -> b -> (a, b)
* forall a.
XRec GhcPs (Pat GhcPs)
-> Maybe (XRec GhcPs (Pat GhcPs), [a], String)
usePString
, String
"Use list literal pattern" forall a b. a -> b -> (a, b)
* XRec GhcPs (Pat GhcPs)
-> Maybe (XRec GhcPs (Pat GhcPs), [(String, SrcSpan)], String)
usePList
]
usePString :: LPat GhcPs -> Maybe (LPat GhcPs, [a], String)
usePString :: forall a.
XRec GhcPs (Pat GhcPs)
-> Maybe (XRec GhcPs (Pat GhcPs), [a], String)
usePString (L SrcSpanAnnA
_ (ListPat XListPat GhcPs
_ [XRec GhcPs (Pat GhcPs)]
xs)) | Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null [XRec GhcPs (Pat GhcPs)]
xs, Just String
s <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM XRec GhcPs (Pat GhcPs) -> Maybe Char
fromPChar [XRec GhcPs (Pat GhcPs)]
xs =
let literal :: XRec GhcPs (Pat GhcPs)
literal = forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall p. XLitPat p -> HsLit p -> Pat p
LitPat NoExtField
noExtField (forall x. XHsString x -> FastString -> HsLit x
HsString SourceText
NoSourceText (String -> FastString
fsLit (forall a. Show a => a -> String
show String
s))) :: LPat GhcPs
in forall a. a -> Maybe a
Just (GenLocated SrcSpanAnnA (Pat GhcPs)
literal, [], forall a. Outputable a => a -> String
unsafePrettyPrint GenLocated SrcSpanAnnA (Pat GhcPs)
literal)
usePString XRec GhcPs (Pat GhcPs)
_ = forall a. Maybe a
Nothing
usePList :: LPat GhcPs -> Maybe (LPat GhcPs, [(String, R.SrcSpan)], String)
usePList :: XRec GhcPs (Pat GhcPs)
-> Maybe (XRec GhcPs (Pat GhcPs), [(String, SrcSpan)], String)
usePList =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ( (\([GenLocated SrcSpanAnnA (Pat GhcPs)]
e, [((String, SrcSpan), GenLocated SrcSpanAnnA (Pat GhcPs))]
s) ->
(forall a an. a -> LocatedAn an a
noLocA (forall p. XListPat p -> [LPat p] -> Pat p
ListPat forall ann. EpAnn ann
EpAnnNotUsed [GenLocated SrcSpanAnnA (Pat GhcPs)]
e)
, forall a b. (a -> b) -> [a] -> [b]
map (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SrcSpan -> SrcSpan
toRefactSrcSpan forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [((String, SrcSpan), GenLocated SrcSpanAnnA (Pat GhcPs))]
s
, forall a. Outputable a => a -> String
unsafePrettyPrint (forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall p. XListPat p -> [LPat p] -> Pat p
ListPat forall ann. EpAnn ann
EpAnnNotUsed (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [((String, SrcSpan), GenLocated SrcSpanAnnA (Pat GhcPs))]
s) :: LPat GhcPs))
)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [(a, b)] -> ([a], [b])
unzip
)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool
-> [String]
-> GenLocated SrcSpanAnnA (Pat GhcPs)
-> Maybe
[(GenLocated SrcSpanAnnA (Pat GhcPs),
((String, SrcSpan), GenLocated SrcSpanAnnA (Pat GhcPs)))]
f Bool
True [String]
substVars
where
f :: Bool
-> [String]
-> GenLocated SrcSpanAnnA (Pat GhcPs)
-> Maybe
[(GenLocated SrcSpanAnnA (Pat GhcPs),
((String, SrcSpan), GenLocated SrcSpanAnnA (Pat GhcPs)))]
f Bool
first [String]
_ GenLocated SrcSpanAnnA (Pat GhcPs)
x | XRec GhcPs (Pat GhcPs) -> String
patToStr GenLocated SrcSpanAnnA (Pat GhcPs)
x forall a. Eq a => a -> a -> Bool
== String
"[]" = if Bool
first then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just []
f Bool
first (String
ident:[String]
cs) (forall a b. View a b => a -> b
view -> PApp_ String
":" [GenLocated SrcSpanAnnA (Pat GhcPs)
a, GenLocated SrcSpanAnnA (Pat GhcPs)
b]) = ((GenLocated SrcSpanAnnA (Pat GhcPs)
a, String
-> XRec GhcPs (Pat GhcPs)
-> ((String, SrcSpan), XRec GhcPs (Pat GhcPs))
g String
ident GenLocated SrcSpanAnnA (Pat GhcPs)
a) forall a. a -> [a] -> [a]
:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool
-> [String]
-> GenLocated SrcSpanAnnA (Pat GhcPs)
-> Maybe
[(GenLocated SrcSpanAnnA (Pat GhcPs),
((String, SrcSpan), GenLocated SrcSpanAnnA (Pat GhcPs)))]
f Bool
False [String]
cs GenLocated SrcSpanAnnA (Pat GhcPs)
b
f Bool
first [String]
_ GenLocated SrcSpanAnnA (Pat GhcPs)
_ = forall a. Maybe a
Nothing
g :: String -> LPat GhcPs -> ((String, SrcSpan), LPat GhcPs)
g :: String
-> XRec GhcPs (Pat GhcPs)
-> ((String, SrcSpan), XRec GhcPs (Pat GhcPs))
g String
s (forall a. SrcSpanAnn' a -> SrcSpan
locA forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall l e. GenLocated l e -> l
getLoc -> SrcSpan
loc) = ((String
s, SrcSpan
loc), forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall p. XVarPat p -> LIdP p -> Pat p
VarPat NoExtField
noExtField (forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ FastString -> RdrName
mkVarUnqual (String -> FastString
fsLit String
s)))
useString :: p -> LHsExpr GhcPs -> Maybe (LHsExpr GhcPs, [a], String)
useString :: forall p a.
p -> LHsExpr GhcPs -> Maybe (LHsExpr GhcPs, [a], String)
useString p
b (L SrcSpanAnnA
_ (ExplicitList XExplicitList GhcPs
_ [LHsExpr GhcPs]
xs)) | Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null [LHsExpr GhcPs]
xs, Just String
s <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM LHsExpr GhcPs -> Maybe Char
fromChar [LHsExpr GhcPs]
xs =
let literal :: LHsExpr GhcPs
literal = forall a an. a -> LocatedAn an a
noLocA (forall p. XLitE p -> HsLit p -> HsExpr p
HsLit forall ann. EpAnn ann
EpAnnNotUsed (forall x. XHsString x -> FastString -> HsLit x
HsString SourceText
NoSourceText (String -> FastString
fsLit (forall a. Show a => a -> String
show String
s)))) :: LHsExpr GhcPs
in forall a. a -> Maybe a
Just (GenLocated SrcSpanAnnA (HsExpr GhcPs)
literal, [], forall a. Outputable a => a -> String
unsafePrettyPrint GenLocated SrcSpanAnnA (HsExpr GhcPs)
literal)
useString p
_ LHsExpr GhcPs
_ = forall a. Maybe a
Nothing
useList :: p -> LHsExpr GhcPs -> Maybe (LHsExpr GhcPs, [(String, R.SrcSpan)], String)
useList :: forall p.
p
-> LHsExpr GhcPs
-> Maybe (LHsExpr GhcPs, [(String, SrcSpan)], String)
useList p
b =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ( (\([GenLocated SrcSpanAnnA (HsExpr GhcPs)]
e, [(String, GenLocated SrcSpanAnnA (HsExpr GhcPs))]
s) ->
(forall a an. a -> LocatedAn an a
noLocA (forall p. XExplicitList p -> [LHsExpr p] -> HsExpr p
ExplicitList forall ann. EpAnn ann
EpAnnNotUsed [GenLocated SrcSpanAnnA (HsExpr GhcPs)]
e)
, forall a b. (a -> b) -> [a] -> [b]
map (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA) [(String, GenLocated SrcSpanAnnA (HsExpr GhcPs))]
s
, forall a. Outputable a => a -> String
unsafePrettyPrint (forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall p. XExplicitList p -> [LHsExpr p] -> HsExpr p
ExplicitList forall ann. EpAnn ann
EpAnnNotUsed (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(String, GenLocated SrcSpanAnnA (HsExpr GhcPs))]
s) :: LHsExpr GhcPs))
)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [(a, b)] -> ([a], [b])
unzip
)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool
-> [String]
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> Maybe
[(GenLocated SrcSpanAnnA (HsExpr GhcPs),
(String, GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
f Bool
True [String]
substVars
where
f :: Bool
-> [String]
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> Maybe
[(GenLocated SrcSpanAnnA (HsExpr GhcPs),
(String, GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
f Bool
first [String]
_ GenLocated SrcSpanAnnA (HsExpr GhcPs)
x | LHsExpr GhcPs -> String
varToStr GenLocated SrcSpanAnnA (HsExpr GhcPs)
x forall a. Eq a => a -> a -> Bool
== String
"[]" = if Bool
first then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just []
f Bool
first (String
ident:[String]
cs) (forall a b. View a b => a -> b
view -> App2 GenLocated SrcSpanAnnA (HsExpr GhcPs)
c GenLocated SrcSpanAnnA (HsExpr GhcPs)
a GenLocated SrcSpanAnnA (HsExpr GhcPs)
b) | LHsExpr GhcPs -> String
varToStr GenLocated SrcSpanAnnA (HsExpr GhcPs)
c forall a. Eq a => a -> a -> Bool
== String
":" =
((GenLocated SrcSpanAnnA (HsExpr GhcPs)
a, String -> LHsExpr GhcPs -> (String, LHsExpr GhcPs)
g String
ident GenLocated SrcSpanAnnA (HsExpr GhcPs)
a) forall a. a -> [a] -> [a]
:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool
-> [String]
-> GenLocated SrcSpanAnnA (HsExpr GhcPs)
-> Maybe
[(GenLocated SrcSpanAnnA (HsExpr GhcPs),
(String, GenLocated SrcSpanAnnA (HsExpr GhcPs)))]
f Bool
False [String]
cs GenLocated SrcSpanAnnA (HsExpr GhcPs)
b
f Bool
first [String]
_ GenLocated SrcSpanAnnA (HsExpr GhcPs)
_ = forall a. Maybe a
Nothing
g :: String -> LHsExpr GhcPs -> (String, LHsExpr GhcPs)
g :: String -> LHsExpr GhcPs -> (String, LHsExpr GhcPs)
g String
s LHsExpr GhcPs
p = (String
s, forall l e. l -> e -> GenLocated l e
L (forall l e. GenLocated l e -> l
getLoc LHsExpr GhcPs
p) (forall l e. GenLocated l e -> e
unLoc forall a b. (a -> b) -> a -> b
$ String -> LHsExpr GhcPs
strToVar String
s))
useCons :: View a App2 => Bool -> a -> Maybe (LHsExpr GhcPs, [(String, R.SrcSpan)], String)
useCons :: forall a.
View a App2 =>
Bool -> a -> Maybe (LHsExpr GhcPs, [(String, SrcSpan)], String)
useCons Bool
False (forall a b. View a b => a -> b
view -> App2 GenLocated SrcSpanAnnA (HsExpr GhcPs)
op GenLocated SrcSpanAnnA (HsExpr GhcPs)
x GenLocated SrcSpanAnnA (HsExpr GhcPs)
y) | LHsExpr GhcPs -> String
varToStr GenLocated SrcSpanAnnA (HsExpr GhcPs)
op forall a. Eq a => a -> a -> Bool
== String
"++"
, Just (LHsExpr GhcPs
newX, LHsExpr GhcPs
tplX, SrcSpan
spanX) <- LHsExpr GhcPs -> Maybe (LHsExpr GhcPs, LHsExpr GhcPs, SrcSpan)
f GenLocated SrcSpanAnnA (HsExpr GhcPs)
x
, Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall a. View a App2 => a -> Bool
isAppend GenLocated SrcSpanAnnA (HsExpr GhcPs)
y =
forall a. a -> Maybe a
Just (LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
gen LHsExpr GhcPs
newX GenLocated SrcSpanAnnA (HsExpr GhcPs)
y
, [(String
"x", SrcSpan
spanX), (String
"xs", forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA GenLocated SrcSpanAnnA (HsExpr GhcPs)
y)]
, forall a. Outputable a => a -> String
unsafePrettyPrint forall a b. (a -> b) -> a -> b
$ LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
gen LHsExpr GhcPs
tplX (String -> LHsExpr GhcPs
strToVar String
"xs")
)
where
f :: LHsExpr GhcPs -> Maybe (LHsExpr GhcPs, LHsExpr GhcPs, R.SrcSpan)
f :: LHsExpr GhcPs -> Maybe (LHsExpr GhcPs, LHsExpr GhcPs, SrcSpan)
f (L SrcSpanAnnA
_ (ExplicitList XExplicitList GhcPs
_ [LHsExpr GhcPs
x]))
| forall a. Brackets a => a -> Bool
isAtom LHsExpr GhcPs
x Bool -> Bool -> Bool
|| LHsExpr GhcPs -> Bool
isApp LHsExpr GhcPs
x = forall a. a -> Maybe a
Just (LHsExpr GhcPs
x, String -> LHsExpr GhcPs
strToVar String
"x", forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LHsExpr GhcPs
x)
| Bool
otherwise = forall a. a -> Maybe a
Just (forall a. Brackets a => a -> a
addParen LHsExpr GhcPs
x, forall a. Brackets a => a -> a
addParen (String -> LHsExpr GhcPs
strToVar String
"x"), forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LHsExpr GhcPs
x)
f LHsExpr GhcPs
_ = forall a. Maybe a
Nothing
gen :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
gen :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
gen LHsExpr GhcPs
x = forall a an. a -> LocatedAn an a
noLocA forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall p.
XOpApp p -> LHsExpr p -> LHsExpr p -> LHsExpr p -> HsExpr p
OpApp forall ann. EpAnn ann
EpAnnNotUsed LHsExpr GhcPs
x (forall a an. a -> LocatedAn an a
noLocA (forall p. XVar p -> LIdP p -> HsExpr p
HsVar NoExtField
noExtField (forall a an. a -> LocatedAn an a
noLocA RdrName
consDataCon_RDR)))
useCons Bool
_ a
_ = forall a. Maybe a
Nothing
typeListChar :: LHsType GhcPs
typeListChar :: LHsType GhcPs
typeListChar =
forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall pass. XListTy pass -> LHsType pass -> HsType pass
HsListTy forall ann. EpAnn ann
EpAnnNotUsed
(forall a an. a -> LocatedAn an a
noLocA (forall pass.
XTyVar pass -> PromotionFlag -> LIdP pass -> HsType pass
HsTyVar forall ann. EpAnn ann
EpAnnNotUsed PromotionFlag
NotPromoted (forall a an. a -> LocatedAn an a
noLocA (FastString -> RdrName
mkVarUnqual (String -> FastString
fsLit String
"Char")))))
typeString :: LHsType GhcPs
typeString :: LHsType GhcPs
typeString =
forall a an. a -> LocatedAn an a
noLocA forall a b. (a -> b) -> a -> b
$ forall pass.
XTyVar pass -> PromotionFlag -> LIdP pass -> HsType pass
HsTyVar forall ann. EpAnn ann
EpAnnNotUsed PromotionFlag
NotPromoted (forall a an. a -> LocatedAn an a
noLocA (FastString -> RdrName
mkVarUnqual (String -> FastString
fsLit String
"String")))
stringType :: LHsDecl GhcPs -> [Idea]
stringType :: LHsDecl GhcPs -> [Idea]
stringType (L SrcSpanAnnA
_ HsDecl GhcPs
x) = case HsDecl GhcPs
x of
InstD XInstD GhcPs
_ ClsInstD{
cid_inst :: forall pass. InstDecl pass -> ClsInstDecl pass
cid_inst=
ClsInstDecl{cid_binds :: forall pass. ClsInstDecl pass -> LHsBinds pass
cid_binds=LHsBinds GhcPs
x, cid_tyfam_insts :: forall pass. ClsInstDecl pass -> [LTyFamInstDecl pass]
cid_tyfam_insts=[LTyFamInstDecl GhcPs]
y, cid_datafam_insts :: forall pass. ClsInstDecl pass -> [LDataFamInstDecl pass]
cid_datafam_insts=[LDataFamInstDecl GhcPs]
z}} ->
forall {from}. Data from => from -> [Idea]
f LHsBinds GhcPs
x forall a. [a] -> [a] -> [a]
++ forall {from}. Data from => from -> [Idea]
f [LTyFamInstDecl GhcPs]
y forall a. [a] -> [a] -> [a]
++ forall {from}. Data from => from -> [Idea]
f [LDataFamInstDecl GhcPs]
z
HsDecl GhcPs
_ -> forall {from}. Data from => from -> [Idea]
f HsDecl GhcPs
x
where
f :: from -> [Idea]
f from
x = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap LHsType GhcPs -> [Idea]
g forall a b. (a -> b) -> a -> b
$ forall from to. Biplate from to => from -> [to]
childrenBi from
x
g :: LHsType GhcPs -> [Idea]
g :: LHsType GhcPs -> [Idea]
g e :: LHsType GhcPs
e@(LHsType GhcPs -> LHsType GhcPs
fromTyParen -> LHsType GhcPs
x) = [forall a.
Outputable a =>
String -> Located a -> Located a -> [Refactoring SrcSpan] -> Idea
ignore String
"Use String" (forall a e. LocatedAn a e -> Located e
reLoc LHsType GhcPs
x) (forall a e. LocatedAn a e -> Located e
reLoc (forall on. Uniplate on => (on -> on) -> on -> on
transform LocatedAn AnnListItem (HsType GhcPs)
-> LocatedAn AnnListItem (HsType GhcPs)
f LHsType GhcPs
x))
[Refactoring SrcSpan]
rs | Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ [Refactoring SrcSpan]
rs]
where f :: LocatedAn AnnListItem (HsType GhcPs) -> LHsType GhcPs
f LocatedAn AnnListItem (HsType GhcPs)
x = if forall a. Data a => a -> a -> Bool
astEq LocatedAn AnnListItem (HsType GhcPs)
x LHsType GhcPs
typeListChar then LHsType GhcPs
typeString else LocatedAn AnnListItem (HsType GhcPs)
x
rs :: [Refactoring SrcSpan]
rs = [forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
Type (forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LocatedAn AnnListItem (HsType GhcPs)
t) [] (forall a. Outputable a => a -> String
unsafePrettyPrint LHsType GhcPs
typeString) | LocatedAn AnnListItem (HsType GhcPs)
t <- forall on. Uniplate on => on -> [on]
universe LHsType GhcPs
x, forall a. Data a => a -> a -> Bool
astEq LocatedAn AnnListItem (HsType GhcPs)
t LHsType GhcPs
typeListChar]