{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
module GHC.Tc.Gen.Export (rnExports, exports_from_avail) where
import GHC.Prelude
import GHC.Hs
import GHC.Types.FieldLabel
import GHC.Builtin.Names
import GHC.Tc.Errors.Types
import GHC.Tc.Utils.Monad
import GHC.Tc.Utils.Env
import GHC.Tc.Utils.TcType
import GHC.Rename.Names
import GHC.Rename.Env
import GHC.Rename.Unbound ( reportUnboundName )
import GHC.Utils.Error
import GHC.Unit.Module
import GHC.Unit.Module.Imported
import GHC.Core.TyCon
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Core.ConLike
import GHC.Core.PatSyn
import GHC.Data.Maybe
import GHC.Data.FastString (fsLit)
import GHC.Driver.Env
import GHC.Types.Unique.Set
import GHC.Types.SrcLoc as SrcLoc
import GHC.Types.Name
import GHC.Types.Name.Env
import GHC.Types.Name.Set
import GHC.Types.Avail
import GHC.Types.SourceFile
import GHC.Types.Id
import GHC.Types.Id.Info
import GHC.Types.Name.Reader
import Control.Monad
import GHC.Driver.Session
import GHC.Parser.PostProcess ( setRdrNameSpace )
import Data.Either ( partitionEithers )
import GHC.Rename.Doc
data ExportAccum
= ExportAccum
ExportOccMap
(UniqSet ModuleName)
emptyExportAccum :: ExportAccum
emptyExportAccum :: ExportAccum
emptyExportAccum = ExportOccMap -> UniqSet ModuleName -> ExportAccum
ExportAccum ExportOccMap
forall a. OccEnv a
emptyOccEnv UniqSet ModuleName
forall a. UniqSet a
emptyUniqSet
accumExports :: (ExportAccum -> x -> TcRn (Maybe (ExportAccum, y)))
-> [x]
-> TcRn [y]
accumExports :: forall x y.
(ExportAccum -> x -> TcRn (Maybe (ExportAccum, y)))
-> [x] -> TcRn [y]
accumExports ExportAccum -> x -> TcRn (Maybe (ExportAccum, y))
f = ((ExportAccum, [Maybe y]) -> [y])
-> IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, [Maybe y])
-> IOEnv (Env TcGblEnv TcLclEnv) [y]
forall a b.
(a -> b)
-> IOEnv (Env TcGblEnv TcLclEnv) a
-> IOEnv (Env TcGblEnv TcLclEnv) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Maybe y] -> [y]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe y] -> [y])
-> ((ExportAccum, [Maybe y]) -> [Maybe y])
-> (ExportAccum, [Maybe y])
-> [y]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ExportAccum, [Maybe y]) -> [Maybe y]
forall a b. (a, b) -> b
snd) (IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, [Maybe y])
-> IOEnv (Env TcGblEnv TcLclEnv) [y])
-> ([x] -> IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, [Maybe y]))
-> [x]
-> IOEnv (Env TcGblEnv TcLclEnv) [y]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ExportAccum
-> x -> IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, Maybe y))
-> ExportAccum
-> [x]
-> IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, [Maybe y])
forall (m :: * -> *) (t :: * -> *) acc x y.
(Monad m, Traversable t) =>
(acc -> x -> m (acc, y)) -> acc -> t x -> m (acc, t y)
mapAccumLM ExportAccum
-> x -> IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, Maybe y)
f' ExportAccum
emptyExportAccum
where f' :: ExportAccum
-> x -> IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, Maybe y)
f' ExportAccum
acc x
x = do
Maybe (Maybe (ExportAccum, y))
m <- TcRn (Maybe (ExportAccum, y))
-> TcRn (Maybe (Maybe (ExportAccum, y)))
forall r. TcRn r -> TcRn (Maybe r)
attemptM (ExportAccum -> x -> TcRn (Maybe (ExportAccum, y))
f ExportAccum
acc x
x)
(ExportAccum, Maybe y)
-> IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, Maybe y)
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((ExportAccum, Maybe y)
-> IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, Maybe y))
-> (ExportAccum, Maybe y)
-> IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, Maybe y)
forall a b. (a -> b) -> a -> b
$ case Maybe (Maybe (ExportAccum, y))
m of
Just (Just (ExportAccum
acc', y
y)) -> (ExportAccum
acc', y -> Maybe y
forall a. a -> Maybe a
Just y
y)
Maybe (Maybe (ExportAccum, y))
_ -> (ExportAccum
acc, Maybe y
forall a. Maybe a
Nothing)
type ExportOccMap = OccEnv (GreName, IE GhcPs)
rnExports :: Bool
-> Maybe (LocatedL [LIE GhcPs])
-> RnM TcGblEnv
rnExports :: Bool -> Maybe (LocatedL [LIE GhcPs]) -> RnM TcGblEnv
rnExports Bool
explicit_mod Maybe (LocatedL [LIE GhcPs])
exports
= RnM TcGblEnv -> RnM TcGblEnv
forall r. TcM r -> TcM r
checkNoErrs (RnM TcGblEnv -> RnM TcGblEnv) -> RnM TcGblEnv -> RnM TcGblEnv
forall a b. (a -> b) -> a -> b
$
WarningFlag -> RnM TcGblEnv -> RnM TcGblEnv
forall gbl lcl a.
WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
unsetWOptM WarningFlag
Opt_WarnWarningsDeprecations (RnM TcGblEnv -> RnM TcGblEnv) -> RnM TcGblEnv -> RnM TcGblEnv
forall a b. (a -> b) -> a -> b
$
do { HscEnv
hsc_env <- TcRnIf TcGblEnv TcLclEnv HscEnv
forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
; TcGblEnv
tcg_env <- RnM TcGblEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
; let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
TcGblEnv { tcg_mod :: TcGblEnv -> Module
tcg_mod = Module
this_mod
, tcg_rdr_env :: TcGblEnv -> GlobalRdrEnv
tcg_rdr_env = GlobalRdrEnv
rdr_env
, tcg_imports :: TcGblEnv -> ImportAvails
tcg_imports = ImportAvails
imports
, tcg_src :: TcGblEnv -> HscSource
tcg_src = HscSource
hsc_src } = TcGblEnv
tcg_env
default_main :: RdrName
default_main | HomeUnitEnv -> Module
mainModIs (HscEnv -> HomeUnitEnv
hsc_HUE HscEnv
hsc_env) Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
this_mod
, Just String
main_fun <- DynFlags -> Maybe String
mainFunIs DynFlags
dflags
= NameSpace -> FastString -> RdrName
mkUnqual NameSpace
varName (String -> FastString
fsLit String
main_fun)
| Bool
otherwise
= RdrName
main_RDR_Unqual
; Bool
has_main <- (Bool -> Bool
not (Bool -> Bool) -> ([Name] -> Bool) -> [Name] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Name] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) ([Name] -> Bool)
-> IOEnv (Env TcGblEnv TcLclEnv) [Name]
-> IOEnv (Env TcGblEnv TcLclEnv) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RdrName -> IOEnv (Env TcGblEnv TcLclEnv) [Name]
lookupInfoOccRn RdrName
default_main
; let real_exports :: Maybe (LocatedL [LIE GhcPs])
real_exports
| Bool
explicit_mod = Maybe (LocatedL [LIE GhcPs])
exports
| Bool
has_main
= LocatedAn AnnList [LocatedAn AnnListItem (IE GhcPs)]
-> Maybe (LocatedAn AnnList [LocatedAn AnnListItem (IE GhcPs)])
forall a. a -> Maybe a
Just ([LocatedAn AnnListItem (IE GhcPs)]
-> LocatedAn AnnList [LocatedAn AnnListItem (IE GhcPs)]
forall a an. a -> LocatedAn an a
noLocA [IE GhcPs -> LocatedAn AnnListItem (IE GhcPs)
forall a an. a -> LocatedAn an a
noLocA (XIEVar GhcPs -> LIEWrappedName GhcPs -> IE GhcPs
forall pass. XIEVar pass -> LIEWrappedName pass -> IE pass
IEVar XIEVar GhcPs
NoExtField
noExtField
(IEWrappedName GhcPs -> LocatedAn AnnListItem (IEWrappedName GhcPs)
forall a an. a -> LocatedAn an a
noLocA (XIEName GhcPs -> LIdP GhcPs -> IEWrappedName GhcPs
forall p. XIEName p -> LIdP p -> IEWrappedName p
IEName XIEName GhcPs
NoExtField
noExtField (LIdP GhcPs -> IEWrappedName GhcPs)
-> LIdP GhcPs -> IEWrappedName GhcPs
forall a b. (a -> b) -> a -> b
$ RdrName -> GenLocated SrcSpanAnnN RdrName
forall a an. a -> LocatedAn an a
noLocA RdrName
default_main)))])
| Bool
otherwise = Maybe (LocatedL [LIE GhcPs])
Maybe (LocatedAn AnnList [LocatedAn AnnListItem (IE GhcPs)])
forall a. Maybe a
Nothing
; let do_it :: RnM (Maybe [(LIE GhcRn, [AvailInfo])], [AvailInfo])
do_it = Maybe (LocatedL [LIE GhcPs])
-> GlobalRdrEnv
-> ImportAvails
-> Module
-> RnM (Maybe [(LIE GhcRn, [AvailInfo])], [AvailInfo])
exports_from_avail Maybe (LocatedL [LIE GhcPs])
real_exports GlobalRdrEnv
rdr_env ImportAvails
imports Module
this_mod
; (Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
rn_exports, [AvailInfo]
final_avails)
<- if HscSource
hsc_src HscSource -> HscSource -> Bool
forall a. Eq a => a -> a -> Bool
== HscSource
HsigFile
then do (Maybe
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
mb_r, Messages TcRnMessage
msgs) <- IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
-> TcRn
(Maybe
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo]),
Messages TcRnMessage)
forall a. TcRn a -> TcRn (Maybe a, Messages TcRnMessage)
tryTc RnM (Maybe [(LIE GhcRn, [AvailInfo])], [AvailInfo])
IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
do_it
case Maybe
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
mb_r of
Just (Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
r -> (Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
-> IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
r
Maybe
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
Nothing -> Messages TcRnMessage -> TcRn ()
addMessages Messages TcRnMessage
msgs TcRn ()
-> IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
-> IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
forall a b.
IOEnv (Env TcGblEnv TcLclEnv) a
-> IOEnv (Env TcGblEnv TcLclEnv) b
-> IOEnv (Env TcGblEnv TcLclEnv) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
forall env a. IOEnv env a
failM
else IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
-> IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
forall r. TcM r -> TcM r
checkNoErrs RnM (Maybe [(LIE GhcRn, [AvailInfo])], [AvailInfo])
IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
do_it
; let final_ns :: NameSet
final_ns = [AvailInfo] -> NameSet
availsToNameSetWithSelectors [AvailInfo]
final_avails
; String -> SDoc -> TcRn ()
traceRn String
"rnExports: Exports:" ([AvailInfo] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [AvailInfo]
final_avails)
; TcGblEnv -> RnM TcGblEnv
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (TcGblEnv
tcg_env { tcg_exports = final_avails
, tcg_rn_exports = case tcg_rn_exports tcg_env of
Maybe [(LIE GhcRn, [AvailInfo])]
Nothing -> Maybe [(LIE GhcRn, [AvailInfo])]
Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
forall a. Maybe a
Nothing
Just [(LIE GhcRn, [AvailInfo])]
_ -> Maybe [(LIE GhcRn, [AvailInfo])]
Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
rn_exports
, tcg_dus = tcg_dus tcg_env `plusDU`
usesOnly final_ns }) }
exports_from_avail :: Maybe (LocatedL [LIE GhcPs])
-> GlobalRdrEnv
-> ImportAvails
-> Module
-> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
exports_from_avail :: Maybe (LocatedL [LIE GhcPs])
-> GlobalRdrEnv
-> ImportAvails
-> Module
-> RnM (Maybe [(LIE GhcRn, [AvailInfo])], [AvailInfo])
exports_from_avail Maybe (LocatedL [LIE GhcPs])
Nothing GlobalRdrEnv
rdr_env ImportAvails
_imports Module
_this_mod
= do {
; TcRnMessage -> TcRn ()
addDiagnostic
(ModuleName -> TcRnMessage
TcRnMissingExportList (ModuleName -> TcRnMessage) -> ModuleName -> TcRnMessage
forall a b. (a -> b) -> a -> b
$ Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
_this_mod)
; let avails :: [AvailInfo]
avails =
(AvailInfo -> AvailInfo) -> [AvailInfo] -> [AvailInfo]
forall a b. (a -> b) -> [a] -> [b]
map AvailInfo -> AvailInfo
fix_faminst ([AvailInfo] -> [AvailInfo])
-> (GlobalRdrEnv -> [AvailInfo]) -> GlobalRdrEnv -> [AvailInfo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [GlobalRdrElt] -> [AvailInfo]
gresToAvailInfo
([GlobalRdrElt] -> [AvailInfo])
-> (GlobalRdrEnv -> [GlobalRdrElt]) -> GlobalRdrEnv -> [AvailInfo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GlobalRdrElt -> Bool) -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. (a -> Bool) -> [a] -> [a]
filter GlobalRdrElt -> Bool
isLocalGRE ([GlobalRdrElt] -> [GlobalRdrElt])
-> (GlobalRdrEnv -> [GlobalRdrElt])
-> GlobalRdrEnv
-> [GlobalRdrElt]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts (GlobalRdrEnv -> [AvailInfo]) -> GlobalRdrEnv -> [AvailInfo]
forall a b. (a -> b) -> a -> b
$ GlobalRdrEnv
rdr_env
; (Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
-> IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
forall a. Maybe a
Nothing, [AvailInfo]
avails) }
where
fix_faminst :: AvailInfo -> AvailInfo
fix_faminst avail :: AvailInfo
avail@(AvailTC Name
n [GreName]
ns)
| AvailInfo -> Bool
availExportsDecl AvailInfo
avail = AvailInfo
avail
| Bool
otherwise = Name -> [GreName] -> AvailInfo
AvailTC Name
n (Name -> GreName
NormalGreName Name
nGreName -> [GreName] -> [GreName]
forall a. a -> [a] -> [a]
:[GreName]
ns)
fix_faminst AvailInfo
avail = AvailInfo
avail
exports_from_avail (Just (L SrcSpanAnnL
_ [LIE GhcPs]
rdr_items)) GlobalRdrEnv
rdr_env ImportAvails
imports Module
this_mod
= do [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
ie_avails <- (ExportAccum
-> LocatedAn AnnListItem (IE GhcPs)
-> TcRn
(Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))))
-> [LocatedAn AnnListItem (IE GhcPs)]
-> TcRn [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
forall x y.
(ExportAccum -> x -> TcRn (Maybe (ExportAccum, y)))
-> [x] -> TcRn [y]
accumExports ExportAccum
-> LIE GhcPs -> RnM (Maybe (ExportAccum, (LIE GhcRn, [AvailInfo])))
ExportAccum
-> LocatedAn AnnListItem (IE GhcPs)
-> TcRn
(Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])))
do_litem [LIE GhcPs]
[LocatedAn AnnListItem (IE GhcPs)]
rdr_items
let final_exports :: [AvailInfo]
final_exports = [AvailInfo] -> [AvailInfo]
nubAvails (((GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]) -> [AvailInfo])
-> [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
-> [AvailInfo]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]) -> [AvailInfo]
forall a b. (a, b) -> b
snd [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
ie_avails)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
-> IOEnv
(Env TcGblEnv TcLclEnv)
(Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])],
[AvailInfo])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ([(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
-> Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
forall a. a -> Maybe a
Just [(GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])]
ie_avails, [AvailInfo]
final_exports)
where
do_litem :: ExportAccum -> LIE GhcPs
-> RnM (Maybe (ExportAccum, (LIE GhcRn, Avails)))
do_litem :: ExportAccum
-> LIE GhcPs -> RnM (Maybe (ExportAccum, (LIE GhcRn, [AvailInfo])))
do_litem ExportAccum
acc LIE GhcPs
lie = SrcSpan
-> TcRn
(Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])))
-> TcRn
(Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])))
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan (LocatedAn AnnListItem (IE GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
getLocA LIE GhcPs
LocatedAn AnnListItem (IE GhcPs)
lie) (ExportAccum
-> LIE GhcPs -> RnM (Maybe (ExportAccum, (LIE GhcRn, [AvailInfo])))
exports_from_item ExportAccum
acc LIE GhcPs
lie)
kids_env :: NameEnv [GlobalRdrElt]
kids_env :: NameEnv [GlobalRdrElt]
kids_env = [GlobalRdrElt] -> NameEnv [GlobalRdrElt]
mkChildEnv (GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts GlobalRdrEnv
rdr_env)
expand_tyty_gre :: GlobalRdrElt -> [GlobalRdrElt]
expand_tyty_gre :: GlobalRdrElt -> [GlobalRdrElt]
expand_tyty_gre (gre :: GlobalRdrElt
gre@GRE { gre_par :: GlobalRdrElt -> Parent
gre_par = ParentIs Name
p })
| Name -> Bool
isTyConName Name
p, Name -> Bool
isTyConName (GlobalRdrElt -> Name
greMangledName GlobalRdrElt
gre) = [GlobalRdrElt
gre, GlobalRdrElt
gre{ gre_par = NoParent }]
expand_tyty_gre GlobalRdrElt
gre = [GlobalRdrElt
gre]
imported_modules :: [ModuleName]
imported_modules = [ ImportedModsVal -> ModuleName
imv_name ImportedModsVal
imv
| [ImportedBy]
xs <- ModuleEnv [ImportedBy] -> [[ImportedBy]]
forall a. ModuleEnv a -> [a]
moduleEnvElts (ModuleEnv [ImportedBy] -> [[ImportedBy]])
-> ModuleEnv [ImportedBy] -> [[ImportedBy]]
forall a b. (a -> b) -> a -> b
$ ImportAvails -> ModuleEnv [ImportedBy]
imp_mods ImportAvails
imports
, ImportedModsVal
imv <- [ImportedBy] -> [ImportedModsVal]
importedByUser [ImportedBy]
xs ]
exports_from_item :: ExportAccum -> LIE GhcPs
-> RnM (Maybe (ExportAccum, (LIE GhcRn, Avails)))
exports_from_item :: ExportAccum
-> LIE GhcPs -> RnM (Maybe (ExportAccum, (LIE GhcRn, [AvailInfo])))
exports_from_item (ExportAccum ExportOccMap
occs UniqSet ModuleName
earlier_mods)
(L SrcSpanAnnA
loc ie :: IE GhcPs
ie@(IEModuleContents XIEModuleContents GhcPs
_ lmod :: XRec GhcPs ModuleName
lmod@(L SrcSpanAnnA
_ ModuleName
mod)))
| ModuleName
mod ModuleName -> UniqSet ModuleName -> Bool
forall a. Uniquable a => a -> UniqSet a -> Bool
`elementOfUniqSet` UniqSet ModuleName
earlier_mods
= do { TcRnMessage -> TcRn ()
addDiagnostic (ModuleName -> TcRnMessage
TcRnDupeModuleExport ModuleName
mod) ;
Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
-> TcRn
(Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
forall a. Maybe a
Nothing }
| Bool
otherwise
= do { let { exportValid :: Bool
exportValid = (ModuleName
mod ModuleName -> [ModuleName] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ModuleName]
imported_modules)
Bool -> Bool -> Bool
|| (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
this_mod ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName
mod)
; gre_prs :: [(GlobalRdrElt, GlobalRdrElt)]
gre_prs = ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)]
pickGREsModExp ModuleName
mod (GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts GlobalRdrEnv
rdr_env)
; new_exports :: [AvailInfo]
new_exports = [ GlobalRdrElt -> AvailInfo
availFromGRE GlobalRdrElt
gre'
| (GlobalRdrElt
gre, GlobalRdrElt
_) <- [(GlobalRdrElt, GlobalRdrElt)]
gre_prs
, GlobalRdrElt
gre' <- GlobalRdrElt -> [GlobalRdrElt]
expand_tyty_gre GlobalRdrElt
gre ]
; all_gres :: [GlobalRdrElt]
all_gres = ((GlobalRdrElt, GlobalRdrElt) -> [GlobalRdrElt] -> [GlobalRdrElt])
-> [GlobalRdrElt]
-> [(GlobalRdrElt, GlobalRdrElt)]
-> [GlobalRdrElt]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\(GlobalRdrElt
gre1,GlobalRdrElt
gre2) [GlobalRdrElt]
gres -> GlobalRdrElt
gre1 GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. a -> [a] -> [a]
: GlobalRdrElt
gre2 GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. a -> [a] -> [a]
: [GlobalRdrElt]
gres) [] [(GlobalRdrElt, GlobalRdrElt)]
gre_prs
; mods :: UniqSet ModuleName
mods = UniqSet ModuleName -> ModuleName -> UniqSet ModuleName
forall a. Uniquable a => UniqSet a -> a -> UniqSet a
addOneToUniqSet UniqSet ModuleName
earlier_mods ModuleName
mod
}
; Bool -> TcRnMessage -> TcRn ()
checkErr Bool
exportValid (ModuleName -> TcRnMessage
TcRnExportedModNotImported ModuleName
mod)
; Bool -> TcRnMessage -> TcRn ()
warnIf (Bool
exportValid Bool -> Bool -> Bool
&& [(GlobalRdrElt, GlobalRdrElt)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(GlobalRdrElt, GlobalRdrElt)]
gre_prs) (ModuleName -> TcRnMessage
TcRnNullExportedModule ModuleName
mod)
; String -> SDoc -> TcRn ()
traceRn String
"efa" (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ [GlobalRdrElt] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [GlobalRdrElt]
all_gres)
; [GlobalRdrElt] -> TcRn ()
addUsedGREs [GlobalRdrElt]
all_gres
; ExportOccMap
occs' <- IE GhcPs -> ExportOccMap -> [AvailInfo] -> RnM ExportOccMap
check_occs IE GhcPs
ie ExportOccMap
occs [AvailInfo]
new_exports
; String -> SDoc -> TcRn ()
traceRn String
"export_mod"
([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod
, [AvailInfo] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [AvailInfo]
new_exports ])
; Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
-> TcRn
(Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ((ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
-> Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
forall a. a -> Maybe a
Just ( ExportOccMap -> UniqSet ModuleName -> ExportAccum
ExportAccum ExportOccMap
occs' UniqSet ModuleName
mods
, ( SrcSpanAnnA -> IE GhcRn -> GenLocated SrcSpanAnnA (IE GhcRn)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
loc (XIEModuleContents GhcRn -> XRec GhcRn ModuleName -> IE GhcRn
forall pass.
XIEModuleContents pass -> XRec pass ModuleName -> IE pass
IEModuleContents XIEModuleContents GhcRn
NoExtField
noExtField XRec GhcPs ModuleName
XRec GhcRn ModuleName
lmod)
, [AvailInfo]
new_exports))) }
exports_from_item acc :: ExportAccum
acc@(ExportAccum ExportOccMap
occs UniqSet ModuleName
mods) (L SrcSpanAnnA
loc IE GhcPs
ie) = do
Maybe (IE GhcRn)
m_new_ie <- IE GhcPs -> RnM (Maybe (IE GhcRn))
lookup_doc_ie IE GhcPs
ie
case Maybe (IE GhcRn)
m_new_ie of
Just IE GhcRn
new_ie -> Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
-> TcRn
(Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ((ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
-> Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
forall a. a -> Maybe a
Just (ExportAccum
acc, (SrcSpanAnnA -> IE GhcRn -> GenLocated SrcSpanAnnA (IE GhcRn)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
loc IE GhcRn
new_ie, [])))
Maybe (IE GhcRn)
Nothing -> do
(IE GhcRn
new_ie, AvailInfo
avail) <- IE GhcPs -> RnM (IE GhcRn, AvailInfo)
lookup_ie IE GhcPs
ie
if Name -> Bool
isUnboundName (IE GhcRn -> IdP GhcRn
forall (p :: Pass). IE (GhcPass p) -> IdP (GhcPass p)
ieName IE GhcRn
new_ie)
then Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
-> TcRn
(Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
forall a. Maybe a
Nothing
else do
ExportOccMap
occs' <- IE GhcPs -> ExportOccMap -> [AvailInfo] -> RnM ExportOccMap
check_occs IE GhcPs
ie ExportOccMap
occs [AvailInfo
avail]
Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
-> TcRn
(Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo])))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ((ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
-> Maybe
(ExportAccum, (GenLocated SrcSpanAnnA (IE GhcRn), [AvailInfo]))
forall a. a -> Maybe a
Just ( ExportOccMap -> UniqSet ModuleName -> ExportAccum
ExportAccum ExportOccMap
occs' UniqSet ModuleName
mods
, (SrcSpanAnnA -> IE GhcRn -> GenLocated SrcSpanAnnA (IE GhcRn)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
loc IE GhcRn
new_ie, [AvailInfo
avail])))
lookup_ie :: IE GhcPs -> RnM (IE GhcRn, AvailInfo)
lookup_ie :: IE GhcPs -> RnM (IE GhcRn, AvailInfo)
lookup_ie (IEVar XIEVar GhcPs
_ (L SrcSpanAnnA
l IEWrappedName GhcPs
rdr))
= do (Name
name, AvailInfo
avail) <- RdrName -> RnM (Name, AvailInfo)
lookupGreAvailRn (RdrName -> RnM (Name, AvailInfo))
-> RdrName -> RnM (Name, AvailInfo)
forall a b. (a -> b) -> a -> b
$ IEWrappedName GhcPs -> IdP GhcPs
forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p)
ieWrappedName IEWrappedName GhcPs
rdr
(IE GhcRn, AvailInfo) -> RnM (IE GhcRn, AvailInfo)
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEVar GhcRn -> LIEWrappedName GhcRn -> IE GhcRn
forall pass. XIEVar pass -> LIEWrappedName pass -> IE pass
IEVar XIEVar GhcRn
NoExtField
noExtField (SrcSpanAnnA
-> IEWrappedName GhcRn
-> GenLocated SrcSpanAnnA (IEWrappedName GhcRn)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l (IEWrappedName GhcPs -> IdP GhcRn -> IEWrappedName GhcRn
replaceWrappedName IEWrappedName GhcPs
rdr IdP GhcRn
Name
name)), AvailInfo
avail)
lookup_ie (IEThingAbs XIEThingAbs GhcPs
_ (L SrcSpanAnnA
l IEWrappedName GhcPs
rdr))
= do (Name
name, AvailInfo
avail) <- RdrName -> RnM (Name, AvailInfo)
lookupGreAvailRn (RdrName -> RnM (Name, AvailInfo))
-> RdrName -> RnM (Name, AvailInfo)
forall a b. (a -> b) -> a -> b
$ IEWrappedName GhcPs -> IdP GhcPs
forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p)
ieWrappedName IEWrappedName GhcPs
rdr
(IE GhcRn, AvailInfo) -> RnM (IE GhcRn, AvailInfo)
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEThingAbs GhcRn -> LIEWrappedName GhcRn -> IE GhcRn
forall pass. XIEThingAbs pass -> LIEWrappedName pass -> IE pass
IEThingAbs XIEThingAbs GhcRn
EpAnn [AddEpAnn]
forall a. EpAnn a
noAnn (SrcSpanAnnA
-> IEWrappedName GhcRn
-> GenLocated SrcSpanAnnA (IEWrappedName GhcRn)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l (IEWrappedName GhcPs -> IdP GhcRn -> IEWrappedName GhcRn
replaceWrappedName IEWrappedName GhcPs
rdr IdP GhcRn
Name
name))
, AvailInfo
avail)
lookup_ie ie :: IE GhcPs
ie@(IEThingAll XIEThingAll GhcPs
_ LIEWrappedName GhcPs
n')
= do
(Located Name
n, [Name]
avail, [FieldLabel]
flds) <- IE GhcPs
-> LIEWrappedName GhcPs -> RnM (Located Name, [Name], [FieldLabel])
lookup_ie_all IE GhcPs
ie LIEWrappedName GhcPs
n'
let name :: Name
name = Located Name -> Name
forall l e. GenLocated l e -> e
unLoc Located Name
n
(IE GhcRn, AvailInfo) -> RnM (IE GhcRn, AvailInfo)
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEThingAll GhcRn -> LIEWrappedName GhcRn -> IE GhcRn
forall pass. XIEThingAll pass -> LIEWrappedName pass -> IE pass
IEThingAll XIEThingAll GhcRn
EpAnn [AddEpAnn]
forall a. EpAnn a
noAnn (LIEWrappedName GhcPs -> IdP GhcRn -> LIEWrappedName GhcRn
replaceLWrappedName LIEWrappedName GhcPs
n' (Located Name -> Name
forall l e. GenLocated l e -> e
unLoc Located Name
n))
, Name -> [Name] -> [FieldLabel] -> AvailInfo
availTC Name
name (Name
nameName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[Name]
avail) [FieldLabel]
flds)
lookup_ie ie :: IE GhcPs
ie@(IEThingWith XIEThingWith GhcPs
_ LIEWrappedName GhcPs
l IEWildcard
wc [LIEWrappedName GhcPs]
sub_rdrs)
= do
(Located Name
lname, [GenLocated SrcSpanAnnA (IEWrappedName GhcRn)]
subs, [Name]
avails, [Located FieldLabel]
flds)
<- IE GhcPs
-> TcM
(Located Name, [LIEWrappedName GhcRn], [Name],
[Located FieldLabel])
-> TcM
(Located Name, [LIEWrappedName GhcRn], [Name],
[Located FieldLabel])
forall (p :: Pass) a.
OutputableBndrId p =>
IE (GhcPass p) -> TcM a -> TcM a
addExportErrCtxt IE GhcPs
ie (TcM
(Located Name, [LIEWrappedName GhcRn], [Name],
[Located FieldLabel])
-> TcM
(Located Name, [LIEWrappedName GhcRn], [Name],
[Located FieldLabel]))
-> TcM
(Located Name, [LIEWrappedName GhcRn], [Name],
[Located FieldLabel])
-> TcM
(Located Name, [LIEWrappedName GhcRn], [Name],
[Located FieldLabel])
forall a b. (a -> b) -> a -> b
$ LIEWrappedName GhcPs
-> [LIEWrappedName GhcPs]
-> TcM
(Located Name, [LIEWrappedName GhcRn], [Name],
[Located FieldLabel])
lookup_ie_with LIEWrappedName GhcPs
l [LIEWrappedName GhcPs]
sub_rdrs
(Located Name
_, [Name]
all_avail, [FieldLabel]
all_flds) <-
case IEWildcard
wc of
IEWildcard
NoIEWildcard -> (Located Name, [Name], [FieldLabel])
-> RnM (Located Name, [Name], [FieldLabel])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Located Name
lname, [], [])
IEWildcard Int
_ -> IE GhcPs
-> LIEWrappedName GhcPs -> RnM (Located Name, [Name], [FieldLabel])
lookup_ie_all IE GhcPs
ie LIEWrappedName GhcPs
l
let name :: Name
name = Located Name -> Name
forall l e. GenLocated l e -> e
unLoc Located Name
lname
let flds' :: [Located FieldLabel]
flds' = [Located FieldLabel]
flds [Located FieldLabel]
-> [Located FieldLabel] -> [Located FieldLabel]
forall a. [a] -> [a] -> [a]
++ ((FieldLabel -> Located FieldLabel)
-> [FieldLabel] -> [Located FieldLabel]
forall a b. (a -> b) -> [a] -> [b]
map FieldLabel -> Located FieldLabel
forall e. e -> Located e
noLoc [FieldLabel]
all_flds)
(IE GhcRn, AvailInfo) -> RnM (IE GhcRn, AvailInfo)
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEThingWith GhcRn
-> LIEWrappedName GhcRn
-> IEWildcard
-> [LIEWrappedName GhcRn]
-> IE GhcRn
forall pass.
XIEThingWith pass
-> LIEWrappedName pass
-> IEWildcard
-> [LIEWrappedName pass]
-> IE pass
IEThingWith [Located FieldLabel]
XIEThingWith GhcRn
flds' (LIEWrappedName GhcPs -> IdP GhcRn -> LIEWrappedName GhcRn
replaceLWrappedName LIEWrappedName GhcPs
l IdP GhcRn
Name
name) IEWildcard
wc [LIEWrappedName GhcRn]
[GenLocated SrcSpanAnnA (IEWrappedName GhcRn)]
subs,
Name -> [Name] -> [FieldLabel] -> AvailInfo
availTC Name
name (Name
name Name -> [Name] -> [Name]
forall a. a -> [a] -> [a]
: [Name]
avails [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ [Name]
all_avail)
((Located FieldLabel -> FieldLabel)
-> [Located FieldLabel] -> [FieldLabel]
forall a b. (a -> b) -> [a] -> [b]
map Located FieldLabel -> FieldLabel
forall l e. GenLocated l e -> e
unLoc [Located FieldLabel]
flds [FieldLabel] -> [FieldLabel] -> [FieldLabel]
forall a. [a] -> [a] -> [a]
++ [FieldLabel]
all_flds))
lookup_ie IE GhcPs
_ = String -> RnM (IE GhcRn, AvailInfo)
forall a. HasCallStack => String -> a
panic String
"lookup_ie"
lookup_ie_with :: LIEWrappedName GhcPs -> [LIEWrappedName GhcPs]
-> RnM (Located Name, [LIEWrappedName GhcRn], [Name],
[Located FieldLabel])
lookup_ie_with :: LIEWrappedName GhcPs
-> [LIEWrappedName GhcPs]
-> TcM
(Located Name, [LIEWrappedName GhcRn], [Name],
[Located FieldLabel])
lookup_ie_with (L SrcSpanAnnA
l IEWrappedName GhcPs
rdr) [LIEWrappedName GhcPs]
sub_rdrs
= do Name
name <- RdrName -> RnM Name
lookupGlobalOccRn (RdrName -> RnM Name) -> RdrName -> RnM Name
forall a b. (a -> b) -> a -> b
$ IEWrappedName GhcPs -> IdP GhcPs
forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p)
ieWrappedName IEWrappedName GhcPs
rdr
([GenLocated SrcSpanAnnA (IEWrappedName GhcRn)]
non_flds, [Located FieldLabel]
flds) <- Name
-> [LIEWrappedName GhcPs]
-> RnM ([LIEWrappedName GhcRn], [Located FieldLabel])
lookupChildrenExport Name
name [LIEWrappedName GhcPs]
sub_rdrs
if Name -> Bool
isUnboundName Name
name
then (Located Name, [GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Name], [Located FieldLabel])
-> IOEnv
(Env TcGblEnv TcLclEnv)
(Located Name, [GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Name], [Located FieldLabel])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (SrcSpan -> Name -> Located Name
forall l e. l -> e -> GenLocated l e
L (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
l) Name
name, [], [Name
name], [])
else (Located Name, [GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Name], [Located FieldLabel])
-> IOEnv
(Env TcGblEnv TcLclEnv)
(Located Name, [GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Name], [Located FieldLabel])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (SrcSpan -> Name -> Located Name
forall l e. l -> e -> GenLocated l e
L (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
l) Name
name, [GenLocated SrcSpanAnnA (IEWrappedName GhcRn)]
non_flds
, (GenLocated SrcSpanAnnA (IEWrappedName GhcRn) -> Name)
-> [GenLocated SrcSpanAnnA (IEWrappedName GhcRn)] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map (IEWrappedName GhcRn -> IdP GhcRn
IEWrappedName GhcRn -> Name
forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p)
ieWrappedName (IEWrappedName GhcRn -> Name)
-> (GenLocated SrcSpanAnnA (IEWrappedName GhcRn)
-> IEWrappedName GhcRn)
-> GenLocated SrcSpanAnnA (IEWrappedName GhcRn)
-> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated SrcSpanAnnA (IEWrappedName GhcRn) -> IEWrappedName GhcRn
forall l e. GenLocated l e -> e
unLoc) [GenLocated SrcSpanAnnA (IEWrappedName GhcRn)]
non_flds
, [Located FieldLabel]
flds)
lookup_ie_all :: IE GhcPs -> LIEWrappedName GhcPs
-> RnM (Located Name, [Name], [FieldLabel])
lookup_ie_all :: IE GhcPs
-> LIEWrappedName GhcPs -> RnM (Located Name, [Name], [FieldLabel])
lookup_ie_all IE GhcPs
ie (L SrcSpanAnnA
l IEWrappedName GhcPs
rdr) =
do Name
name <- RdrName -> RnM Name
lookupGlobalOccRn (RdrName -> RnM Name) -> RdrName -> RnM Name
forall a b. (a -> b) -> a -> b
$ IEWrappedName GhcPs -> IdP GhcPs
forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p)
ieWrappedName IEWrappedName GhcPs
rdr
let gres :: [GlobalRdrElt]
gres = NameEnv [GlobalRdrElt] -> Name -> [GlobalRdrElt]
forall a. NameEnv [a] -> Name -> [a]
findChildren NameEnv [GlobalRdrElt]
kids_env Name
name
([Name]
non_flds, [FieldLabel]
flds) = [GlobalRdrElt] -> ([Name], [FieldLabel])
classifyGREs [GlobalRdrElt]
gres
RdrName -> [GlobalRdrElt] -> TcRn ()
addUsedKids (IEWrappedName GhcPs -> IdP GhcPs
forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p)
ieWrappedName IEWrappedName GhcPs
rdr) [GlobalRdrElt]
gres
Bool -> TcRn () -> TcRn ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([GlobalRdrElt] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [GlobalRdrElt]
gres) (TcRn () -> TcRn ()) -> TcRn () -> TcRn ()
forall a b. (a -> b) -> a -> b
$
if Name -> Bool
isTyConName Name
name
then TcRnMessage -> TcRn ()
addTcRnDiagnostic (Name -> TcRnMessage
TcRnDodgyExports Name
name)
else
TcRnMessage -> TcRn ()
addErr (IE GhcPs -> TcRnMessage
TcRnExportHiddenComponents IE GhcPs
ie)
(Located Name, [Name], [FieldLabel])
-> RnM (Located Name, [Name], [FieldLabel])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (SrcSpan -> Name -> Located Name
forall l e. l -> e -> GenLocated l e
L (SrcSpanAnnA -> SrcSpan
forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
l) Name
name, [Name]
non_flds, [FieldLabel]
flds)
lookup_doc_ie :: IE GhcPs -> RnM (Maybe (IE GhcRn))
lookup_doc_ie :: IE GhcPs -> RnM (Maybe (IE GhcRn))
lookup_doc_ie (IEGroup XIEGroup GhcPs
_ Int
lev LHsDoc GhcPs
doc) = do
LHsDoc GhcRn
doc' <- LHsDoc GhcPs -> RnM (LHsDoc GhcRn)
rnLHsDoc LHsDoc GhcPs
doc
Maybe (IE GhcRn) -> RnM (Maybe (IE GhcRn))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (IE GhcRn) -> RnM (Maybe (IE GhcRn)))
-> Maybe (IE GhcRn) -> RnM (Maybe (IE GhcRn))
forall a b. (a -> b) -> a -> b
$ IE GhcRn -> Maybe (IE GhcRn)
forall a. a -> Maybe a
Just (XIEGroup GhcRn -> Int -> LHsDoc GhcRn -> IE GhcRn
forall pass. XIEGroup pass -> Int -> LHsDoc pass -> IE pass
IEGroup XIEGroup GhcRn
NoExtField
noExtField Int
lev LHsDoc GhcRn
doc')
lookup_doc_ie (IEDoc XIEDoc GhcPs
_ LHsDoc GhcPs
doc) = do
LHsDoc GhcRn
doc' <- LHsDoc GhcPs -> RnM (LHsDoc GhcRn)
rnLHsDoc LHsDoc GhcPs
doc
Maybe (IE GhcRn) -> RnM (Maybe (IE GhcRn))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (IE GhcRn) -> RnM (Maybe (IE GhcRn)))
-> Maybe (IE GhcRn) -> RnM (Maybe (IE GhcRn))
forall a b. (a -> b) -> a -> b
$ IE GhcRn -> Maybe (IE GhcRn)
forall a. a -> Maybe a
Just (XIEDoc GhcRn -> LHsDoc GhcRn -> IE GhcRn
forall pass. XIEDoc pass -> LHsDoc pass -> IE pass
IEDoc XIEDoc GhcRn
NoExtField
noExtField LHsDoc GhcRn
doc')
lookup_doc_ie (IEDocNamed XIEDocNamed GhcPs
_ String
str) = Maybe (IE GhcRn) -> RnM (Maybe (IE GhcRn))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (IE GhcRn) -> RnM (Maybe (IE GhcRn)))
-> Maybe (IE GhcRn) -> RnM (Maybe (IE GhcRn))
forall a b. (a -> b) -> a -> b
$ IE GhcRn -> Maybe (IE GhcRn)
forall a. a -> Maybe a
Just (XIEDocNamed GhcRn -> String -> IE GhcRn
forall pass. XIEDocNamed pass -> String -> IE pass
IEDocNamed XIEDocNamed GhcRn
NoExtField
noExtField String
str)
lookup_doc_ie IE GhcPs
_ = Maybe (IE GhcRn) -> RnM (Maybe (IE GhcRn))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (IE GhcRn)
forall a. Maybe a
Nothing
addUsedKids :: RdrName -> [GlobalRdrElt] -> RnM ()
addUsedKids :: RdrName -> [GlobalRdrElt] -> TcRn ()
addUsedKids RdrName
parent_rdr [GlobalRdrElt]
kid_gres = [GlobalRdrElt] -> TcRn ()
addUsedGREs (RdrName -> [GlobalRdrElt] -> [GlobalRdrElt]
pickGREs RdrName
parent_rdr [GlobalRdrElt]
kid_gres)
classifyGREs :: [GlobalRdrElt] -> ([Name], [FieldLabel])
classifyGREs :: [GlobalRdrElt] -> ([Name], [FieldLabel])
classifyGREs = [GreName] -> ([Name], [FieldLabel])
partitionGreNames ([GreName] -> ([Name], [FieldLabel]))
-> ([GlobalRdrElt] -> [GreName])
-> [GlobalRdrElt]
-> ([Name], [FieldLabel])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GlobalRdrElt -> GreName) -> [GlobalRdrElt] -> [GreName]
forall a b. (a -> b) -> [a] -> [b]
map GlobalRdrElt -> GreName
gre_name
lookupChildrenExport :: Name -> [LIEWrappedName GhcPs]
-> RnM ([LIEWrappedName GhcRn], [Located FieldLabel])
lookupChildrenExport :: Name
-> [LIEWrappedName GhcPs]
-> RnM ([LIEWrappedName GhcRn], [Located FieldLabel])
lookupChildrenExport Name
spec_parent [LIEWrappedName GhcPs]
rdr_items =
do
[Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel)]
xs <- (LocatedAn AnnListItem (IEWrappedName GhcPs)
-> TcRn
(Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel)))
-> [LocatedAn AnnListItem (IEWrappedName GhcPs)]
-> TcRn
[Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel)]
forall a b. (a -> TcRn b) -> [a] -> TcRn [b]
mapAndReportM LIEWrappedName GhcPs
-> RnM (Either (LIEWrappedName GhcRn) (Located FieldLabel))
LocatedAn AnnListItem (IEWrappedName GhcPs)
-> TcRn
(Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel))
doOne [LIEWrappedName GhcPs]
[LocatedAn AnnListItem (IEWrappedName GhcPs)]
rdr_items
([GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Located FieldLabel])
-> IOEnv
(Env TcGblEnv TcLclEnv)
([GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Located FieldLabel])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (([GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Located FieldLabel])
-> IOEnv
(Env TcGblEnv TcLclEnv)
([GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Located FieldLabel]))
-> ([GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Located FieldLabel])
-> IOEnv
(Env TcGblEnv TcLclEnv)
([GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Located FieldLabel])
forall a b. (a -> b) -> a -> b
$ [Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel)]
-> ([GenLocated SrcSpanAnnA (IEWrappedName GhcRn)],
[Located FieldLabel])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel)]
xs
where
choosePossibleNamespaces :: NameSpace -> [NameSpace]
choosePossibleNamespaces :: NameSpace -> [NameSpace]
choosePossibleNamespaces NameSpace
ns
| NameSpace
ns NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
varName = [NameSpace
varName, NameSpace
tcName]
| NameSpace
ns NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
tcName = [NameSpace
dataName, NameSpace
tcName]
| Bool
otherwise = [NameSpace
ns]
doOne :: LIEWrappedName GhcPs
-> RnM (Either (LIEWrappedName GhcRn) (Located FieldLabel))
doOne :: LIEWrappedName GhcPs
-> RnM (Either (LIEWrappedName GhcRn) (Located FieldLabel))
doOne LIEWrappedName GhcPs
n = do
let bareName :: RdrName
bareName = (IEWrappedName GhcPs -> IdP GhcPs
IEWrappedName GhcPs -> RdrName
forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p)
ieWrappedName (IEWrappedName GhcPs -> RdrName)
-> (LocatedAn AnnListItem (IEWrappedName GhcPs)
-> IEWrappedName GhcPs)
-> LocatedAn AnnListItem (IEWrappedName GhcPs)
-> RdrName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LocatedAn AnnListItem (IEWrappedName GhcPs) -> IEWrappedName GhcPs
forall l e. GenLocated l e -> e
unLoc) LIEWrappedName GhcPs
LocatedAn AnnListItem (IEWrappedName GhcPs)
n
lkup :: NameSpace -> RnM ChildLookupResult
lkup NameSpace
v = Bool -> Bool -> Name -> RdrName -> RnM ChildLookupResult
lookupSubBndrOcc_helper Bool
False Bool
True
Name
spec_parent (RdrName -> NameSpace -> RdrName
setRdrNameSpace RdrName
bareName NameSpace
v)
ChildLookupResult
name <- [RnM ChildLookupResult] -> RnM ChildLookupResult
combineChildLookupResult ([RnM ChildLookupResult] -> RnM ChildLookupResult)
-> [RnM ChildLookupResult] -> RnM ChildLookupResult
forall a b. (a -> b) -> a -> b
$ (NameSpace -> RnM ChildLookupResult)
-> [NameSpace] -> [RnM ChildLookupResult]
forall a b. (a -> b) -> [a] -> [b]
map NameSpace -> RnM ChildLookupResult
lkup ([NameSpace] -> [RnM ChildLookupResult])
-> [NameSpace] -> [RnM ChildLookupResult]
forall a b. (a -> b) -> a -> b
$
NameSpace -> [NameSpace]
choosePossibleNamespaces (RdrName -> NameSpace
rdrNameSpace RdrName
bareName)
String -> SDoc -> TcRn ()
traceRn String
"lookupChildrenExport" (ChildLookupResult -> SDoc
forall a. Outputable a => a -> SDoc
ppr ChildLookupResult
name)
let unboundName :: RdrName
unboundName :: RdrName
unboundName = if RdrName -> NameSpace
rdrNameSpace RdrName
bareName NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
varName
then RdrName
bareName
else RdrName -> NameSpace -> RdrName
setRdrNameSpace RdrName
bareName NameSpace
dataName
case ChildLookupResult
name of
ChildLookupResult
NameNotFound -> do { Name
ub <- RdrName -> RnM Name
reportUnboundName RdrName
unboundName
; let l :: SrcSpanAnnA
l = LocatedAn AnnListItem (IEWrappedName GhcPs) -> SrcSpanAnnA
forall l e. GenLocated l e -> l
getLoc LIEWrappedName GhcPs
LocatedAn AnnListItem (IEWrappedName GhcPs)
n
; Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn)) (Located FieldLabel)
-> TcRn
(Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenLocated SrcSpanAnnA (IEWrappedName GhcRn)
-> Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn)) (Located FieldLabel)
forall a b. a -> Either a b
Left (SrcSpanAnnA
-> IEWrappedName GhcRn
-> GenLocated SrcSpanAnnA (IEWrappedName GhcRn)
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnA
l (XIEName GhcRn -> LIdP GhcRn -> IEWrappedName GhcRn
forall p. XIEName p -> LIdP p -> IEWrappedName p
IEName XIEName GhcRn
NoExtField
noExtField (SrcSpanAnnN -> Name -> GenLocated SrcSpanAnnN Name
forall l e. l -> e -> GenLocated l e
L (SrcSpanAnnA -> SrcSpanAnnN
forall a. SrcSpanAnn' a -> SrcSpanAnnN
la2na SrcSpanAnnA
l) Name
ub))))}
FoundChild Parent
par GreName
child -> do { Name -> Parent -> GreName -> TcRn ()
checkPatSynParent Name
spec_parent Parent
par GreName
child
; Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn)) (Located FieldLabel)
-> TcRn
(Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel))
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn)) (Located FieldLabel)
-> TcRn
(Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel)))
-> Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn)) (Located FieldLabel)
-> TcRn
(Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel))
forall a b. (a -> b) -> a -> b
$ case GreName
child of
FieldGreName FieldLabel
fl -> Located FieldLabel
-> Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn)) (Located FieldLabel)
forall a b. b -> Either a b
Right (SrcSpan -> FieldLabel -> Located FieldLabel
forall l e. l -> e -> GenLocated l e
L (LocatedAn AnnListItem (IEWrappedName GhcPs) -> SrcSpan
forall a e. GenLocated (SrcSpanAnn' a) e -> SrcSpan
getLocA LIEWrappedName GhcPs
LocatedAn AnnListItem (IEWrappedName GhcPs)
n) FieldLabel
fl)
NormalGreName Name
name -> GenLocated SrcSpanAnnA (IEWrappedName GhcRn)
-> Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn)) (Located FieldLabel)
forall a b. a -> Either a b
Left (LIEWrappedName GhcPs -> IdP GhcRn -> LIEWrappedName GhcRn
replaceLWrappedName LIEWrappedName GhcPs
n IdP GhcRn
Name
name)
}
IncorrectParent Name
p GreName
c [Name]
gs -> Name
-> GreName
-> [Name]
-> TcRn
(Either
(GenLocated SrcSpanAnnA (IEWrappedName GhcRn))
(Located FieldLabel))
forall a. Name -> GreName -> [Name] -> TcM a
failWithDcErr Name
p GreName
c [Name]
gs
checkPatSynParent :: Name
-> Parent
-> GreName
-> TcM ()
checkPatSynParent :: Name -> Parent -> GreName -> TcRn ()
checkPatSynParent Name
_ (ParentIs {}) GreName
_
= () -> TcRn ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkPatSynParent Name
parent Parent
NoParent GreName
gname
| Name -> Bool
isUnboundName Name
parent
= () -> TcRn ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise
= do { TyCon
parent_ty_con <- Name -> TcM TyCon
tcLookupTyCon Name
parent
; TyThing
mpat_syn_thing <- Name -> TcM TyThing
tcLookupGlobal (GreName -> Name
greNameMangledName GreName
gname)
; case TyThing
mpat_syn_thing of
AnId Id
i | Id -> Bool
isId Id
i
, RecSelId { sel_tycon :: IdDetails -> RecSelParent
sel_tycon = RecSelPatSyn PatSyn
p } <- Id -> IdDetails
idDetails Id
i
-> SDoc -> TyCon -> PatSyn -> TcRn ()
handle_pat_syn (GreName -> SDoc
selErr GreName
gname) TyCon
parent_ty_con PatSyn
p
AConLike (PatSynCon PatSyn
p) -> SDoc -> TyCon -> PatSyn -> TcRn ()
handle_pat_syn (PatSyn -> SDoc
psErr PatSyn
p) TyCon
parent_ty_con PatSyn
p
TyThing
_ -> Name -> GreName -> [Name] -> TcRn ()
forall a. Name -> GreName -> [Name] -> TcM a
failWithDcErr Name
parent GreName
gname [] }
where
psErr :: PatSyn -> SDoc
psErr = String -> PatSyn -> SDoc
forall o. Outputable o => String -> o -> SDoc
exportErrCtxt String
"pattern synonym"
selErr :: GreName -> SDoc
selErr = String -> GreName -> SDoc
forall o. Outputable o => String -> o -> SDoc
exportErrCtxt String
"pattern synonym record selector"
handle_pat_syn :: SDoc
-> TyCon
-> PatSyn
-> TcM ()
handle_pat_syn :: SDoc -> TyCon -> PatSyn -> TcRn ()
handle_pat_syn SDoc
doc TyCon
ty_con PatSyn
pat_syn
| Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ TyCon -> Bool
isTyConWithSrcDataCons TyCon
ty_con
= SDoc -> TcRn () -> TcRn ()
forall a. SDoc -> TcM a -> TcM a
addErrCtxt SDoc
doc (TcRn () -> TcRn ()) -> TcRn () -> TcRn ()
forall a b. (a -> b) -> a -> b
$ TcRnMessage -> TcRn ()
forall a. TcRnMessage -> TcM a
failWithTc TcRnMessage
TcRnPatSynBundledWithNonDataCon
| Maybe TyCon
Nothing <- Maybe TyCon
mtycon
= () -> TcRn ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Just TyCon
p_ty_con <- Maybe TyCon
mtycon, TyCon
p_ty_con TyCon -> TyCon -> Bool
forall a. Eq a => a -> a -> Bool
/= TyCon
ty_con
= SDoc -> TcRn () -> TcRn ()
forall a. SDoc -> TcM a -> TcM a
addErrCtxt SDoc
doc (TcRn () -> TcRn ()) -> TcRn () -> TcRn ()
forall a b. (a -> b) -> a -> b
$ TcRnMessage -> TcRn ()
forall a. TcRnMessage -> TcM a
failWithTc
(Type -> Type -> TcRnMessage
TcRnPatSynBundledWithWrongType Type
expected_res_ty Type
res_ty)
| Bool
otherwise
= () -> TcRn ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
where
expected_res_ty :: Type
expected_res_ty = TyCon -> [Type] -> Type
mkTyConApp TyCon
ty_con ([Id] -> [Type]
mkTyVarTys (TyCon -> [Id]
tyConTyVars TyCon
ty_con))
([Id]
_, [Type]
_, [Id]
_, [Type]
_, [Scaled Type]
_, Type
res_ty) = PatSyn -> ([Id], [Type], [Id], [Type], [Scaled Type], Type)
patSynSig PatSyn
pat_syn
mtycon :: Maybe TyCon
mtycon = (TyCon, [Type]) -> TyCon
forall a b. (a, b) -> a
fst ((TyCon, [Type]) -> TyCon) -> Maybe (TyCon, [Type]) -> Maybe TyCon
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HasCallStack => Type -> Maybe (TyCon, [Type])
Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
res_ty
check_occs :: IE GhcPs -> ExportOccMap -> [AvailInfo]
-> RnM ExportOccMap
check_occs :: IE GhcPs -> ExportOccMap -> [AvailInfo] -> RnM ExportOccMap
check_occs IE GhcPs
ie ExportOccMap
occs [AvailInfo]
avails
= (ExportOccMap -> GreName -> RnM ExportOccMap)
-> ExportOccMap -> [GreName] -> RnM ExportOccMap
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM ExportOccMap -> GreName -> RnM ExportOccMap
check ExportOccMap
occs [GreName]
children
where
children :: [GreName]
children = (AvailInfo -> [GreName]) -> [AvailInfo] -> [GreName]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap AvailInfo -> [GreName]
availGreNames [AvailInfo]
avails
check :: ExportOccMap -> GreName -> RnM ExportOccMap
check :: ExportOccMap -> GreName -> RnM ExportOccMap
check ExportOccMap
occs GreName
child
= case ExportOccMap -> GreName -> Either (GreName, IE GhcPs) ExportOccMap
try_insert ExportOccMap
occs GreName
child of
Right ExportOccMap
occs' -> ExportOccMap -> RnM ExportOccMap
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ExportOccMap
occs'
Left (GreName
child', IE GhcPs
ie')
| GreName -> Name
greNameMangledName GreName
child Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== GreName -> Name
greNameMangledName GreName
child'
-> do { Bool -> TcRnMessage -> TcRn ()
warnIf (Bool -> Bool
not (GreName -> IE GhcPs -> IE GhcPs -> Bool
dupExport_ok GreName
child IE GhcPs
ie IE GhcPs
ie')) (GreName -> IE GhcPs -> IE GhcPs -> TcRnMessage
TcRnDuplicateExport GreName
child IE GhcPs
ie IE GhcPs
ie')
; ExportOccMap -> RnM ExportOccMap
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ExportOccMap
occs }
| Bool
otherwise
-> do { GlobalRdrEnv
global_env <- TcRn GlobalRdrEnv
getGlobalRdrEnv ;
TcRnMessage -> TcRn ()
addErr (GlobalRdrEnv
-> GreName -> GreName -> IE GhcPs -> IE GhcPs -> TcRnMessage
exportClashErr GlobalRdrEnv
global_env GreName
child' GreName
child IE GhcPs
ie' IE GhcPs
ie) ;
ExportOccMap -> RnM ExportOccMap
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ExportOccMap
occs }
try_insert :: ExportOccMap -> GreName -> Either (GreName, IE GhcPs) ExportOccMap
try_insert :: ExportOccMap -> GreName -> Either (GreName, IE GhcPs) ExportOccMap
try_insert ExportOccMap
occs GreName
child
= case ExportOccMap -> OccName -> Maybe (GreName, IE GhcPs)
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv ExportOccMap
occs OccName
name_occ of
Maybe (GreName, IE GhcPs)
Nothing -> ExportOccMap -> Either (GreName, IE GhcPs) ExportOccMap
forall a b. b -> Either a b
Right (ExportOccMap -> OccName -> (GreName, IE GhcPs) -> ExportOccMap
forall a. OccEnv a -> OccName -> a -> OccEnv a
extendOccEnv ExportOccMap
occs OccName
name_occ (GreName
child, IE GhcPs
ie))
Just (GreName, IE GhcPs)
x -> (GreName, IE GhcPs) -> Either (GreName, IE GhcPs) ExportOccMap
forall a b. a -> Either a b
Left (GreName, IE GhcPs)
x
where
name_occ :: OccName
name_occ = Name -> OccName
nameOccName (GreName -> Name
greNameMangledName GreName
child)
dupExport_ok :: GreName -> IE GhcPs -> IE GhcPs -> Bool
dupExport_ok :: GreName -> IE GhcPs -> IE GhcPs -> Bool
dupExport_ok GreName
child IE GhcPs
ie1 IE GhcPs
ie2
= Bool -> Bool
not ( IE GhcPs -> Bool
forall {pass}. IE pass -> Bool
single IE GhcPs
ie1 Bool -> Bool -> Bool
|| IE GhcPs -> Bool
forall {pass}. IE pass -> Bool
single IE GhcPs
ie2
Bool -> Bool -> Bool
|| (IE GhcPs -> Bool
explicit_in IE GhcPs
ie1 Bool -> Bool -> Bool
&& IE GhcPs -> Bool
explicit_in IE GhcPs
ie2) )
where
explicit_in :: IE GhcPs -> Bool
explicit_in (IEModuleContents {}) = Bool
False
explicit_in (IEThingAll XIEThingAll GhcPs
_ LIEWrappedName GhcPs
r)
= GreName -> OccName
forall name. HasOccName name => name -> OccName
occName GreName
child OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
== RdrName -> OccName
rdrNameOcc (IEWrappedName GhcPs -> IdP GhcPs
forall (p :: Pass). IEWrappedName (GhcPass p) -> IdP (GhcPass p)
ieWrappedName (IEWrappedName GhcPs -> IdP GhcPs)
-> IEWrappedName GhcPs -> IdP GhcPs
forall a b. (a -> b) -> a -> b
$ LocatedAn AnnListItem (IEWrappedName GhcPs) -> IEWrappedName GhcPs
forall l e. GenLocated l e -> e
unLoc LIEWrappedName GhcPs
LocatedAn AnnListItem (IEWrappedName GhcPs)
r)
explicit_in IE GhcPs
_ = Bool
True
single :: IE pass -> Bool
single IEVar {} = Bool
True
single IEThingAbs {} = Bool
True
single IE pass
_ = Bool
False
exportErrCtxt :: Outputable o => String -> o -> SDoc
exportErrCtxt :: forall o. Outputable o => String -> o -> SDoc
exportErrCtxt String
herald o
exp =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"In the" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text (String
herald String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":") SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> o -> SDoc
forall a. Outputable a => a -> SDoc
ppr o
exp
addExportErrCtxt :: (OutputableBndrId p)
=> IE (GhcPass p) -> TcM a -> TcM a
addExportErrCtxt :: forall (p :: Pass) a.
OutputableBndrId p =>
IE (GhcPass p) -> TcM a -> TcM a
addExportErrCtxt IE (GhcPass p)
ie = SDoc -> TcM a -> TcM a
forall a. SDoc -> TcM a -> TcM a
addErrCtxt SDoc
exportCtxt
where
exportCtxt :: SDoc
exportCtxt = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"In the export:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IE (GhcPass p) -> SDoc
forall a. Outputable a => a -> SDoc
ppr IE (GhcPass p)
ie
failWithDcErr :: Name -> GreName -> [Name] -> TcM a
failWithDcErr :: forall a. Name -> GreName -> [Name] -> TcM a
failWithDcErr Name
parent GreName
child [Name]
parents = do
TyThing
ty_thing <- Name -> TcM TyThing
tcLookupGlobal (GreName -> Name
greNameMangledName GreName
child)
TcRnMessage -> TcM a
forall a. TcRnMessage -> TcM a
failWithTc (TcRnMessage -> TcM a) -> TcRnMessage -> TcM a
forall a b. (a -> b) -> a -> b
$ Name -> TyThing -> GreName -> [Name] -> TcRnMessage
TcRnExportedParentChildMismatch Name
parent TyThing
ty_thing GreName
child [Name]
parents
exportClashErr :: GlobalRdrEnv
-> GreName -> GreName
-> IE GhcPs -> IE GhcPs
-> TcRnMessage
exportClashErr :: GlobalRdrEnv
-> GreName -> GreName -> IE GhcPs -> IE GhcPs -> TcRnMessage
exportClashErr GlobalRdrEnv
global_env GreName
child1 GreName
child2 IE GhcPs
ie1 IE GhcPs
ie2
= OccName
-> GreName
-> GlobalRdrElt
-> IE GhcPs
-> GreName
-> GlobalRdrElt
-> IE GhcPs
-> TcRnMessage
TcRnConflictingExports OccName
occ GreName
child1' GlobalRdrElt
gre1' IE GhcPs
ie1' GreName
child2' GlobalRdrElt
gre2' IE GhcPs
ie2'
where
occ :: OccName
occ = GreName -> OccName
forall name. HasOccName name => name -> OccName
occName GreName
child1
gre1 :: GlobalRdrElt
gre1 = GreName -> GlobalRdrElt
get_gre GreName
child1
gre2 :: GlobalRdrElt
gre2 = GreName -> GlobalRdrElt
get_gre GreName
child2
get_gre :: GreName -> GlobalRdrElt
get_gre GreName
child
= GlobalRdrElt -> Maybe GlobalRdrElt -> GlobalRdrElt
forall a. a -> Maybe a -> a
fromMaybe (String -> SDoc -> GlobalRdrElt
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"exportClashErr" (GreName -> SDoc
forall a. Outputable a => a -> SDoc
ppr GreName
child))
(GlobalRdrEnv -> GreName -> Maybe GlobalRdrElt
lookupGRE_GreName GlobalRdrEnv
global_env GreName
child)
(GreName
child1', GlobalRdrElt
gre1', IE GhcPs
ie1', GreName
child2', GlobalRdrElt
gre2', IE GhcPs
ie2') =
case SrcSpan -> SrcSpan -> Ordering
SrcLoc.leftmost_smallest (GlobalRdrElt -> SrcSpan
greSrcSpan GlobalRdrElt
gre1) (GlobalRdrElt -> SrcSpan
greSrcSpan GlobalRdrElt
gre2) of
Ordering
LT -> (GreName
child1, GlobalRdrElt
gre1, IE GhcPs
ie1, GreName
child2, GlobalRdrElt
gre2, IE GhcPs
ie2)
Ordering
GT -> (GreName
child2, GlobalRdrElt
gre2, IE GhcPs
ie2, GreName
child1, GlobalRdrElt
gre1, IE GhcPs
ie1)
Ordering
EQ -> String
-> (GreName, GlobalRdrElt, IE GhcPs, GreName, GlobalRdrElt,
IE GhcPs)
forall a. HasCallStack => String -> a
panic String
"exportClashErr: clashing exports have identical location"