module TcRnExports (tcRnExports, exports_from_avail) where
import HsSyn
import PrelNames
import RdrName
import TcRnMonad
import TcEnv
import TcMType
import TcType
import RnNames
import RnEnv
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 FastString
import Maybes
import qualified GHC.LanguageExtensions as LangExt
import Util (capitalise)
import Control.Monad
import DynFlags
import RnHsDoc ( rnHsDoc )
import RdrHsSyn ( setRdrNameSpace )
import Data.Either ( partitionEithers )
data ExportAccum
= ExportAccum
[LIE Name]
ExportOccMap
[AvailInfo]
emptyExportAccum :: ExportAccum
emptyExportAccum = ExportAccum [] emptyOccEnv []
type ExportOccMap = OccEnv (Name, IE RdrName)
tcRnExports :: Bool
-> Maybe (Located [LIE RdrName])
-> TcGblEnv
-> RnM TcGblEnv
tcRnExports explicit_mod exports
tcg_env@TcGblEnv { tcg_mod = this_mod,
tcg_rdr_env = rdr_env,
tcg_imports = imports,
tcg_src = hsc_src }
= unsetWOptM Opt_WarnWarningsDeprecations $
do {
; dflags <- getDynFlags
; let real_exports
| explicit_mod = exports
| ghcLink dflags == LinkInMemory = Nothing
| otherwise
= Just (noLoc [noLoc
(IEVar (noLoc (IEName $ noLoc main_RDR_Unqual)))])
; let do_it = exports_from_avail real_exports rdr_env imports this_mod
; (rn_exports, final_avails)
<- if hsc_src == HsigFile
then do (msgs, mb_r) <- tryTc do_it
case mb_r of
Just r -> return r
Nothing -> addMessages msgs >> failM
else checkNoErrs $ do_it
; let final_ns = availsToNameSetWithSelectors final_avails
; traceRn "rnExports: Exports:" (ppr final_avails)
; let new_tcg_env =
tcg_env { tcg_exports = final_avails,
tcg_rn_exports = case tcg_rn_exports tcg_env of
Nothing -> Nothing
Just _ -> rn_exports,
tcg_dus = tcg_dus tcg_env `plusDU`
usesOnly final_ns }
; failIfErrsM
; return new_tcg_env }
exports_from_avail :: Maybe (Located [LIE RdrName])
-> GlobalRdrEnv
-> ImportAvails
-> Module
-> RnM (Maybe [LIE Name], [AvailInfo])
exports_from_avail Nothing rdr_env _imports _this_mod
= let avails =
map fix_faminst . gresToAvailInfo
. filter isLocalGRE . globalRdrEnvElts $ rdr_env
in return (Nothing, avails)
where
fix_faminst (AvailTC n ns flds) =
let new_ns =
case ns of
[] -> [n]
(p:_) -> if p == n then ns else n:ns
in AvailTC n new_ns flds
fix_faminst avail = avail
exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
= do ExportAccum ie_names _ exports
<- foldAndRecoverM do_litem emptyExportAccum rdr_items
let final_exports = nubAvails exports
return (Just ie_names, final_exports)
where
do_litem :: ExportAccum -> LIE RdrName -> RnM ExportAccum
do_litem acc lie = setSrcSpan (getLoc lie) (exports_from_item acc lie)
kids_env :: NameEnv [GlobalRdrElt]
kids_env = mkChildEnv (globalRdrEnvElts rdr_env)
imported_modules = [ imv_name imv
| xs <- moduleEnvElts $ imp_mods imports
, imv <- importedByUser xs ]
exports_from_item :: ExportAccum -> LIE RdrName -> RnM ExportAccum
exports_from_item acc@(ExportAccum ie_names occs exports)
(L loc (IEModuleContents (L lm mod)))
| let earlier_mods = [ mod
| (L _ (IEModuleContents (L _ mod))) <- ie_names ]
, mod `elem` earlier_mods
= do { warnIf (Reason Opt_WarnDuplicateExports) True
(dupModuleExport mod) ;
return acc }
| otherwise
= do { let { exportValid = (mod `elem` imported_modules)
|| (moduleName this_mod == mod)
; gre_prs = pickGREsModExp mod (globalRdrEnvElts rdr_env)
; new_exports = map (availFromGRE . fst) gre_prs
; names = map (gre_name . fst) gre_prs
; all_gres = foldr (\(gre1,gre2) gres -> gre1 : gre2 : gres) [] gre_prs
}
; checkErr exportValid (moduleNotImported mod)
; warnIf (Reason Opt_WarnDodgyExports)
(exportValid && null gre_prs)
(nullModuleExport mod)
; traceRn "efa" (ppr mod $$ ppr all_gres)
; addUsedGREs all_gres
; occs' <- check_occs (IEModuleContents (noLoc mod)) occs names
; traceRn "export_mod"
(vcat [ ppr mod
, ppr new_exports ])
; return (ExportAccum (L loc (IEModuleContents (L lm mod)) : ie_names)
occs'
(new_exports ++ exports)) }
exports_from_item acc@(ExportAccum lie_names occs exports) (L loc ie)
| isDoc ie
= do new_ie <- lookup_doc_ie ie
return (ExportAccum (L loc new_ie : lie_names) occs exports)
| otherwise
= do (new_ie, avail) <-
setSrcSpan loc $ lookup_ie ie
if isUnboundName (ieName new_ie)
then return acc
else do
occs' <- check_occs ie occs (availNames avail)
return (ExportAccum (L loc new_ie : lie_names) occs' (avail : exports))
lookup_ie :: IE RdrName -> RnM (IE Name, AvailInfo)
lookup_ie (IEVar (L l rdr))
= do (name, avail) <- lookupGreAvailRn $ ieWrappedName rdr
return (IEVar (L l (replaceWrappedName rdr name)), avail)
lookup_ie (IEThingAbs (L l rdr))
= do (name, avail) <- lookupGreAvailRn $ ieWrappedName rdr
return (IEThingAbs (L l (replaceWrappedName rdr name)), avail)
lookup_ie ie@(IEThingAll n')
= do
(n, avail, flds) <- lookup_ie_all ie n'
let name = unLoc n
return (IEThingAll (replaceLWrappedName n' (unLoc n))
, AvailTC name (name:avail) flds)
lookup_ie ie@(IEThingWith l wc sub_rdrs _)
= do
(lname, subs, avails, flds)
<- addExportErrCtxt ie $ lookup_ie_with l sub_rdrs
(_, all_avail, all_flds) <-
case wc of
NoIEWildcard -> return (lname, [], [])
IEWildcard _ -> lookup_ie_all ie l
let name = unLoc lname
subs' = map (replaceLWrappedName l . unLoc) subs
return (IEThingWith (replaceLWrappedName l name) wc subs'
(map noLoc (flds ++ all_flds)),
AvailTC name (name : avails ++ all_avail)
(flds ++ all_flds))
lookup_ie _ = panic "lookup_ie"
lookup_ie_with :: LIEWrappedName RdrName -> [LIEWrappedName RdrName]
-> RnM (Located Name, [Located Name], [Name], [FieldLabel])
lookup_ie_with (L l rdr) sub_rdrs
= do name <- lookupGlobalOccRn $ ieWrappedName rdr
(non_flds, flds) <- lookupChildrenExport name
(map ieLWrappedName sub_rdrs)
if isUnboundName name
then return (L l name, [], [name], [])
else return (L l name, non_flds
, map unLoc non_flds
, map unLoc flds)
lookup_ie_all :: IE RdrName -> LIEWrappedName RdrName
-> RnM (Located Name, [Name], [FieldLabel])
lookup_ie_all ie (L l rdr) =
do name <- lookupGlobalOccRn $ ieWrappedName rdr
let gres = findChildren kids_env name
(non_flds, flds) = classifyGREs gres
addUsedKids (ieWrappedName rdr) gres
warnDodgyExports <- woptM Opt_WarnDodgyExports
when (null gres) $
if isTyConName name
then when warnDodgyExports $
addWarn (Reason Opt_WarnDodgyExports)
(dodgyExportWarn name)
else
addErr (exportItemErr ie)
return (L l name, non_flds, flds)
lookup_doc_ie :: IE RdrName -> RnM (IE Name)
lookup_doc_ie (IEGroup lev doc) = do rn_doc <- rnHsDoc doc
return (IEGroup lev rn_doc)
lookup_doc_ie (IEDoc doc) = do rn_doc <- rnHsDoc doc
return (IEDoc rn_doc)
lookup_doc_ie (IEDocNamed str) = return (IEDocNamed str)
lookup_doc_ie _ = panic "lookup_doc_ie"
addUsedKids :: RdrName -> [GlobalRdrElt] -> RnM ()
addUsedKids parent_rdr kid_gres = addUsedGREs (pickGREs parent_rdr kid_gres)
classifyGREs :: [GlobalRdrElt] -> ([Name], [FieldLabel])
classifyGREs = partitionEithers . map classifyGRE
classifyGRE :: GlobalRdrElt -> Either Name FieldLabel
classifyGRE gre = case gre_par gre of
FldParent _ Nothing -> Right (FieldLabel (occNameFS (nameOccName n)) False n)
FldParent _ (Just lbl) -> Right (FieldLabel lbl True n)
_ -> Left n
where
n = gre_name gre
isDoc :: IE RdrName -> Bool
isDoc (IEDoc _) = True
isDoc (IEDocNamed _) = True
isDoc (IEGroup _ _) = True
isDoc _ = False
data ChildLookupResult
= NameNotFound
| NameErr ErrMsg
| FoundName Name
| FoundFL FieldLabel
instance Outputable ChildLookupResult where
ppr NameNotFound = text "NameNotFound"
ppr (FoundName n) = text "Found:" <+> ppr n
ppr (FoundFL fls) = text "FoundFL:" <+> ppr fls
ppr (NameErr _) = text "Error"
instance Monoid ChildLookupResult where
mempty = NameNotFound
NameNotFound `mappend` m2 = m2
NameErr m `mappend` _ = NameErr m
FoundName n1 `mappend` _ = FoundName n1
FoundFL fls `mappend` _ = FoundFL fls
lookupChildrenExport :: Name -> [Located RdrName]
-> RnM ([Located Name], [Located FieldLabel])
lookupChildrenExport parent rdr_items =
do
xs <- mapAndReportM doOne rdr_items
return $ partitionEithers xs
where
choosePossibleNamespaces :: NameSpace -> [NameSpace]
choosePossibleNamespaces ns
| ns == varName = [varName, tcName]
| ns == tcName = [dataName, tcName]
| otherwise = [ns]
doOne :: Located RdrName
-> RnM (Either (Located Name) (Located FieldLabel))
doOne n = do
let bareName = unLoc n
lkup v = lookupExportChild parent (setRdrNameSpace bareName v)
name <- tryChildLookupResult $ map lkup $
(choosePossibleNamespaces (rdrNameSpace bareName))
let unboundName :: RdrName
unboundName = if rdrNameSpace bareName == varName
then bareName
else setRdrNameSpace bareName dataName
case name of
NameNotFound -> Left . L (getLoc n) <$> reportUnboundName unboundName
FoundFL fls -> return $ Right (L (getLoc n) fls)
FoundName name -> return $ Left (L (getLoc n) name)
NameErr err_msg -> reportError err_msg >> failM
tryChildLookupResult :: [RnM ChildLookupResult] -> RnM ChildLookupResult
tryChildLookupResult [x] = x
tryChildLookupResult (x:xs) = do
res <- x
case res of
FoundFL {} -> return res
FoundName {} -> return res
NameErr {} -> return res
_ -> tryChildLookupResult xs
tryChildLookupResult _ = panic "tryChildLookupResult:empty list"
mkNameErr :: SDoc -> TcM ChildLookupResult
mkNameErr errMsg = do
tcinit <- tcInitTidyEnv
NameErr <$> mkErrTcM (tcinit, errMsg)
lookupExportChild :: Name -> RdrName -> RnM ChildLookupResult
lookupExportChild parent rdr_name
| isUnboundName parent
= return (FoundName (mkUnboundNameRdr rdr_name))
| otherwise = do
gre_env <- getGlobalRdrEnv
let original_gres = lookupGlobalRdrEnv gre_env (rdrNameOcc rdr_name)
traceRn "lookupExportChild original_gres:" (ppr original_gres)
case picked_gres original_gres of
NoOccurrence ->
noMatchingParentErr original_gres
UniqueOccurrence g ->
checkPatSynParent parent (gre_name g)
DisambiguatedOccurrence g ->
checkFld g
AmbiguousOccurrence gres ->
mkNameClashErr gres
where
checkFld :: GlobalRdrElt -> RnM ChildLookupResult
checkFld g@GRE{gre_name, gre_par} = do
addUsedGRE True g
return $ case gre_par of
FldParent _ mfs -> do
FoundFL (fldParentToFieldLabel gre_name mfs)
_ -> FoundName gre_name
fldParentToFieldLabel :: Name -> Maybe FastString -> FieldLabel
fldParentToFieldLabel name mfs =
case mfs of
Nothing ->
let fs = occNameFS (nameOccName name)
in FieldLabel fs False name
Just fs -> FieldLabel fs True name
noMatchingParentErr :: [GlobalRdrElt] -> RnM ChildLookupResult
noMatchingParentErr original_gres = do
overload_ok <- xoptM LangExt.DuplicateRecordFields
case original_gres of
[] -> return NameNotFound
[g] -> mkDcErrMsg parent (gre_name g) [p | Just p <- [getParent g]]
gss@(g:_:_) ->
if all isRecFldGRE gss && overload_ok
then mkNameErr (dcErrMsg parent "record selector"
(expectJust "noMatchingParentErr" (greLabel g))
[ppr p | x <- gss, Just p <- [getParent x]])
else mkNameClashErr gss
mkNameClashErr :: [GlobalRdrElt] -> RnM ChildLookupResult
mkNameClashErr gres = do
addNameClashErrRn rdr_name gres
return (FoundName (gre_name (head gres)))
getParent :: GlobalRdrElt -> Maybe Name
getParent (GRE { gre_par = p } ) =
case p of
ParentIs cur_parent -> Just cur_parent
FldParent { par_is = cur_parent } -> Just cur_parent
NoParent -> Nothing
picked_gres :: [GlobalRdrElt] -> DisambigInfo
picked_gres gres
| isUnqual rdr_name = mconcat (map right_parent gres)
| otherwise = mconcat (map right_parent (pickGREs rdr_name gres))
right_parent :: GlobalRdrElt -> DisambigInfo
right_parent p
| Just cur_parent <- getParent p
= if parent == cur_parent
then DisambiguatedOccurrence p
else NoOccurrence
| otherwise
= UniqueOccurrence p
data DisambigInfo
= NoOccurrence
| UniqueOccurrence GlobalRdrElt
| DisambiguatedOccurrence GlobalRdrElt
| AmbiguousOccurrence [GlobalRdrElt]
instance Monoid DisambigInfo where
mempty = NoOccurrence
_ `mappend` DisambiguatedOccurrence g' = DisambiguatedOccurrence g'
DisambiguatedOccurrence g' `mappend` _ = DisambiguatedOccurrence g'
NoOccurrence `mappend` m = m
m `mappend` NoOccurrence = m
UniqueOccurrence g `mappend` UniqueOccurrence g' = AmbiguousOccurrence [g, g']
UniqueOccurrence g `mappend` AmbiguousOccurrence gs = AmbiguousOccurrence (g:gs)
AmbiguousOccurrence gs `mappend` UniqueOccurrence g' = AmbiguousOccurrence (g':gs)
AmbiguousOccurrence gs `mappend` AmbiguousOccurrence gs' = AmbiguousOccurrence (gs ++ gs')
checkPatSynParent :: Name
-> Name
-> TcM ChildLookupResult
checkPatSynParent parent mpat_syn = do
parent_ty_con <- tcLookupTyCon parent
mpat_syn_thing <- tcLookupGlobal mpat_syn
let expected_res_ty =
mkTyConApp parent_ty_con (mkTyVarTys (tyConTyVars parent_ty_con))
handlePatSyn errCtxt =
addErrCtxt errCtxt
. tc_one_ps_export_with expected_res_ty parent_ty_con
case mpat_syn_thing of
AnId i
| isId i ->
case idDetails i of
RecSelId { sel_tycon = RecSelPatSyn p } -> handlePatSyn (selErr i) p
_ -> mkDcErrMsg parent mpat_syn []
AConLike (PatSynCon p) -> handlePatSyn (psErr p) p
_ -> mkDcErrMsg parent mpat_syn []
where
psErr = exportErrCtxt "pattern synonym"
selErr = exportErrCtxt "pattern synonym record selector"
assocClassErr :: SDoc
assocClassErr =
text "Pattern synonyms can be bundled only with datatypes."
tc_one_ps_export_with :: TcTauType
-> TyCon
-> PatSyn
-> TcM ChildLookupResult
tc_one_ps_export_with expected_res_ty ty_con pat_syn
| not $ isTyConWithSrcDataCons ty_con = mkNameErr assocClassErr
| Nothing <- mtycon = return (FoundName mpat_syn)
| Just p_ty_con <- mtycon, p_ty_con /= ty_con = mkNameErr typeMismatchError
| otherwise = return (FoundName mpat_syn)
where
(_, _, _, _, _, res_ty) = patSynSig pat_syn
mtycon = fst <$> tcSplitTyConApp_maybe res_ty
typeMismatchError :: SDoc
typeMismatchError =
text "Pattern synonyms can only be bundled with matching type constructors"
$$ text "Couldn't match expected type of"
<+> quotes (ppr expected_res_ty)
<+> text "with actual type of"
<+> quotes (ppr res_ty)
check_occs :: IE RdrName -> ExportOccMap -> [Name] -> RnM ExportOccMap
check_occs ie occs names
= foldlM check occs names
where
check occs name
= case lookupOccEnv occs name_occ of
Nothing -> return (extendOccEnv occs name_occ (name, ie))
Just (name', ie')
| name == name'
-> do { warnIf (Reason Opt_WarnDuplicateExports)
(not (dupExport_ok name ie ie'))
(dupExportWarn name_occ ie ie')
; return occs }
| otherwise
-> do { global_env <- getGlobalRdrEnv ;
addErr (exportClashErr global_env name' name ie' ie) ;
return occs }
where
name_occ = nameOccName name
dupExport_ok :: Name -> IE RdrName -> IE RdrName -> Bool
dupExport_ok n ie1 ie2
= not ( single ie1 || single ie2
|| (explicit_in ie1 && explicit_in ie2) )
where
explicit_in (IEModuleContents _) = False
explicit_in (IEThingAll r)
= nameOccName n == rdrNameOcc (ieWrappedName $ unLoc r)
explicit_in _ = True
single IEVar {} = True
single IEThingAbs {} = True
single _ = False
dupModuleExport :: ModuleName -> SDoc
dupModuleExport mod
= hsep [text "Duplicate",
quotes (text "Module" <+> ppr mod),
text "in export list"]
moduleNotImported :: ModuleName -> SDoc
moduleNotImported mod
= text "The export item `module" <+> ppr mod <>
text "' is not imported"
nullModuleExport :: ModuleName -> SDoc
nullModuleExport mod
= text "The export item `module" <+> ppr mod <> ptext (sLit "' exports nothing")
dodgyExportWarn :: Name -> SDoc
dodgyExportWarn item = dodgyMsg (text "export") item
exportErrCtxt :: Outputable o => String -> o -> SDoc
exportErrCtxt herald exp =
text "In the" <+> text (herald ++ ":") <+> ppr exp
addExportErrCtxt :: (HasOccName s, OutputableBndr s) => IE s -> TcM a -> TcM a
addExportErrCtxt ie = addErrCtxt exportCtxt
where
exportCtxt = text "In the export:" <+> ppr ie
exportItemErr :: IE RdrName -> SDoc
exportItemErr export_item
= sep [ text "The export item" <+> quotes (ppr export_item),
text "attempts to export constructors or class methods that are not visible here" ]
dupExportWarn :: OccName -> IE RdrName -> IE RdrName -> SDoc
dupExportWarn occ_name ie1 ie2
= hsep [quotes (ppr occ_name),
text "is exported by", quotes (ppr ie1),
text "and", quotes (ppr ie2)]
dcErrMsg :: Outputable a => Name -> String -> a -> [SDoc] -> SDoc
dcErrMsg ty_con what_is thing parents =
text "The type constructor" <+> quotes (ppr ty_con)
<+> text "is not the parent of the" <+> text what_is
<+> quotes (ppr thing) <> char '.'
$$ text (capitalise what_is)
<> text "s can only be exported with their parent type constructor."
$$ (case parents of
[] -> empty
[_] -> text "Parent:"
_ -> text "Parents:") <+> fsep (punctuate comma parents)
mkDcErrMsg :: Name -> Name -> [Name] -> TcM ChildLookupResult
mkDcErrMsg parent thing parents = do
ty_thing <- tcLookupGlobal thing
mkNameErr (dcErrMsg parent (tyThingCategory' ty_thing) thing (map ppr parents))
where
tyThingCategory' :: TyThing -> String
tyThingCategory' (AnId i)
| isRecordSelector i = "record selector"
tyThingCategory' i = tyThingCategory i
exportClashErr :: GlobalRdrEnv -> Name -> Name -> IE RdrName -> IE RdrName
-> MsgDoc
exportClashErr global_env name1 name2 ie1 ie2
= vcat [ text "Conflicting exports for" <+> quotes (ppr occ) <> colon
, ppr_export ie1' name1'
, ppr_export ie2' name2' ]
where
occ = nameOccName name1
ppr_export ie name = nest 3 (hang (quotes (ppr ie) <+> text "exports" <+>
quotes (ppr name))
2 (pprNameProvenance (get_gre name)))
get_gre name
= fromMaybe (pprPanic "exportClashErr" (ppr name)) (lookupGRE_Name global_env name)
get_loc name = greSrcSpan (get_gre name)
(name1', ie1', name2', ie2') = if get_loc name1 < get_loc name2
then (name1, ie1, name2, ie2)
else (name2, ie2, name1, ie1)