{-# 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 = Just (noLocA [noLocA (IEModuleContents (Nothing, EpAnnNotUsed) name)] )} in
[(String
-> GenLocated SrcSpan (HsModule GhcPs)
-> GenLocated SrcSpan (HsModule GhcPs)
-> [Refactoring SrcSpan]
-> Idea
forall a.
Outputable a =>
String -> Located a -> Located a -> [Refactoring SrcSpan] -> Idea
ignore String
"Use module export list" (SrcSpan -> HsModule GhcPs -> GenLocated SrcSpan (HsModule GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
s HsModule GhcPs
o) (HsModule GhcPs -> GenLocated SrcSpan (HsModule GhcPs)
forall e. e -> Located e
noLoc HsModule GhcPs
r) []){ideaNote = [Note "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, LocatedAn AnnListItem (IE GhcPs) -> Bool
forall {l} {pass}. GenLocated l (IE pass) -> Bool
isMod LocatedAn AnnListItem (IE GhcPs)
x]
, String
modName <- ModuleName -> String
moduleNameString (GenLocated SrcSpanAnnA ModuleName -> ModuleName
forall l e. GenLocated l e -> e
unLoc XRec GhcPs ModuleName
GenLocated SrcSpanAnnA ModuleName
name)
, [String]
names <- [ ModuleName -> String
moduleNameString (GenLocated SrcSpanAnnA ModuleName -> ModuleName
forall l e. GenLocated l e -> e
unLoc XRec GhcPs ModuleName
GenLocated SrcSpanAnnA 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 (String -> LocatedAn AnnListItem (IE GhcPs) -> Bool
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 String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
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 = Just (noLocA (noLocA (IEVar Nothing (noLocA (IEName noExtField (noLocA dots)))) : exports') )}
in
[String
-> GenLocated SrcSpan (HsModule GhcPs)
-> GenLocated SrcSpan (HsModule GhcPs)
-> [Refactoring SrcSpan]
-> Idea
forall a.
Outputable a =>
String -> Located a -> Located a -> [Refactoring SrcSpan] -> Idea
ignore String
"Use explicit module export list" (SrcSpan -> HsModule GhcPs -> GenLocated SrcSpan (HsModule GhcPs)
forall l e. l -> e -> GenLocated l e
L SrcSpan
s HsModule GhcPs
o) (HsModule GhcPs -> GenLocated SrcSpan (HsModule GhcPs)
forall e. e -> Located e
noLoc HsModule GhcPs
r) []]
where
o :: HsModule GhcPs
o = HsModule GhcPs
m{hsmodImports=[], 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 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
m
matchesModName String
_ GenLocated l (IE pass)
_ = Bool
False
exportHint Scope
_ ModuleEx
_ = []