{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module TcRnExports (tcRnExports, exports_from_avail) where
import GhcPrelude
import GHC.Hs
import PrelNames
import RdrName
import TcRnMonad
import TcEnv
import TcType
import RnNames
import RnEnv
import RnUnbound ( reportUnboundName )
import ErrUtils
import Id
import IdInfo
import Module
import Name
import NameEnv
import NameSet
import Avail
import TyCon
import SrcLoc
import HscTypes
import Outputable
import ConLike
import DataCon
import PatSyn
import Maybes
import UniqSet
import Util (capitalise)
import FastString (fsLit)
import Control.Monad
import DynFlags
import RnHsDoc ( rnHsDoc )
import RdrHsSyn ( setRdrNameSpace )
import Data.Either ( partitionEithers )
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 :: (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])
-> TcRn [y]
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])
-> TcRn [y])
-> ([x] -> IOEnv (Env TcGblEnv TcLclEnv) (ExportAccum, [Maybe y]))
-> [x]
-> TcRn [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 :: * -> *) acc x y.
Monad m =>
(acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [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 (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 (Name, IE GhcPs)
tcRnExports :: Bool
-> Maybe (Located [LIE GhcPs])
-> TcGblEnv
-> RnM TcGblEnv
tcRnExports :: Bool -> Maybe (Located [LIE GhcPs]) -> TcGblEnv -> RnM TcGblEnv
tcRnExports Bool
explicit_mod Maybe (Located [LIE GhcPs])
exports
tcg_env :: TcGblEnv
tcg_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 }
= 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 {
; DynFlags
dflags <- IOEnv (Env TcGblEnv TcLclEnv) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
; let is_main_mod :: Bool
is_main_mod = DynFlags -> Module
mainModIs DynFlags
dflags Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
this_mod
; let default_main :: RdrName
default_main = case DynFlags -> Maybe String
mainFunIs DynFlags
dflags of
Just String
main_fun
| Bool
is_main_mod -> NameSpace -> FastString -> RdrName
mkUnqual NameSpace
varName (String -> FastString
fsLit String
main_fun)
Maybe String
_ -> 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 (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 (Located [LIE GhcPs])
real_exports
| Bool
explicit_mod = Maybe (Located [LIE GhcPs])
exports
| Bool
has_main
= Located [LIE GhcPs] -> Maybe (Located [LIE GhcPs])
forall a. a -> Maybe a
Just (SrcSpanLess (Located [LIE GhcPs]) -> Located [LIE GhcPs]
forall a. HasSrcSpan a => SrcSpanLess a -> a
noLoc [SrcSpanLess (LIE GhcPs) -> LIE GhcPs
forall a. HasSrcSpan a => SrcSpanLess a -> a
noLoc (XIEVar GhcPs -> LIEWrappedName (IdP GhcPs) -> IE GhcPs
forall pass. XIEVar pass -> LIEWrappedName (IdP pass) -> IE pass
IEVar XIEVar GhcPs
NoExtField
noExtField
(SrcSpanLess (LIEWrappedName RdrName) -> LIEWrappedName RdrName
forall a. HasSrcSpan a => SrcSpanLess a -> a
noLoc (Located RdrName -> IEWrappedName RdrName
forall name. Located name -> IEWrappedName name
IEName (Located RdrName -> IEWrappedName RdrName)
-> Located RdrName -> IEWrappedName RdrName
forall a b. (a -> b) -> a -> b
$ SrcSpanLess (Located RdrName) -> Located RdrName
forall a. HasSrcSpan a => SrcSpanLess a -> a
noLoc SrcSpanLess (Located RdrName)
RdrName
default_main)))])
| Bool
otherwise = Maybe (Located [LIE GhcPs])
forall a. Maybe a
Nothing
; let do_it :: RnM (Maybe [(LIE GhcRn, Avails)], Avails)
do_it = Maybe (Located [LIE GhcPs])
-> GlobalRdrEnv
-> ImportAvails
-> Module
-> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
exports_from_avail Maybe (Located [LIE GhcPs])
real_exports GlobalRdrEnv
rdr_env ImportAvails
imports Module
this_mod
; (Maybe [(LIE GhcRn, Avails)]
rn_exports, Avails
final_avails)
<- if HscSource
hsc_src HscSource -> HscSource -> Bool
forall a. Eq a => a -> a -> Bool
== HscSource
HsigFile
then do (Maybe (Maybe [(LIE GhcRn, Avails)], Avails)
mb_r, Messages
msgs) <- RnM (Maybe [(LIE GhcRn, Avails)], Avails)
-> TcRn (Maybe (Maybe [(LIE GhcRn, Avails)], Avails), Messages)
forall a. TcRn a -> TcRn (Maybe a, Messages)
tryTc RnM (Maybe [(LIE GhcRn, Avails)], Avails)
do_it
case Maybe (Maybe [(LIE GhcRn, Avails)], Avails)
mb_r of
Just (Maybe [(LIE GhcRn, Avails)], Avails)
r -> (Maybe [(LIE GhcRn, Avails)], Avails)
-> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [(LIE GhcRn, Avails)], Avails)
r
Maybe (Maybe [(LIE GhcRn, Avails)], Avails)
Nothing -> Messages -> TcRn ()
addMessages Messages
msgs TcRn ()
-> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
-> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
forall env a. IOEnv env a
failM
else RnM (Maybe [(LIE GhcRn, Avails)], Avails)
-> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
forall r. TcM r -> TcM r
checkNoErrs RnM (Maybe [(LIE GhcRn, Avails)], Avails)
do_it
; let final_ns :: NameSet
final_ns = Avails -> NameSet
availsToNameSetWithSelectors Avails
final_avails
; String -> SDoc -> TcRn ()
traceRn String
"rnExports: Exports:" (Avails -> SDoc
forall a. Outputable a => a -> SDoc
ppr Avails
final_avails)
; let new_tcg_env :: TcGblEnv
new_tcg_env =
TcGblEnv
tcg_env { tcg_exports :: Avails
tcg_exports = Avails
final_avails,
tcg_rn_exports :: Maybe [(LIE GhcRn, Avails)]
tcg_rn_exports = case TcGblEnv -> Maybe [(LIE GhcRn, Avails)]
tcg_rn_exports TcGblEnv
tcg_env of
Maybe [(LIE GhcRn, Avails)]
Nothing -> Maybe [(LIE GhcRn, Avails)]
forall a. Maybe a
Nothing
Just [(LIE GhcRn, Avails)]
_ -> Maybe [(LIE GhcRn, Avails)]
rn_exports,
tcg_dus :: DefUses
tcg_dus = TcGblEnv -> DefUses
tcg_dus TcGblEnv
tcg_env DefUses -> DefUses -> DefUses
`plusDU`
NameSet -> DefUses
usesOnly NameSet
final_ns }
; TcRn ()
failIfErrsM
; TcGblEnv -> RnM TcGblEnv
forall (m :: * -> *) a. Monad m => a -> m a
return TcGblEnv
new_tcg_env }
exports_from_avail :: Maybe (Located [LIE GhcPs])
-> GlobalRdrEnv
-> ImportAvails
-> Module
-> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
exports_from_avail :: Maybe (Located [LIE GhcPs])
-> GlobalRdrEnv
-> ImportAvails
-> Module
-> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
exports_from_avail Maybe (Located [LIE GhcPs])
Nothing GlobalRdrEnv
rdr_env ImportAvails
_imports Module
_this_mod
= do {
; Bool
warnMissingExportList <- WarningFlag -> IOEnv (Env TcGblEnv TcLclEnv) Bool
forall gbl lcl. WarningFlag -> TcRnIf gbl lcl Bool
woptM WarningFlag
Opt_WarnMissingExportList
; WarningFlag -> Bool -> SDoc -> TcRn ()
warnIfFlag WarningFlag
Opt_WarnMissingExportList
Bool
warnMissingExportList
(ModuleName -> SDoc
missingModuleExportWarn (ModuleName -> SDoc) -> ModuleName -> SDoc
forall a b. (a -> b) -> a -> b
$ Module -> ModuleName
moduleName Module
_this_mod)
; let avails :: Avails
avails =
(AvailInfo -> AvailInfo) -> Avails -> Avails
forall a b. (a -> b) -> [a] -> [b]
map AvailInfo -> AvailInfo
fix_faminst (Avails -> Avails)
-> (GlobalRdrEnv -> Avails) -> GlobalRdrEnv -> Avails
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [GlobalRdrElt] -> Avails
gresToAvailInfo
([GlobalRdrElt] -> Avails)
-> (GlobalRdrEnv -> [GlobalRdrElt]) -> GlobalRdrEnv -> Avails
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 -> Avails) -> GlobalRdrEnv -> Avails
forall a b. (a -> b) -> a -> b
$ GlobalRdrEnv
rdr_env
; (Maybe [(LIE GhcRn, Avails)], Avails)
-> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [(LIE GhcRn, Avails)]
forall a. Maybe a
Nothing, Avails
avails) }
where
fix_faminst :: AvailInfo -> AvailInfo
fix_faminst (AvailTC Name
n [Name]
ns [FieldLabel]
flds) =
let new_ns :: [Name]
new_ns =
case [Name]
ns of
[] -> [Name
n]
(Name
p:[Name]
_) -> if Name
p Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
n then [Name]
ns else Name
nName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[Name]
ns
in Name -> [Name] -> [FieldLabel] -> AvailInfo
AvailTC Name
n [Name]
new_ns [FieldLabel]
flds
fix_faminst AvailInfo
avail = AvailInfo
avail
exports_from_avail (Just (Located [LIE GhcPs] -> Located (SrcSpanLess (Located [LIE GhcPs]))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
_ SrcSpanLess (Located [LIE GhcPs])
rdr_items)) GlobalRdrEnv
rdr_env ImportAvails
imports Module
this_mod
= do [(LIE GhcRn, Avails)]
ie_avails <- (ExportAccum
-> LIE GhcPs -> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails))))
-> [LIE GhcPs] -> TcRn [(LIE GhcRn, Avails)]
forall x y.
(ExportAccum -> x -> TcRn (Maybe (ExportAccum, y)))
-> [x] -> TcRn [y]
accumExports ExportAccum
-> LIE GhcPs -> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
do_litem [LIE GhcPs]
SrcSpanLess (Located [LIE GhcPs])
rdr_items
let final_exports :: Avails
final_exports = Avails -> Avails
nubAvails ([Avails] -> Avails
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (((LIE GhcRn, Avails) -> Avails)
-> [(LIE GhcRn, Avails)] -> [Avails]
forall a b. (a -> b) -> [a] -> [b]
map (LIE GhcRn, Avails) -> Avails
forall a b. (a, b) -> b
snd [(LIE GhcRn, Avails)]
ie_avails))
(Maybe [(LIE GhcRn, Avails)], Avails)
-> RnM (Maybe [(LIE GhcRn, Avails)], Avails)
forall (m :: * -> *) a. Monad m => a -> m a
return ([(LIE GhcRn, Avails)] -> Maybe [(LIE GhcRn, Avails)]
forall a. a -> Maybe a
Just [(LIE GhcRn, Avails)]
ie_avails, Avails
final_exports)
where
do_litem :: ExportAccum -> LIE GhcPs
-> RnM (Maybe (ExportAccum, (LIE GhcRn, Avails)))
do_litem :: ExportAccum
-> LIE GhcPs -> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
do_litem ExportAccum
acc LIE GhcPs
lie = SrcSpan
-> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
-> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan (LIE GhcPs -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc LIE GhcPs
lie) (ExportAccum
-> LIE GhcPs -> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
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_name :: GlobalRdrElt -> Name
gre_name = Name
me, gre_par :: GlobalRdrElt -> Parent
gre_par = ParentIs Name
p })
| Name -> Bool
isTyConName Name
p, Name -> Bool
isTyConName Name
me = [GlobalRdrElt
gre, GlobalRdrElt
gre{ gre_par :: Parent
gre_par = Parent
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 -> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
exports_from_item (ExportAccum ExportOccMap
occs UniqSet ModuleName
earlier_mods)
(LIE GhcPs -> Located (SrcSpanLess (LIE GhcPs))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
loc ie :: SrcSpanLess (LIE GhcPs)
ie@(IEModuleContents _ lmod@(dL->L _ mod)))
| ModuleName
SrcSpanLess (Located ModuleName)
mod ModuleName -> UniqSet ModuleName -> Bool
forall a. Uniquable a => a -> UniqSet a -> Bool
`elementOfUniqSet` UniqSet ModuleName
earlier_mods
= do { WarningFlag -> Bool -> SDoc -> TcRn ()
warnIfFlag WarningFlag
Opt_WarnDuplicateExports Bool
True
(ModuleName -> SDoc
dupModuleExport ModuleName
SrcSpanLess (Located ModuleName)
mod) ;
Maybe (ExportAccum, (LIE GhcRn, Avails))
-> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (ExportAccum, (LIE GhcRn, Avails))
forall a. Maybe a
Nothing }
| Bool
otherwise
= do { let { exportValid :: Bool
exportValid = (ModuleName
SrcSpanLess (Located ModuleName)
mod ModuleName -> [ModuleName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ModuleName]
imported_modules)
Bool -> Bool -> Bool
|| (Module -> ModuleName
moduleName Module
this_mod ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName
SrcSpanLess (Located ModuleName)
mod)
; gre_prs :: [(GlobalRdrElt, GlobalRdrElt)]
gre_prs = ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)]
pickGREsModExp ModuleName
SrcSpanLess (Located ModuleName)
mod (GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts GlobalRdrEnv
rdr_env)
; new_exports :: Avails
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 (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
SrcSpanLess (Located ModuleName)
mod
}
; Bool -> SDoc -> TcRn ()
checkErr Bool
exportValid (ModuleName -> SDoc
moduleNotImported ModuleName
SrcSpanLess (Located ModuleName)
mod)
; WarningFlag -> Bool -> SDoc -> TcRn ()
warnIfFlag WarningFlag
Opt_WarnDodgyExports
(Bool
exportValid Bool -> Bool -> Bool
&& [(GlobalRdrElt, GlobalRdrElt)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(GlobalRdrElt, GlobalRdrElt)]
gre_prs)
(ModuleName -> SDoc
nullModuleExport ModuleName
SrcSpanLess (Located ModuleName)
mod)
; String -> SDoc -> TcRn ()
traceRn String
"efa" (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
SrcSpanLess (Located ModuleName)
mod SDoc -> SDoc -> SDoc
$$ [GlobalRdrElt] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [GlobalRdrElt]
all_gres)
; [GlobalRdrElt] -> TcRn ()
addUsedGREs [GlobalRdrElt]
all_gres
; ExportOccMap
occs' <- IE GhcPs -> ExportOccMap -> Avails -> RnM ExportOccMap
check_occs SrcSpanLess (LIE GhcPs)
IE GhcPs
ie ExportOccMap
occs Avails
new_exports
; String -> SDoc -> TcRn ()
traceRn String
"export_mod"
([SDoc] -> SDoc
vcat [ ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
SrcSpanLess (Located ModuleName)
mod
, Avails -> SDoc
forall a. Outputable a => a -> SDoc
ppr Avails
new_exports ])
; Maybe (ExportAccum, (LIE GhcRn, Avails))
-> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
forall (m :: * -> *) a. Monad m => a -> m a
return ((ExportAccum, (LIE GhcRn, Avails))
-> Maybe (ExportAccum, (LIE GhcRn, Avails))
forall a. a -> Maybe a
Just ( ExportOccMap -> UniqSet ModuleName -> ExportAccum
ExportAccum ExportOccMap
occs' UniqSet ModuleName
mods
, ( SrcSpan -> SrcSpanLess (LIE GhcRn) -> LIE GhcRn
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
loc (XIEModuleContents GhcRn -> Located ModuleName -> IE GhcRn
forall pass.
XIEModuleContents pass -> Located ModuleName -> IE pass
IEModuleContents XIEModuleContents GhcRn
NoExtField
noExtField Located ModuleName
lmod)
, Avails
new_exports))) }
exports_from_item acc :: ExportAccum
acc@(ExportAccum ExportOccMap
occs UniqSet ModuleName
mods) (LIE GhcPs -> Located (SrcSpanLess (LIE GhcPs))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
loc SrcSpanLess (LIE GhcPs)
ie)
| IE GhcPs -> Bool
isDoc SrcSpanLess (LIE GhcPs)
IE GhcPs
ie
= do IE GhcRn
new_ie <- IE GhcPs -> RnM (IE GhcRn)
lookup_doc_ie SrcSpanLess (LIE GhcPs)
IE GhcPs
ie
Maybe (ExportAccum, (LIE GhcRn, Avails))
-> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
forall (m :: * -> *) a. Monad m => a -> m a
return ((ExportAccum, (LIE GhcRn, Avails))
-> Maybe (ExportAccum, (LIE GhcRn, Avails))
forall a. a -> Maybe a
Just (ExportAccum
acc, (SrcSpan -> SrcSpanLess (LIE GhcRn) -> LIE GhcRn
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
loc SrcSpanLess (LIE GhcRn)
IE GhcRn
new_ie, [])))
| Bool
otherwise
= do (IE GhcRn
new_ie, AvailInfo
avail) <- IE GhcPs -> RnM (IE GhcRn, AvailInfo)
lookup_ie SrcSpanLess (LIE GhcPs)
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, (LIE GhcRn, Avails))
-> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (ExportAccum, (LIE GhcRn, Avails))
forall a. Maybe a
Nothing
else do
ExportOccMap
occs' <- IE GhcPs -> ExportOccMap -> Avails -> RnM ExportOccMap
check_occs SrcSpanLess (LIE GhcPs)
IE GhcPs
ie ExportOccMap
occs [AvailInfo
avail]
Maybe (ExportAccum, (LIE GhcRn, Avails))
-> TcRn (Maybe (ExportAccum, (LIE GhcRn, Avails)))
forall (m :: * -> *) a. Monad m => a -> m a
return ((ExportAccum, (LIE GhcRn, Avails))
-> Maybe (ExportAccum, (LIE GhcRn, Avails))
forall a. a -> Maybe a
Just ( ExportOccMap -> UniqSet ModuleName -> ExportAccum
ExportAccum ExportOccMap
occs' UniqSet ModuleName
mods
, (SrcSpan -> SrcSpanLess (LIE GhcRn) -> LIE GhcRn
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
loc SrcSpanLess (LIE GhcRn)
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
_ (LIEWrappedName (IdP GhcPs)
-> Located (SrcSpanLess (LIEWrappedName RdrName))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
l SrcSpanLess (LIEWrappedName RdrName)
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 RdrName -> RdrName
forall name. IEWrappedName name -> name
ieWrappedName SrcSpanLess (LIEWrappedName RdrName)
IEWrappedName RdrName
rdr
(IE GhcRn, AvailInfo) -> RnM (IE GhcRn, AvailInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEVar GhcRn -> LIEWrappedName (IdP GhcRn) -> IE GhcRn
forall pass. XIEVar pass -> LIEWrappedName (IdP pass) -> IE pass
IEVar XIEVar GhcRn
NoExtField
noExtField (SrcSpan -> SrcSpanLess (LIEWrappedName Name) -> LIEWrappedName Name
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
l (IEWrappedName RdrName -> Name -> IEWrappedName Name
forall name1 name2.
IEWrappedName name1 -> name2 -> IEWrappedName name2
replaceWrappedName SrcSpanLess (LIEWrappedName RdrName)
IEWrappedName RdrName
rdr Name
name)), AvailInfo
avail)
lookup_ie (IEThingAbs XIEThingAbs GhcPs
_ (LIEWrappedName (IdP GhcPs)
-> Located (SrcSpanLess (LIEWrappedName RdrName))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
l SrcSpanLess (LIEWrappedName RdrName)
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 RdrName -> RdrName
forall name. IEWrappedName name -> name
ieWrappedName SrcSpanLess (LIEWrappedName RdrName)
IEWrappedName RdrName
rdr
(IE GhcRn, AvailInfo) -> RnM (IE GhcRn, AvailInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEThingAbs GhcRn -> LIEWrappedName (IdP GhcRn) -> IE GhcRn
forall pass.
XIEThingAbs pass -> LIEWrappedName (IdP pass) -> IE pass
IEThingAbs XIEThingAbs GhcRn
NoExtField
noExtField (SrcSpan -> SrcSpanLess (LIEWrappedName Name) -> LIEWrappedName Name
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
l (IEWrappedName RdrName -> Name -> IEWrappedName Name
forall name1 name2.
IEWrappedName name1 -> name2 -> IEWrappedName name2
replaceWrappedName SrcSpanLess (LIEWrappedName RdrName)
IEWrappedName RdrName
rdr Name
name))
, AvailInfo
avail)
lookup_ie ie :: IE GhcPs
ie@(IEThingAll XIEThingAll GhcPs
_ LIEWrappedName (IdP GhcPs)
n')
= do
(Located Name
n, [Name]
avail, [FieldLabel]
flds) <- IE GhcPs
-> LIEWrappedName RdrName
-> RnM (Located Name, [Name], [FieldLabel])
lookup_ie_all IE GhcPs
ie LIEWrappedName RdrName
LIEWrappedName (IdP GhcPs)
n'
let name :: SrcSpanLess (Located Name)
name = Located Name -> SrcSpanLess (Located Name)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Name
n
(IE GhcRn, AvailInfo) -> RnM (IE GhcRn, AvailInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEThingAll GhcRn -> LIEWrappedName (IdP GhcRn) -> IE GhcRn
forall pass.
XIEThingAll pass -> LIEWrappedName (IdP pass) -> IE pass
IEThingAll XIEThingAll GhcRn
NoExtField
noExtField (LIEWrappedName RdrName -> Name -> LIEWrappedName Name
forall name1 name2.
LIEWrappedName name1 -> name2 -> LIEWrappedName name2
replaceLWrappedName LIEWrappedName RdrName
LIEWrappedName (IdP GhcPs)
n' (Located Name -> SrcSpanLess (Located Name)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Name
n))
, Name -> [Name] -> [FieldLabel] -> AvailInfo
AvailTC Name
SrcSpanLess (Located Name)
name (Name
SrcSpanLess (Located Name)
nameName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[Name]
avail) [FieldLabel]
flds)
lookup_ie ie :: IE GhcPs
ie@(IEThingWith XIEThingWith GhcPs
_ LIEWrappedName (IdP GhcPs)
l IEWildcard
wc [LIEWrappedName (IdP GhcPs)]
sub_rdrs [Located (FieldLbl (IdP GhcPs))]
_)
= do
(Located Name
lname, [LIEWrappedName Name]
subs, [Name]
avails, [Located FieldLabel]
flds)
<- IE GhcPs
-> TcM
(Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
-> TcM
(Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
forall (p :: Pass) a.
OutputableBndrId p =>
IE (GhcPass p) -> TcM a -> TcM a
addExportErrCtxt IE GhcPs
ie (TcM
(Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
-> TcM
(Located Name, [LIEWrappedName Name], [Name],
[Located FieldLabel]))
-> TcM
(Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
-> TcM
(Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
forall a b. (a -> b) -> a -> b
$ LIEWrappedName RdrName
-> [LIEWrappedName RdrName]
-> TcM
(Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
lookup_ie_with LIEWrappedName RdrName
LIEWrappedName (IdP GhcPs)
l [LIEWrappedName RdrName]
[LIEWrappedName (IdP 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 (m :: * -> *) a. Monad m => a -> m a
return (Located Name
lname, [], [])
IEWildcard Int
_ -> IE GhcPs
-> LIEWrappedName RdrName
-> RnM (Located Name, [Name], [FieldLabel])
lookup_ie_all IE GhcPs
ie LIEWrappedName RdrName
LIEWrappedName (IdP GhcPs)
l
let name :: SrcSpanLess (Located Name)
name = Located Name -> SrcSpanLess (Located Name)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Name
lname
(IE GhcRn, AvailInfo) -> RnM (IE GhcRn, AvailInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEThingWith GhcRn
-> LIEWrappedName (IdP GhcRn)
-> IEWildcard
-> [LIEWrappedName (IdP GhcRn)]
-> [Located (FieldLbl (IdP GhcRn))]
-> IE GhcRn
forall pass.
XIEThingWith pass
-> LIEWrappedName (IdP pass)
-> IEWildcard
-> [LIEWrappedName (IdP pass)]
-> [Located (FieldLbl (IdP pass))]
-> IE pass
IEThingWith XIEThingWith GhcRn
NoExtField
noExtField (LIEWrappedName RdrName -> Name -> LIEWrappedName Name
forall name1 name2.
LIEWrappedName name1 -> name2 -> LIEWrappedName name2
replaceLWrappedName LIEWrappedName RdrName
LIEWrappedName (IdP GhcPs)
l Name
SrcSpanLess (Located Name)
name) IEWildcard
wc [LIEWrappedName Name]
[LIEWrappedName (IdP GhcRn)]
subs
([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 a. HasSrcSpan a => SrcSpanLess a -> a
noLoc [FieldLabel]
all_flds)),
Name -> [Name] -> [FieldLabel] -> AvailInfo
AvailTC Name
SrcSpanLess (Located Name)
name (Name
SrcSpanLess (Located 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 a. HasSrcSpan a => a -> SrcSpanLess a
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. String -> a
panic String
"lookup_ie"
lookup_ie_with :: LIEWrappedName RdrName -> [LIEWrappedName RdrName]
-> RnM (Located Name, [LIEWrappedName Name], [Name],
[Located FieldLabel])
lookup_ie_with :: LIEWrappedName RdrName
-> [LIEWrappedName RdrName]
-> TcM
(Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
lookup_ie_with (LIEWrappedName RdrName
-> Located (SrcSpanLess (LIEWrappedName RdrName))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
l SrcSpanLess (LIEWrappedName RdrName)
rdr) [LIEWrappedName RdrName]
sub_rdrs
= do Name
name <- RdrName -> RnM Name
lookupGlobalOccRn (RdrName -> RnM Name) -> RdrName -> RnM Name
forall a b. (a -> b) -> a -> b
$ IEWrappedName RdrName -> RdrName
forall name. IEWrappedName name -> name
ieWrappedName SrcSpanLess (LIEWrappedName RdrName)
IEWrappedName RdrName
rdr
([LIEWrappedName Name]
non_flds, [Located FieldLabel]
flds) <- Name
-> [LIEWrappedName RdrName]
-> RnM ([LIEWrappedName Name], [Located FieldLabel])
lookupChildrenExport Name
name [LIEWrappedName RdrName]
sub_rdrs
if Name -> Bool
isUnboundName Name
name
then (Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
-> TcM
(Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
forall (m :: * -> *) a. Monad m => a -> m a
return (SrcSpan -> SrcSpanLess (Located Name) -> Located Name
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
l Name
SrcSpanLess (Located Name)
name, [], [Name
name], [])
else (Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
-> TcM
(Located Name, [LIEWrappedName Name], [Name], [Located FieldLabel])
forall (m :: * -> *) a. Monad m => a -> m a
return (SrcSpan -> SrcSpanLess (Located Name) -> Located Name
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
l Name
SrcSpanLess (Located Name)
name, [LIEWrappedName Name]
non_flds
, (LIEWrappedName Name -> Name) -> [LIEWrappedName Name] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map (IEWrappedName Name -> Name
forall name. IEWrappedName name -> name
ieWrappedName (IEWrappedName Name -> Name)
-> (LIEWrappedName Name -> IEWrappedName Name)
-> LIEWrappedName Name
-> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LIEWrappedName Name -> IEWrappedName Name
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc) [LIEWrappedName Name]
non_flds
, [Located FieldLabel]
flds)
lookup_ie_all :: IE GhcPs -> LIEWrappedName RdrName
-> RnM (Located Name, [Name], [FieldLabel])
lookup_ie_all :: IE GhcPs
-> LIEWrappedName RdrName
-> RnM (Located Name, [Name], [FieldLabel])
lookup_ie_all IE GhcPs
ie (LIEWrappedName RdrName
-> Located (SrcSpanLess (LIEWrappedName RdrName))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L SrcSpan
l SrcSpanLess (LIEWrappedName RdrName)
rdr) =
do Name
name <- RdrName -> RnM Name
lookupGlobalOccRn (RdrName -> RnM Name) -> RdrName -> RnM Name
forall a b. (a -> b) -> a -> b
$ IEWrappedName RdrName -> RdrName
forall name. IEWrappedName name -> name
ieWrappedName SrcSpanLess (LIEWrappedName RdrName)
IEWrappedName RdrName
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 RdrName -> RdrName
forall name. IEWrappedName name -> name
ieWrappedName SrcSpanLess (LIEWrappedName RdrName)
IEWrappedName RdrName
rdr) [GlobalRdrElt]
gres
Bool
warnDodgyExports <- WarningFlag -> IOEnv (Env TcGblEnv TcLclEnv) Bool
forall gbl lcl. WarningFlag -> TcRnIf gbl lcl Bool
woptM WarningFlag
Opt_WarnDodgyExports
Bool -> TcRn () -> TcRn ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([GlobalRdrElt] -> 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 Bool -> TcRn () -> TcRn ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
warnDodgyExports (TcRn () -> TcRn ()) -> TcRn () -> TcRn ()
forall a b. (a -> b) -> a -> b
$
WarnReason -> SDoc -> TcRn ()
addWarn (WarningFlag -> WarnReason
Reason WarningFlag
Opt_WarnDodgyExports)
(Name -> SDoc
dodgyExportWarn Name
name)
else
SDoc -> TcRn ()
addErr (IE GhcPs -> SDoc
exportItemErr IE GhcPs
ie)
(Located Name, [Name], [FieldLabel])
-> RnM (Located Name, [Name], [FieldLabel])
forall (m :: * -> *) a. Monad m => a -> m a
return (SrcSpan -> SrcSpanLess (Located Name) -> Located Name
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
l Name
SrcSpanLess (Located Name)
name, [Name]
non_flds, [FieldLabel]
flds)
lookup_doc_ie :: IE GhcPs -> RnM (IE GhcRn)
lookup_doc_ie :: IE GhcPs -> RnM (IE GhcRn)
lookup_doc_ie (IEGroup XIEGroup GhcPs
_ Int
lev HsDocString
doc) = do HsDocString
rn_doc <- HsDocString -> RnM HsDocString
rnHsDoc HsDocString
doc
IE GhcRn -> RnM (IE GhcRn)
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEGroup GhcRn -> Int -> HsDocString -> IE GhcRn
forall pass. XIEGroup pass -> Int -> HsDocString -> IE pass
IEGroup XIEGroup GhcRn
NoExtField
noExtField Int
lev HsDocString
rn_doc)
lookup_doc_ie (IEDoc XIEDoc GhcPs
_ HsDocString
doc) = do HsDocString
rn_doc <- HsDocString -> RnM HsDocString
rnHsDoc HsDocString
doc
IE GhcRn -> RnM (IE GhcRn)
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEDoc GhcRn -> HsDocString -> IE GhcRn
forall pass. XIEDoc pass -> HsDocString -> IE pass
IEDoc XIEDoc GhcRn
NoExtField
noExtField HsDocString
rn_doc)
lookup_doc_ie (IEDocNamed XIEDocNamed GhcPs
_ String
str) = IE GhcRn -> RnM (IE GhcRn)
forall (m :: * -> *) a. Monad m => a -> m a
return (XIEDocNamed GhcRn -> String -> IE GhcRn
forall pass. XIEDocNamed pass -> String -> IE pass
IEDocNamed XIEDocNamed GhcRn
NoExtField
noExtField String
str)
lookup_doc_ie IE GhcPs
_ = String -> RnM (IE GhcRn)
forall a. String -> a
panic String
"lookup_doc_ie"
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 = [Either Name FieldLabel] -> ([Name], [FieldLabel])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ([Either Name FieldLabel] -> ([Name], [FieldLabel]))
-> ([GlobalRdrElt] -> [Either Name FieldLabel])
-> [GlobalRdrElt]
-> ([Name], [FieldLabel])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GlobalRdrElt -> Either Name FieldLabel)
-> [GlobalRdrElt] -> [Either Name FieldLabel]
forall a b. (a -> b) -> [a] -> [b]
map GlobalRdrElt -> Either Name FieldLabel
classifyGRE
classifyGRE :: GlobalRdrElt -> Either Name FieldLabel
classifyGRE :: GlobalRdrElt -> Either Name FieldLabel
classifyGRE GlobalRdrElt
gre = case GlobalRdrElt -> Parent
gre_par GlobalRdrElt
gre of
FldParent Name
_ Maybe FastString
Nothing -> FieldLabel -> Either Name FieldLabel
forall a b. b -> Either a b
Right (FastString -> Bool -> Name -> FieldLabel
forall a. FastString -> Bool -> a -> FieldLbl a
FieldLabel (OccName -> FastString
occNameFS (Name -> OccName
nameOccName Name
n)) Bool
False Name
n)
FldParent Name
_ (Just FastString
lbl) -> FieldLabel -> Either Name FieldLabel
forall a b. b -> Either a b
Right (FastString -> Bool -> Name -> FieldLabel
forall a. FastString -> Bool -> a -> FieldLbl a
FieldLabel FastString
lbl Bool
True Name
n)
Parent
_ -> Name -> Either Name FieldLabel
forall a b. a -> Either a b
Left Name
n
where
n :: Name
n = GlobalRdrElt -> Name
gre_name GlobalRdrElt
gre
isDoc :: IE GhcPs -> Bool
isDoc :: IE GhcPs -> Bool
isDoc (IEDoc {}) = Bool
True
isDoc (IEDocNamed {}) = Bool
True
isDoc (IEGroup {}) = Bool
True
isDoc IE GhcPs
_ = Bool
False
lookupChildrenExport :: Name -> [LIEWrappedName RdrName]
-> RnM ([LIEWrappedName Name], [Located FieldLabel])
lookupChildrenExport :: Name
-> [LIEWrappedName RdrName]
-> RnM ([LIEWrappedName Name], [Located FieldLabel])
lookupChildrenExport Name
spec_parent [LIEWrappedName RdrName]
rdr_items =
do
[Either (LIEWrappedName Name) (Located FieldLabel)]
xs <- (LIEWrappedName RdrName
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel)))
-> [LIEWrappedName RdrName]
-> TcRn [Either (LIEWrappedName Name) (Located FieldLabel)]
forall a b. (a -> TcRn b) -> [a] -> TcRn [b]
mapAndReportM LIEWrappedName RdrName
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel))
doOne [LIEWrappedName RdrName]
rdr_items
([LIEWrappedName Name], [Located FieldLabel])
-> RnM ([LIEWrappedName Name], [Located FieldLabel])
forall (m :: * -> *) a. Monad m => a -> m a
return (([LIEWrappedName Name], [Located FieldLabel])
-> RnM ([LIEWrappedName Name], [Located FieldLabel]))
-> ([LIEWrappedName Name], [Located FieldLabel])
-> RnM ([LIEWrappedName Name], [Located FieldLabel])
forall a b. (a -> b) -> a -> b
$ [Either (LIEWrappedName Name) (Located FieldLabel)]
-> ([LIEWrappedName Name], [Located FieldLabel])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either (LIEWrappedName Name) (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 RdrName
-> RnM (Either (LIEWrappedName Name) (Located FieldLabel))
doOne :: LIEWrappedName RdrName
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel))
doOne LIEWrappedName RdrName
n = do
let bareName :: RdrName
bareName = (IEWrappedName RdrName -> RdrName
forall name. IEWrappedName name -> name
ieWrappedName (IEWrappedName RdrName -> RdrName)
-> (LIEWrappedName RdrName -> IEWrappedName RdrName)
-> LIEWrappedName RdrName
-> RdrName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LIEWrappedName RdrName -> IEWrappedName RdrName
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc) LIEWrappedName RdrName
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 :: SrcSpan
l = LIEWrappedName RdrName -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc LIEWrappedName RdrName
n
; Either (LIEWrappedName Name) (Located FieldLabel)
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel))
forall (m :: * -> *) a. Monad m => a -> m a
return (LIEWrappedName Name
-> Either (LIEWrappedName Name) (Located FieldLabel)
forall a b. a -> Either a b
Left (SrcSpan -> SrcSpanLess (LIEWrappedName Name) -> LIEWrappedName Name
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
l (Located Name -> IEWrappedName Name
forall name. Located name -> IEWrappedName name
IEName (SrcSpan -> SrcSpanLess (Located Name) -> Located Name
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
l Name
SrcSpanLess (Located Name)
ub))))}
FoundFL FieldLabel
fls -> Either (LIEWrappedName Name) (Located FieldLabel)
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either (LIEWrappedName Name) (Located FieldLabel)
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel)))
-> Either (LIEWrappedName Name) (Located FieldLabel)
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel))
forall a b. (a -> b) -> a -> b
$ Located FieldLabel
-> Either (LIEWrappedName Name) (Located FieldLabel)
forall a b. b -> Either a b
Right (SrcSpan -> SrcSpanLess (Located FieldLabel) -> Located FieldLabel
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL (LIEWrappedName RdrName -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc LIEWrappedName RdrName
n) SrcSpanLess (Located FieldLabel)
FieldLabel
fls)
FoundName Parent
par Name
name -> do { Name -> Parent -> Name -> TcRn ()
checkPatSynParent Name
spec_parent Parent
par Name
name
; Either (LIEWrappedName Name) (Located FieldLabel)
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel))
forall (m :: * -> *) a. Monad m => a -> m a
return
(Either (LIEWrappedName Name) (Located FieldLabel)
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel)))
-> Either (LIEWrappedName Name) (Located FieldLabel)
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel))
forall a b. (a -> b) -> a -> b
$ LIEWrappedName Name
-> Either (LIEWrappedName Name) (Located FieldLabel)
forall a b. a -> Either a b
Left (LIEWrappedName RdrName -> Name -> LIEWrappedName Name
forall name1 name2.
LIEWrappedName name1 -> name2 -> LIEWrappedName name2
replaceLWrappedName LIEWrappedName RdrName
n Name
name) }
IncorrectParent Name
p Name
g SDoc
td [Name]
gs -> Name
-> Name
-> SDoc
-> [Name]
-> TcRn (Either (LIEWrappedName Name) (Located FieldLabel))
forall a. Name -> Name -> SDoc -> [Name] -> TcM a
failWithDcErr Name
p Name
g SDoc
td [Name]
gs
checkPatSynParent :: Name
-> Parent
-> Name
-> TcM ()
checkPatSynParent :: Name -> Parent -> Name -> TcRn ()
checkPatSynParent Name
_ (ParentIs {}) Name
_
= () -> TcRn ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkPatSynParent Name
_ (FldParent {}) Name
_
= () -> TcRn ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkPatSynParent Name
parent Parent
NoParent Name
mpat_syn
| Name -> Bool
isUnboundName Name
parent
= () -> TcRn ()
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 Name
mpat_syn
; 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 (Id -> SDoc
selErr Id
i) 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 -> Name -> SDoc -> [Name] -> TcRn ()
forall a. Name -> Name -> SDoc -> [Name] -> TcM a
failWithDcErr Name
parent Name
mpat_syn (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
mpat_syn) [] }
where
psErr :: PatSyn -> SDoc
psErr = String -> PatSyn -> SDoc
forall o. Outputable o => String -> o -> SDoc
exportErrCtxt String
"pattern synonym"
selErr :: Id -> SDoc
selErr = String -> Id -> SDoc
forall o. Outputable o => String -> o -> SDoc
exportErrCtxt String
"pattern synonym record selector"
assocClassErr :: SDoc
assocClassErr :: SDoc
assocClassErr = String -> SDoc
text String
"Pattern synonyms can be bundled only with datatypes."
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
$ SDoc -> TcRn ()
forall a. SDoc -> TcM a
failWithTc SDoc
assocClassErr
| Maybe TyCon
Nothing <- Maybe TyCon
mtycon
= () -> TcRn ()
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
$ SDoc -> TcRn ()
forall a. SDoc -> TcM a
failWithTc SDoc
typeMismatchError
| Bool
otherwise
= () -> TcRn ()
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]
_, [Type]
_, Type
res_ty) = PatSyn -> ([Id], [Type], [Id], [Type], [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
typeMismatchError :: SDoc
typeMismatchError :: SDoc
typeMismatchError =
String -> SDoc
text String
"Pattern synonyms can only be bundled with matching type constructors"
SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"Couldn't match expected type of"
SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Type -> SDoc
forall a. Outputable a => a -> SDoc
ppr Type
expected_res_ty)
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"with actual type of"
SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Type -> SDoc
forall a. Outputable a => a -> SDoc
ppr Type
res_ty)
check_occs :: IE GhcPs -> ExportOccMap -> [AvailInfo]
-> RnM ExportOccMap
check_occs :: IE GhcPs -> ExportOccMap -> Avails -> RnM ExportOccMap
check_occs IE GhcPs
ie ExportOccMap
occs Avails
avails
= (ExportOccMap -> (Name, OccName) -> RnM ExportOccMap)
-> ExportOccMap -> [(Name, OccName)] -> RnM ExportOccMap
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM ExportOccMap -> (Name, OccName) -> RnM ExportOccMap
check ExportOccMap
occs [(Name, OccName)]
names_with_occs
where
names_with_occs :: [(Name, OccName)]
names_with_occs = Avails -> [(Name, OccName)]
availsNamesWithOccs Avails
avails
check :: ExportOccMap -> (Name, OccName) -> RnM ExportOccMap
check ExportOccMap
occs (Name
name, OccName
occ)
= case ExportOccMap -> OccName -> Maybe (Name, IE GhcPs)
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv ExportOccMap
occs OccName
name_occ of
Maybe (Name, IE GhcPs)
Nothing -> ExportOccMap -> RnM ExportOccMap
forall (m :: * -> *) a. Monad m => a -> m a
return (ExportOccMap -> OccName -> (Name, IE GhcPs) -> ExportOccMap
forall a. OccEnv a -> OccName -> a -> OccEnv a
extendOccEnv ExportOccMap
occs OccName
name_occ (Name
name, IE GhcPs
ie))
Just (Name
name', IE GhcPs
ie')
| Name
name Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name'
-> do { WarningFlag -> Bool -> SDoc -> TcRn ()
warnIfFlag WarningFlag
Opt_WarnDuplicateExports
(Bool -> Bool
not (Name -> IE GhcPs -> IE GhcPs -> Bool
dupExport_ok Name
name IE GhcPs
ie IE GhcPs
ie'))
(OccName -> IE GhcPs -> IE GhcPs -> SDoc
dupExportWarn OccName
occ IE GhcPs
ie IE GhcPs
ie')
; ExportOccMap -> RnM ExportOccMap
forall (m :: * -> *) a. Monad m => a -> m a
return ExportOccMap
occs }
| Bool
otherwise
-> do { GlobalRdrEnv
global_env <- TcRn GlobalRdrEnv
getGlobalRdrEnv ;
SDoc -> TcRn ()
addErr (GlobalRdrEnv
-> OccName -> Name -> Name -> IE GhcPs -> IE GhcPs -> SDoc
exportClashErr GlobalRdrEnv
global_env OccName
occ Name
name' Name
name IE GhcPs
ie' IE GhcPs
ie) ;
ExportOccMap -> RnM ExportOccMap
forall (m :: * -> *) a. Monad m => a -> m a
return ExportOccMap
occs }
where
name_occ :: OccName
name_occ = Name -> OccName
nameOccName Name
name
dupExport_ok :: Name -> IE GhcPs -> IE GhcPs -> Bool
dupExport_ok :: Name -> IE GhcPs -> IE GhcPs -> Bool
dupExport_ok Name
n 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 (IdP GhcPs)
r)
= Name -> OccName
nameOccName Name
n OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
== RdrName -> OccName
rdrNameOcc (IEWrappedName RdrName -> RdrName
forall name. IEWrappedName name -> name
ieWrappedName (IEWrappedName RdrName -> RdrName)
-> IEWrappedName RdrName -> RdrName
forall a b. (a -> b) -> a -> b
$ LIEWrappedName RdrName -> SrcSpanLess (LIEWrappedName RdrName)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc LIEWrappedName RdrName
LIEWrappedName (IdP 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
dupModuleExport :: ModuleName -> SDoc
dupModuleExport :: ModuleName -> SDoc
dupModuleExport ModuleName
mod
= [SDoc] -> SDoc
hsep [String -> SDoc
text String
"Duplicate",
SDoc -> SDoc
quotes (String -> SDoc
text String
"Module" SDoc -> SDoc -> SDoc
<+> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod),
String -> SDoc
text String
"in export list"]
moduleNotImported :: ModuleName -> SDoc
moduleNotImported :: ModuleName -> SDoc
moduleNotImported ModuleName
mod
= [SDoc] -> SDoc
hsep [String -> SDoc
text String
"The export item",
SDoc -> SDoc
quotes (String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod),
String -> SDoc
text String
"is not imported"]
nullModuleExport :: ModuleName -> SDoc
nullModuleExport :: ModuleName -> SDoc
nullModuleExport ModuleName
mod
= [SDoc] -> SDoc
hsep [String -> SDoc
text String
"The export item",
SDoc -> SDoc
quotes (String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod),
String -> SDoc
text String
"exports nothing"]
missingModuleExportWarn :: ModuleName -> SDoc
missingModuleExportWarn :: ModuleName -> SDoc
missingModuleExportWarn ModuleName
mod
= [SDoc] -> SDoc
hsep [String -> SDoc
text String
"The export item",
SDoc -> SDoc
quotes (String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod),
String -> SDoc
text String
"is missing an export list"]
dodgyExportWarn :: Name -> SDoc
dodgyExportWarn :: Name -> SDoc
dodgyExportWarn Name
item
= SDoc -> Name -> IE GhcRn -> SDoc
forall a b. (Outputable a, Outputable b) => SDoc -> a -> b -> SDoc
dodgyMsg (String -> SDoc
text String
"export") Name
item (IdP GhcRn -> IE GhcRn
forall (p :: Pass). IdP (GhcPass p) -> IE (GhcPass p)
dodgyMsgInsert Name
IdP GhcRn
item :: IE GhcRn)
exportErrCtxt :: Outputable o => String -> o -> SDoc
exportErrCtxt :: String -> o -> SDoc
exportErrCtxt String
herald o
exp =
String -> SDoc
text String
"In the" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text (String
herald String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":") SDoc -> SDoc -> SDoc
<+> o -> SDoc
forall a. Outputable a => a -> SDoc
ppr o
exp
addExportErrCtxt :: (OutputableBndrId p)
=> IE (GhcPass p) -> TcM a -> TcM a
addExportErrCtxt :: 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
text String
"In the export:" SDoc -> SDoc -> SDoc
<+> IE (GhcPass p) -> SDoc
forall a. Outputable a => a -> SDoc
ppr IE (GhcPass p)
ie
exportItemErr :: IE GhcPs -> SDoc
exportItemErr :: IE GhcPs -> SDoc
exportItemErr IE GhcPs
export_item
= [SDoc] -> SDoc
sep [ String -> SDoc
text String
"The export item" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (IE GhcPs -> SDoc
forall a. Outputable a => a -> SDoc
ppr IE GhcPs
export_item),
String -> SDoc
text String
"attempts to export constructors or class methods that are not visible here" ]
dupExportWarn :: OccName -> IE GhcPs -> IE GhcPs -> SDoc
dupExportWarn :: OccName -> IE GhcPs -> IE GhcPs -> SDoc
dupExportWarn OccName
occ_name IE GhcPs
ie1 IE GhcPs
ie2
= [SDoc] -> SDoc
hsep [SDoc -> SDoc
quotes (OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ_name),
String -> SDoc
text String
"is exported by", SDoc -> SDoc
quotes (IE GhcPs -> SDoc
forall a. Outputable a => a -> SDoc
ppr IE GhcPs
ie1),
String -> SDoc
text String
"and", SDoc -> SDoc
quotes (IE GhcPs -> SDoc
forall a. Outputable a => a -> SDoc
ppr IE GhcPs
ie2)]
dcErrMsg :: Name -> String -> SDoc -> [SDoc] -> SDoc
dcErrMsg :: Name -> String -> SDoc -> [SDoc] -> SDoc
dcErrMsg Name
ty_con String
what_is SDoc
thing [SDoc]
parents =
String -> SDoc
text String
"The type constructor" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
ty_con)
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is not the parent of the" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
what_is
SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes SDoc
thing SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'.'
SDoc -> SDoc -> SDoc
$$ String -> SDoc
text (String -> String
capitalise String
what_is)
SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"s can only be exported with their parent type constructor."
SDoc -> SDoc -> SDoc
$$ (case [SDoc]
parents of
[] -> SDoc
empty
[SDoc
_] -> String -> SDoc
text String
"Parent:"
[SDoc]
_ -> String -> SDoc
text String
"Parents:") SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
fsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma [SDoc]
parents)
failWithDcErr :: Name -> Name -> SDoc -> [Name] -> TcM a
failWithDcErr :: Name -> Name -> SDoc -> [Name] -> TcM a
failWithDcErr Name
parent Name
thing SDoc
thing_doc [Name]
parents = do
TyThing
ty_thing <- Name -> TcM TyThing
tcLookupGlobal Name
thing
SDoc -> TcM a
forall a. SDoc -> TcM a
failWithTc (SDoc -> TcM a) -> SDoc -> TcM a
forall a b. (a -> b) -> a -> b
$ Name -> String -> SDoc -> [SDoc] -> SDoc
dcErrMsg Name
parent (TyThing -> String
tyThingCategory' TyThing
ty_thing)
SDoc
thing_doc ((Name -> SDoc) -> [Name] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Name]
parents)
where
tyThingCategory' :: TyThing -> String
tyThingCategory' :: TyThing -> String
tyThingCategory' (AnId Id
i)
| Id -> Bool
isRecordSelector Id
i = String
"record selector"
tyThingCategory' TyThing
i = TyThing -> String
tyThingCategory TyThing
i
exportClashErr :: GlobalRdrEnv -> OccName
-> Name -> Name
-> IE GhcPs -> IE GhcPs
-> MsgDoc
exportClashErr :: GlobalRdrEnv
-> OccName -> Name -> Name -> IE GhcPs -> IE GhcPs -> SDoc
exportClashErr GlobalRdrEnv
global_env OccName
occ Name
name1 Name
name2 IE GhcPs
ie1 IE GhcPs
ie2
= [SDoc] -> SDoc
vcat [ String -> SDoc
text String
"Conflicting exports for" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ) SDoc -> SDoc -> SDoc
<> SDoc
colon
, IE GhcPs -> Name -> SDoc
ppr_export IE GhcPs
ie1' Name
name1'
, IE GhcPs -> Name -> SDoc
ppr_export IE GhcPs
ie2' Name
name2' ]
where
ppr_export :: IE GhcPs -> Name -> SDoc
ppr_export IE GhcPs
ie Name
name = Int -> SDoc -> SDoc
nest Int
3 (SDoc -> Int -> SDoc -> SDoc
hang (SDoc -> SDoc
quotes (IE GhcPs -> SDoc
forall a. Outputable a => a -> SDoc
ppr IE GhcPs
ie) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"exports" SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
quotes (Name -> SDoc
ppr_name Name
name))
Int
2 (GlobalRdrElt -> SDoc
pprNameProvenance (Name -> GlobalRdrElt
get_gre Name
name)))
ppr_name :: Name -> SDoc
ppr_name Name
name
| Name -> OccName
nameOccName Name
name OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
== OccName
occ = Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name
| Bool
otherwise = OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ
get_gre :: Name -> GlobalRdrElt
get_gre Name
name
= GlobalRdrElt -> Maybe GlobalRdrElt -> GlobalRdrElt
forall a. a -> Maybe a -> a
fromMaybe (String -> SDoc -> GlobalRdrElt
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"exportClashErr" (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name))
(GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
lookupGRE_Name_OccName GlobalRdrEnv
global_env Name
name OccName
occ)
get_loc :: Name -> SrcSpan
get_loc Name
name = GlobalRdrElt -> SrcSpan
greSrcSpan (Name -> GlobalRdrElt
get_gre Name
name)
(Name
name1', IE GhcPs
ie1', Name
name2', IE GhcPs
ie2') = if Name -> SrcSpan
get_loc Name
name1 SrcSpan -> SrcSpan -> Bool
forall a. Ord a => a -> a -> Bool
< Name -> SrcSpan
get_loc Name
name2
then (Name
name1, IE GhcPs
ie1, Name
name2, IE GhcPs
ie2)
else (Name
name2, IE GhcPs
ie2, Name
name1, IE GhcPs
ie1)