{-# LANGUAGE CPP, DeriveDataTypeable #-}
module GHC.Types.Name.Reader (
RdrName(..),
mkRdrUnqual, mkRdrQual,
mkUnqual, mkVarUnqual, mkQual, mkOrig,
nameRdrName, getRdrName,
rdrNameOcc, rdrNameSpace, demoteRdrName, promoteRdrName,
isRdrDataCon, isRdrTyVar, isRdrTc, isQual, isQual_maybe, isUnqual,
isOrig, isOrig_maybe, isExact, isExact_maybe, isSrcRdrName,
LocalRdrEnv, emptyLocalRdrEnv, extendLocalRdrEnv, extendLocalRdrEnvList,
lookupLocalRdrEnv, lookupLocalRdrOcc,
elemLocalRdrEnv, inLocalRdrEnvScope,
localRdrEnvElts, delLocalRdrEnvList,
GlobalRdrEnv, emptyGlobalRdrEnv, mkGlobalRdrEnv, plusGlobalRdrEnv,
lookupGlobalRdrEnv, extendGlobalRdrEnv, greOccName, shadowNames,
pprGlobalRdrEnv, globalRdrEnvElts,
lookupGRE_RdrName, lookupGRE_RdrName', lookupGRE_Name,
lookupGRE_GreName, lookupGRE_FieldLabel,
lookupGRE_Name_OccName,
getGRE_NameQualifier_maybes,
transformGREs, pickGREs, pickGREsModExp,
gresFromAvails, gresFromAvail, localGREsFromAvail, availFromGRE,
greRdrNames, greSrcSpan, greQualModName,
gresToAvailInfo,
greDefinitionModule, greDefinitionSrcSpan,
greMangledName, grePrintableName,
greFieldLabel,
GlobalRdrElt(..), isLocalGRE, isRecFldGRE,
isDuplicateRecFldGRE, isNoFieldSelectorGRE, isFieldSelectorGRE,
unQualOK, qualSpecOK, unQualSpecOK,
pprNameProvenance,
GreName(..), greNameSrcSpan,
Parent(..), greParent_maybe,
ImportSpec(..), ImpDeclSpec(..), ImpItemSpec(..),
importSpecLoc, importSpecModule, isExplicitItem, bestImport,
starInfo,
opIsAt,
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Unit.Module
import GHC.Types.Name
import GHC.Types.Avail
import GHC.Types.Name.Set
import GHC.Data.Maybe
import GHC.Types.SrcLoc as SrcLoc
import GHC.Data.FastString
import GHC.Types.FieldLabel
import GHC.Utils.Outputable
import GHC.Types.Unique
import GHC.Types.Unique.FM
import GHC.Types.Unique.Set
import GHC.Utils.Misc as Utils
import GHC.Utils.Panic
import GHC.Types.Name.Env
import Data.Data
import Data.List( sortBy )
data RdrName
= Unqual OccName
| Qual ModuleName OccName
| Orig Module OccName
| Exact Name
deriving Typeable RdrName
RdrName -> DataType
RdrName -> Constr
(forall b. Data b => b -> b) -> RdrName -> RdrName
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> RdrName -> u
forall u. (forall d. Data d => d -> u) -> RdrName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RdrName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RdrName -> c RdrName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RdrName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RdrName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RdrName -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> RdrName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RdrName -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
gmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName
$cgmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RdrName)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RdrName)
dataTypeOf :: RdrName -> DataType
$cdataTypeOf :: RdrName -> DataType
toConstr :: RdrName -> Constr
$ctoConstr :: RdrName -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RdrName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RdrName
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RdrName -> c RdrName
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RdrName -> c RdrName
Data
instance HasOccName RdrName where
occName :: RdrName -> OccName
occName = RdrName -> OccName
rdrNameOcc
rdrNameOcc :: RdrName -> OccName
rdrNameOcc :: RdrName -> OccName
rdrNameOcc (Qual ModuleName
_ OccName
occ) = OccName
occ
rdrNameOcc (Unqual OccName
occ) = OccName
occ
rdrNameOcc (Orig Module
_ OccName
occ) = OccName
occ
rdrNameOcc (Exact Name
name) = Name -> OccName
nameOccName Name
name
rdrNameSpace :: RdrName -> NameSpace
rdrNameSpace :: RdrName -> NameSpace
rdrNameSpace = OccName -> NameSpace
occNameSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. RdrName -> OccName
rdrNameOcc
demoteRdrName :: RdrName -> Maybe RdrName
demoteRdrName :: RdrName -> Maybe RdrName
demoteRdrName (Unqual OccName
occ) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OccName -> RdrName
Unqual (OccName -> Maybe OccName
demoteOccName OccName
occ)
demoteRdrName (Qual ModuleName
m OccName
occ) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ModuleName -> OccName -> RdrName
Qual ModuleName
m) (OccName -> Maybe OccName
demoteOccName OccName
occ)
demoteRdrName (Orig Module
_ OccName
_) = forall a. Maybe a
Nothing
demoteRdrName (Exact Name
_) = forall a. Maybe a
Nothing
promoteRdrName :: RdrName -> Maybe RdrName
promoteRdrName :: RdrName -> Maybe RdrName
promoteRdrName (Unqual OccName
occ) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OccName -> RdrName
Unqual (OccName -> Maybe OccName
promoteOccName OccName
occ)
promoteRdrName (Qual ModuleName
m OccName
occ) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ModuleName -> OccName -> RdrName
Qual ModuleName
m) (OccName -> Maybe OccName
promoteOccName OccName
occ)
promoteRdrName (Orig Module
_ OccName
_) = forall a. Maybe a
Nothing
promoteRdrName (Exact Name
_) = forall a. Maybe a
Nothing
mkRdrUnqual :: OccName -> RdrName
mkRdrUnqual :: OccName -> RdrName
mkRdrUnqual OccName
occ = OccName -> RdrName
Unqual OccName
occ
mkRdrQual :: ModuleName -> OccName -> RdrName
mkRdrQual :: ModuleName -> OccName -> RdrName
mkRdrQual ModuleName
mod OccName
occ = ModuleName -> OccName -> RdrName
Qual ModuleName
mod OccName
occ
mkOrig :: Module -> OccName -> RdrName
mkOrig :: Module -> OccName -> RdrName
mkOrig Module
mod OccName
occ = Module -> OccName -> RdrName
Orig Module
mod OccName
occ
mkUnqual :: NameSpace -> FastString -> RdrName
mkUnqual :: NameSpace -> FastString -> RdrName
mkUnqual NameSpace
sp FastString
n = OccName -> RdrName
Unqual (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
sp FastString
n)
mkVarUnqual :: FastString -> RdrName
mkVarUnqual :: FastString -> RdrName
mkVarUnqual FastString
n = OccName -> RdrName
Unqual (FastString -> OccName
mkVarOccFS FastString
n)
mkQual :: NameSpace -> (FastString, FastString) -> RdrName
mkQual :: NameSpace -> (FastString, FastString) -> RdrName
mkQual NameSpace
sp (FastString
m, FastString
n) = ModuleName -> OccName -> RdrName
Qual (FastString -> ModuleName
mkModuleNameFS FastString
m) (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
sp FastString
n)
getRdrName :: NamedThing thing => thing -> RdrName
getRdrName :: forall thing. NamedThing thing => thing -> RdrName
getRdrName thing
name = Name -> RdrName
nameRdrName (forall a. NamedThing a => a -> Name
getName thing
name)
nameRdrName :: Name -> RdrName
nameRdrName :: Name -> RdrName
nameRdrName Name
name = Name -> RdrName
Exact Name
name
nukeExact :: Name -> RdrName
nukeExact :: Name -> RdrName
nukeExact Name
n
| Name -> Bool
isExternalName Name
n = Module -> OccName -> RdrName
Orig (HasDebugCallStack => Name -> Module
nameModule Name
n) (Name -> OccName
nameOccName Name
n)
| Bool
otherwise = OccName -> RdrName
Unqual (Name -> OccName
nameOccName Name
n)
isRdrDataCon :: RdrName -> Bool
isRdrTyVar :: RdrName -> Bool
isRdrTc :: RdrName -> Bool
isRdrDataCon :: RdrName -> Bool
isRdrDataCon RdrName
rn = OccName -> Bool
isDataOcc (RdrName -> OccName
rdrNameOcc RdrName
rn)
isRdrTyVar :: RdrName -> Bool
isRdrTyVar RdrName
rn = OccName -> Bool
isTvOcc (RdrName -> OccName
rdrNameOcc RdrName
rn)
isRdrTc :: RdrName -> Bool
isRdrTc RdrName
rn = OccName -> Bool
isTcOcc (RdrName -> OccName
rdrNameOcc RdrName
rn)
isSrcRdrName :: RdrName -> Bool
isSrcRdrName :: RdrName -> Bool
isSrcRdrName (Unqual OccName
_) = Bool
True
isSrcRdrName (Qual ModuleName
_ OccName
_) = Bool
True
isSrcRdrName RdrName
_ = Bool
False
isUnqual :: RdrName -> Bool
isUnqual :: RdrName -> Bool
isUnqual (Unqual OccName
_) = Bool
True
isUnqual RdrName
_ = Bool
False
isQual :: RdrName -> Bool
isQual :: RdrName -> Bool
isQual (Qual ModuleName
_ OccName
_) = Bool
True
isQual RdrName
_ = Bool
False
isQual_maybe :: RdrName -> Maybe (ModuleName, OccName)
isQual_maybe :: RdrName -> Maybe (ModuleName, OccName)
isQual_maybe (Qual ModuleName
m OccName
n) = forall a. a -> Maybe a
Just (ModuleName
m,OccName
n)
isQual_maybe RdrName
_ = forall a. Maybe a
Nothing
isOrig :: RdrName -> Bool
isOrig :: RdrName -> Bool
isOrig (Orig Module
_ OccName
_) = Bool
True
isOrig RdrName
_ = Bool
False
isOrig_maybe :: RdrName -> Maybe (Module, OccName)
isOrig_maybe :: RdrName -> Maybe (Module, OccName)
isOrig_maybe (Orig Module
m OccName
n) = forall a. a -> Maybe a
Just (Module
m,OccName
n)
isOrig_maybe RdrName
_ = forall a. Maybe a
Nothing
isExact :: RdrName -> Bool
isExact :: RdrName -> Bool
isExact (Exact Name
_) = Bool
True
isExact RdrName
_ = Bool
False
isExact_maybe :: RdrName -> Maybe Name
isExact_maybe :: RdrName -> Maybe Name
isExact_maybe (Exact Name
n) = forall a. a -> Maybe a
Just Name
n
isExact_maybe RdrName
_ = forall a. Maybe a
Nothing
instance Outputable RdrName where
ppr :: RdrName -> SDoc
ppr (Exact Name
name) = forall a. Outputable a => a -> SDoc
ppr Name
name
ppr (Unqual OccName
occ) = forall a. Outputable a => a -> SDoc
ppr OccName
occ
ppr (Qual ModuleName
mod OccName
occ) = forall a. Outputable a => a -> SDoc
ppr ModuleName
mod SDoc -> SDoc -> SDoc
<> SDoc
dot SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr OccName
occ
ppr (Orig Module
mod OccName
occ) = (PprStyle -> SDoc) -> SDoc
getPprStyle (\PprStyle
sty -> PprStyle -> Module -> OccName -> SDoc
pprModulePrefix PprStyle
sty Module
mod OccName
occ SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr OccName
occ)
instance OutputableBndr RdrName where
pprBndr :: BindingSite -> RdrName -> SDoc
pprBndr BindingSite
_ RdrName
n
| OccName -> Bool
isTvOcc (RdrName -> OccName
rdrNameOcc RdrName
n) = Char -> SDoc
char Char
'@' SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr RdrName
n
| Bool
otherwise = forall a. Outputable a => a -> SDoc
ppr RdrName
n
pprInfixOcc :: RdrName -> SDoc
pprInfixOcc RdrName
rdr = Bool -> SDoc -> SDoc
pprInfixVar (OccName -> Bool
isSymOcc (RdrName -> OccName
rdrNameOcc RdrName
rdr)) (forall a. Outputable a => a -> SDoc
ppr RdrName
rdr)
pprPrefixOcc :: RdrName -> SDoc
pprPrefixOcc RdrName
rdr
| Just Name
name <- RdrName -> Maybe Name
isExact_maybe RdrName
rdr = forall a. NamedThing a => a -> SDoc
pprPrefixName Name
name
| Bool
otherwise = Bool -> SDoc -> SDoc
pprPrefixVar (OccName -> Bool
isSymOcc (RdrName -> OccName
rdrNameOcc RdrName
rdr)) (forall a. Outputable a => a -> SDoc
ppr RdrName
rdr)
instance Eq RdrName where
(Exact Name
n1) == :: RdrName -> RdrName -> Bool
== (Exact Name
n2) = Name
n1forall a. Eq a => a -> a -> Bool
==Name
n2
(Exact Name
n1) == r2 :: RdrName
r2@(Orig Module
_ OccName
_) = Name -> RdrName
nukeExact Name
n1 forall a. Eq a => a -> a -> Bool
== RdrName
r2
r1 :: RdrName
r1@(Orig Module
_ OccName
_) == (Exact Name
n2) = RdrName
r1 forall a. Eq a => a -> a -> Bool
== Name -> RdrName
nukeExact Name
n2
(Orig Module
m1 OccName
o1) == (Orig Module
m2 OccName
o2) = Module
m1forall a. Eq a => a -> a -> Bool
==Module
m2 Bool -> Bool -> Bool
&& OccName
o1forall a. Eq a => a -> a -> Bool
==OccName
o2
(Qual ModuleName
m1 OccName
o1) == (Qual ModuleName
m2 OccName
o2) = ModuleName
m1forall a. Eq a => a -> a -> Bool
==ModuleName
m2 Bool -> Bool -> Bool
&& OccName
o1forall a. Eq a => a -> a -> Bool
==OccName
o2
(Unqual OccName
o1) == (Unqual OccName
o2) = OccName
o1forall a. Eq a => a -> a -> Bool
==OccName
o2
RdrName
_ == RdrName
_ = Bool
False
instance Ord RdrName where
RdrName
a <= :: RdrName -> RdrName -> Bool
<= RdrName
b = case (RdrName
a forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { Ordering
LT -> Bool
True; Ordering
EQ -> Bool
True; Ordering
GT -> Bool
False }
RdrName
a < :: RdrName -> RdrName -> Bool
< RdrName
b = case (RdrName
a forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { Ordering
LT -> Bool
True; Ordering
EQ -> Bool
False; Ordering
GT -> Bool
False }
RdrName
a >= :: RdrName -> RdrName -> Bool
>= RdrName
b = case (RdrName
a forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { Ordering
LT -> Bool
False; Ordering
EQ -> Bool
True; Ordering
GT -> Bool
True }
RdrName
a > :: RdrName -> RdrName -> Bool
> RdrName
b = case (RdrName
a forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { Ordering
LT -> Bool
False; Ordering
EQ -> Bool
False; Ordering
GT -> Bool
True }
compare :: RdrName -> RdrName -> Ordering
compare (Exact Name
n1) (Exact Name
n2) = Name
n1 forall a. Ord a => a -> a -> Ordering
`compare` Name
n2
compare (Exact Name
_) RdrName
_ = Ordering
LT
compare (Unqual OccName
_) (Exact Name
_) = Ordering
GT
compare (Unqual OccName
o1) (Unqual OccName
o2) = OccName
o1 forall a. Ord a => a -> a -> Ordering
`compare` OccName
o2
compare (Unqual OccName
_) RdrName
_ = Ordering
LT
compare (Qual ModuleName
_ OccName
_) (Exact Name
_) = Ordering
GT
compare (Qual ModuleName
_ OccName
_) (Unqual OccName
_) = Ordering
GT
compare (Qual ModuleName
m1 OccName
o1) (Qual ModuleName
m2 OccName
o2) = (OccName
o1 forall a. Ord a => a -> a -> Ordering
`compare` OccName
o2) Ordering -> Ordering -> Ordering
`thenCmp` (ModuleName
m1 forall a. Ord a => a -> a -> Ordering
`compare` ModuleName
m2)
compare (Qual ModuleName
_ OccName
_) (Orig Module
_ OccName
_) = Ordering
LT
compare (Orig Module
m1 OccName
o1) (Orig Module
m2 OccName
o2) = (OccName
o1 forall a. Ord a => a -> a -> Ordering
`compare` OccName
o2) Ordering -> Ordering -> Ordering
`thenCmp` (Module
m1 forall a. Ord a => a -> a -> Ordering
`compare` Module
m2)
compare (Orig Module
_ OccName
_) RdrName
_ = Ordering
GT
data LocalRdrEnv = LRE { LocalRdrEnv -> OccEnv Name
lre_env :: OccEnv Name
, LocalRdrEnv -> NameSet
lre_in_scope :: NameSet }
instance Outputable LocalRdrEnv where
ppr :: LocalRdrEnv -> SDoc
ppr (LRE {lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env, lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns})
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"LocalRdrEnv {")
Int
2 ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"env =" SDoc -> SDoc -> SDoc
<+> forall a. (a -> SDoc) -> OccEnv a -> SDoc
pprOccEnv Name -> SDoc
ppr_elt OccEnv Name
env
, String -> SDoc
text String
"in_scope ="
SDoc -> SDoc -> SDoc
<+> forall key a. UniqFM key a -> ([a] -> SDoc) -> SDoc
pprUFM (forall a. UniqSet a -> UniqFM a a
getUniqSet NameSet
ns) (SDoc -> SDoc
braces forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> SDoc) -> [a] -> SDoc
pprWithCommas forall a. Outputable a => a -> SDoc
ppr)
] SDoc -> SDoc -> SDoc
<+> Char -> SDoc
char Char
'}')
where
ppr_elt :: Name -> SDoc
ppr_elt Name
name = SDoc -> SDoc
parens (forall a. Outputable a => a -> SDoc
ppr (forall a. Uniquable a => a -> Unique
getUnique (Name -> OccName
nameOccName Name
name))) SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Name
name
emptyLocalRdrEnv :: LocalRdrEnv
emptyLocalRdrEnv :: LocalRdrEnv
emptyLocalRdrEnv = LRE { lre_env :: OccEnv Name
lre_env = forall a. OccEnv a
emptyOccEnv
, lre_in_scope :: NameSet
lre_in_scope = NameSet
emptyNameSet }
extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv
extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv
extendLocalRdrEnv lre :: LocalRdrEnv
lre@(LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env, lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns }) Name
name
= LocalRdrEnv
lre { lre_env :: OccEnv Name
lre_env = forall a. OccEnv a -> OccName -> a -> OccEnv a
extendOccEnv OccEnv Name
env (Name -> OccName
nameOccName Name
name) Name
name
, lre_in_scope :: NameSet
lre_in_scope = NameSet -> Name -> NameSet
extendNameSet NameSet
ns Name
name }
extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv
extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv
extendLocalRdrEnvList lre :: LocalRdrEnv
lre@(LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env, lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns }) [Name]
names
= LocalRdrEnv
lre { lre_env :: OccEnv Name
lre_env = forall a. OccEnv a -> [(OccName, a)] -> OccEnv a
extendOccEnvList OccEnv Name
env [(Name -> OccName
nameOccName Name
n, Name
n) | Name
n <- [Name]
names]
, lre_in_scope :: NameSet
lre_in_scope = NameSet -> [Name] -> NameSet
extendNameSetList NameSet
ns [Name]
names }
lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name
lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name
lookupLocalRdrEnv (LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env, lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns }) RdrName
rdr
| Unqual OccName
occ <- RdrName
rdr
= forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv Name
env OccName
occ
| Exact Name
name <- RdrName
rdr
, Name
name Name -> NameSet -> Bool
`elemNameSet` NameSet
ns
= forall a. a -> Maybe a
Just Name
name
| Bool
otherwise
= forall a. Maybe a
Nothing
lookupLocalRdrOcc :: LocalRdrEnv -> OccName -> Maybe Name
lookupLocalRdrOcc :: LocalRdrEnv -> OccName -> Maybe Name
lookupLocalRdrOcc (LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env }) OccName
occ = forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv Name
env OccName
occ
elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool
elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool
elemLocalRdrEnv RdrName
rdr_name (LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env, lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns })
= case RdrName
rdr_name of
Unqual OccName
occ -> OccName
occ forall a. OccName -> OccEnv a -> Bool
`elemOccEnv` OccEnv Name
env
Exact Name
name -> Name
name Name -> NameSet -> Bool
`elemNameSet` NameSet
ns
Qual {} -> Bool
False
Orig {} -> Bool
False
localRdrEnvElts :: LocalRdrEnv -> [Name]
localRdrEnvElts :: LocalRdrEnv -> [Name]
localRdrEnvElts (LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env }) = forall a. OccEnv a -> [a]
occEnvElts OccEnv Name
env
inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool
inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool
inLocalRdrEnvScope Name
name (LRE { lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns }) = Name
name Name -> NameSet -> Bool
`elemNameSet` NameSet
ns
delLocalRdrEnvList :: LocalRdrEnv -> [OccName] -> LocalRdrEnv
delLocalRdrEnvList :: LocalRdrEnv -> [OccName] -> LocalRdrEnv
delLocalRdrEnvList lre :: LocalRdrEnv
lre@(LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env }) [OccName]
occs
= LocalRdrEnv
lre { lre_env :: OccEnv Name
lre_env = forall a. OccEnv a -> [OccName] -> OccEnv a
delListFromOccEnv OccEnv Name
env [OccName]
occs }
type GlobalRdrEnv = OccEnv [GlobalRdrElt]
data GlobalRdrElt
= GRE { GlobalRdrElt -> GreName
gre_name :: !GreName
, GlobalRdrElt -> Parent
gre_par :: !Parent
, GlobalRdrElt -> Bool
gre_lcl :: !Bool
, GlobalRdrElt -> [ImportSpec]
gre_imp :: ![ImportSpec]
} deriving (Typeable GlobalRdrElt
GlobalRdrElt -> DataType
GlobalRdrElt -> Constr
(forall b. Data b => b -> b) -> GlobalRdrElt -> GlobalRdrElt
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u
forall u. (forall d. Data d => d -> u) -> GlobalRdrElt -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GlobalRdrElt
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GlobalRdrElt -> c GlobalRdrElt
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GlobalRdrElt)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c GlobalRdrElt)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> GlobalRdrElt -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> GlobalRdrElt -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r
gmapT :: (forall b. Data b => b -> b) -> GlobalRdrElt -> GlobalRdrElt
$cgmapT :: (forall b. Data b => b -> b) -> GlobalRdrElt -> GlobalRdrElt
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c GlobalRdrElt)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c GlobalRdrElt)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GlobalRdrElt)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GlobalRdrElt)
dataTypeOf :: GlobalRdrElt -> DataType
$cdataTypeOf :: GlobalRdrElt -> DataType
toConstr :: GlobalRdrElt -> Constr
$ctoConstr :: GlobalRdrElt -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GlobalRdrElt
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GlobalRdrElt
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GlobalRdrElt -> c GlobalRdrElt
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GlobalRdrElt -> c GlobalRdrElt
Data, GlobalRdrElt -> GlobalRdrElt -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GlobalRdrElt -> GlobalRdrElt -> Bool
$c/= :: GlobalRdrElt -> GlobalRdrElt -> Bool
== :: GlobalRdrElt -> GlobalRdrElt -> Bool
$c== :: GlobalRdrElt -> GlobalRdrElt -> Bool
Eq)
data Parent = NoParent
| ParentIs { Parent -> Name
par_is :: Name }
deriving (Parent -> Parent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Parent -> Parent -> Bool
$c/= :: Parent -> Parent -> Bool
== :: Parent -> Parent -> Bool
$c== :: Parent -> Parent -> Bool
Eq, Typeable Parent
Parent -> DataType
Parent -> Constr
(forall b. Data b => b -> b) -> Parent -> Parent
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Parent -> u
forall u. (forall d. Data d => d -> u) -> Parent -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Parent
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Parent -> c Parent
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Parent)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Parent -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Parent -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Parent -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Parent -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
gmapT :: (forall b. Data b => b -> b) -> Parent -> Parent
$cgmapT :: (forall b. Data b => b -> b) -> Parent -> Parent
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Parent)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Parent)
dataTypeOf :: Parent -> DataType
$cdataTypeOf :: Parent -> DataType
toConstr :: Parent -> Constr
$ctoConstr :: Parent -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Parent
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Parent
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Parent -> c Parent
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Parent -> c Parent
Data)
instance Outputable Parent where
ppr :: Parent -> SDoc
ppr Parent
NoParent = SDoc
empty
ppr (ParentIs Name
n) = String -> SDoc
text String
"parent:" SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr Name
n
plusParent :: Parent -> Parent -> Parent
plusParent :: Parent -> Parent -> Parent
plusParent p1 :: Parent
p1@(ParentIs Name
_) Parent
p2 = Parent -> Parent -> Parent
hasParent Parent
p1 Parent
p2
plusParent Parent
p1 p2 :: Parent
p2@(ParentIs Name
_) = Parent -> Parent -> Parent
hasParent Parent
p2 Parent
p1
plusParent Parent
NoParent Parent
NoParent = Parent
NoParent
hasParent :: Parent -> Parent -> Parent
#if defined(DEBUG)
hasParent p NoParent = p
hasParent p p'
| p /= p' = pprPanic "hasParent" (ppr p <+> ppr p')
#endif
hasParent :: Parent -> Parent -> Parent
hasParent Parent
p Parent
_ = Parent
p
gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt]
gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt]
gresFromAvails Maybe ImportSpec
prov [AvailInfo]
avails
= forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt]
gresFromAvail (forall a b. a -> b -> a
const Maybe ImportSpec
prov)) [AvailInfo]
avails
localGREsFromAvail :: AvailInfo -> [GlobalRdrElt]
localGREsFromAvail :: AvailInfo -> [GlobalRdrElt]
localGREsFromAvail = (Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt]
gresFromAvail (forall a b. a -> b -> a
const forall a. Maybe a
Nothing)
gresFromAvail :: (Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt]
gresFromAvail :: (Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt]
gresFromAvail Name -> Maybe ImportSpec
prov_fn AvailInfo
avail
= forall a b. (a -> b) -> [a] -> [b]
map Name -> GlobalRdrElt
mk_gre (AvailInfo -> [Name]
availNonFldNames AvailInfo
avail) forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map FieldLabel -> GlobalRdrElt
mk_fld_gre (AvailInfo -> [FieldLabel]
availFlds AvailInfo
avail)
where
mk_gre :: Name -> GlobalRdrElt
mk_gre Name
n
= case Name -> Maybe ImportSpec
prov_fn Name
n of
Maybe ImportSpec
Nothing -> GRE { gre_name :: GreName
gre_name = Name -> GreName
NormalGreName Name
n, gre_par :: Parent
gre_par = Name -> AvailInfo -> Parent
mkParent Name
n AvailInfo
avail
, gre_lcl :: Bool
gre_lcl = Bool
True, gre_imp :: [ImportSpec]
gre_imp = [] }
Just ImportSpec
is -> GRE { gre_name :: GreName
gre_name = Name -> GreName
NormalGreName Name
n, gre_par :: Parent
gre_par = Name -> AvailInfo -> Parent
mkParent Name
n AvailInfo
avail
, gre_lcl :: Bool
gre_lcl = Bool
False, gre_imp :: [ImportSpec]
gre_imp = [ImportSpec
is] }
mk_fld_gre :: FieldLabel -> GlobalRdrElt
mk_fld_gre FieldLabel
fl
= case Name -> Maybe ImportSpec
prov_fn (FieldLabel -> Name
flSelector FieldLabel
fl) of
Maybe ImportSpec
Nothing -> GRE { gre_name :: GreName
gre_name = FieldLabel -> GreName
FieldGreName FieldLabel
fl, gre_par :: Parent
gre_par = AvailInfo -> Parent
availParent AvailInfo
avail
, gre_lcl :: Bool
gre_lcl = Bool
True, gre_imp :: [ImportSpec]
gre_imp = [] }
Just ImportSpec
is -> GRE { gre_name :: GreName
gre_name = FieldLabel -> GreName
FieldGreName FieldLabel
fl, gre_par :: Parent
gre_par = AvailInfo -> Parent
availParent AvailInfo
avail
, gre_lcl :: Bool
gre_lcl = Bool
False, gre_imp :: [ImportSpec]
gre_imp = [ImportSpec
is] }
instance HasOccName GlobalRdrElt where
occName :: GlobalRdrElt -> OccName
occName = GlobalRdrElt -> OccName
greOccName
greOccName :: GlobalRdrElt -> OccName
greOccName :: GlobalRdrElt -> OccName
greOccName = forall name. HasOccName name => name -> OccName
occName forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> GreName
gre_name
greMangledName :: GlobalRdrElt -> Name
greMangledName :: GlobalRdrElt -> Name
greMangledName = GreName -> Name
greNameMangledName forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> GreName
gre_name
grePrintableName :: GlobalRdrElt -> Name
grePrintableName :: GlobalRdrElt -> Name
grePrintableName = GreName -> Name
greNamePrintableName forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> GreName
gre_name
greDefinitionSrcSpan :: GlobalRdrElt -> SrcSpan
greDefinitionSrcSpan :: GlobalRdrElt -> SrcSpan
greDefinitionSrcSpan = Name -> SrcSpan
nameSrcSpan forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Name
greMangledName
greDefinitionModule :: GlobalRdrElt -> Maybe Module
greDefinitionModule :: GlobalRdrElt -> Maybe Module
greDefinitionModule = Name -> Maybe Module
nameModule_maybe forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Name
greMangledName
greQualModName :: GlobalRdrElt -> ModuleName
greQualModName :: GlobalRdrElt -> ModuleName
greQualModName gre :: GlobalRdrElt
gre@(GRE { gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss })
| Bool
lcl, Just Module
mod <- GlobalRdrElt -> Maybe Module
greDefinitionModule GlobalRdrElt
gre = forall unit. GenModule unit -> ModuleName
moduleName Module
mod
| (ImportSpec
is:[ImportSpec]
_) <- [ImportSpec]
iss = ImpDeclSpec -> ModuleName
is_as (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is)
| Bool
otherwise = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"greQualModName" (forall a. Outputable a => a -> SDoc
ppr GlobalRdrElt
gre)
greRdrNames :: GlobalRdrElt -> [RdrName]
greRdrNames :: GlobalRdrElt -> [RdrName]
greRdrNames gre :: GlobalRdrElt
gre@GRE{ gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss }
= (if Bool
lcl then [RdrName
unqual] else []) forall a. [a] -> [a] -> [a]
++ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ImpDeclSpec -> [RdrName]
do_spec (forall a b. (a -> b) -> [a] -> [b]
map ImportSpec -> ImpDeclSpec
is_decl [ImportSpec]
iss)
where
occ :: OccName
occ = GlobalRdrElt -> OccName
greOccName GlobalRdrElt
gre
unqual :: RdrName
unqual = OccName -> RdrName
Unqual OccName
occ
do_spec :: ImpDeclSpec -> [RdrName]
do_spec ImpDeclSpec
decl_spec
| ImpDeclSpec -> Bool
is_qual ImpDeclSpec
decl_spec = [RdrName
qual]
| Bool
otherwise = [RdrName
unqual,RdrName
qual]
where qual :: RdrName
qual = ModuleName -> OccName -> RdrName
Qual (ImpDeclSpec -> ModuleName
is_as ImpDeclSpec
decl_spec) OccName
occ
greSrcSpan :: GlobalRdrElt -> SrcSpan
greSrcSpan :: GlobalRdrElt -> SrcSpan
greSrcSpan gre :: GlobalRdrElt
gre@(GRE { gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss } )
| Bool
lcl = GlobalRdrElt -> SrcSpan
greDefinitionSrcSpan GlobalRdrElt
gre
| (ImportSpec
is:[ImportSpec]
_) <- [ImportSpec]
iss = ImpDeclSpec -> SrcSpan
is_dloc (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is)
| Bool
otherwise = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"greSrcSpan" (forall a. Outputable a => a -> SDoc
ppr GlobalRdrElt
gre)
mkParent :: Name -> AvailInfo -> Parent
mkParent :: Name -> AvailInfo -> Parent
mkParent Name
_ (Avail GreName
_) = Parent
NoParent
mkParent Name
n (AvailTC Name
m [GreName]
_) | Name
n forall a. Eq a => a -> a -> Bool
== Name
m = Parent
NoParent
| Bool
otherwise = Name -> Parent
ParentIs Name
m
availParent :: AvailInfo -> Parent
availParent :: AvailInfo -> Parent
availParent (AvailTC Name
m [GreName]
_) = Name -> Parent
ParentIs Name
m
availParent (Avail {}) = Parent
NoParent
greParent_maybe :: GlobalRdrElt -> Maybe Name
greParent_maybe :: GlobalRdrElt -> Maybe Name
greParent_maybe GlobalRdrElt
gre = case GlobalRdrElt -> Parent
gre_par GlobalRdrElt
gre of
Parent
NoParent -> forall a. Maybe a
Nothing
ParentIs Name
n -> forall a. a -> Maybe a
Just Name
n
gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo]
gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo]
gresToAvailInfo [GlobalRdrElt]
gres
= forall a. NameEnv a -> [a]
nameEnvElts NameEnv AvailInfo
avail_env
where
avail_env :: NameEnv AvailInfo
(NameEnv AvailInfo
avail_env, NameSet
_) = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (NameEnv AvailInfo, NameSet)
-> GlobalRdrElt -> (NameEnv AvailInfo, NameSet)
add (forall a. NameEnv a
emptyNameEnv, NameSet
emptyNameSet) [GlobalRdrElt]
gres
add :: (NameEnv AvailInfo, NameSet)
-> GlobalRdrElt
-> (NameEnv AvailInfo, NameSet)
add :: (NameEnv AvailInfo, NameSet)
-> GlobalRdrElt -> (NameEnv AvailInfo, NameSet)
add (NameEnv AvailInfo
env, NameSet
done) GlobalRdrElt
gre
| Name
name Name -> NameSet -> Bool
`elemNameSet` NameSet
done
= (NameEnv AvailInfo
env, NameSet
done)
| Bool
otherwise
= ( forall a b.
(a -> b -> b) -> (a -> b) -> NameEnv b -> Name -> a -> NameEnv b
extendNameEnv_Acc GlobalRdrElt -> AvailInfo -> AvailInfo
comb GlobalRdrElt -> AvailInfo
availFromGRE NameEnv AvailInfo
env Name
key GlobalRdrElt
gre
, NameSet
done NameSet -> Name -> NameSet
`extendNameSet` Name
name )
where
name :: Name
name = GlobalRdrElt -> Name
greMangledName GlobalRdrElt
gre
key :: Name
key = case GlobalRdrElt -> Maybe Name
greParent_maybe GlobalRdrElt
gre of
Just Name
parent -> Name
parent
Maybe Name
Nothing -> GlobalRdrElt -> Name
greMangledName GlobalRdrElt
gre
insertChildIntoChildren :: Name -> [GreName] -> GreName -> [GreName]
insertChildIntoChildren :: Name -> [GreName] -> GreName -> [GreName]
insertChildIntoChildren Name
_ [] GreName
k = [GreName
k]
insertChildIntoChildren Name
p (GreName
n:[GreName]
ns) GreName
k
| Name -> GreName
NormalGreName Name
p forall a. Eq a => a -> a -> Bool
== GreName
k = GreName
kforall a. a -> [a] -> [a]
:GreName
nforall a. a -> [a] -> [a]
:[GreName]
ns
| Bool
otherwise = GreName
nforall a. a -> [a] -> [a]
:GreName
kforall a. a -> [a] -> [a]
:[GreName]
ns
comb :: GlobalRdrElt -> AvailInfo -> AvailInfo
comb :: GlobalRdrElt -> AvailInfo -> AvailInfo
comb GlobalRdrElt
_ (Avail GreName
n) = GreName -> AvailInfo
Avail GreName
n
comb GlobalRdrElt
gre (AvailTC Name
m [GreName]
ns)
= case GlobalRdrElt -> Parent
gre_par GlobalRdrElt
gre of
Parent
NoParent -> Name -> [GreName] -> AvailInfo
AvailTC Name
m (GlobalRdrElt -> GreName
gre_name GlobalRdrElt
greforall a. a -> [a] -> [a]
:[GreName]
ns)
ParentIs {} -> Name -> [GreName] -> AvailInfo
AvailTC Name
m (Name -> [GreName] -> GreName -> [GreName]
insertChildIntoChildren Name
m [GreName]
ns (GlobalRdrElt -> GreName
gre_name GlobalRdrElt
gre))
availFromGRE :: GlobalRdrElt -> AvailInfo
availFromGRE :: GlobalRdrElt -> AvailInfo
availFromGRE (GRE { gre_name :: GlobalRdrElt -> GreName
gre_name = GreName
child, gre_par :: GlobalRdrElt -> Parent
gre_par = Parent
parent })
= case Parent
parent of
ParentIs Name
p -> Name -> [GreName] -> AvailInfo
AvailTC Name
p [GreName
child]
Parent
NoParent | NormalGreName Name
me <- GreName
child, Name -> Bool
isTyConName Name
me -> Name -> [GreName] -> AvailInfo
AvailTC Name
me [GreName
child]
| Bool
otherwise -> GreName -> AvailInfo
Avail GreName
child
emptyGlobalRdrEnv :: GlobalRdrEnv
emptyGlobalRdrEnv :: GlobalRdrEnv
emptyGlobalRdrEnv = forall a. OccEnv a
emptyOccEnv
globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts GlobalRdrEnv
env = forall a b. (a -> b -> b) -> b -> OccEnv a -> b
foldOccEnv forall a. [a] -> [a] -> [a]
(++) [] GlobalRdrEnv
env
instance Outputable GlobalRdrElt where
ppr :: GlobalRdrElt -> SDoc
ppr GlobalRdrElt
gre = SDoc -> Int -> SDoc -> SDoc
hang (forall a. Outputable a => a -> SDoc
ppr (GlobalRdrElt -> Name
greMangledName GlobalRdrElt
gre) SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (GlobalRdrElt -> Parent
gre_par GlobalRdrElt
gre))
Int
2 (GlobalRdrElt -> SDoc
pprNameProvenance GlobalRdrElt
gre)
pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc
pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc
pprGlobalRdrEnv Bool
locals_only GlobalRdrEnv
env
= [SDoc] -> SDoc
vcat [ String -> SDoc
text String
"GlobalRdrEnv" SDoc -> SDoc -> SDoc
<+> Bool -> SDoc -> SDoc
ppWhen Bool
locals_only (PtrString -> SDoc
ptext (String -> PtrString
sLit String
"(locals only)"))
SDoc -> SDoc -> SDoc
<+> SDoc
lbrace
, Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
vcat [ [GlobalRdrElt] -> SDoc
pp ([GlobalRdrElt] -> [GlobalRdrElt]
remove_locals [GlobalRdrElt]
gre_list) | [GlobalRdrElt]
gre_list <- forall a. OccEnv a -> [a]
occEnvElts GlobalRdrEnv
env ]
SDoc -> SDoc -> SDoc
<+> SDoc
rbrace) ]
where
remove_locals :: [GlobalRdrElt] -> [GlobalRdrElt]
remove_locals [GlobalRdrElt]
gres | Bool
locals_only = forall a. (a -> Bool) -> [a] -> [a]
filter GlobalRdrElt -> Bool
isLocalGRE [GlobalRdrElt]
gres
| Bool
otherwise = [GlobalRdrElt]
gres
pp :: [GlobalRdrElt] -> SDoc
pp [] = SDoc
empty
pp [GlobalRdrElt]
gres = SDoc -> Int -> SDoc -> SDoc
hang (forall a. Outputable a => a -> SDoc
ppr OccName
occ
SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (String -> SDoc
text String
"unique" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (forall a. Uniquable a => a -> Unique
getUnique OccName
occ))
SDoc -> SDoc -> SDoc
<> SDoc
colon)
Int
2 ([SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [GlobalRdrElt]
gres))
where
occ :: OccName
occ = Name -> OccName
nameOccName (GlobalRdrElt -> Name
greMangledName (forall a. [a] -> a
head [GlobalRdrElt]
gres))
lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt]
lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt]
lookupGlobalRdrEnv GlobalRdrEnv
env OccName
occ_name = case forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv GlobalRdrEnv
env OccName
occ_name of
Maybe [GlobalRdrElt]
Nothing -> []
Just [GlobalRdrElt]
gres -> [GlobalRdrElt]
gres
lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
lookupGRE_RdrName RdrName
rdr_name GlobalRdrEnv
env =
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Bool
isNoFieldSelectorGRE) (RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
lookupGRE_RdrName' RdrName
rdr_name GlobalRdrEnv
env)
lookupGRE_RdrName' :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
lookupGRE_RdrName' :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
lookupGRE_RdrName' RdrName
rdr_name GlobalRdrEnv
env
= case forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv GlobalRdrEnv
env (RdrName -> OccName
rdrNameOcc RdrName
rdr_name) of
Maybe [GlobalRdrElt]
Nothing -> []
Just [GlobalRdrElt]
gres -> RdrName -> [GlobalRdrElt] -> [GlobalRdrElt]
pickGREs RdrName
rdr_name [GlobalRdrElt]
gres
lookupGRE_Name :: GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
lookupGRE_Name :: GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
lookupGRE_Name GlobalRdrEnv
env Name
name
= GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
lookupGRE_Name_OccName GlobalRdrEnv
env Name
name (Name -> OccName
nameOccName Name
name)
lookupGRE_GreName :: GlobalRdrEnv -> GreName -> Maybe GlobalRdrElt
lookupGRE_GreName :: GlobalRdrEnv -> GreName -> Maybe GlobalRdrElt
lookupGRE_GreName GlobalRdrEnv
env GreName
gname
= GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
lookupGRE_Name_OccName GlobalRdrEnv
env (GreName -> Name
greNameMangledName GreName
gname) (forall name. HasOccName name => name -> OccName
occName GreName
gname)
lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt
lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt
lookupGRE_FieldLabel GlobalRdrEnv
env FieldLabel
fl
= GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
lookupGRE_Name_OccName GlobalRdrEnv
env (FieldLabel -> Name
flSelector FieldLabel
fl) (FastString -> OccName
mkVarOccFS (FieldLabel -> FastString
flLabel FieldLabel
fl))
lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
lookupGRE_Name_OccName GlobalRdrEnv
env Name
name OccName
occ
= case [ GlobalRdrElt
gre | GlobalRdrElt
gre <- GlobalRdrEnv -> OccName -> [GlobalRdrElt]
lookupGlobalRdrEnv GlobalRdrEnv
env OccName
occ
, GlobalRdrElt -> Name
greMangledName GlobalRdrElt
gre forall a. Eq a => a -> a -> Bool
== Name
name ] of
[] -> forall a. Maybe a
Nothing
[GlobalRdrElt
gre] -> forall a. a -> Maybe a
Just GlobalRdrElt
gre
[GlobalRdrElt]
gres -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"lookupGRE_Name_OccName"
(forall a. Outputable a => a -> SDoc
ppr Name
name SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr OccName
occ SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr [GlobalRdrElt]
gres)
getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]]
getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]]
getGRE_NameQualifier_maybes GlobalRdrEnv
env Name
name
= case GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
lookupGRE_Name GlobalRdrEnv
env Name
name of
Just GlobalRdrElt
gre -> [GlobalRdrElt -> Maybe [ModuleName]
qualifier_maybe GlobalRdrElt
gre]
Maybe GlobalRdrElt
Nothing -> []
where
qualifier_maybe :: GlobalRdrElt -> Maybe [ModuleName]
qualifier_maybe (GRE { gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss })
| Bool
lcl = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (ImpDeclSpec -> ModuleName
is_as forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImportSpec -> ImpDeclSpec
is_decl) [ImportSpec]
iss
isLocalGRE :: GlobalRdrElt -> Bool
isLocalGRE :: GlobalRdrElt -> Bool
isLocalGRE (GRE {gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl }) = Bool
lcl
isRecFldGRE :: GlobalRdrElt -> Bool
isRecFldGRE :: GlobalRdrElt -> Bool
isRecFldGRE = forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Maybe FieldLabel
greFieldLabel
isDuplicateRecFldGRE :: GlobalRdrElt -> Bool
isDuplicateRecFldGRE :: GlobalRdrElt -> Bool
isDuplicateRecFldGRE =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False ((DuplicateRecordFields
DuplicateRecordFields forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLabel -> DuplicateRecordFields
flHasDuplicateRecordFields) forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Maybe FieldLabel
greFieldLabel
isNoFieldSelectorGRE :: GlobalRdrElt -> Bool
isNoFieldSelectorGRE :: GlobalRdrElt -> Bool
isNoFieldSelectorGRE =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False ((FieldSelectors
NoFieldSelectors forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLabel -> FieldSelectors
flHasFieldSelector) forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Maybe FieldLabel
greFieldLabel
isFieldSelectorGRE :: GlobalRdrElt -> Bool
isFieldSelectorGRE :: GlobalRdrElt -> Bool
isFieldSelectorGRE =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False ((FieldSelectors
FieldSelectors forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLabel -> FieldSelectors
flHasFieldSelector) forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Maybe FieldLabel
greFieldLabel
greFieldLabel :: GlobalRdrElt -> Maybe FieldLabel
greFieldLabel :: GlobalRdrElt -> Maybe FieldLabel
greFieldLabel = GreName -> Maybe FieldLabel
greNameFieldLabel forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> GreName
gre_name
unQualOK :: GlobalRdrElt -> Bool
unQualOK :: GlobalRdrElt -> Bool
unQualOK (GRE {gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss })
| Bool
lcl = Bool
True
| Bool
otherwise = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ImportSpec -> Bool
unQualSpecOK [ImportSpec]
iss
pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt]
pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt]
pickGREs (Unqual {}) [GlobalRdrElt]
gres = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe GlobalRdrElt -> Maybe GlobalRdrElt
pickUnqualGRE [GlobalRdrElt]
gres
pickGREs (Qual ModuleName
mod OccName
_) [GlobalRdrElt]
gres = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (ModuleName -> GlobalRdrElt -> Maybe GlobalRdrElt
pickQualGRE ModuleName
mod) [GlobalRdrElt]
gres
pickGREs RdrName
_ [GlobalRdrElt]
_ = []
pickUnqualGRE :: GlobalRdrElt -> Maybe GlobalRdrElt
pickUnqualGRE :: GlobalRdrElt -> Maybe GlobalRdrElt
pickUnqualGRE gre :: GlobalRdrElt
gre@(GRE { gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss })
| Bool -> Bool
not Bool
lcl, forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ImportSpec]
iss' = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just (GlobalRdrElt
gre { gre_imp :: [ImportSpec]
gre_imp = [ImportSpec]
iss' })
where
iss' :: [ImportSpec]
iss' = forall a. (a -> Bool) -> [a] -> [a]
filter ImportSpec -> Bool
unQualSpecOK [ImportSpec]
iss
pickQualGRE :: ModuleName -> GlobalRdrElt -> Maybe GlobalRdrElt
pickQualGRE :: ModuleName -> GlobalRdrElt -> Maybe GlobalRdrElt
pickQualGRE ModuleName
mod gre :: GlobalRdrElt
gre@(GRE { gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss })
| Bool -> Bool
not Bool
lcl', forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ImportSpec]
iss' = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just (GlobalRdrElt
gre { gre_lcl :: Bool
gre_lcl = Bool
lcl', gre_imp :: [ImportSpec]
gre_imp = [ImportSpec]
iss' })
where
iss' :: [ImportSpec]
iss' = forall a. (a -> Bool) -> [a] -> [a]
filter (ModuleName -> ImportSpec -> Bool
qualSpecOK ModuleName
mod) [ImportSpec]
iss
lcl' :: Bool
lcl' = Bool
lcl Bool -> Bool -> Bool
&& ModuleName -> Bool
name_is_from ModuleName
mod
name_is_from :: ModuleName -> Bool
name_is_from :: ModuleName -> Bool
name_is_from ModuleName
mod = case GlobalRdrElt -> Maybe Module
greDefinitionModule GlobalRdrElt
gre of
Just Module
n_mod -> forall unit. GenModule unit -> ModuleName
moduleName Module
n_mod forall a. Eq a => a -> a -> Bool
== ModuleName
mod
Maybe Module
Nothing -> Bool
False
pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt,GlobalRdrElt)]
pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)]
pickGREsModExp ModuleName
mod [GlobalRdrElt]
gres = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (ModuleName -> GlobalRdrElt -> Maybe (GlobalRdrElt, GlobalRdrElt)
pickBothGRE ModuleName
mod) [GlobalRdrElt]
gres
pickBothGRE :: ModuleName -> GlobalRdrElt -> Maybe (GlobalRdrElt, GlobalRdrElt)
pickBothGRE :: ModuleName -> GlobalRdrElt -> Maybe (GlobalRdrElt, GlobalRdrElt)
pickBothGRE ModuleName
mod GlobalRdrElt
gre
| Name -> Bool
isBuiltInSyntax (GlobalRdrElt -> Name
greMangledName GlobalRdrElt
gre) = forall a. Maybe a
Nothing
| Just GlobalRdrElt
gre1 <- ModuleName -> GlobalRdrElt -> Maybe GlobalRdrElt
pickQualGRE ModuleName
mod GlobalRdrElt
gre
, Just GlobalRdrElt
gre2 <- GlobalRdrElt -> Maybe GlobalRdrElt
pickUnqualGRE GlobalRdrElt
gre = forall a. a -> Maybe a
Just (GlobalRdrElt
gre1, GlobalRdrElt
gre2)
| Bool
otherwise = forall a. Maybe a
Nothing
plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
plusGlobalRdrEnv GlobalRdrEnv
env1 GlobalRdrEnv
env2 = forall a. (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a
plusOccEnv_C (forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE) GlobalRdrEnv
env1 GlobalRdrEnv
env2
mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv
mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv
mkGlobalRdrEnv [GlobalRdrElt]
gres
= forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr GlobalRdrElt -> GlobalRdrEnv -> GlobalRdrEnv
add GlobalRdrEnv
emptyGlobalRdrEnv [GlobalRdrElt]
gres
where
add :: GlobalRdrElt -> GlobalRdrEnv -> GlobalRdrEnv
add GlobalRdrElt
gre GlobalRdrEnv
env = forall a b.
(a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b
extendOccEnv_Acc GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE forall a. a -> [a]
Utils.singleton GlobalRdrEnv
env
(GlobalRdrElt -> OccName
greOccName GlobalRdrElt
gre)
GlobalRdrElt
gre
insertGRE :: GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE :: GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE GlobalRdrElt
new_g [] = [GlobalRdrElt
new_g]
insertGRE GlobalRdrElt
new_g (GlobalRdrElt
old_g : [GlobalRdrElt]
old_gs)
| GlobalRdrElt -> GreName
gre_name GlobalRdrElt
new_g forall a. Eq a => a -> a -> Bool
== GlobalRdrElt -> GreName
gre_name GlobalRdrElt
old_g
= GlobalRdrElt
new_g GlobalRdrElt -> GlobalRdrElt -> GlobalRdrElt
`plusGRE` GlobalRdrElt
old_g forall a. a -> [a] -> [a]
: [GlobalRdrElt]
old_gs
| Bool
otherwise
= GlobalRdrElt
old_g forall a. a -> [a] -> [a]
: GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE GlobalRdrElt
new_g [GlobalRdrElt]
old_gs
plusGRE :: GlobalRdrElt -> GlobalRdrElt -> GlobalRdrElt
plusGRE :: GlobalRdrElt -> GlobalRdrElt -> GlobalRdrElt
plusGRE GlobalRdrElt
g1 GlobalRdrElt
g2
= GRE { gre_name :: GreName
gre_name = GlobalRdrElt -> GreName
gre_name GlobalRdrElt
g1
, gre_lcl :: Bool
gre_lcl = GlobalRdrElt -> Bool
gre_lcl GlobalRdrElt
g1 Bool -> Bool -> Bool
|| GlobalRdrElt -> Bool
gre_lcl GlobalRdrElt
g2
, gre_imp :: [ImportSpec]
gre_imp = GlobalRdrElt -> [ImportSpec]
gre_imp GlobalRdrElt
g1 forall a. [a] -> [a] -> [a]
++ GlobalRdrElt -> [ImportSpec]
gre_imp GlobalRdrElt
g2
, gre_par :: Parent
gre_par = GlobalRdrElt -> Parent
gre_par GlobalRdrElt
g1 Parent -> Parent -> Parent
`plusParent` GlobalRdrElt -> Parent
gre_par GlobalRdrElt
g2 }
transformGREs :: (GlobalRdrElt -> GlobalRdrElt)
-> [OccName]
-> GlobalRdrEnv -> GlobalRdrEnv
transformGREs :: (GlobalRdrElt -> GlobalRdrElt)
-> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv
transformGREs GlobalRdrElt -> GlobalRdrElt
trans_gre [OccName]
occs GlobalRdrEnv
rdr_env
= forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr OccName -> GlobalRdrEnv -> GlobalRdrEnv
trans GlobalRdrEnv
rdr_env [OccName]
occs
where
trans :: OccName -> GlobalRdrEnv -> GlobalRdrEnv
trans OccName
occ GlobalRdrEnv
env
= case forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv GlobalRdrEnv
env OccName
occ of
Just [GlobalRdrElt]
gres -> forall a. OccEnv a -> OccName -> a -> OccEnv a
extendOccEnv GlobalRdrEnv
env OccName
occ (forall a b. (a -> b) -> [a] -> [b]
map GlobalRdrElt -> GlobalRdrElt
trans_gre [GlobalRdrElt]
gres)
Maybe [GlobalRdrElt]
Nothing -> GlobalRdrEnv
env
extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
extendGlobalRdrEnv GlobalRdrEnv
env GlobalRdrElt
gre
= forall a b.
(a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b
extendOccEnv_Acc GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE forall a. a -> [a]
Utils.singleton GlobalRdrEnv
env
(GlobalRdrElt -> OccName
greOccName GlobalRdrElt
gre) GlobalRdrElt
gre
shadowNames :: GlobalRdrEnv -> [GreName] -> GlobalRdrEnv
shadowNames :: GlobalRdrEnv -> [GreName] -> GlobalRdrEnv
shadowNames = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' GlobalRdrEnv -> GreName -> GlobalRdrEnv
shadowName
shadowName :: GlobalRdrEnv -> GreName -> GlobalRdrEnv
shadowName :: GlobalRdrEnv -> GreName -> GlobalRdrEnv
shadowName GlobalRdrEnv
env GreName
new_name
= forall elt.
(Maybe elt -> Maybe elt) -> OccEnv elt -> OccName -> OccEnv elt
alterOccEnv (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe GlobalRdrElt -> Maybe GlobalRdrElt
shadow)) GlobalRdrEnv
env (forall name. HasOccName name => name -> OccName
occName GreName
new_name)
where
maybe_new_mod :: Maybe Module
maybe_new_mod = Name -> Maybe Module
nameModule_maybe (GreName -> Name
greNameMangledName GreName
new_name)
shadow :: GlobalRdrElt -> Maybe GlobalRdrElt
shadow :: GlobalRdrElt -> Maybe GlobalRdrElt
shadow
old_gre :: GlobalRdrElt
old_gre@(GRE { gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss })
= case GlobalRdrElt -> Maybe Module
greDefinitionModule GlobalRdrElt
old_gre of
Maybe Module
Nothing -> forall a. a -> Maybe a
Just GlobalRdrElt
old_gre
Just Module
old_mod
| Just Module
new_mod <- Maybe Module
maybe_new_mod
, Module
new_mod forall a. Eq a => a -> a -> Bool
== Module
old_mod
-> forall a. Maybe a
Nothing
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ImportSpec]
iss'
-> forall a. Maybe a
Nothing
| Bool
otherwise
-> forall a. a -> Maybe a
Just (GlobalRdrElt
old_gre { gre_lcl :: Bool
gre_lcl = Bool
False, gre_imp :: [ImportSpec]
gre_imp = [ImportSpec]
iss' })
where
iss' :: [ImportSpec]
iss' = [ImportSpec]
lcl_imp forall a. [a] -> [a] -> [a]
++ forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ImportSpec -> Maybe ImportSpec
shadow_is [ImportSpec]
iss
lcl_imp :: [ImportSpec]
lcl_imp | Bool
lcl = [forall {unit}. GlobalRdrElt -> GenModule unit -> ImportSpec
mk_fake_imp_spec GlobalRdrElt
old_gre Module
old_mod]
| Bool
otherwise = []
mk_fake_imp_spec :: GlobalRdrElt -> GenModule unit -> ImportSpec
mk_fake_imp_spec GlobalRdrElt
old_gre GenModule unit
old_mod
= ImpDeclSpec -> ImpItemSpec -> ImportSpec
ImpSpec ImpDeclSpec
id_spec ImpItemSpec
ImpAll
where
old_mod_name :: ModuleName
old_mod_name = forall unit. GenModule unit -> ModuleName
moduleName GenModule unit
old_mod
id_spec :: ImpDeclSpec
id_spec = ImpDeclSpec { is_mod :: ModuleName
is_mod = ModuleName
old_mod_name
, is_as :: ModuleName
is_as = ModuleName
old_mod_name
, is_qual :: Bool
is_qual = Bool
True
, is_dloc :: SrcSpan
is_dloc = GlobalRdrElt -> SrcSpan
greDefinitionSrcSpan GlobalRdrElt
old_gre }
shadow_is :: ImportSpec -> Maybe ImportSpec
shadow_is :: ImportSpec -> Maybe ImportSpec
shadow_is is :: ImportSpec
is@(ImpSpec { is_decl :: ImportSpec -> ImpDeclSpec
is_decl = ImpDeclSpec
id_spec })
| Just Module
new_mod <- Maybe Module
maybe_new_mod
, ImpDeclSpec -> ModuleName
is_as ImpDeclSpec
id_spec forall a. Eq a => a -> a -> Bool
== forall unit. GenModule unit -> ModuleName
moduleName Module
new_mod
= forall a. Maybe a
Nothing
| Bool
otherwise
= forall a. a -> Maybe a
Just (ImportSpec
is { is_decl :: ImpDeclSpec
is_decl = ImpDeclSpec
id_spec { is_qual :: Bool
is_qual = Bool
True } })
data ImportSpec = ImpSpec { ImportSpec -> ImpDeclSpec
is_decl :: ImpDeclSpec,
ImportSpec -> ImpItemSpec
is_item :: ImpItemSpec }
deriving( ImportSpec -> ImportSpec -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportSpec -> ImportSpec -> Bool
$c/= :: ImportSpec -> ImportSpec -> Bool
== :: ImportSpec -> ImportSpec -> Bool
$c== :: ImportSpec -> ImportSpec -> Bool
Eq, Typeable ImportSpec
ImportSpec -> DataType
ImportSpec -> Constr
(forall b. Data b => b -> b) -> ImportSpec -> ImportSpec
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ImportSpec -> u
forall u. (forall d. Data d => d -> u) -> ImportSpec -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportSpec
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImportSpec -> c ImportSpec
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportSpec)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImportSpec -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImportSpec -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ImportSpec -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ImportSpec -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
gmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec
$cgmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportSpec)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportSpec)
dataTypeOf :: ImportSpec -> DataType
$cdataTypeOf :: ImportSpec -> DataType
toConstr :: ImportSpec -> Constr
$ctoConstr :: ImportSpec -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportSpec
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportSpec
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImportSpec -> c ImportSpec
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImportSpec -> c ImportSpec
Data )
data ImpDeclSpec
= ImpDeclSpec {
ImpDeclSpec -> ModuleName
is_mod :: ModuleName,
ImpDeclSpec -> ModuleName
is_as :: ModuleName,
ImpDeclSpec -> Bool
is_qual :: Bool,
ImpDeclSpec -> SrcSpan
is_dloc :: SrcSpan
} deriving (ImpDeclSpec -> ImpDeclSpec -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImpDeclSpec -> ImpDeclSpec -> Bool
$c/= :: ImpDeclSpec -> ImpDeclSpec -> Bool
== :: ImpDeclSpec -> ImpDeclSpec -> Bool
$c== :: ImpDeclSpec -> ImpDeclSpec -> Bool
Eq, Typeable ImpDeclSpec
ImpDeclSpec -> DataType
ImpDeclSpec -> Constr
(forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u
forall u. (forall d. Data d => d -> u) -> ImpDeclSpec -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpDeclSpec
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpDeclSpec)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ImpDeclSpec -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ImpDeclSpec -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
gmapT :: (forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec
$cgmapT :: (forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpDeclSpec)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpDeclSpec)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec)
dataTypeOf :: ImpDeclSpec -> DataType
$cdataTypeOf :: ImpDeclSpec -> DataType
toConstr :: ImpDeclSpec -> Constr
$ctoConstr :: ImpDeclSpec -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpDeclSpec
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpDeclSpec
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec
Data)
data ImpItemSpec
= ImpAll
| ImpSome {
ImpItemSpec -> Bool
is_explicit :: Bool,
ImpItemSpec -> SrcSpan
is_iloc :: SrcSpan
}
deriving (ImpItemSpec -> ImpItemSpec -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImpItemSpec -> ImpItemSpec -> Bool
$c/= :: ImpItemSpec -> ImpItemSpec -> Bool
== :: ImpItemSpec -> ImpItemSpec -> Bool
$c== :: ImpItemSpec -> ImpItemSpec -> Bool
Eq, Typeable ImpItemSpec
ImpItemSpec -> DataType
ImpItemSpec -> Constr
(forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u
forall u. (forall d. Data d => d -> u) -> ImpItemSpec -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpItemSpec
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpItemSpec)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ImpItemSpec -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ImpItemSpec -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
gmapT :: (forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec
$cgmapT :: (forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpItemSpec)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpItemSpec)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec)
dataTypeOf :: ImpItemSpec -> DataType
$cdataTypeOf :: ImpItemSpec -> DataType
toConstr :: ImpItemSpec -> Constr
$ctoConstr :: ImpItemSpec -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpItemSpec
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpItemSpec
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec
Data)
bestImport :: [ImportSpec] -> ImportSpec
bestImport :: [ImportSpec] -> ImportSpec
bestImport [ImportSpec]
iss
= case forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ImportSpec -> ImportSpec -> Ordering
best [ImportSpec]
iss of
(ImportSpec
is:[ImportSpec]
_) -> ImportSpec
is
[] -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"bestImport" (forall a. Outputable a => a -> SDoc
ppr [ImportSpec]
iss)
where
best :: ImportSpec -> ImportSpec -> Ordering
best :: ImportSpec -> ImportSpec -> Ordering
best (ImpSpec { is_item :: ImportSpec -> ImpItemSpec
is_item = ImpItemSpec
item1, is_decl :: ImportSpec -> ImpDeclSpec
is_decl = ImpDeclSpec
d1 })
(ImpSpec { is_item :: ImportSpec -> ImpItemSpec
is_item = ImpItemSpec
item2, is_decl :: ImportSpec -> ImpDeclSpec
is_decl = ImpDeclSpec
d2 })
= (ImpDeclSpec -> Bool
is_qual ImpDeclSpec
d1 forall a. Ord a => a -> a -> Ordering
`compare` ImpDeclSpec -> Bool
is_qual ImpDeclSpec
d2) Ordering -> Ordering -> Ordering
`thenCmp`
(ImpItemSpec -> ImpItemSpec -> Ordering
best_item ImpItemSpec
item1 ImpItemSpec
item2) Ordering -> Ordering -> Ordering
`thenCmp`
SrcSpan -> SrcSpan -> Ordering
SrcLoc.leftmost_smallest (ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
d1) (ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
d2)
best_item :: ImpItemSpec -> ImpItemSpec -> Ordering
best_item :: ImpItemSpec -> ImpItemSpec -> Ordering
best_item ImpItemSpec
ImpAll ImpItemSpec
ImpAll = Ordering
EQ
best_item ImpItemSpec
ImpAll (ImpSome {}) = Ordering
LT
best_item (ImpSome {}) ImpItemSpec
ImpAll = Ordering
GT
best_item (ImpSome { is_explicit :: ImpItemSpec -> Bool
is_explicit = Bool
e1 })
(ImpSome { is_explicit :: ImpItemSpec -> Bool
is_explicit = Bool
e2 }) = Bool
e1 forall a. Ord a => a -> a -> Ordering
`compare` Bool
e2
unQualSpecOK :: ImportSpec -> Bool
unQualSpecOK :: ImportSpec -> Bool
unQualSpecOK ImportSpec
is = Bool -> Bool
not (ImpDeclSpec -> Bool
is_qual (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is))
qualSpecOK :: ModuleName -> ImportSpec -> Bool
qualSpecOK :: ModuleName -> ImportSpec -> Bool
qualSpecOK ModuleName
mod ImportSpec
is = ModuleName
mod forall a. Eq a => a -> a -> Bool
== ImpDeclSpec -> ModuleName
is_as (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is)
importSpecLoc :: ImportSpec -> SrcSpan
importSpecLoc :: ImportSpec -> SrcSpan
importSpecLoc (ImpSpec ImpDeclSpec
decl ImpItemSpec
ImpAll) = ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
decl
importSpecLoc (ImpSpec ImpDeclSpec
_ ImpItemSpec
item) = ImpItemSpec -> SrcSpan
is_iloc ImpItemSpec
item
importSpecModule :: ImportSpec -> ModuleName
importSpecModule :: ImportSpec -> ModuleName
importSpecModule ImportSpec
is = ImpDeclSpec -> ModuleName
is_mod (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is)
isExplicitItem :: ImpItemSpec -> Bool
isExplicitItem :: ImpItemSpec -> Bool
isExplicitItem ImpItemSpec
ImpAll = Bool
False
isExplicitItem (ImpSome {is_explicit :: ImpItemSpec -> Bool
is_explicit = Bool
exp}) = Bool
exp
pprNameProvenance :: GlobalRdrElt -> SDoc
pprNameProvenance :: GlobalRdrElt -> SDoc
pprNameProvenance gre :: GlobalRdrElt
gre@(GRE { gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss })
= SDoc -> SDoc -> SDoc
ifPprDebug ([SDoc] -> SDoc
vcat [SDoc]
pp_provs)
(forall a. [a] -> a
head [SDoc]
pp_provs)
where
name :: Name
name = GlobalRdrElt -> Name
greMangledName GlobalRdrElt
gre
pp_provs :: [SDoc]
pp_provs = [SDoc]
pp_lcl forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map ImportSpec -> SDoc
pp_is [ImportSpec]
iss
pp_lcl :: [SDoc]
pp_lcl = if Bool
lcl then [String -> SDoc
text String
"defined at" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (Name -> SrcLoc
nameSrcLoc Name
name)]
else []
pp_is :: ImportSpec -> SDoc
pp_is ImportSpec
is = [SDoc] -> SDoc
sep [forall a. Outputable a => a -> SDoc
ppr ImportSpec
is, ImportSpec -> Name -> SDoc
ppr_defn_site ImportSpec
is Name
name]
ppr_defn_site :: ImportSpec -> Name -> SDoc
ppr_defn_site :: ImportSpec -> Name -> SDoc
ppr_defn_site ImportSpec
imp_spec Name
name
| Bool
same_module Bool -> Bool -> Bool
&& Bool -> Bool
not (SrcSpan -> Bool
isGoodSrcSpan SrcSpan
loc)
= SDoc
empty
| Bool
otherwise
= SDoc -> SDoc
parens forall a b. (a -> b) -> a -> b
$ SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"and originally defined" SDoc -> SDoc -> SDoc
<+> SDoc
pp_mod)
Int
2 (SrcSpan -> SDoc
pprLoc SrcSpan
loc)
where
loc :: SrcSpan
loc = Name -> SrcSpan
nameSrcSpan Name
name
defining_mod :: Module
defining_mod = ASSERT2( isExternalName name, ppr name ) nameModule name
same_module :: Bool
same_module = ImportSpec -> ModuleName
importSpecModule ImportSpec
imp_spec forall a. Eq a => a -> a -> Bool
== forall unit. GenModule unit -> ModuleName
moduleName Module
defining_mod
pp_mod :: SDoc
pp_mod | Bool
same_module = SDoc
empty
| Bool
otherwise = String -> SDoc
text String
"in" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr Module
defining_mod)
instance Outputable ImportSpec where
ppr :: ImportSpec -> SDoc
ppr ImportSpec
imp_spec
= String -> SDoc
text String
"imported" SDoc -> SDoc -> SDoc
<+> SDoc
qual
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"from" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr (ImportSpec -> ModuleName
importSpecModule ImportSpec
imp_spec))
SDoc -> SDoc -> SDoc
<+> SrcSpan -> SDoc
pprLoc (ImportSpec -> SrcSpan
importSpecLoc ImportSpec
imp_spec)
where
qual :: SDoc
qual | ImpDeclSpec -> Bool
is_qual (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
imp_spec) = String -> SDoc
text String
"qualified"
| Bool
otherwise = SDoc
empty
pprLoc :: SrcSpan -> SDoc
pprLoc :: SrcSpan -> SDoc
pprLoc (RealSrcSpan RealSrcSpan
s Maybe BufSpan
_) = String -> SDoc
text String
"at" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr RealSrcSpan
s
pprLoc (UnhelpfulSpan {}) = SDoc
empty
starInfo :: Bool -> RdrName -> SDoc
starInfo :: Bool -> RdrName -> SDoc
starInfo Bool
star_is_type RdrName
rdr_name =
if Bool
isUnqualStar Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
star_is_type
then String -> SDoc
text String
"With NoStarIsType, " SDoc -> SDoc -> SDoc
<>
SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr RdrName
rdr_name) SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" is treated as a regular type operator. "
SDoc -> SDoc -> SDoc
$$
String -> SDoc
text String
"Did you mean to use " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (String -> SDoc
text String
"Type") SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" from Data.Kind instead?"
else SDoc
empty
where
isUnqualStar :: Bool
isUnqualStar
| Unqual OccName
occName <- RdrName
rdr_name
= let fs :: FastString
fs = OccName -> FastString
occNameFS OccName
occName
in FastString
fs forall a. Eq a => a -> a -> Bool
== String -> FastString
fsLit String
"*" Bool -> Bool -> Bool
|| FastString
fs forall a. Eq a => a -> a -> Bool
== String -> FastString
fsLit String
"★"
| Bool
otherwise = Bool
False
opIsAt :: RdrName -> Bool
opIsAt :: RdrName -> Bool
opIsAt RdrName
e = RdrName
e forall a. Eq a => a -> a -> Bool
== NameSpace -> FastString -> RdrName
mkUnqual NameSpace
varName (String -> FastString
fsLit String
"@")