{-# LANGUAGE TypeFamilies #-}
module Hint.Export(exportHint) where
import Hint.Type(ModuHint, ModuleEx(..),ideaNote,ignore,Note(..))
import GHC.Hs
import GHC.Types.SrcLoc
import GHC.Types.Name.Occurrence
import GHC.Types.Name.Reader
exportHint :: ModuHint
exportHint :: ModuHint
exportHint Scope
_ (ModuleEx (L SrcSpan
s m :: HsModule GhcPs
m@HsModule {hsmodName :: forall p. HsModule p -> Maybe (XRec p ModuleName)
hsmodName = Just XRec GhcPs ModuleName
name, hsmodExports :: forall p. HsModule p -> Maybe (XRec p [LIE p])
hsmodExports = Maybe (XRec GhcPs [LIE GhcPs])
exports}) )
| Maybe (XRec GhcPs [LIE GhcPs])
Nothing <- Maybe (XRec GhcPs [LIE GhcPs])
exports =
let r :: HsModule GhcPs
r = HsModule GhcPs
o{ hsmodExports :: Maybe (XRec GhcPs [LIE GhcPs])
hsmodExports = forall a. a -> Maybe a
Just (forall a an. a -> LocatedAn an a
noLocA [forall a an. a -> LocatedAn an a
noLocA (forall pass.
XIEModuleContents pass -> XRec pass ModuleName -> IE pass
IEModuleContents forall ann. EpAnn ann
EpAnnNotUsed XRec GhcPs ModuleName
name)] )} in
[(forall a.
Outputable a =>
String -> Located a -> Located a -> [Refactoring SrcSpan] -> Idea
ignore String
"Use module export list" (forall l e. l -> e -> GenLocated l e
L SrcSpan
s HsModule GhcPs
o) (forall e. e -> Located e
noLoc HsModule GhcPs
r) []){ideaNote :: [Note]
ideaNote = [String -> Note
Note String
"an explicit list is usually better"]}]
| Just (L SrcSpanAnnL
_ [LocatedAn AnnListItem (IE GhcPs)]
xs) <- Maybe (XRec GhcPs [LIE GhcPs])
exports
, [LocatedAn AnnListItem (IE GhcPs)]
mods <- [LocatedAn AnnListItem (IE GhcPs)
x | LocatedAn AnnListItem (IE GhcPs)
x <- [LocatedAn AnnListItem (IE GhcPs)]
xs, forall {l} {pass}. GenLocated l (IE pass) -> Bool
isMod LocatedAn AnnListItem (IE GhcPs)
x]
, String
modName <- ModuleName -> String
moduleNameString (forall l e. GenLocated l e -> e
unLoc XRec GhcPs ModuleName
name)
, [String]
names <- [ ModuleName -> String
moduleNameString (forall l e. GenLocated l e -> e
unLoc XRec GhcPs ModuleName
n) | (L SrcSpanAnnA
_ (IEModuleContents XIEModuleContents GhcPs
_ XRec GhcPs ModuleName
n)) <- [LocatedAn AnnListItem (IE GhcPs)]
mods]
, [LocatedAn AnnListItem (IE GhcPs)]
exports' <- [LocatedAn AnnListItem (IE GhcPs)
x | LocatedAn AnnListItem (IE GhcPs)
x <- [LocatedAn AnnListItem (IE GhcPs)]
xs, Bool -> Bool
not (forall {pass} {l} {l}.
(XRec pass ModuleName ~ GenLocated l ModuleName) =>
String -> GenLocated l (IE pass) -> Bool
matchesModName String
modName LocatedAn AnnListItem (IE GhcPs)
x)]
, String
modName forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
names =
let dots :: RdrName
dots = OccName -> RdrName
mkRdrUnqual (String -> OccName
mkVarOcc String
" ... ")
r :: HsModule GhcPs
r = HsModule GhcPs
o{ hsmodExports :: Maybe (XRec GhcPs [LIE GhcPs])
hsmodExports = forall a. a -> Maybe a
Just (forall a an. a -> LocatedAn an a
noLocA (forall a an. a -> LocatedAn an a
noLocA (forall pass. XIEVar pass -> LIEWrappedName pass -> IE pass
IEVar NoExtField
noExtField (forall a an. a -> LocatedAn an a
noLocA (forall p. XIEName p -> LIdP p -> IEWrappedName p
IEName NoExtField
noExtField (forall a an. a -> LocatedAn an a
noLocA RdrName
dots)))) forall a. a -> [a] -> [a]
: [LocatedAn AnnListItem (IE GhcPs)]
exports') )}
in
[forall a.
Outputable a =>
String -> Located a -> Located a -> [Refactoring SrcSpan] -> Idea
ignore String
"Use explicit module export list" (forall l e. l -> e -> GenLocated l e
L SrcSpan
s HsModule GhcPs
o) (forall e. e -> Located e
noLoc HsModule GhcPs
r) []]
where
o :: HsModule GhcPs
o = HsModule GhcPs
m{hsmodImports :: [LImportDecl GhcPs]
hsmodImports=[], hsmodDecls :: [LHsDecl GhcPs]
hsmodDecls=[] }
isMod :: GenLocated l (IE pass) -> Bool
isMod (L l
_ (IEModuleContents XIEModuleContents pass
_ XRec pass ModuleName
_)) = Bool
True
isMod GenLocated l (IE pass)
_ = Bool
False
matchesModName :: String -> GenLocated l (IE pass) -> Bool
matchesModName String
m (L l
_ (IEModuleContents XIEModuleContents pass
_ (L l
_ ModuleName
n))) = ModuleName -> String
moduleNameString ModuleName
n forall a. Eq a => a -> a -> Bool
== String
m
matchesModName String
_ GenLocated l (IE pass)
_ = Bool
False
exportHint Scope
_ ModuleEx
_ = []