{-# LANGUAGE CPP, DeriveDataTypeable #-}
module RdrName (
RdrName(..),
mkRdrUnqual, mkRdrQual,
mkUnqual, mkVarUnqual, mkQual, mkOrig,
nameRdrName, getRdrName,
rdrNameOcc, rdrNameSpace, demoteRdrName,
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_Name, lookupGRE_FieldLabel,
lookupGRE_Name_OccName,
getGRE_NameQualifier_maybes,
transformGREs, pickGREs, pickGREsModExp,
gresFromAvails, gresFromAvail, localGREsFromAvail, availFromGRE,
greRdrNames, greSrcSpan, greQualModName,
gresToAvailInfo,
GlobalRdrElt(..), isLocalGRE, isRecFldGRE, greLabel,
unQualOK, qualSpecOK, unQualSpecOK,
pprNameProvenance,
Parent(..), greParent_maybe,
ImportSpec(..), ImpDeclSpec(..), ImpItemSpec(..),
importSpecLoc, importSpecModule, isExplicitItem, bestImport,
starInfo
) where
#include "HsVersions.h"
import GhcPrelude
import Module
import Name
import Avail
import NameSet
import Maybes
import SrcLoc
import FastString
import FieldLabel
import Outputable
import Unique
import UniqFM
import UniqSet
import Util
import NameEnv
import Data.Data
import Data.List( sortBy )
data RdrName
= Unqual OccName
| Qual ModuleName OccName
| Orig Module OccName
| Exact Name
deriving Typeable RdrName
DataType
Constr
Typeable RdrName =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RdrName -> c RdrName)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RdrName)
-> (RdrName -> Constr)
-> (RdrName -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> RdrName -> RdrName)
-> (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 u. (forall d. Data d => d -> u) -> RdrName -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> RdrName -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName)
-> Data RdrName
RdrName -> DataType
RdrName -> Constr
(forall b. Data b => b -> b) -> RdrName -> RdrName
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RdrName -> c RdrName
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cExact :: Constr
$cOrig :: Constr
$cQual :: Constr
$cUnqual :: Constr
$tRdrName :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> RdrName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RdrName -> u
gmapQ :: (forall d. Data d => d -> u) -> RdrName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RdrName -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable RdrName
Data
instance HasOccName RdrName where
occName :: RdrName -> OccName
occName = RdrName -> OccName
rdrNameOcc
rdrNameOcc :: RdrName -> OccName
rdrNameOcc :: RdrName -> OccName
rdrNameOcc (Qual _ occ :: OccName
occ) = OccName
occ
rdrNameOcc (Unqual occ :: OccName
occ) = OccName
occ
rdrNameOcc (Orig _ occ :: OccName
occ) = OccName
occ
rdrNameOcc (Exact name :: Name
name) = Name -> OccName
nameOccName Name
name
rdrNameSpace :: RdrName -> NameSpace
rdrNameSpace :: RdrName -> NameSpace
rdrNameSpace = OccName -> NameSpace
occNameSpace (OccName -> NameSpace)
-> (RdrName -> OccName) -> RdrName -> NameSpace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RdrName -> OccName
rdrNameOcc
demoteRdrName :: RdrName -> Maybe RdrName
demoteRdrName :: RdrName -> Maybe RdrName
demoteRdrName (Unqual occ :: OccName
occ) = (OccName -> RdrName) -> Maybe OccName -> Maybe RdrName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OccName -> RdrName
Unqual (OccName -> Maybe OccName
demoteOccName OccName
occ)
demoteRdrName (Qual m :: ModuleName
m occ :: OccName
occ) = (OccName -> RdrName) -> Maybe OccName -> Maybe RdrName
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 _ _) = String -> Maybe RdrName
forall a. String -> a
panic "demoteRdrName"
demoteRdrName (Exact _) = String -> Maybe RdrName
forall a. String -> a
panic "demoteRdrName"
mkRdrUnqual :: OccName -> RdrName
mkRdrUnqual :: OccName -> RdrName
mkRdrUnqual occ :: OccName
occ = OccName -> RdrName
Unqual OccName
occ
mkRdrQual :: ModuleName -> OccName -> RdrName
mkRdrQual :: ModuleName -> OccName -> RdrName
mkRdrQual mod :: ModuleName
mod occ :: OccName
occ = ModuleName -> OccName -> RdrName
Qual ModuleName
mod OccName
occ
mkOrig :: Module -> OccName -> RdrName
mkOrig :: Module -> OccName -> RdrName
mkOrig mod :: Module
mod occ :: OccName
occ = Module -> OccName -> RdrName
Orig Module
mod OccName
occ
mkUnqual :: NameSpace -> FastString -> RdrName
mkUnqual :: NameSpace -> FastString -> RdrName
mkUnqual sp :: NameSpace
sp n :: FastString
n = OccName -> RdrName
Unqual (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
sp FastString
n)
mkVarUnqual :: FastString -> RdrName
mkVarUnqual :: FastString -> RdrName
mkVarUnqual n :: FastString
n = OccName -> RdrName
Unqual (FastString -> OccName
mkVarOccFS FastString
n)
mkQual :: NameSpace -> (FastString, FastString) -> RdrName
mkQual :: NameSpace -> (FastString, FastString) -> RdrName
mkQual sp :: NameSpace
sp (m :: FastString
m, n :: 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 :: thing -> RdrName
getRdrName name :: thing
name = Name -> RdrName
nameRdrName (thing -> Name
forall a. NamedThing a => a -> Name
getName thing
name)
nameRdrName :: Name -> RdrName
nameRdrName :: Name -> RdrName
nameRdrName name :: Name
name = Name -> RdrName
Exact Name
name
nukeExact :: Name -> RdrName
nukeExact :: Name -> RdrName
nukeExact n :: Name
n
| Name -> Bool
isExternalName Name
n = Module -> OccName -> RdrName
Orig (HasDebugCallStack => Name -> Module
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 rn :: RdrName
rn = OccName -> Bool
isDataOcc (RdrName -> OccName
rdrNameOcc RdrName
rn)
isRdrTyVar :: RdrName -> Bool
isRdrTyVar rn :: RdrName
rn = OccName -> Bool
isTvOcc (RdrName -> OccName
rdrNameOcc RdrName
rn)
isRdrTc :: RdrName -> Bool
isRdrTc rn :: RdrName
rn = OccName -> Bool
isTcOcc (RdrName -> OccName
rdrNameOcc RdrName
rn)
isSrcRdrName :: RdrName -> Bool
isSrcRdrName :: RdrName -> Bool
isSrcRdrName (Unqual _) = Bool
True
isSrcRdrName (Qual _ _) = Bool
True
isSrcRdrName _ = Bool
False
isUnqual :: RdrName -> Bool
isUnqual :: RdrName -> Bool
isUnqual (Unqual _) = Bool
True
isUnqual _ = Bool
False
isQual :: RdrName -> Bool
isQual :: RdrName -> Bool
isQual (Qual _ _) = Bool
True
isQual _ = Bool
False
isQual_maybe :: RdrName -> Maybe (ModuleName, OccName)
isQual_maybe :: RdrName -> Maybe (ModuleName, OccName)
isQual_maybe (Qual m :: ModuleName
m n :: OccName
n) = (ModuleName, OccName) -> Maybe (ModuleName, OccName)
forall a. a -> Maybe a
Just (ModuleName
m,OccName
n)
isQual_maybe _ = Maybe (ModuleName, OccName)
forall a. Maybe a
Nothing
isOrig :: RdrName -> Bool
isOrig :: RdrName -> Bool
isOrig (Orig _ _) = Bool
True
isOrig _ = Bool
False
isOrig_maybe :: RdrName -> Maybe (Module, OccName)
isOrig_maybe :: RdrName -> Maybe (Module, OccName)
isOrig_maybe (Orig m :: Module
m n :: OccName
n) = (Module, OccName) -> Maybe (Module, OccName)
forall a. a -> Maybe a
Just (Module
m,OccName
n)
isOrig_maybe _ = Maybe (Module, OccName)
forall a. Maybe a
Nothing
isExact :: RdrName -> Bool
isExact :: RdrName -> Bool
isExact (Exact _) = Bool
True
isExact _ = Bool
False
isExact_maybe :: RdrName -> Maybe Name
isExact_maybe :: RdrName -> Maybe Name
isExact_maybe (Exact n :: Name
n) = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
n
isExact_maybe _ = Maybe Name
forall a. Maybe a
Nothing
instance Outputable RdrName where
ppr :: RdrName -> SDoc
ppr (Exact name :: Name
name) = Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name
ppr (Unqual occ :: OccName
occ) = OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ
ppr (Qual mod :: ModuleName
mod occ :: OccName
occ) = ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod SDoc -> SDoc -> SDoc
<> SDoc
dot SDoc -> SDoc -> SDoc
<> OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ
ppr (Orig mod :: Module
mod occ :: OccName
occ) = (PprStyle -> SDoc) -> SDoc
getPprStyle (\sty :: PprStyle
sty -> PprStyle -> Module -> OccName -> SDoc
pprModulePrefix PprStyle
sty Module
mod OccName
occ SDoc -> SDoc -> SDoc
<> OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ)
instance OutputableBndr RdrName where
pprBndr :: BindingSite -> RdrName -> SDoc
pprBndr _ n :: RdrName
n
| OccName -> Bool
isTvOcc (RdrName -> OccName
rdrNameOcc RdrName
n) = Char -> SDoc
char '@' SDoc -> SDoc -> SDoc
<+> RdrName -> SDoc
forall a. Outputable a => a -> SDoc
ppr RdrName
n
| Bool
otherwise = RdrName -> SDoc
forall a. Outputable a => a -> SDoc
ppr RdrName
n
pprInfixOcc :: RdrName -> SDoc
pprInfixOcc rdr :: RdrName
rdr = Bool -> SDoc -> SDoc
pprInfixVar (OccName -> Bool
isSymOcc (RdrName -> OccName
rdrNameOcc RdrName
rdr)) (RdrName -> SDoc
forall a. Outputable a => a -> SDoc
ppr RdrName
rdr)
pprPrefixOcc :: RdrName -> SDoc
pprPrefixOcc rdr :: RdrName
rdr
| Just name :: Name
name <- RdrName -> Maybe Name
isExact_maybe RdrName
rdr = Name -> SDoc
forall a. NamedThing a => a -> SDoc
pprPrefixName Name
name
| Bool
otherwise = Bool -> SDoc -> SDoc
pprPrefixVar (OccName -> Bool
isSymOcc (RdrName -> OccName
rdrNameOcc RdrName
rdr)) (RdrName -> SDoc
forall a. Outputable a => a -> SDoc
ppr RdrName
rdr)
instance Eq RdrName where
(Exact n1 :: Name
n1) == :: RdrName -> RdrName -> Bool
== (Exact n2 :: Name
n2) = Name
n1Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
==Name
n2
(Exact n1 :: Name
n1) == r2 :: RdrName
r2@(Orig _ _) = Name -> RdrName
nukeExact Name
n1 RdrName -> RdrName -> Bool
forall a. Eq a => a -> a -> Bool
== RdrName
r2
r1 :: RdrName
r1@(Orig _ _) == (Exact n2 :: Name
n2) = RdrName
r1 RdrName -> RdrName -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> RdrName
nukeExact Name
n2
(Orig m1 :: Module
m1 o1 :: OccName
o1) == (Orig m2 :: Module
m2 o2 :: OccName
o2) = Module
m1Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
==Module
m2 Bool -> Bool -> Bool
&& OccName
o1OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
==OccName
o2
(Qual m1 :: ModuleName
m1 o1 :: OccName
o1) == (Qual m2 :: ModuleName
m2 o2 :: OccName
o2) = ModuleName
m1ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
==ModuleName
m2 Bool -> Bool -> Bool
&& OccName
o1OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
==OccName
o2
(Unqual o1 :: OccName
o1) == (Unqual o2 :: OccName
o2) = OccName
o1OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
==OccName
o2
_ == _ = Bool
False
instance Ord RdrName where
a :: RdrName
a <= :: RdrName -> RdrName -> Bool
<= b :: RdrName
b = case (RdrName
a RdrName -> RdrName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { LT -> Bool
True; EQ -> Bool
True; GT -> Bool
False }
a :: RdrName
a < :: RdrName -> RdrName -> Bool
< b :: RdrName
b = case (RdrName
a RdrName -> RdrName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { LT -> Bool
True; EQ -> Bool
False; GT -> Bool
False }
a :: RdrName
a >= :: RdrName -> RdrName -> Bool
>= b :: RdrName
b = case (RdrName
a RdrName -> RdrName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { LT -> Bool
False; EQ -> Bool
True; GT -> Bool
True }
a :: RdrName
a > :: RdrName -> RdrName -> Bool
> b :: RdrName
b = case (RdrName
a RdrName -> RdrName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { LT -> Bool
False; EQ -> Bool
False; GT -> Bool
True }
compare :: RdrName -> RdrName -> Ordering
compare (Exact n1 :: Name
n1) (Exact n2 :: Name
n2) = Name
n1 Name -> Name -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Name
n2
compare (Exact _) _ = Ordering
LT
compare (Unqual _) (Exact _) = Ordering
GT
compare (Unqual o1 :: OccName
o1) (Unqual o2 :: OccName
o2) = OccName
o1 OccName -> OccName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` OccName
o2
compare (Unqual _) _ = Ordering
LT
compare (Qual _ _) (Exact _) = Ordering
GT
compare (Qual _ _) (Unqual _) = Ordering
GT
compare (Qual m1 :: ModuleName
m1 o1 :: OccName
o1) (Qual m2 :: ModuleName
m2 o2 :: OccName
o2) = (OccName
o1 OccName -> OccName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` OccName
o2) Ordering -> Ordering -> Ordering
`thenCmp` (ModuleName
m1 ModuleName -> ModuleName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` ModuleName
m2)
compare (Qual _ _) (Orig _ _) = Ordering
LT
compare (Orig m1 :: Module
m1 o1 :: OccName
o1) (Orig m2 :: Module
m2 o2 :: OccName
o2) = (OccName
o1 OccName -> OccName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` OccName
o2) Ordering -> Ordering -> Ordering
`thenCmp` (Module
m1 Module -> Module -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Module
m2)
compare (Orig _ _) _ = 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 "LocalRdrEnv {")
2 ([SDoc] -> SDoc
vcat [ String -> SDoc
text "env =" SDoc -> SDoc -> SDoc
<+> (Name -> SDoc) -> OccEnv Name -> SDoc
forall a. (a -> SDoc) -> OccEnv a -> SDoc
pprOccEnv Name -> SDoc
ppr_elt OccEnv Name
env
, String -> SDoc
text "in_scope ="
SDoc -> SDoc -> SDoc
<+> UniqFM Name -> ([Name] -> SDoc) -> SDoc
forall a. UniqFM a -> ([a] -> SDoc) -> SDoc
pprUFM (NameSet -> UniqFM Name
forall a. UniqSet a -> UniqFM a
getUniqSet NameSet
ns) (SDoc -> SDoc
braces (SDoc -> SDoc) -> ([Name] -> SDoc) -> [Name] -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name -> SDoc) -> [Name] -> SDoc
forall a. (a -> SDoc) -> [a] -> SDoc
pprWithCommas Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr)
] SDoc -> SDoc -> SDoc
<+> Char -> SDoc
char '}')
where
ppr_elt :: Name -> SDoc
ppr_elt name :: Name
name = SDoc -> SDoc
parens (Unique -> SDoc
forall a. Outputable a => a -> SDoc
ppr (OccName -> Unique
forall a. Uniquable a => a -> Unique
getUnique (Name -> OccName
nameOccName Name
name))) SDoc -> SDoc -> SDoc
<+> Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name
emptyLocalRdrEnv :: LocalRdrEnv
emptyLocalRdrEnv :: LocalRdrEnv
emptyLocalRdrEnv = LRE :: OccEnv Name -> NameSet -> LocalRdrEnv
LRE { lre_env :: OccEnv Name
lre_env = OccEnv Name
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
name
= WARN( isExternalName name, ppr name )
LocalRdrEnv
lre { lre_env :: OccEnv Name
lre_env = OccEnv Name -> OccName -> Name -> OccEnv Name
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 }) names :: [Name]
names
= WARN( any isExternalName names, ppr names )
LocalRdrEnv
lre { lre_env :: OccEnv Name
lre_env = OccEnv Name -> [(OccName, Name)] -> OccEnv Name
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 }) rdr :: RdrName
rdr
| Unqual occ :: OccName
occ <- RdrName
rdr
= OccEnv Name -> OccName -> Maybe Name
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv Name
env OccName
occ
| Exact name :: Name
name <- RdrName
rdr
, Name
name Name -> NameSet -> Bool
`elemNameSet` NameSet
ns
= Name -> Maybe Name
forall a. a -> Maybe a
Just Name
name
| Bool
otherwise
= Maybe Name
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 }) occ :: OccName
occ = OccEnv Name -> OccName -> Maybe Name
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv Name
env OccName
occ
elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool
elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool
elemLocalRdrEnv rdr_name :: 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 occ :: OccName
occ -> OccName
occ OccName -> OccEnv Name -> Bool
forall a. OccName -> OccEnv a -> Bool
`elemOccEnv` OccEnv Name
env
Exact name :: 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 }) = OccEnv Name -> [Name]
forall a. OccEnv a -> [a]
occEnvElts OccEnv Name
env
inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool
inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool
inLocalRdrEnvScope name :: 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 }) occs :: [OccName]
occs
= LocalRdrEnv
lre { lre_env :: OccEnv Name
lre_env = OccEnv Name -> [OccName] -> OccEnv Name
forall a. OccEnv a -> [OccName] -> OccEnv a
delListFromOccEnv OccEnv Name
env [OccName]
occs }
type GlobalRdrEnv = OccEnv [GlobalRdrElt]
data GlobalRdrElt
= GRE { GlobalRdrElt -> Name
gre_name :: Name
, GlobalRdrElt -> Parent
gre_par :: Parent
, GlobalRdrElt -> Bool
gre_lcl :: Bool
, GlobalRdrElt -> [ImportSpec]
gre_imp :: [ImportSpec]
} deriving (Typeable GlobalRdrElt
DataType
Constr
Typeable GlobalRdrElt =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GlobalRdrElt -> c GlobalRdrElt)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GlobalRdrElt)
-> (GlobalRdrElt -> Constr)
-> (GlobalRdrElt -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> GlobalRdrElt -> GlobalRdrElt)
-> (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 u. (forall d. Data d => d -> u) -> GlobalRdrElt -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt)
-> Data GlobalRdrElt
GlobalRdrElt -> DataType
GlobalRdrElt -> Constr
(forall b. Data b => b -> b) -> GlobalRdrElt -> GlobalRdrElt
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GlobalRdrElt -> c GlobalRdrElt
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cGRE :: Constr
$tGlobalRdrElt :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u
gmapQ :: (forall d. Data d => d -> u) -> GlobalRdrElt -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> GlobalRdrElt -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable GlobalRdrElt
Data, GlobalRdrElt -> GlobalRdrElt -> Bool
(GlobalRdrElt -> GlobalRdrElt -> Bool)
-> (GlobalRdrElt -> GlobalRdrElt -> Bool) -> Eq GlobalRdrElt
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 }
| FldParent { par_is :: Name, Parent -> Maybe FastString
par_lbl :: Maybe FieldLabelString }
deriving (Parent -> Parent -> Bool
(Parent -> Parent -> Bool)
-> (Parent -> Parent -> Bool) -> Eq Parent
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
DataType
Constr
Typeable Parent =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Parent -> c Parent)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Parent)
-> (Parent -> Constr)
-> (Parent -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> Parent -> Parent)
-> (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 u. (forall d. Data d => d -> u) -> Parent -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Parent -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent)
-> Data Parent
Parent -> DataType
Parent -> Constr
(forall b. Data b => b -> b) -> Parent -> Parent
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Parent -> c Parent
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cFldParent :: Constr
$cParentIs :: Constr
$cNoParent :: Constr
$tParent :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> Parent -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Parent -> u
gmapQ :: (forall d. Data d => d -> u) -> Parent -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Parent -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable Parent
Data)
instance Outputable Parent where
ppr :: Parent -> SDoc
ppr NoParent = SDoc
empty
ppr (ParentIs n :: Name
n) = String -> SDoc
text "parent:" SDoc -> SDoc -> SDoc
<> Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
n
ppr (FldParent n :: Name
n f :: Maybe FastString
f) = String -> SDoc
text "fldparent:"
SDoc -> SDoc -> SDoc
<> Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
n SDoc -> SDoc -> SDoc
<> SDoc
colon SDoc -> SDoc -> SDoc
<> Maybe FastString -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe FastString
f
plusParent :: Parent -> Parent -> Parent
plusParent :: Parent -> Parent -> Parent
plusParent p1 :: Parent
p1@(ParentIs _) p2 :: Parent
p2 = Parent -> Parent -> Parent
hasParent Parent
p1 Parent
p2
plusParent p1 :: Parent
p1@(FldParent _ _) p2 :: Parent
p2 = Parent -> Parent -> Parent
hasParent Parent
p1 Parent
p2
plusParent p1 :: Parent
p1 p2 :: Parent
p2@(ParentIs _) = Parent -> Parent -> Parent
hasParent Parent
p2 Parent
p1
plusParent p1 :: Parent
p1 p2 :: Parent
p2@(FldParent _ _) = Parent -> Parent -> Parent
hasParent Parent
p2 Parent
p1
plusParent _ _ = 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 p :: Parent
p _ = Parent
p
gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt]
gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt]
gresFromAvails prov :: Maybe ImportSpec
prov avails :: [AvailInfo]
avails
= (AvailInfo -> [GlobalRdrElt]) -> [AvailInfo] -> [GlobalRdrElt]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt]
gresFromAvail (Maybe ImportSpec -> Name -> Maybe ImportSpec
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 (Maybe ImportSpec -> Name -> Maybe ImportSpec
forall a b. a -> b -> a
const Maybe ImportSpec
forall a. Maybe a
Nothing)
gresFromAvail :: (Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt]
gresFromAvail :: (Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt]
gresFromAvail prov_fn :: Name -> Maybe ImportSpec
prov_fn avail :: AvailInfo
avail
= (Name -> GlobalRdrElt) -> [Name] -> [GlobalRdrElt]
forall a b. (a -> b) -> [a] -> [b]
map Name -> GlobalRdrElt
mk_gre (AvailInfo -> [Name]
availNonFldNames AvailInfo
avail) [GlobalRdrElt] -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. [a] -> [a] -> [a]
++ (FieldLbl Name -> GlobalRdrElt)
-> [FieldLbl Name] -> [GlobalRdrElt]
forall a b. (a -> b) -> [a] -> [b]
map FieldLbl Name -> GlobalRdrElt
mk_fld_gre (AvailInfo -> [FieldLbl Name]
availFlds AvailInfo
avail)
where
mk_gre :: Name -> GlobalRdrElt
mk_gre n :: Name
n
= case Name -> Maybe ImportSpec
prov_fn Name
n of
Nothing -> GRE :: Name -> Parent -> Bool -> [ImportSpec] -> GlobalRdrElt
GRE { gre_name :: Name
gre_name = 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 is :: ImportSpec
is -> GRE :: Name -> Parent -> Bool -> [ImportSpec] -> GlobalRdrElt
GRE { gre_name :: Name
gre_name = 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 :: FieldLbl Name -> GlobalRdrElt
mk_fld_gre (FieldLabel { flLabel :: forall a. FieldLbl a -> FastString
flLabel = FastString
lbl, flIsOverloaded :: forall a. FieldLbl a -> Bool
flIsOverloaded = Bool
is_overloaded
, flSelector :: forall a. FieldLbl a -> a
flSelector = Name
n })
= case Name -> Maybe ImportSpec
prov_fn Name
n of
Nothing -> GRE :: Name -> Parent -> Bool -> [ImportSpec] -> GlobalRdrElt
GRE { gre_name :: Name
gre_name = Name
n, gre_par :: Parent
gre_par = Name -> Maybe FastString -> Parent
FldParent (AvailInfo -> Name
availName AvailInfo
avail) Maybe FastString
mb_lbl
, gre_lcl :: Bool
gre_lcl = Bool
True, gre_imp :: [ImportSpec]
gre_imp = [] }
Just is :: ImportSpec
is -> GRE :: Name -> Parent -> Bool -> [ImportSpec] -> GlobalRdrElt
GRE { gre_name :: Name
gre_name = Name
n, gre_par :: Parent
gre_par = Name -> Maybe FastString -> Parent
FldParent (AvailInfo -> Name
availName AvailInfo
avail) Maybe FastString
mb_lbl
, gre_lcl :: Bool
gre_lcl = Bool
False, gre_imp :: [ImportSpec]
gre_imp = [ImportSpec
is] }
where
mb_lbl :: Maybe FastString
mb_lbl | Bool
is_overloaded = FastString -> Maybe FastString
forall a. a -> Maybe a
Just FastString
lbl
| Bool
otherwise = Maybe FastString
forall a. Maybe a
Nothing
greQualModName :: GlobalRdrElt -> ModuleName
greQualModName :: GlobalRdrElt -> ModuleName
greQualModName gre :: GlobalRdrElt
gre@(GRE { gre_name :: GlobalRdrElt -> Name
gre_name = Name
name, gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss })
| Bool
lcl, Just mod :: Module
mod <- Name -> Maybe Module
nameModule_maybe Name
name = Module -> ModuleName
moduleName Module
mod
| (is :: ImportSpec
is:_) <- [ImportSpec]
iss = ImpDeclSpec -> ModuleName
is_as (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is)
| Bool
otherwise = String -> SDoc -> ModuleName
forall a. HasCallStack => String -> SDoc -> a
pprPanic "greQualModName" (GlobalRdrElt -> SDoc
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 []) [RdrName] -> [RdrName] -> [RdrName]
forall a. [a] -> [a] -> [a]
++ (ImpDeclSpec -> [RdrName]) -> [ImpDeclSpec] -> [RdrName]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ImpDeclSpec -> [RdrName]
do_spec ((ImportSpec -> ImpDeclSpec) -> [ImportSpec] -> [ImpDeclSpec]
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 decl_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_name :: GlobalRdrElt -> Name
gre_name = Name
name, gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss } )
| Bool
lcl = Name -> SrcSpan
nameSrcSpan Name
name
| (is :: ImportSpec
is:_) <- [ImportSpec]
iss = ImpDeclSpec -> SrcSpan
is_dloc (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is)
| Bool
otherwise = String -> SDoc -> SrcSpan
forall a. HasCallStack => String -> SDoc -> a
pprPanic "greSrcSpan" (GlobalRdrElt -> SDoc
forall a. Outputable a => a -> SDoc
ppr GlobalRdrElt
gre)
mkParent :: Name -> AvailInfo -> Parent
mkParent :: Name -> AvailInfo -> Parent
mkParent _ (Avail _) = Parent
NoParent
mkParent n :: Name
n (AvailTC m :: Name
m _ _) | Name
n Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
m = Parent
NoParent
| Bool
otherwise = Name -> Parent
ParentIs Name
m
greParent_maybe :: GlobalRdrElt -> Maybe Name
greParent_maybe :: GlobalRdrElt -> Maybe Name
greParent_maybe gre :: GlobalRdrElt
gre = case GlobalRdrElt -> Parent
gre_par GlobalRdrElt
gre of
NoParent -> Maybe Name
forall a. Maybe a
Nothing
ParentIs n :: Name
n -> Name -> Maybe Name
forall a. a -> Maybe a
Just Name
n
FldParent n :: Name
n _ -> Name -> Maybe Name
forall a. a -> Maybe a
Just Name
n
gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo]
gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo]
gresToAvailInfo gres :: [GlobalRdrElt]
gres
= NameEnv AvailInfo -> [AvailInfo]
forall a. NameEnv a -> [a]
nameEnvElts NameEnv AvailInfo
avail_env
where
avail_env :: NameEnv AvailInfo
(avail_env :: NameEnv AvailInfo
avail_env, _) = ((NameEnv AvailInfo, NameSet)
-> GlobalRdrElt -> (NameEnv AvailInfo, NameSet))
-> (NameEnv AvailInfo, NameSet)
-> [GlobalRdrElt]
-> (NameEnv AvailInfo, NameSet)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (NameEnv AvailInfo, NameSet)
-> GlobalRdrElt -> (NameEnv AvailInfo, NameSet)
add (NameEnv AvailInfo
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 (env :: NameEnv AvailInfo
env, done :: NameSet
done) gre :: GlobalRdrElt
gre
| Name
name Name -> NameSet -> Bool
`elemNameSet` NameSet
done
= (NameEnv AvailInfo
env, NameSet
done)
| Bool
otherwise
= ( (GlobalRdrElt -> AvailInfo -> AvailInfo)
-> (GlobalRdrElt -> AvailInfo)
-> NameEnv AvailInfo
-> Name
-> GlobalRdrElt
-> NameEnv AvailInfo
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
gre_name GlobalRdrElt
gre
key :: Name
key = case GlobalRdrElt -> Maybe Name
greParent_maybe GlobalRdrElt
gre of
Just parent :: Name
parent -> Name
parent
Nothing -> GlobalRdrElt -> Name
gre_name GlobalRdrElt
gre
insertChildIntoChildren :: Name -> [Name] -> Name -> [Name]
insertChildIntoChildren :: Name -> [Name] -> Name -> [Name]
insertChildIntoChildren _ [] k :: Name
k = [Name
k]
insertChildIntoChildren p :: Name
p (n :: Name
n:ns :: [Name]
ns) k :: Name
k
| Name
p Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
k = Name
kName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:Name
nName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[Name]
ns
| Bool
otherwise = Name
nName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:Name
kName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[Name]
ns
comb :: GlobalRdrElt -> AvailInfo -> AvailInfo
comb :: GlobalRdrElt -> AvailInfo -> AvailInfo
comb _ (Avail n :: Name
n) = Name -> AvailInfo
Avail Name
n
comb gre :: GlobalRdrElt
gre (AvailTC m :: Name
m ns :: [Name]
ns fls :: [FieldLbl Name]
fls)
= case GlobalRdrElt -> Parent
gre_par GlobalRdrElt
gre of
NoParent -> Name -> [Name] -> [FieldLbl Name] -> AvailInfo
AvailTC Name
m (Name
nameName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[Name]
ns) [FieldLbl Name]
fls
ParentIs {} -> Name -> [Name] -> [FieldLbl Name] -> AvailInfo
AvailTC Name
m (Name -> [Name] -> Name -> [Name]
insertChildIntoChildren Name
m [Name]
ns Name
name) [FieldLbl Name]
fls
FldParent _ mb_lbl :: Maybe FastString
mb_lbl -> Name -> [Name] -> [FieldLbl Name] -> AvailInfo
AvailTC Name
m [Name]
ns (Name -> Maybe FastString -> FieldLbl Name
mkFieldLabel Name
name Maybe FastString
mb_lbl FieldLbl Name -> [FieldLbl Name] -> [FieldLbl Name]
forall a. a -> [a] -> [a]
: [FieldLbl Name]
fls)
availFromGRE :: GlobalRdrElt -> AvailInfo
availFromGRE :: GlobalRdrElt -> AvailInfo
availFromGRE (GRE { gre_name :: GlobalRdrElt -> Name
gre_name = Name
me, gre_par :: GlobalRdrElt -> Parent
gre_par = Parent
parent })
= case Parent
parent of
ParentIs p :: Name
p -> Name -> [Name] -> [FieldLbl Name] -> AvailInfo
AvailTC Name
p [Name
me] []
NoParent | Name -> Bool
isTyConName Name
me -> Name -> [Name] -> [FieldLbl Name] -> AvailInfo
AvailTC Name
me [Name
me] []
| Bool
otherwise -> Name -> AvailInfo
avail Name
me
FldParent p :: Name
p mb_lbl :: Maybe FastString
mb_lbl -> Name -> [Name] -> [FieldLbl Name] -> AvailInfo
AvailTC Name
p [] [Name -> Maybe FastString -> FieldLbl Name
mkFieldLabel Name
me Maybe FastString
mb_lbl]
mkFieldLabel :: Name -> Maybe FastString -> FieldLabel
mkFieldLabel :: Name -> Maybe FastString -> FieldLbl Name
mkFieldLabel me :: Name
me mb_lbl :: Maybe FastString
mb_lbl =
case Maybe FastString
mb_lbl of
Nothing -> FieldLabel :: forall a. FastString -> Bool -> a -> FieldLbl a
FieldLabel { flLabel :: FastString
flLabel = OccName -> FastString
occNameFS (Name -> OccName
nameOccName Name
me)
, flIsOverloaded :: Bool
flIsOverloaded = Bool
False
, flSelector :: Name
flSelector = Name
me }
Just lbl :: FastString
lbl -> FieldLabel :: forall a. FastString -> Bool -> a -> FieldLbl a
FieldLabel { flLabel :: FastString
flLabel = FastString
lbl
, flIsOverloaded :: Bool
flIsOverloaded = Bool
True
, flSelector :: Name
flSelector = Name
me }
emptyGlobalRdrEnv :: GlobalRdrEnv
emptyGlobalRdrEnv :: GlobalRdrEnv
emptyGlobalRdrEnv = GlobalRdrEnv
forall a. OccEnv a
emptyOccEnv
globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts env :: GlobalRdrEnv
env = ([GlobalRdrElt] -> [GlobalRdrElt] -> [GlobalRdrElt])
-> [GlobalRdrElt] -> GlobalRdrEnv -> [GlobalRdrElt]
forall a b. (a -> b -> b) -> b -> OccEnv a -> b
foldOccEnv [GlobalRdrElt] -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. [a] -> [a] -> [a]
(++) [] GlobalRdrEnv
env
instance Outputable GlobalRdrElt where
ppr :: GlobalRdrElt -> SDoc
ppr gre :: GlobalRdrElt
gre = SDoc -> Int -> SDoc -> SDoc
hang (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GlobalRdrElt -> Name
gre_name GlobalRdrElt
gre) SDoc -> SDoc -> SDoc
<+> Parent -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GlobalRdrElt -> Parent
gre_par GlobalRdrElt
gre))
2 (GlobalRdrElt -> SDoc
pprNameProvenance GlobalRdrElt
gre)
pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc
pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc
pprGlobalRdrEnv locals_only :: Bool
locals_only env :: GlobalRdrEnv
env
= [SDoc] -> SDoc
vcat [ String -> SDoc
text "GlobalRdrEnv" SDoc -> SDoc -> SDoc
<+> Bool -> SDoc -> SDoc
ppWhen Bool
locals_only (PtrString -> SDoc
ptext (String -> PtrString
sLit "(locals only)"))
SDoc -> SDoc -> SDoc
<+> SDoc
lbrace
, Int -> SDoc -> SDoc
nest 2 ([SDoc] -> SDoc
vcat [ [GlobalRdrElt] -> SDoc
pp ([GlobalRdrElt] -> [GlobalRdrElt]
remove_locals [GlobalRdrElt]
gre_list) | [GlobalRdrElt]
gre_list <- GlobalRdrEnv -> [[GlobalRdrElt]]
forall a. OccEnv a -> [a]
occEnvElts GlobalRdrEnv
env ]
SDoc -> SDoc -> SDoc
<+> SDoc
rbrace) ]
where
remove_locals :: [GlobalRdrElt] -> [GlobalRdrElt]
remove_locals gres :: [GlobalRdrElt]
gres | Bool
locals_only = (GlobalRdrElt -> Bool) -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. (a -> Bool) -> [a] -> [a]
filter GlobalRdrElt -> Bool
isLocalGRE [GlobalRdrElt]
gres
| Bool
otherwise = [GlobalRdrElt]
gres
pp :: [GlobalRdrElt] -> SDoc
pp [] = SDoc
empty
pp gres :: [GlobalRdrElt]
gres = SDoc -> Int -> SDoc -> SDoc
hang (OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ
SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (String -> SDoc
text "unique" SDoc -> SDoc -> SDoc
<+> Unique -> SDoc
forall a. Outputable a => a -> SDoc
ppr (OccName -> Unique
forall a. Uniquable a => a -> Unique
getUnique OccName
occ))
SDoc -> SDoc -> SDoc
<> SDoc
colon)
2 ([SDoc] -> SDoc
vcat ((GlobalRdrElt -> SDoc) -> [GlobalRdrElt] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map GlobalRdrElt -> SDoc
forall a. Outputable a => a -> SDoc
ppr [GlobalRdrElt]
gres))
where
occ :: OccName
occ = Name -> OccName
nameOccName (GlobalRdrElt -> Name
gre_name ([GlobalRdrElt] -> GlobalRdrElt
forall a. [a] -> a
head [GlobalRdrElt]
gres))
lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt]
lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt]
lookupGlobalRdrEnv env :: GlobalRdrEnv
env occ_name :: OccName
occ_name = case GlobalRdrEnv -> OccName -> Maybe [GlobalRdrElt]
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv GlobalRdrEnv
env OccName
occ_name of
Nothing -> []
Just gres :: [GlobalRdrElt]
gres -> [GlobalRdrElt]
gres
greOccName :: GlobalRdrElt -> OccName
greOccName :: GlobalRdrElt -> OccName
greOccName (GRE{gre_par :: GlobalRdrElt -> Parent
gre_par = FldParent{par_lbl :: Parent -> Maybe FastString
par_lbl = Just lbl :: FastString
lbl}}) = FastString -> OccName
mkVarOccFS FastString
lbl
greOccName gre :: GlobalRdrElt
gre = Name -> OccName
nameOccName (GlobalRdrElt -> Name
gre_name GlobalRdrElt
gre)
lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
lookupGRE_RdrName rdr_name :: RdrName
rdr_name env :: GlobalRdrEnv
env
= case GlobalRdrEnv -> OccName -> Maybe [GlobalRdrElt]
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv GlobalRdrEnv
env (RdrName -> OccName
rdrNameOcc RdrName
rdr_name) of
Nothing -> []
Just gres :: [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 env :: GlobalRdrEnv
env name :: Name
name
= GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
lookupGRE_Name_OccName GlobalRdrEnv
env Name
name (Name -> OccName
nameOccName Name
name)
lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt
lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLbl Name -> Maybe GlobalRdrElt
lookupGRE_FieldLabel env :: GlobalRdrEnv
env fl :: FieldLbl Name
fl
= GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
lookupGRE_Name_OccName GlobalRdrEnv
env (FieldLbl Name -> Name
forall a. FieldLbl a -> a
flSelector FieldLbl Name
fl) (FastString -> OccName
mkVarOccFS (FieldLbl Name -> FastString
forall a. FieldLbl a -> FastString
flLabel FieldLbl Name
fl))
lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
lookupGRE_Name_OccName env :: GlobalRdrEnv
env name :: Name
name occ :: OccName
occ
= case [ GlobalRdrElt
gre | GlobalRdrElt
gre <- GlobalRdrEnv -> OccName -> [GlobalRdrElt]
lookupGlobalRdrEnv GlobalRdrEnv
env OccName
occ
, GlobalRdrElt -> Name
gre_name GlobalRdrElt
gre Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name ] of
[] -> Maybe GlobalRdrElt
forall a. Maybe a
Nothing
[gre :: GlobalRdrElt
gre] -> GlobalRdrElt -> Maybe GlobalRdrElt
forall a. a -> Maybe a
Just GlobalRdrElt
gre
gres :: [GlobalRdrElt]
gres -> String -> SDoc -> Maybe GlobalRdrElt
forall a. HasCallStack => String -> SDoc -> a
pprPanic "lookupGRE_Name_OccName"
(Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name SDoc -> SDoc -> SDoc
$$ OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ SDoc -> SDoc -> SDoc
$$ [GlobalRdrElt] -> 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 env :: GlobalRdrEnv
env name :: Name
name
= case GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
lookupGRE_Name GlobalRdrEnv
env Name
name of
Just gre :: GlobalRdrElt
gre -> [GlobalRdrElt -> Maybe [ModuleName]
qualifier_maybe GlobalRdrElt
gre]
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 = Maybe [ModuleName]
forall a. Maybe a
Nothing
| Bool
otherwise = [ModuleName] -> Maybe [ModuleName]
forall a. a -> Maybe a
Just ([ModuleName] -> Maybe [ModuleName])
-> [ModuleName] -> Maybe [ModuleName]
forall a b. (a -> b) -> a -> b
$ (ImportSpec -> ModuleName) -> [ImportSpec] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map (ImpDeclSpec -> ModuleName
is_as (ImpDeclSpec -> ModuleName)
-> (ImportSpec -> ImpDeclSpec) -> ImportSpec -> ModuleName
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 (GRE {gre_par :: GlobalRdrElt -> Parent
gre_par = FldParent{}}) = Bool
True
isRecFldGRE _ = Bool
False
greLabel :: GlobalRdrElt -> Maybe FieldLabelString
greLabel :: GlobalRdrElt -> Maybe FastString
greLabel (GRE{gre_par :: GlobalRdrElt -> Parent
gre_par = FldParent{par_lbl :: Parent -> Maybe FastString
par_lbl = Just lbl :: FastString
lbl}}) = FastString -> Maybe FastString
forall a. a -> Maybe a
Just FastString
lbl
greLabel (GRE{gre_name :: GlobalRdrElt -> Name
gre_name = Name
n, gre_par :: GlobalRdrElt -> Parent
gre_par = FldParent{}}) = FastString -> Maybe FastString
forall a. a -> Maybe a
Just (OccName -> FastString
occNameFS (Name -> OccName
nameOccName Name
n))
greLabel _ = Maybe FastString
forall a. Maybe a
Nothing
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 = (ImportSpec -> Bool) -> [ImportSpec] -> Bool
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 {}) gres :: [GlobalRdrElt]
gres = (GlobalRdrElt -> Maybe GlobalRdrElt)
-> [GlobalRdrElt] -> [GlobalRdrElt]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe GlobalRdrElt -> Maybe GlobalRdrElt
pickUnqualGRE [GlobalRdrElt]
gres
pickGREs (Qual mod :: ModuleName
mod _) gres :: [GlobalRdrElt]
gres = (GlobalRdrElt -> Maybe GlobalRdrElt)
-> [GlobalRdrElt] -> [GlobalRdrElt]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (ModuleName -> GlobalRdrElt -> Maybe GlobalRdrElt
pickQualGRE ModuleName
mod) [GlobalRdrElt]
gres
pickGREs _ _ = []
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, [ImportSpec] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ImportSpec]
iss' = Maybe GlobalRdrElt
forall a. Maybe a
Nothing
| Bool
otherwise = GlobalRdrElt -> Maybe GlobalRdrElt
forall a. a -> Maybe a
Just (GlobalRdrElt
gre { gre_imp :: [ImportSpec]
gre_imp = [ImportSpec]
iss' })
where
iss' :: [ImportSpec]
iss' = (ImportSpec -> Bool) -> [ImportSpec] -> [ImportSpec]
forall a. (a -> Bool) -> [a] -> [a]
filter ImportSpec -> Bool
unQualSpecOK [ImportSpec]
iss
pickQualGRE :: ModuleName -> GlobalRdrElt -> Maybe GlobalRdrElt
pickQualGRE :: ModuleName -> GlobalRdrElt -> Maybe GlobalRdrElt
pickQualGRE mod :: ModuleName
mod gre :: GlobalRdrElt
gre@(GRE { gre_name :: GlobalRdrElt -> Name
gre_name = Name
n, gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss })
| Bool -> Bool
not Bool
lcl', [ImportSpec] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ImportSpec]
iss' = Maybe GlobalRdrElt
forall a. Maybe a
Nothing
| Bool
otherwise = GlobalRdrElt -> Maybe GlobalRdrElt
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' = (ImportSpec -> Bool) -> [ImportSpec] -> [ImportSpec]
forall a. (a -> Bool) -> [a] -> [a]
filter (ModuleName -> ImportSpec -> Bool
qualSpecOK ModuleName
mod) [ImportSpec]
iss
lcl' :: Bool
lcl' = Bool
lcl Bool -> Bool -> Bool
&& ModuleName -> Name -> Bool
name_is_from ModuleName
mod Name
n
name_is_from :: ModuleName -> Name -> Bool
name_is_from :: ModuleName -> Name -> Bool
name_is_from mod :: ModuleName
mod name :: Name
name = case Name -> Maybe Module
nameModule_maybe Name
name of
Just n_mod :: Module
n_mod -> Module -> ModuleName
moduleName Module
n_mod ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName
mod
Nothing -> Bool
False
pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt,GlobalRdrElt)]
pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)]
pickGREsModExp mod :: ModuleName
mod gres :: [GlobalRdrElt]
gres = (GlobalRdrElt -> Maybe (GlobalRdrElt, GlobalRdrElt))
-> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)]
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 mod :: ModuleName
mod gre :: GlobalRdrElt
gre@(GRE { gre_name :: GlobalRdrElt -> Name
gre_name = Name
n })
| Name -> Bool
isBuiltInSyntax Name
n = Maybe (GlobalRdrElt, GlobalRdrElt)
forall a. Maybe a
Nothing
| Just gre1 :: GlobalRdrElt
gre1 <- ModuleName -> GlobalRdrElt -> Maybe GlobalRdrElt
pickQualGRE ModuleName
mod GlobalRdrElt
gre
, Just gre2 :: GlobalRdrElt
gre2 <- GlobalRdrElt -> Maybe GlobalRdrElt
pickUnqualGRE GlobalRdrElt
gre = (GlobalRdrElt, GlobalRdrElt) -> Maybe (GlobalRdrElt, GlobalRdrElt)
forall a. a -> Maybe a
Just (GlobalRdrElt
gre1, GlobalRdrElt
gre2)
| Bool
otherwise = Maybe (GlobalRdrElt, GlobalRdrElt)
forall a. Maybe a
Nothing
where
plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
plusGlobalRdrEnv env1 :: GlobalRdrEnv
env1 env2 :: GlobalRdrEnv
env2 = ([GlobalRdrElt] -> [GlobalRdrElt] -> [GlobalRdrElt])
-> GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
forall a. (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a
plusOccEnv_C ((GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt])
-> [GlobalRdrElt] -> [GlobalRdrElt] -> [GlobalRdrElt]
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 gres :: [GlobalRdrElt]
gres
= (GlobalRdrElt -> GlobalRdrEnv -> GlobalRdrEnv)
-> GlobalRdrEnv -> [GlobalRdrElt] -> GlobalRdrEnv
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 gre :: GlobalRdrElt
gre env :: GlobalRdrEnv
env = (GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt])
-> (GlobalRdrElt -> [GlobalRdrElt])
-> GlobalRdrEnv
-> OccName
-> GlobalRdrElt
-> GlobalRdrEnv
forall a b.
(a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b
extendOccEnv_Acc GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE GlobalRdrElt -> [GlobalRdrElt]
forall a. a -> [a]
singleton GlobalRdrEnv
env
(GlobalRdrElt -> OccName
greOccName GlobalRdrElt
gre)
GlobalRdrElt
gre
insertGRE :: GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE :: GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE new_g :: GlobalRdrElt
new_g [] = [GlobalRdrElt
new_g]
insertGRE new_g :: GlobalRdrElt
new_g (old_g :: GlobalRdrElt
old_g : old_gs :: [GlobalRdrElt]
old_gs)
| GlobalRdrElt -> Name
gre_name GlobalRdrElt
new_g Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== GlobalRdrElt -> Name
gre_name GlobalRdrElt
old_g
= GlobalRdrElt
new_g GlobalRdrElt -> GlobalRdrElt -> GlobalRdrElt
`plusGRE` GlobalRdrElt
old_g GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. a -> [a] -> [a]
: [GlobalRdrElt]
old_gs
| Bool
otherwise
= GlobalRdrElt
old_g GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. a -> [a] -> [a]
: GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE GlobalRdrElt
new_g [GlobalRdrElt]
old_gs
plusGRE :: GlobalRdrElt -> GlobalRdrElt -> GlobalRdrElt
plusGRE :: GlobalRdrElt -> GlobalRdrElt -> GlobalRdrElt
plusGRE g1 :: GlobalRdrElt
g1 g2 :: GlobalRdrElt
g2
= GRE :: Name -> Parent -> Bool -> [ImportSpec] -> GlobalRdrElt
GRE { gre_name :: Name
gre_name = GlobalRdrElt -> Name
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 [ImportSpec] -> [ImportSpec] -> [ImportSpec]
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 trans_gre :: GlobalRdrElt -> GlobalRdrElt
trans_gre occs :: [OccName]
occs rdr_env :: GlobalRdrEnv
rdr_env
= (OccName -> GlobalRdrEnv -> GlobalRdrEnv)
-> GlobalRdrEnv -> [OccName] -> GlobalRdrEnv
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 occ :: OccName
occ env :: GlobalRdrEnv
env
= case GlobalRdrEnv -> OccName -> Maybe [GlobalRdrElt]
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv GlobalRdrEnv
env OccName
occ of
Just gres :: [GlobalRdrElt]
gres -> GlobalRdrEnv -> OccName -> [GlobalRdrElt] -> GlobalRdrEnv
forall a. OccEnv a -> OccName -> a -> OccEnv a
extendOccEnv GlobalRdrEnv
env OccName
occ ((GlobalRdrElt -> GlobalRdrElt) -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a b. (a -> b) -> [a] -> [b]
map GlobalRdrElt -> GlobalRdrElt
trans_gre [GlobalRdrElt]
gres)
Nothing -> GlobalRdrEnv
env
extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
extendGlobalRdrEnv env :: GlobalRdrEnv
env gre :: GlobalRdrElt
gre
= (GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt])
-> (GlobalRdrElt -> [GlobalRdrElt])
-> GlobalRdrEnv
-> OccName
-> GlobalRdrElt
-> GlobalRdrEnv
forall a b.
(a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b
extendOccEnv_Acc GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE GlobalRdrElt -> [GlobalRdrElt]
forall a. a -> [a]
singleton GlobalRdrEnv
env
(GlobalRdrElt -> OccName
greOccName GlobalRdrElt
gre) GlobalRdrElt
gre
shadowNames :: GlobalRdrEnv -> [Name] -> GlobalRdrEnv
shadowNames :: GlobalRdrEnv -> [Name] -> GlobalRdrEnv
shadowNames = (GlobalRdrEnv -> Name -> GlobalRdrEnv)
-> GlobalRdrEnv -> [Name] -> GlobalRdrEnv
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' GlobalRdrEnv -> Name -> GlobalRdrEnv
shadowName
shadowName :: GlobalRdrEnv -> Name -> GlobalRdrEnv
shadowName :: GlobalRdrEnv -> Name -> GlobalRdrEnv
shadowName env :: GlobalRdrEnv
env name :: Name
name
= (Maybe [GlobalRdrElt] -> Maybe [GlobalRdrElt])
-> GlobalRdrEnv -> OccName -> GlobalRdrEnv
forall elt.
(Maybe elt -> Maybe elt) -> OccEnv elt -> OccName -> OccEnv elt
alterOccEnv (([GlobalRdrElt] -> [GlobalRdrElt])
-> Maybe [GlobalRdrElt] -> Maybe [GlobalRdrElt]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [GlobalRdrElt] -> [GlobalRdrElt]
alter_fn) GlobalRdrEnv
env (Name -> OccName
nameOccName Name
name)
where
alter_fn :: [GlobalRdrElt] -> [GlobalRdrElt]
alter_fn :: [GlobalRdrElt] -> [GlobalRdrElt]
alter_fn gres :: [GlobalRdrElt]
gres = (GlobalRdrElt -> Maybe GlobalRdrElt)
-> [GlobalRdrElt] -> [GlobalRdrElt]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Name -> GlobalRdrElt -> Maybe GlobalRdrElt
shadow_with Name
name) [GlobalRdrElt]
gres
shadow_with :: Name -> GlobalRdrElt -> Maybe GlobalRdrElt
shadow_with :: Name -> GlobalRdrElt -> Maybe GlobalRdrElt
shadow_with new_name :: Name
new_name
old_gre :: GlobalRdrElt
old_gre@(GRE { gre_name :: GlobalRdrElt -> Name
gre_name = Name
old_name, gre_lcl :: GlobalRdrElt -> Bool
gre_lcl = Bool
lcl, gre_imp :: GlobalRdrElt -> [ImportSpec]
gre_imp = [ImportSpec]
iss })
= case Name -> Maybe Module
nameModule_maybe Name
old_name of
Nothing -> GlobalRdrElt -> Maybe GlobalRdrElt
forall a. a -> Maybe a
Just GlobalRdrElt
old_gre
Just old_mod :: Module
old_mod
| Just new_mod :: Module
new_mod <- Name -> Maybe Module
nameModule_maybe Name
new_name
, Module
new_mod Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
old_mod
-> Maybe GlobalRdrElt
forall a. Maybe a
Nothing
| [ImportSpec] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ImportSpec]
iss'
-> Maybe GlobalRdrElt
forall a. Maybe a
Nothing
| Bool
otherwise
-> GlobalRdrElt -> Maybe GlobalRdrElt
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 [ImportSpec] -> [ImportSpec] -> [ImportSpec]
forall a. [a] -> [a] -> [a]
++ (ImportSpec -> Maybe ImportSpec) -> [ImportSpec] -> [ImportSpec]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Name -> ImportSpec -> Maybe ImportSpec
shadow_is Name
new_name) [ImportSpec]
iss
lcl_imp :: [ImportSpec]
lcl_imp | Bool
lcl = [Name -> Module -> ImportSpec
mk_fake_imp_spec Name
old_name Module
old_mod]
| Bool
otherwise = []
mk_fake_imp_spec :: Name -> Module -> ImportSpec
mk_fake_imp_spec old_name :: Name
old_name old_mod :: Module
old_mod
= ImpDeclSpec -> ImpItemSpec -> ImportSpec
ImpSpec ImpDeclSpec
id_spec ImpItemSpec
ImpAll
where
old_mod_name :: ModuleName
old_mod_name = Module -> ModuleName
moduleName Module
old_mod
id_spec :: ImpDeclSpec
id_spec = ImpDeclSpec :: ModuleName -> ModuleName -> Bool -> SrcSpan -> ImpDeclSpec
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 = Name -> SrcSpan
nameSrcSpan Name
old_name }
shadow_is :: Name -> ImportSpec -> Maybe ImportSpec
shadow_is :: Name -> ImportSpec -> Maybe ImportSpec
shadow_is new_name :: Name
new_name is :: ImportSpec
is@(ImpSpec { is_decl :: ImportSpec -> ImpDeclSpec
is_decl = ImpDeclSpec
id_spec })
| Just new_mod :: Module
new_mod <- Name -> Maybe Module
nameModule_maybe Name
new_name
, ImpDeclSpec -> ModuleName
is_as ImpDeclSpec
id_spec ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== Module -> ModuleName
moduleName Module
new_mod
= Maybe ImportSpec
forall a. Maybe a
Nothing
| Bool
otherwise
= ImportSpec -> Maybe ImportSpec
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
(ImportSpec -> ImportSpec -> Bool)
-> (ImportSpec -> ImportSpec -> Bool) -> Eq ImportSpec
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, Eq ImportSpec
Eq ImportSpec =>
(ImportSpec -> ImportSpec -> Ordering)
-> (ImportSpec -> ImportSpec -> Bool)
-> (ImportSpec -> ImportSpec -> Bool)
-> (ImportSpec -> ImportSpec -> Bool)
-> (ImportSpec -> ImportSpec -> Bool)
-> (ImportSpec -> ImportSpec -> ImportSpec)
-> (ImportSpec -> ImportSpec -> ImportSpec)
-> Ord ImportSpec
ImportSpec -> ImportSpec -> Bool
ImportSpec -> ImportSpec -> Ordering
ImportSpec -> ImportSpec -> ImportSpec
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ImportSpec -> ImportSpec -> ImportSpec
$cmin :: ImportSpec -> ImportSpec -> ImportSpec
max :: ImportSpec -> ImportSpec -> ImportSpec
$cmax :: ImportSpec -> ImportSpec -> ImportSpec
>= :: ImportSpec -> ImportSpec -> Bool
$c>= :: ImportSpec -> ImportSpec -> Bool
> :: ImportSpec -> ImportSpec -> Bool
$c> :: ImportSpec -> ImportSpec -> Bool
<= :: ImportSpec -> ImportSpec -> Bool
$c<= :: ImportSpec -> ImportSpec -> Bool
< :: ImportSpec -> ImportSpec -> Bool
$c< :: ImportSpec -> ImportSpec -> Bool
compare :: ImportSpec -> ImportSpec -> Ordering
$ccompare :: ImportSpec -> ImportSpec -> Ordering
$cp1Ord :: Eq ImportSpec
Ord, Typeable ImportSpec
DataType
Constr
Typeable ImportSpec =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImportSpec -> c ImportSpec)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportSpec)
-> (ImportSpec -> Constr)
-> (ImportSpec -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> ImportSpec -> ImportSpec)
-> (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 u. (forall d. Data d => d -> u) -> ImportSpec -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ImportSpec -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec)
-> Data ImportSpec
ImportSpec -> DataType
ImportSpec -> Constr
(forall b. Data b => b -> b) -> ImportSpec -> ImportSpec
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImportSpec -> c ImportSpec
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cImpSpec :: Constr
$tImportSpec :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> ImportSpec -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImportSpec -> u
gmapQ :: (forall d. Data d => d -> u) -> ImportSpec -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ImportSpec -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable 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 Typeable ImpDeclSpec
DataType
Constr
Typeable ImpDeclSpec =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpDeclSpec)
-> (ImpDeclSpec -> Constr)
-> (ImpDeclSpec -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec)
-> (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 u. (forall d. Data d => d -> u) -> ImpDeclSpec -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec)
-> Data ImpDeclSpec
ImpDeclSpec -> DataType
ImpDeclSpec -> Constr
(forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cImpDeclSpec :: Constr
$tImpDeclSpec :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u
gmapQ :: (forall d. Data d => d -> u) -> ImpDeclSpec -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ImpDeclSpec -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable ImpDeclSpec
Data
data ImpItemSpec
= ImpAll
| ImpSome {
ImpItemSpec -> Bool
is_explicit :: Bool,
ImpItemSpec -> SrcSpan
is_iloc :: SrcSpan
}
deriving Typeable ImpItemSpec
DataType
Constr
Typeable ImpItemSpec =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpItemSpec)
-> (ImpItemSpec -> Constr)
-> (ImpItemSpec -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec)
-> (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 u. (forall d. Data d => d -> u) -> ImpItemSpec -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec)
-> Data ImpItemSpec
ImpItemSpec -> DataType
ImpItemSpec -> Constr
(forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cImpSome :: Constr
$cImpAll :: Constr
$tImpItemSpec :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u
gmapQ :: (forall d. Data d => d -> u) -> ImpItemSpec -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ImpItemSpec -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable ImpItemSpec
Data
instance Eq ImpDeclSpec where
p1 :: ImpDeclSpec
p1 == :: ImpDeclSpec -> ImpDeclSpec -> Bool
== p2 :: ImpDeclSpec
p2 = case ImpDeclSpec
p1 ImpDeclSpec -> ImpDeclSpec -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` ImpDeclSpec
p2 of EQ -> Bool
True; _ -> Bool
False
instance Ord ImpDeclSpec where
compare :: ImpDeclSpec -> ImpDeclSpec -> Ordering
compare is1 :: ImpDeclSpec
is1 is2 :: ImpDeclSpec
is2 = (ImpDeclSpec -> ModuleName
is_mod ImpDeclSpec
is1 ModuleName -> ModuleName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` ImpDeclSpec -> ModuleName
is_mod ImpDeclSpec
is2) Ordering -> Ordering -> Ordering
`thenCmp`
(ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
is1 SrcSpan -> SrcSpan -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
is2)
instance Eq ImpItemSpec where
p1 :: ImpItemSpec
p1 == :: ImpItemSpec -> ImpItemSpec -> Bool
== p2 :: ImpItemSpec
p2 = case ImpItemSpec
p1 ImpItemSpec -> ImpItemSpec -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` ImpItemSpec
p2 of EQ -> Bool
True; _ -> Bool
False
instance Ord ImpItemSpec where
compare :: ImpItemSpec -> ImpItemSpec -> Ordering
compare is1 :: ImpItemSpec
is1 is2 :: ImpItemSpec
is2 =
case (ImpItemSpec
is1, ImpItemSpec
is2) of
(ImpAll, ImpAll) -> Ordering
EQ
(ImpAll, _) -> Ordering
GT
(_, ImpAll) -> Ordering
LT
(ImpSome _ l1 :: SrcSpan
l1, ImpSome _ l2 :: SrcSpan
l2) -> SrcSpan
l1 SrcSpan -> SrcSpan -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` SrcSpan
l2
bestImport :: [ImportSpec] -> ImportSpec
bestImport :: [ImportSpec] -> ImportSpec
bestImport iss :: [ImportSpec]
iss
= case (ImportSpec -> ImportSpec -> Ordering)
-> [ImportSpec] -> [ImportSpec]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ImportSpec -> ImportSpec -> Ordering
best [ImportSpec]
iss of
(is :: ImportSpec
is:_) -> ImportSpec
is
[] -> String -> SDoc -> ImportSpec
forall a. HasCallStack => String -> SDoc -> a
pprPanic "bestImport" ([ImportSpec] -> SDoc
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 Bool -> Bool -> Ordering
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`
(ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
d1 SrcSpan -> SrcSpan -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
d2)
best_item :: ImpItemSpec -> ImpItemSpec -> Ordering
best_item :: ImpItemSpec -> ImpItemSpec -> Ordering
best_item ImpAll ImpAll = Ordering
EQ
best_item ImpAll (ImpSome {}) = Ordering
LT
best_item (ImpSome {}) 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 Bool -> Bool -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Bool
e2
unQualSpecOK :: ImportSpec -> Bool
unQualSpecOK :: ImportSpec -> Bool
unQualSpecOK is :: ImportSpec
is = Bool -> Bool
not (ImpDeclSpec -> Bool
is_qual (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is))
qualSpecOK :: ModuleName -> ImportSpec -> Bool
qualSpecOK :: ModuleName -> ImportSpec -> Bool
qualSpecOK mod :: ModuleName
mod is :: ImportSpec
is = ModuleName
mod ModuleName -> ModuleName -> Bool
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 decl :: ImpDeclSpec
decl ImpAll) = ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
decl
importSpecLoc (ImpSpec _ item :: ImpItemSpec
item) = ImpItemSpec -> SrcSpan
is_iloc ImpItemSpec
item
importSpecModule :: ImportSpec -> ModuleName
importSpecModule :: ImportSpec -> ModuleName
importSpecModule is :: ImportSpec
is = ImpDeclSpec -> ModuleName
is_mod (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is)
isExplicitItem :: ImpItemSpec -> Bool
isExplicitItem :: ImpItemSpec -> Bool
isExplicitItem ImpAll = Bool
False
isExplicitItem (ImpSome {is_explicit :: ImpItemSpec -> Bool
is_explicit = Bool
exp}) = Bool
exp
pprNameProvenance :: GlobalRdrElt -> SDoc
pprNameProvenance :: GlobalRdrElt -> SDoc
pprNameProvenance (GRE { gre_name :: GlobalRdrElt -> Name
gre_name = Name
name, 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)
([SDoc] -> SDoc
forall a. [a] -> a
head [SDoc]
pp_provs)
where
pp_provs :: [SDoc]
pp_provs = [SDoc]
pp_lcl [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++ (ImportSpec -> SDoc) -> [ImportSpec] -> [SDoc]
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 "defined at" SDoc -> SDoc -> SDoc
<+> SrcLoc -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Name -> SrcLoc
nameSrcLoc Name
name)]
else []
pp_is :: ImportSpec -> SDoc
pp_is is :: ImportSpec
is = [SDoc] -> SDoc
sep [ImportSpec -> SDoc
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 imp_spec :: ImportSpec
imp_spec name :: Name
name
| Bool
same_module Bool -> Bool -> Bool
&& Bool -> Bool
not (SrcSpan -> Bool
isGoodSrcSpan SrcSpan
loc)
= SDoc
empty
| Bool
otherwise
= SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text "and originally defined" SDoc -> SDoc -> SDoc
<+> SDoc
pp_mod)
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 ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== Module -> ModuleName
moduleName Module
defining_mod
pp_mod :: SDoc
pp_mod | Bool
same_module = SDoc
empty
| Bool
otherwise = String -> SDoc
text "in" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
defining_mod)
instance Outputable ImportSpec where
ppr :: ImportSpec -> SDoc
ppr imp_spec :: ImportSpec
imp_spec
= String -> SDoc
text "imported" SDoc -> SDoc -> SDoc
<+> SDoc
qual
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text "from" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (ModuleName -> SDoc
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 "qualified"
| Bool
otherwise = SDoc
empty
pprLoc :: SrcSpan -> SDoc
pprLoc :: SrcSpan -> SDoc
pprLoc (RealSrcSpan s :: RealSrcSpan
s) = String -> SDoc
text "at" SDoc -> SDoc -> SDoc
<+> RealSrcSpan -> SDoc
forall a. Outputable a => a -> SDoc
ppr RealSrcSpan
s
pprLoc (UnhelpfulSpan {}) = SDoc
empty
starInfo :: Bool -> RdrName -> SDoc
starInfo :: Bool -> RdrName -> SDoc
starInfo star_is_type :: Bool
star_is_type rdr_name :: RdrName
rdr_name =
if Bool
isUnqualStar Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
star_is_type
then String -> SDoc
text "With NoStarIsType, " SDoc -> SDoc -> SDoc
<>
SDoc -> SDoc
quotes (RdrName -> SDoc
forall a. Outputable a => a -> SDoc
ppr RdrName
rdr_name) SDoc -> SDoc -> SDoc
<>
String -> SDoc
text " is treated as a regular type operator. "
SDoc -> SDoc -> SDoc
$$
String -> SDoc
text "Did you mean to use " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (String -> SDoc
text "Type") SDoc -> SDoc -> SDoc
<>
String -> SDoc
text " from Data.Kind instead?"
else SDoc
empty
where
isUnqualStar :: Bool
isUnqualStar
| Unqual occName :: OccName
occName <- RdrName
rdr_name
= let fs :: FastString
fs = OccName -> FastString
occNameFS OccName
occName
in FastString
fs FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
== String -> FastString
fsLit "*" Bool -> Bool -> Bool
|| FastString
fs FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
== String -> FastString
fsLit "★"
| Bool
otherwise = Bool
False