{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase, PatternGuards, RecordWildCards #-}
module Hint.Import(importHint) where
import Hint.Type(ModuHint,ModuleEx(..),Idea(..),Severity(..),suggest,toSSA,rawIdea)
import Refact.Types hiding (ModuleName)
import Refact.Types qualified as R
import Data.Tuple.Extra
import Data.List.Extra
import Data.Generics.Uniplate.DataOnly
import Data.Maybe
import Control.Applicative
import Prelude
import GHC.Data.FastString
import GHC.Types.SourceText
import GHC.Hs
import GHC.Types.SrcLoc
import GHC.Types.PkgQual
import Language.Haskell.GhclibParserEx.GHC.Utils.Outputable
rawPkgQualToMaybe :: RawPkgQual -> Maybe StringLiteral
rawPkgQualToMaybe :: RawPkgQual -> Maybe StringLiteral
rawPkgQualToMaybe RawPkgQual
x =
case RawPkgQual
x of
RawPkgQual
NoRawPkgQual -> Maybe StringLiteral
forall a. Maybe a
Nothing
RawPkgQual StringLiteral
lit -> StringLiteral -> Maybe StringLiteral
forall a. a -> Maybe a
Just StringLiteral
lit
importHint :: ModuHint
importHint :: ModuHint
importHint Scope
_ ModuleEx {ghcModule :: ModuleEx -> Located (HsModule GhcPs)
ghcModule=L SrcSpan
_ HsModule{hsmodImports :: forall p. HsModule p -> [LImportDecl p]
hsmodImports=[LImportDecl GhcPs]
ms}} =
(((ModuleName, Maybe String),
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)])
-> [Idea])
-> [((ModuleName, Maybe String),
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)])]
-> [Idea]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([LImportDecl GhcPs] -> [Idea]
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)] -> [Idea]
reduceImports ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)] -> [Idea])
-> (((ModuleName, Maybe String),
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)])
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)])
-> ((ModuleName, Maybe String),
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)])
-> [Idea]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ModuleName, Maybe String),
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)])
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
forall a b. (a, b) -> b
snd) (
[((ModuleName, Maybe String),
GenLocated SrcSpanAnnA (ImportDecl GhcPs))]
-> [((ModuleName, Maybe String),
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)])]
forall k v. Ord k => [(k, v)] -> [(k, [v])]
groupSort [((ModuleName
n, Maybe String
pkg), GenLocated SrcSpanAnnA (ImportDecl GhcPs)
i) | GenLocated SrcSpanAnnA (ImportDecl GhcPs)
i <- [LImportDecl GhcPs]
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
ms
, ImportDecl GhcPs -> IsBootInterface
forall pass. ImportDecl pass -> IsBootInterface
ideclSource (GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> ImportDecl GhcPs
forall l e. GenLocated l e -> e
unLoc GenLocated SrcSpanAnnA (ImportDecl GhcPs)
i) IsBootInterface -> IsBootInterface -> Bool
forall a. Eq a => a -> a -> Bool
== IsBootInterface
NotBoot
, let i' :: ImportDecl GhcPs
i' = GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> ImportDecl GhcPs
forall l e. GenLocated l e -> e
unLoc GenLocated SrcSpanAnnA (ImportDecl GhcPs)
i
, let n :: ModuleName
n = GenLocated SrcSpanAnnA ModuleName -> ModuleName
forall l e. GenLocated l e -> e
unLoc (GenLocated SrcSpanAnnA ModuleName -> ModuleName)
-> GenLocated SrcSpanAnnA ModuleName -> ModuleName
forall a b. (a -> b) -> a -> b
$ ImportDecl GhcPs -> XRec GhcPs ModuleName
forall pass. ImportDecl pass -> XRec pass ModuleName
ideclName ImportDecl GhcPs
i'
, let pkg :: Maybe String
pkg = FastString -> String
unpackFS (FastString -> String)
-> (StringLiteral -> FastString) -> StringLiteral -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StringLiteral -> FastString
sl_fs (StringLiteral -> String) -> Maybe StringLiteral -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RawPkgQual -> Maybe StringLiteral
rawPkgQualToMaybe (ImportDecl GhcPs -> ImportDeclPkgQual GhcPs
forall pass. ImportDecl pass -> ImportDeclPkgQual pass
ideclPkgQual ImportDecl GhcPs
i')]) [Idea] -> [Idea] -> [Idea]
forall a. [a] -> [a] -> [a]
++
(GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> [Idea])
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)] -> [Idea]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap LImportDecl GhcPs -> [Idea]
GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> [Idea]
stripRedundantAlias [LImportDecl GhcPs]
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
ms
reduceImports :: [LImportDecl GhcPs] -> [Idea]
reduceImports :: [LImportDecl GhcPs] -> [Idea]
reduceImports [] = []
reduceImports ms :: [LImportDecl GhcPs]
ms@(LImportDecl GhcPs
m:[LImportDecl GhcPs]
_) =
[Severity
-> String
-> SrcSpan
-> String
-> Maybe String
-> [Note]
-> [Refactoring SrcSpan]
-> Idea
rawIdea Severity
Hint.Type.Warning String
"Use fewer imports" (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA (GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> SrcSpanAnnA
forall l e. GenLocated l e -> l
getLoc LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
m)) ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)] -> String
f [LImportDecl GhcPs]
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
ms) (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ [GenLocated SrcSpanAnnA (ImportDecl GhcPs)] -> String
f [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
x) [] [Refactoring SrcSpan]
rs
| Just ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
x, [Refactoring SrcSpan]
rs) <- [[LImportDecl GhcPs]
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
simplify [LImportDecl GhcPs]
ms]]
where f :: [GenLocated SrcSpanAnnA (ImportDecl GhcPs)] -> String
f = [String] -> String
unlines ([String] -> String)
-> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)] -> [String])
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> String)
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> String
forall a. Outputable a => a -> String
unsafePrettyPrint
simplify :: [LImportDecl GhcPs]
-> Maybe ([LImportDecl GhcPs], [Refactoring R.SrcSpan])
simplify :: [LImportDecl GhcPs]
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
simplify [] = Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
Maybe
([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
forall a. Maybe a
Nothing
simplify (LImportDecl GhcPs
x : [LImportDecl GhcPs]
xs) = case LImportDecl GhcPs
-> [LImportDecl GhcPs]
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
simplifyHead LImportDecl GhcPs
x [LImportDecl GhcPs]
xs of
Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
Nothing -> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)])
-> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
-> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
forall a a' b. (a -> a') -> (a, b) -> (a', b)
first (LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
xGenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
forall a. a -> [a] -> [a]
:) (([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
-> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan]))
-> Maybe
([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
-> Maybe
([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [LImportDecl GhcPs]
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
simplify [LImportDecl GhcPs]
xs
Just ([LImportDecl GhcPs]
xs, [Refactoring SrcSpan]
rs) ->
let deletions :: [Refactoring SrcSpan]
deletions = (Refactoring SrcSpan -> Bool)
-> [Refactoring SrcSpan] -> [Refactoring SrcSpan]
forall a. (a -> Bool) -> [a] -> [a]
filter (\case Delete{} -> Bool
True; Refactoring SrcSpan
_ -> Bool
False) [Refactoring SrcSpan]
rs
in ([LImportDecl GhcPs], [Refactoring SrcSpan])
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
forall a. a -> Maybe a
Just (([LImportDecl GhcPs], [Refactoring SrcSpan])
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan]))
-> ([LImportDecl GhcPs], [Refactoring SrcSpan])
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
forall a b. (a -> b) -> a -> b
$ ([LImportDecl GhcPs], [Refactoring SrcSpan])
-> (([LImportDecl GhcPs], [Refactoring SrcSpan])
-> ([LImportDecl GhcPs], [Refactoring SrcSpan]))
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
-> ([LImportDecl GhcPs], [Refactoring SrcSpan])
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([LImportDecl GhcPs]
xs, [Refactoring SrcSpan]
rs) (([Refactoring SrcSpan] -> [Refactoring SrcSpan])
-> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
-> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
forall b b' a. (b -> b') -> (a, b) -> (a, b')
second ([Refactoring SrcSpan]
-> [Refactoring SrcSpan] -> [Refactoring SrcSpan]
forall a. [a] -> [a] -> [a]
++ [Refactoring SrcSpan]
deletions)) (Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
-> ([LImportDecl GhcPs], [Refactoring SrcSpan]))
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
-> ([LImportDecl GhcPs], [Refactoring SrcSpan])
forall a b. (a -> b) -> a -> b
$ [LImportDecl GhcPs]
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
simplify [LImportDecl GhcPs]
xs
simplifyHead :: LImportDecl GhcPs
-> [LImportDecl GhcPs]
-> Maybe ([LImportDecl GhcPs], [Refactoring R.SrcSpan])
simplifyHead :: LImportDecl GhcPs
-> [LImportDecl GhcPs]
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
simplifyHead LImportDecl GhcPs
x (LImportDecl GhcPs
y : [LImportDecl GhcPs]
ys) = case LImportDecl GhcPs
-> LImportDecl GhcPs
-> Maybe (LImportDecl GhcPs, [Refactoring SrcSpan])
combine LImportDecl GhcPs
x LImportDecl GhcPs
y of
Maybe (LImportDecl GhcPs, [Refactoring SrcSpan])
Nothing -> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)])
-> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
-> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
forall a a' b. (a -> a') -> (a, b) -> (a', b)
first (LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
yGenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
forall a. a -> [a] -> [a]
:) (([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
-> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan]))
-> Maybe
([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
-> Maybe
([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LImportDecl GhcPs
-> [LImportDecl GhcPs]
-> Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
simplifyHead LImportDecl GhcPs
x [LImportDecl GhcPs]
ys
Just (LImportDecl GhcPs
xy, [Refactoring SrcSpan]
rs) -> ([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
-> Maybe
([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
forall a. a -> Maybe a
Just (LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
xy GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
-> [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
forall a. a -> [a] -> [a]
: [LImportDecl GhcPs]
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
ys, [Refactoring SrcSpan]
rs)
simplifyHead LImportDecl GhcPs
x [] = Maybe ([LImportDecl GhcPs], [Refactoring SrcSpan])
Maybe
([GenLocated SrcSpanAnnA (ImportDecl GhcPs)],
[Refactoring SrcSpan])
forall a. Maybe a
Nothing
combine :: LImportDecl GhcPs
-> LImportDecl GhcPs
-> Maybe (LImportDecl GhcPs, [Refactoring R.SrcSpan])
combine :: LImportDecl GhcPs
-> LImportDecl GhcPs
-> Maybe (LImportDecl GhcPs, [Refactoring SrcSpan])
combine x :: LImportDecl GhcPs
x@(L SrcSpanAnnA
loc ImportDecl GhcPs
x') y :: LImportDecl GhcPs
y@(L SrcSpanAnnA
_ ImportDecl GhcPs
y')
| Bool
qual, Bool
as, Bool
specs = (GenLocated SrcSpanAnnA (ImportDecl GhcPs), [Refactoring SrcSpan])
-> Maybe
(GenLocated SrcSpanAnnA (ImportDecl GhcPs), [Refactoring SrcSpan])
forall a. a -> Maybe a
Just (LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
x, [RType -> SrcSpan -> Refactoring SrcSpan
forall a. RType -> a -> Refactoring a
Delete RType
Import (GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
y)])
| Bool
qual, Bool
as
, Just (Bool
False, GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)]
xs) <- (ImportListInterpretation -> Bool)
-> (ImportListInterpretation,
GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)])
-> (Bool, GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)])
forall a a' b. (a -> a') -> (a, b) -> (a', b)
first (ImportListInterpretation -> ImportListInterpretation -> Bool
forall a. Eq a => a -> a -> Bool
== ImportListInterpretation
EverythingBut) ((ImportListInterpretation,
GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)])
-> (Bool, GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)]))
-> Maybe
(ImportListInterpretation,
GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)])
-> Maybe (Bool, GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ImportDecl GhcPs
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclImportList ImportDecl GhcPs
x'
, Just (Bool
False, GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)]
ys) <- (ImportListInterpretation -> Bool)
-> (ImportListInterpretation,
GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)])
-> (Bool, GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)])
forall a a' b. (a -> a') -> (a, b) -> (a', b)
first (ImportListInterpretation -> ImportListInterpretation -> Bool
forall a. Eq a => a -> a -> Bool
== ImportListInterpretation
EverythingBut) ((ImportListInterpretation,
GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)])
-> (Bool, GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)]))
-> Maybe
(ImportListInterpretation,
GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)])
-> Maybe (Bool, GenLocated SrcSpanAnnL [XRec GhcPs (IE GhcPs)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ImportDecl GhcPs
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclImportList ImportDecl GhcPs
y' =
let newImp :: GenLocated SrcSpanAnnA (ImportDecl GhcPs)
newImp = SrcSpanAnnA
-> ImportDecl GhcPs -> GenLocated SrcSpanAnnA (ImportDecl GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
loc ImportDecl GhcPs
x'{ideclImportList = Just (Exactly, noLocA (unLoc xs ++ unLoc ys))}
in (GenLocated SrcSpanAnnA (ImportDecl GhcPs), [Refactoring SrcSpan])
-> Maybe
(GenLocated SrcSpanAnnA (ImportDecl GhcPs), [Refactoring SrcSpan])
forall a. a -> Maybe a
Just (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
newImp, [RType
-> SrcSpan -> [(String, SrcSpan)] -> String -> Refactoring SrcSpan
forall a. RType -> a -> [(String, a)] -> String -> Refactoring a
Replace RType
Import (GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
x) [] (ImportDecl GhcPs -> String
forall a. Outputable a => a -> String
unsafePrettyPrint (GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> ImportDecl GhcPs
forall l e. GenLocated l e -> e
unLoc GenLocated SrcSpanAnnA (ImportDecl GhcPs)
newImp))
, RType -> SrcSpan -> Refactoring SrcSpan
forall a. RType -> a -> Refactoring a
Delete RType
Import (GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
y)])
| Bool
qual, Bool
as, Maybe
(ImportListInterpretation,
GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)])
-> Bool
forall a. Maybe a -> Bool
isNothing (ImportDecl GhcPs
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclImportList ImportDecl GhcPs
x') Bool -> Bool -> Bool
|| Maybe
(ImportListInterpretation,
GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (IE GhcPs)])
-> Bool
forall a. Maybe a -> Bool
isNothing (ImportDecl GhcPs
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclImportList ImportDecl GhcPs
y') =
let (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
newImp, GenLocated SrcSpanAnnA (ImportDecl GhcPs)
toDelete) = if Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
-> Bool
forall a. Maybe a -> Bool
isNothing (ImportDecl GhcPs
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclImportList ImportDecl GhcPs
x') then (LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
x, LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
y) else (LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
y, LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
x)
in (GenLocated SrcSpanAnnA (ImportDecl GhcPs), [Refactoring SrcSpan])
-> Maybe
(GenLocated SrcSpanAnnA (ImportDecl GhcPs), [Refactoring SrcSpan])
forall a. a -> Maybe a
Just (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
newImp, [RType -> SrcSpan -> Refactoring SrcSpan
forall a. RType -> a -> Refactoring a
Delete RType
Import (GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA GenLocated SrcSpanAnnA (ImportDecl GhcPs)
toDelete)])
| ImportDecl GhcPs -> ImportDeclQualifiedStyle
forall pass. ImportDecl pass -> ImportDeclQualifiedStyle
ideclQualified ImportDecl GhcPs
x' ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
forall a. Eq a => a -> a -> Bool
== ImportDeclQualifiedStyle
NotQualified, Bool
qual, Bool
specs, [GenLocated SrcSpanAnnA ModuleName] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [XRec GhcPs ModuleName]
[GenLocated SrcSpanAnnA ModuleName]
ass Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 =
let (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
newImp, GenLocated SrcSpanAnnA (ImportDecl GhcPs)
toDelete) = if Maybe (XRec GhcPs ModuleName) -> Bool
forall a. Maybe a -> Bool
isJust (ImportDecl GhcPs -> Maybe (XRec GhcPs ModuleName)
forall pass. ImportDecl pass -> Maybe (XRec pass ModuleName)
ideclAs ImportDecl GhcPs
x') then (LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
x, LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
y) else (LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
y, LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
x)
in (GenLocated SrcSpanAnnA (ImportDecl GhcPs), [Refactoring SrcSpan])
-> Maybe
(GenLocated SrcSpanAnnA (ImportDecl GhcPs), [Refactoring SrcSpan])
forall a. a -> Maybe a
Just (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
newImp, [RType -> SrcSpan -> Refactoring SrcSpan
forall a. RType -> a -> Refactoring a
Delete RType
Import (GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA GenLocated SrcSpanAnnA (ImportDecl GhcPs)
toDelete)])
| Bool
otherwise = Maybe (LImportDecl GhcPs, [Refactoring SrcSpan])
Maybe
(GenLocated SrcSpanAnnA (ImportDecl GhcPs), [Refactoring SrcSpan])
forall a. Maybe a
Nothing
where
eqMaybe:: Eq a => Maybe (LocatedA a) -> Maybe (LocatedA a) -> Bool
eqMaybe :: forall a. Eq a => Maybe (LocatedA a) -> Maybe (LocatedA a) -> Bool
eqMaybe (Just LocatedA a
x) (Just LocatedA a
y) = LocatedA a
x LocatedA a -> LocatedA a -> Bool
forall a l. Eq a => GenLocated l a -> GenLocated l a -> Bool
`eqLocated` LocatedA a
y
eqMaybe Maybe (LocatedA a)
Nothing Maybe (LocatedA a)
Nothing = Bool
True
eqMaybe Maybe (LocatedA a)
_ Maybe (LocatedA a)
_ = Bool
False
qual :: Bool
qual = ImportDecl GhcPs -> ImportDeclQualifiedStyle
forall pass. ImportDecl pass -> ImportDeclQualifiedStyle
ideclQualified ImportDecl GhcPs
x' ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
forall a. Eq a => a -> a -> Bool
== ImportDecl GhcPs -> ImportDeclQualifiedStyle
forall pass. ImportDecl pass -> ImportDeclQualifiedStyle
ideclQualified ImportDecl GhcPs
y'
as :: Bool
as = ImportDecl GhcPs -> Maybe (XRec GhcPs ModuleName)
forall pass. ImportDecl pass -> Maybe (XRec pass ModuleName)
ideclAs ImportDecl GhcPs
x' Maybe (GenLocated SrcSpanAnnA ModuleName)
-> Maybe (GenLocated SrcSpanAnnA ModuleName) -> Bool
forall a. Eq a => Maybe (LocatedA a) -> Maybe (LocatedA a) -> Bool
`eqMaybe` ImportDecl GhcPs -> Maybe (XRec GhcPs ModuleName)
forall pass. ImportDecl pass -> Maybe (XRec pass ModuleName)
ideclAs ImportDecl GhcPs
y'
ass :: [XRec GhcPs ModuleName]
ass = (ImportDecl GhcPs -> Maybe (XRec GhcPs ModuleName))
-> [ImportDecl GhcPs] -> [XRec GhcPs ModuleName]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ImportDecl GhcPs -> Maybe (XRec GhcPs ModuleName)
forall pass. ImportDecl pass -> Maybe (XRec pass ModuleName)
ideclAs [ImportDecl GhcPs
x', ImportDecl GhcPs
y']
specs :: Bool
specs = (SrcSpan -> SrcSpan)
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
forall from to. Biplate from to => (to -> to) -> from -> from
transformBi (SrcSpan -> SrcSpan -> SrcSpan
forall a b. a -> b -> a
const SrcSpan
noSrcSpan) (ImportDecl GhcPs
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclImportList ImportDecl GhcPs
x') Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
-> Bool
forall a. Eq a => a -> a -> Bool
==
(SrcSpan -> SrcSpan)
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
forall from to. Biplate from to => (to -> to) -> from -> from
transformBi (SrcSpan -> SrcSpan -> SrcSpan
forall a b. a -> b -> a
const SrcSpan
noSrcSpan) (ImportDecl GhcPs
-> Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclImportList ImportDecl GhcPs
y')
stripRedundantAlias :: LImportDecl GhcPs -> [Idea]
stripRedundantAlias :: LImportDecl GhcPs -> [Idea]
stripRedundantAlias x :: LImportDecl GhcPs
x@(L SrcSpanAnnA
_ i :: ImportDecl GhcPs
i@ImportDecl {Bool
Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
Maybe (XRec GhcPs ModuleName)
ImportDeclPkgQual GhcPs
XCImportDecl GhcPs
XRec GhcPs ModuleName
IsBootInterface
ImportDeclQualifiedStyle
ideclSource :: forall pass. ImportDecl pass -> IsBootInterface
ideclName :: forall pass. ImportDecl pass -> XRec pass ModuleName
ideclPkgQual :: forall pass. ImportDecl pass -> ImportDeclPkgQual pass
ideclImportList :: forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclQualified :: forall pass. ImportDecl pass -> ImportDeclQualifiedStyle
ideclAs :: forall pass. ImportDecl pass -> Maybe (XRec pass ModuleName)
ideclExt :: XCImportDecl GhcPs
ideclName :: XRec GhcPs ModuleName
ideclPkgQual :: ImportDeclPkgQual GhcPs
ideclSource :: IsBootInterface
ideclSafe :: Bool
ideclQualified :: ImportDeclQualifiedStyle
ideclAs :: Maybe (XRec GhcPs ModuleName)
ideclImportList :: Maybe
(ImportListInterpretation, XRec GhcPs [XRec GhcPs (IE GhcPs)])
ideclExt :: forall pass. ImportDecl pass -> XCImportDecl pass
ideclSafe :: forall pass. ImportDecl pass -> Bool
..})
| ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just (GenLocated SrcSpanAnnA ModuleName -> ModuleName
forall l e. GenLocated l e -> e
unLoc XRec GhcPs ModuleName
GenLocated SrcSpanAnnA ModuleName
ideclName) Maybe ModuleName -> Maybe ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== (GenLocated SrcSpanAnnA ModuleName -> ModuleName)
-> Maybe (GenLocated SrcSpanAnnA ModuleName) -> Maybe ModuleName
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GenLocated SrcSpanAnnA ModuleName -> ModuleName
forall l e. GenLocated l e -> e
unLoc Maybe (XRec GhcPs ModuleName)
Maybe (GenLocated SrcSpanAnnA ModuleName)
ideclAs =
[String
-> Located (ImportDecl GhcPs)
-> Located (ImportDecl GhcPs)
-> [Refactoring SrcSpan]
-> Idea
forall a b.
(Outputable a, Outputable b) =>
String -> Located a -> Located b -> [Refactoring SrcSpan] -> Idea
suggest String
"Redundant as" (GenLocated SrcSpanAnnA (ImportDecl GhcPs)
-> Located (ImportDecl GhcPs)
forall a e. LocatedAn a e -> Located e
reLoc LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
x) (ImportDecl GhcPs -> Located (ImportDecl GhcPs)
forall e. e -> Located e
noLoc ImportDecl GhcPs
i{ideclAs=Nothing} :: Located (ImportDecl GhcPs)) [SrcSpan -> Refactoring SrcSpan
forall a. a -> Refactoring a
RemoveAsKeyword (GenLocated SrcSpanAnnA (ImportDecl GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
toSSA LImportDecl GhcPs
GenLocated SrcSpanAnnA (ImportDecl GhcPs)
x)]]
stripRedundantAlias LImportDecl GhcPs
_ = []