{-
(c) The University of Glasgow 2006
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
-}

{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}

-- |
-- #name_types#
-- GHC uses several kinds of name internally:
--
-- * 'GHC.Types.Name.Occurrence.OccName': see "GHC.Types.Name.Occurrence#name_types"
--
-- * 'GHC.Types.Name.Reader.RdrName' is the type of names that come directly from the parser. They
--   have not yet had their scoping and binding resolved by the renamer and can be
--   thought of to a first approximation as an 'GHC.Types.Name.Occurrence.OccName' with an optional module
--   qualifier
--
-- * 'GHC.Types.Name.Name': see "GHC.Types.Name#name_types"
--
-- * 'GHC.Types.Id.Id': see "GHC.Types.Id#name_types"
--
-- * 'GHC.Types.Var.Var': see "GHC.Types.Var#name_types"

module GHC.Types.Name.Reader (
        -- * The main type
        RdrName(..),    -- Constructors exported only to GHC.Iface.Binary

        -- ** Construction
        mkRdrUnqual, mkRdrQual,
        mkUnqual, mkVarUnqual, mkQual, mkOrig,
        nameRdrName, getRdrName,

        -- ** Destruction
        rdrNameOcc, rdrNameSpace, demoteRdrName, demoteRdrNameTv, promoteRdrName,
        isRdrDataCon, isRdrTyVar, isRdrTc, isQual, isQual_maybe, isUnqual,
        isOrig, isOrig_maybe, isExact, isExact_maybe, isSrcRdrName,

        -- * Local mapping of 'RdrName' to 'Name.Name'
        LocalRdrEnv, emptyLocalRdrEnv, extendLocalRdrEnv, extendLocalRdrEnvList,
        lookupLocalRdrEnv, lookupLocalRdrOcc,
        elemLocalRdrEnv, inLocalRdrEnvScope,
        localRdrEnvElts, minusLocalRdrEnv, minusLocalRdrEnvList,

        -- * Global mapping of 'RdrName' to 'GlobalRdrElt's
        GlobalRdrEnvX, GlobalRdrEnv, IfGlobalRdrEnv,
        emptyGlobalRdrEnv, mkGlobalRdrEnv, plusGlobalRdrEnv,
        extendGlobalRdrEnv, greOccName,
        pprGlobalRdrEnv, globalRdrEnvElts,

        -- ** Looking up 'GlobalRdrElt's
        FieldsOrSelectors(..), filterFieldGREs, allowGRE,

        LookupGRE(..), lookupGRE,
        WhichGREs(.., AllRelevantGREs, RelevantGREsFOS),
        greIsRelevant,
        LookupChild(..),

        lookupGRE_Name,
        lookupGRE_FieldLabel,
        getGRE_NameQualifier_maybes,
        transformGREs, pickGREs, pickGREsModExp,

        -- * GlobalRdrElts
        availFromGRE,
        greRdrNames, greSrcSpan, greQualModName,
        gresToAvailInfo,
        greDefinitionModule, greDefinitionSrcSpan,
        greFieldLabel_maybe,

        -- ** Global 'RdrName' mapping elements: 'GlobalRdrElt', 'Provenance', 'ImportSpec'
        GlobalRdrEltX(..), GlobalRdrElt, IfGlobalRdrElt, FieldGlobalRdrElt,
        greName, greNameSpace, greParent, greInfo,
        plusGRE, insertGRE,
        forceGlobalRdrEnv, hydrateGlobalRdrEnv,
        isLocalGRE, isImportedGRE, isRecFldGRE,
        fieldGREInfo,
        isDuplicateRecFldGRE, isNoFieldSelectorGRE, isFieldSelectorGRE,
        unQualOK, qualSpecOK, unQualSpecOK,
        pprNameProvenance,
        mkGRE, mkExactGRE, mkLocalGRE, mkLocalVanillaGRE, mkLocalTyConGRE,
        mkLocalConLikeGRE, mkLocalFieldGREs,
        gresToNameSet,

        -- ** Shadowing
        greClashesWith, shadowNames,

        -- ** Information attached to a 'GlobalRdrElt'
        ConLikeName(..),
        GREInfo(..), RecFieldInfo(..),
        plusGREInfo,
        recFieldConLike_maybe, recFieldInfo_maybe,
        fieldGRE_maybe, fieldGRELabel,

        -- ** Parent information
        Parent(..), greParent_maybe,
        mkParent, availParent,
        ImportSpec(..), ImpDeclSpec(..), ImpItemSpec(..),
        importSpecLoc, importSpecModule, isExplicitItem, bestImport,

        -- * Utils
        opIsAt
  ) where

import GHC.Prelude

import GHC.Data.Bag
import GHC.Data.FastString
import GHC.Data.Maybe

import GHC.Types.Avail
import GHC.Types.Basic
import GHC.Types.GREInfo
import GHC.Types.FieldLabel
import GHC.Types.Name
import GHC.Types.Name.Env
    ( NameEnv, nonDetNameEnvElts, emptyNameEnv, extendNameEnv_Acc )
import GHC.Types.Name.Set
import GHC.Types.SrcLoc as SrcLoc
import GHC.Types.Unique
import GHC.Types.Unique.FM
import GHC.Types.Unique.Set
import GHC.Builtin.Uniques ( isFldNSUnique )

import GHC.Unit.Module

import GHC.Utils.Misc as Utils
import GHC.Utils.Outputable
import GHC.Utils.Panic

import Control.DeepSeq
import Control.Monad ( guard )
import Data.Data
import Data.List ( sort )
import qualified Data.List.NonEmpty as NE
import qualified Data.Map.Strict as Map
import qualified Data.Semigroup as S
import System.IO.Unsafe ( unsafePerformIO )

{-
************************************************************************
*                                                                      *
\subsection{The main data type}
*                                                                      *
************************************************************************
-}

-- | Reader Name
--
-- Do not use the data constructors of RdrName directly: prefer the family
-- of functions that creates them, such as 'mkRdrUnqual'
--
-- - Note: A Located RdrName will only have API Annotations if it is a
--         compound one,
--   e.g.
--
-- > `bar`
-- > ( ~ )
--
-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnType',
--           'GHC.Parser.Annotation.AnnOpen'  @'('@ or @'['@ or @'[:'@,
--           'GHC.Parser.Annotation.AnnClose' @')'@ or @']'@ or @':]'@,,
--           'GHC.Parser.Annotation.AnnBackquote' @'`'@,
--           'GHC.Parser.Annotation.AnnVal'
--           'GHC.Parser.Annotation.AnnTilde',

-- For details on above see Note [exact print annotations] in "GHC.Parser.Annotation"
data RdrName
  = Unqual OccName
        -- ^ Unqualified  name
        --
        -- Used for ordinary, unqualified occurrences, e.g. @x@, @y@ or @Foo@.
        -- Create such a 'RdrName' with 'mkRdrUnqual'

  | Qual ModuleName OccName
        -- ^ Qualified name
        --
        -- A qualified name written by the user in
        -- /source/ code.  The module isn't necessarily
        -- the module where the thing is defined;
        -- just the one from which it is imported.
        -- Examples are @Bar.x@, @Bar.y@ or @Bar.Foo@.
        -- Create such a 'RdrName' with 'mkRdrQual'

  | Orig Module OccName
        -- ^ Original name
        --
        -- An original name; the module is the /defining/ module.
        -- This is used when GHC generates code that will be fed
        -- into the renamer (e.g. from deriving clauses), but where
        -- we want to say \"Use Prelude.map dammit\". One of these
        -- can be created with 'mkOrig'

  | Exact Name
        -- ^ Exact name
        --
        -- We know exactly the 'Name'. This is used:
        --
        --  (1) When the parser parses built-in syntax like @[]@
        --      and @(,)@, but wants a 'RdrName' from it
        --
        --  (2) By Template Haskell, when TH has generated a unique name
        --
        -- Such a 'RdrName' can be created by using 'getRdrName' on a 'Name'
  deriving Typeable RdrName
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 -> Constr
RdrName -> DataType
(forall b. Data b => b -> b) -> RdrName -> RdrName
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> RdrName -> u
forall u. (forall d. Data d => d -> u) -> RdrName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RdrName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RdrName -> c RdrName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RdrName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RdrName -> c RdrName
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RdrName -> c RdrName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RdrName
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RdrName
$ctoConstr :: RdrName -> Constr
toConstr :: RdrName -> Constr
$cdataTypeOf :: RdrName -> DataType
dataTypeOf :: RdrName -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RdrName)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RdrName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName)
$cgmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName
gmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RdrName -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RdrName -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RdrName -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RdrName -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RdrName -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RdrName -> m RdrName
Data

{-
************************************************************************
*                                                                      *
\subsection{Simple functions}
*                                                                      *
************************************************************************
-}

instance HasOccName RdrName where
  occName :: RdrName -> OccName
occName = RdrName -> OccName
rdrNameOcc

rdrNameOcc :: RdrName -> OccName
rdrNameOcc :: RdrName -> OccName
rdrNameOcc (Qual ModuleName
_ OccName
occ) = OccName
occ
rdrNameOcc (Unqual OccName
occ) = OccName
occ
rdrNameOcc (Orig Module
_ OccName
occ) = OccName
occ
rdrNameOcc (Exact Name
name) = Name -> OccName
nameOccName Name
name

rdrNameSpace :: RdrName -> NameSpace
rdrNameSpace :: RdrName -> NameSpace
rdrNameSpace = OccName -> NameSpace
occNameSpace (OccName -> NameSpace)
-> (RdrName -> OccName) -> RdrName -> NameSpace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RdrName -> OccName
rdrNameOcc

-- demoteRdrName lowers the NameSpace of RdrName.
-- See Note [Demotion] in GHC.Rename.Env
demoteRdrName :: RdrName -> Maybe RdrName
demoteRdrName :: RdrName -> Maybe RdrName
demoteRdrName (Unqual OccName
occ) = (OccName -> RdrName) -> Maybe OccName -> Maybe RdrName
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OccName -> RdrName
Unqual (OccName -> Maybe OccName
demoteOccName OccName
occ)
demoteRdrName (Qual ModuleName
m OccName
occ) = (OccName -> RdrName) -> Maybe OccName -> Maybe RdrName
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ModuleName -> OccName -> RdrName
Qual ModuleName
m) (OccName -> Maybe OccName
demoteOccName OccName
occ)
demoteRdrName (Orig Module
_ OccName
_) = Maybe RdrName
forall a. Maybe a
Nothing
demoteRdrName (Exact Name
_) = Maybe RdrName
forall a. Maybe a
Nothing

demoteRdrNameTv :: RdrName -> Maybe RdrName
demoteRdrNameTv :: RdrName -> Maybe RdrName
demoteRdrNameTv (Unqual OccName
occ) = (OccName -> RdrName) -> Maybe OccName -> Maybe RdrName
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OccName -> RdrName
Unqual (OccName -> Maybe OccName
demoteOccTvName OccName
occ)
demoteRdrNameTv (Qual ModuleName
m OccName
occ) = (OccName -> RdrName) -> Maybe OccName -> Maybe RdrName
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ModuleName -> OccName -> RdrName
Qual ModuleName
m) (OccName -> Maybe OccName
demoteOccTvName OccName
occ)
demoteRdrNameTv (Orig Module
_ OccName
_) = Maybe RdrName
forall a. Maybe a
Nothing
demoteRdrNameTv (Exact Name
_) = Maybe RdrName
forall a. Maybe a
Nothing

-- promoteRdrName promotes the NameSpace of RdrName.
-- See Note [Promotion] in GHC.Rename.Env.
promoteRdrName :: RdrName -> Maybe RdrName
promoteRdrName :: RdrName -> Maybe RdrName
promoteRdrName (Unqual OccName
occ) = (OccName -> RdrName) -> Maybe OccName -> Maybe RdrName
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap OccName -> RdrName
Unqual (OccName -> Maybe OccName
promoteOccName OccName
occ)
promoteRdrName (Qual ModuleName
m OccName
occ) = (OccName -> RdrName) -> Maybe OccName -> Maybe RdrName
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ModuleName -> OccName -> RdrName
Qual ModuleName
m) (OccName -> Maybe OccName
promoteOccName OccName
occ)
promoteRdrName (Orig Module
_ OccName
_) = Maybe RdrName
forall a. Maybe a
Nothing
promoteRdrName (Exact Name
_)  = Maybe RdrName
forall a. Maybe a
Nothing

        -- These two are the basic constructors
mkRdrUnqual :: OccName -> RdrName
mkRdrUnqual :: OccName -> RdrName
mkRdrUnqual OccName
occ = OccName -> RdrName
Unqual OccName
occ

mkRdrQual :: ModuleName -> OccName -> RdrName
mkRdrQual :: ModuleName -> OccName -> RdrName
mkRdrQual ModuleName
mod OccName
occ = ModuleName -> OccName -> RdrName
Qual ModuleName
mod OccName
occ

mkOrig :: Module -> OccName -> RdrName
mkOrig :: Module -> OccName -> RdrName
mkOrig Module
mod OccName
occ = Module -> OccName -> RdrName
Orig Module
mod OccName
occ

---------------
        -- These two are used when parsing source files
        -- They do encode the module and occurrence names
mkUnqual :: NameSpace -> FastString -> RdrName
mkUnqual :: NameSpace -> FastString -> RdrName
mkUnqual NameSpace
sp FastString
n = OccName -> RdrName
Unqual (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
sp FastString
n)

mkVarUnqual :: FastString -> RdrName
mkVarUnqual :: FastString -> RdrName
mkVarUnqual FastString
n = OccName -> RdrName
Unqual (FastString -> OccName
mkVarOccFS FastString
n)

-- | Make a qualified 'RdrName' in the given namespace and where the 'ModuleName' and
-- the 'OccName' are taken from the first and second elements of the tuple respectively
mkQual :: NameSpace -> (FastString, FastString) -> RdrName
mkQual :: NameSpace -> (FastString, FastString) -> RdrName
mkQual NameSpace
sp (FastString
m, FastString
n) = ModuleName -> OccName -> RdrName
Qual (FastString -> ModuleName
mkModuleNameFS FastString
m) (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
sp FastString
n)

getRdrName :: NamedThing thing => thing -> RdrName
getRdrName :: forall thing. NamedThing thing => thing -> RdrName
getRdrName thing
name = Name -> RdrName
nameRdrName (thing -> Name
forall a. NamedThing a => a -> Name
getName thing
name)

nameRdrName :: Name -> RdrName
nameRdrName :: Name -> RdrName
nameRdrName Name
name = Name -> RdrName
Exact Name
name
-- Keep the Name even for Internal names, so that the
-- unique is still there for debug printing, particularly
-- of Types (which are converted to IfaceTypes before printing)

nukeExact :: Name -> RdrName
nukeExact :: Name -> RdrName
nukeExact Name
n
  | Name -> Bool
isExternalName Name
n = Module -> OccName -> RdrName
Orig ((() :: Constraint) => 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 RdrName
rn = OccName -> Bool
isDataOcc (RdrName -> OccName
rdrNameOcc RdrName
rn)
isRdrTyVar :: RdrName -> Bool
isRdrTyVar   RdrName
rn = OccName -> Bool
isTvOcc   (RdrName -> OccName
rdrNameOcc RdrName
rn)
isRdrTc :: RdrName -> Bool
isRdrTc      RdrName
rn = OccName -> Bool
isTcOcc   (RdrName -> OccName
rdrNameOcc RdrName
rn)

isSrcRdrName :: RdrName -> Bool
isSrcRdrName :: RdrName -> Bool
isSrcRdrName (Unqual OccName
_) = Bool
True
isSrcRdrName (Qual ModuleName
_ OccName
_) = Bool
True
isSrcRdrName RdrName
_          = Bool
False

isUnqual :: RdrName -> Bool
isUnqual :: RdrName -> Bool
isUnqual (Unqual OccName
_) = Bool
True
isUnqual RdrName
_          = Bool
False

isQual :: RdrName -> Bool
isQual :: RdrName -> Bool
isQual (Qual ModuleName
_ OccName
_) = Bool
True
isQual RdrName
_          = Bool
False

isQual_maybe :: RdrName -> Maybe (ModuleName, OccName)
isQual_maybe :: RdrName -> Maybe (ModuleName, OccName)
isQual_maybe (Qual ModuleName
m OccName
n) = (ModuleName, OccName) -> Maybe (ModuleName, OccName)
forall a. a -> Maybe a
Just (ModuleName
m,OccName
n)
isQual_maybe RdrName
_          = Maybe (ModuleName, OccName)
forall a. Maybe a
Nothing

isOrig :: RdrName -> Bool
isOrig :: RdrName -> Bool
isOrig (Orig Module
_ OccName
_) = Bool
True
isOrig RdrName
_          = Bool
False

isOrig_maybe :: RdrName -> Maybe (Module, OccName)
isOrig_maybe :: RdrName -> Maybe (Module, OccName)
isOrig_maybe (Orig Module
m OccName
n) = (Module, OccName) -> Maybe (Module, OccName)
forall a. a -> Maybe a
Just (Module
m,OccName
n)
isOrig_maybe RdrName
_          = Maybe (Module, OccName)
forall a. Maybe a
Nothing

isExact :: RdrName -> Bool
isExact :: RdrName -> Bool
isExact (Exact Name
_) = Bool
True
isExact RdrName
_         = Bool
False

isExact_maybe :: RdrName -> Maybe Name
isExact_maybe :: RdrName -> Maybe Name
isExact_maybe (Exact Name
n) = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
n
isExact_maybe RdrName
_         = Maybe Name
forall a. Maybe a
Nothing

{-
************************************************************************
*                                                                      *
\subsection{Instances}
*                                                                      *
************************************************************************
-}

instance Outputable RdrName where
    ppr :: RdrName -> SDoc
ppr (Exact Name
name)   = Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name
    ppr (Unqual OccName
occ)   = OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ
    ppr (Qual ModuleName
mod OccName
occ) = ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
dot SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ
    ppr (Orig Module
mod OccName
occ) = (PprStyle -> SDoc) -> SDoc
getPprStyle (\PprStyle
sty -> PprStyle -> Module -> OccName -> SDoc
pprModulePrefix PprStyle
sty Module
mod OccName
occ SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ)

instance OutputableBndr RdrName where
    pprBndr :: BindingSite -> RdrName -> SDoc
pprBndr BindingSite
_ RdrName
n
        | OccName -> Bool
isTvOcc (RdrName -> OccName
rdrNameOcc RdrName
n) = Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'@' SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> 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  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 RdrName
rdr
      | Just Name
name <- RdrName -> Maybe Name
isExact_maybe RdrName
rdr = Name -> SDoc
forall a. NamedThing a => a -> SDoc
pprPrefixName Name
name
             -- pprPrefixName has some special cases, so
             -- we delegate to them rather than reproduce them
      | 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 Name
n1)    == :: RdrName -> RdrName -> Bool
== (Exact Name
n2)    = Name
n1Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
==Name
n2
        -- Convert exact to orig
    (Exact Name
n1)    == r2 :: RdrName
r2@(Orig Module
_ OccName
_) = Name -> RdrName
nukeExact Name
n1 RdrName -> RdrName -> Bool
forall a. Eq a => a -> a -> Bool
== RdrName
r2
    r1 :: RdrName
r1@(Orig Module
_ OccName
_) == (Exact Name
n2)    = RdrName
r1 RdrName -> RdrName -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> RdrName
nukeExact Name
n2

    (Orig Module
m1 OccName
o1)  == (Orig Module
m2 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 ModuleName
m1 OccName
o1)  == (Qual ModuleName
m2 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 OccName
o1)   == (Unqual OccName
o2)   = OccName
o1OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
==OccName
o2
    RdrName
_             == RdrName
_             = Bool
False

instance Ord RdrName where
    RdrName
a <= :: RdrName -> RdrName -> Bool
<= RdrName
b = case (RdrName
a RdrName -> RdrName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { Ordering
LT -> Bool
True;  Ordering
EQ -> Bool
True;  Ordering
GT -> Bool
False }
    RdrName
a < :: RdrName -> RdrName -> Bool
<  RdrName
b = case (RdrName
a RdrName -> RdrName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { Ordering
LT -> Bool
True;  Ordering
EQ -> Bool
False; Ordering
GT -> Bool
False }
    RdrName
a >= :: RdrName -> RdrName -> Bool
>= RdrName
b = case (RdrName
a RdrName -> RdrName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { Ordering
LT -> Bool
False; Ordering
EQ -> Bool
True;  Ordering
GT -> Bool
True  }
    RdrName
a > :: RdrName -> RdrName -> Bool
>  RdrName
b = case (RdrName
a RdrName -> RdrName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` RdrName
b) of { Ordering
LT -> Bool
False; Ordering
EQ -> Bool
False; Ordering
GT -> Bool
True  }

        -- Exact < Unqual < Qual < Orig
        -- [Note: Apr 2004] We used to use nukeExact to convert Exact to Orig
        --      before comparing so that Prelude.map == the exact Prelude.map, but
        --      that meant that we reported duplicates when renaming bindings
        --      generated by Template Haskell; e.g
        --      do { n1 <- newName "foo"; n2 <- newName "foo";
        --           <decl involving n1,n2> }
        --      I think we can do without this conversion
    compare :: RdrName -> RdrName -> Ordering
compare (Exact Name
n1) (Exact Name
n2) = Name
n1 Name -> Name -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Name
n2
    compare (Exact Name
_)  RdrName
_          = Ordering
LT

    compare (Unqual OccName
_)   (Exact Name
_)    = Ordering
GT
    compare (Unqual OccName
o1)  (Unqual  OccName
o2) = OccName
o1 OccName -> OccName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` OccName
o2
    compare (Unqual OccName
_)   RdrName
_            = Ordering
LT

    compare (Qual ModuleName
_ OccName
_)   (Exact Name
_)    = Ordering
GT
    compare (Qual ModuleName
_ OccName
_)   (Unqual OccName
_)   = Ordering
GT
    compare (Qual ModuleName
m1 OccName
o1) (Qual ModuleName
m2 OccName
o2) = OccName -> OccName -> Ordering
forall a. Ord a => a -> a -> Ordering
compare OccName
o1 OccName
o2 Ordering -> Ordering -> Ordering
forall a. Semigroup a => a -> a -> a
S.<> ModuleName -> ModuleName -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ModuleName
m1 ModuleName
m2
    compare (Qual ModuleName
_ OccName
_)   (Orig Module
_ OccName
_)   = Ordering
LT

    compare (Orig Module
m1 OccName
o1) (Orig Module
m2 OccName
o2) = OccName -> OccName -> Ordering
forall a. Ord a => a -> a -> Ordering
compare OccName
o1 OccName
o2 Ordering -> Ordering -> Ordering
forall a. Semigroup a => a -> a -> a
S.<> Module -> Module -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Module
m1 Module
m2
    compare (Orig Module
_ OccName
_)   RdrName
_            = Ordering
GT

{-
************************************************************************
*                                                                      *
                        LocalRdrEnv
*                                                                      *
************************************************************************
-}

{- Note [LocalRdrEnv]
~~~~~~~~~~~~~~~~~~~~~
The LocalRdrEnv is used to store local bindings (let, where, lambda, case).

* It is keyed by OccName, because we never use it for qualified names.

* It maps the OccName to a Name.  That Name is almost always an
  Internal Name, but (hackily) it can be External too for top-level
  pattern bindings.  See Note [bindLocalNames for an External name]
  in GHC.Rename.Pat

* We keep the current mapping (lre_env), *and* the set of all Names in
  scope (lre_in_scope).  Reason: see Note [Splicing Exact names] in
  GHC.Rename.Env.
-}

-- | Local Reader Environment
-- See Note [LocalRdrEnv]
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
forall doc. IsLine doc => String -> doc
text String
"LocalRdrEnv {")
         Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"env =" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Name -> SDoc) -> OccEnv Name -> SDoc
forall a. (a -> SDoc) -> OccEnv a -> SDoc
pprOccEnv Name -> SDoc
ppr_elt OccEnv Name
env
                 , String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"in_scope ="
                    SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> UniqFM Name Name -> ([Name] -> SDoc) -> SDoc
forall key a. UniqFM key a -> ([a] -> SDoc) -> SDoc
pprUFM (NameSet -> UniqFM Name Name
forall a. UniqSet a -> UniqFM a a
getUniqSet NameSet
ns) (SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
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
forall doc. IsLine doc => doc -> doc -> doc
<+> Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'}')
    where
      ppr_elt :: Name -> SDoc
ppr_elt Name
name = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Name -> OccName
nameOccName Name
name)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name
                     -- So we can see if the keys line up correctly

emptyLocalRdrEnv :: LocalRdrEnv
emptyLocalRdrEnv :: LocalRdrEnv
emptyLocalRdrEnv = 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
-- See Note [LocalRdrEnv]
extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv
extendLocalRdrEnv lre :: LocalRdrEnv
lre@(LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env, lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns }) Name
name
  = LocalRdrEnv
lre { lre_env      = extendOccEnv env (nameOccName name) name
        , lre_in_scope = extendNameSet ns name }

extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv
-- See Note [LocalRdrEnv]
extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv
extendLocalRdrEnvList lre :: LocalRdrEnv
lre@(LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env, lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns }) [Name]
names
  = LocalRdrEnv
lre { lre_env = extendOccEnvList env [(nameOccName n, n) | n <- names]
        , lre_in_scope = extendNameSetList ns names }

lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name
lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name
lookupLocalRdrEnv (LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env, lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns }) RdrName
rdr
  | Unqual OccName
occ <- RdrName
rdr
  = OccEnv Name -> OccName -> Maybe Name
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv Name
env OccName
occ

  -- See Note [Local bindings with Exact Names]
  | Exact 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 }) 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 RdrName
rdr_name (LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env, lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns })
  = case RdrName
rdr_name of
      Unqual OccName
occ -> OccName
occ  OccName -> OccEnv Name -> Bool
forall a. OccName -> OccEnv a -> Bool
`elemOccEnv` OccEnv Name
env
      Exact Name
name -> Name
name Name -> NameSet -> Bool
`elemNameSet` NameSet
ns  -- See Note [Local bindings with Exact Names]
      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]
nonDetOccEnvElts OccEnv Name
env

inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool
-- This is the point of the NameSet
inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool
inLocalRdrEnvScope Name
name (LRE { lre_in_scope :: LocalRdrEnv -> NameSet
lre_in_scope = NameSet
ns }) = Name
name Name -> NameSet -> Bool
`elemNameSet` NameSet
ns

minusLocalRdrEnv :: LocalRdrEnv -> OccEnv a -> LocalRdrEnv
minusLocalRdrEnv :: forall a. LocalRdrEnv -> OccEnv a -> LocalRdrEnv
minusLocalRdrEnv lre :: LocalRdrEnv
lre@(LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env }) OccEnv a
occs
  = LocalRdrEnv
lre { lre_env = minusOccEnv env occs }

minusLocalRdrEnvList :: LocalRdrEnv -> [OccName] -> LocalRdrEnv
minusLocalRdrEnvList :: LocalRdrEnv -> [OccName] -> LocalRdrEnv
minusLocalRdrEnvList lre :: LocalRdrEnv
lre@(LRE { lre_env :: LocalRdrEnv -> OccEnv Name
lre_env = OccEnv Name
env }) [OccName]
occs
  = LocalRdrEnv
lre { lre_env = delListFromOccEnv env occs }

{-
Note [Local bindings with Exact Names]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
With Template Haskell we can make local bindings that have Exact Names.
Computing shadowing etc may use elemLocalRdrEnv (at least it certainly
does so in GHC.Rename.HsType.bindHsQTyVars), so for an Exact Name we must consult
the in-scope-name-set.


************************************************************************
*                                                                      *
                        GlobalRdrEnv
*                                                                      *
************************************************************************
-}

-- | Global Reader Environment
type GlobalRdrEnv = GlobalRdrEnvX GREInfo
-- ^ Keyed by 'OccName'; when looking up a qualified name
-- we look up the 'OccName' part, and then check the 'Provenance'
-- to see if the appropriate qualification is valid.  This
-- saves routinely doubling the size of the env by adding both
-- qualified and unqualified names to the domain.
--
-- The list in the codomain is required because there may be name clashes
-- These only get reported on lookup, not on construction
--
-- INVARIANT 1: All the members of the list have distinct
--              'gre_name' fields; that is, no duplicate Names
--
-- INVARIANT 2: Imported provenance => Name is an ExternalName
--              However LocalDefs can have an InternalName.  This
--              happens only when type-checking a [d| ... |] Template
--              Haskell quotation; see this note in GHC.Rename.Names
--              Note [Top-level Names in Template Haskell decl quotes]
--
-- INVARIANT 3: If the GlobalRdrEnv maps [occ -> gre], then
--                 greOccName gre = occ

-- | A 'GlobalRdrEnv' in which the 'GlobalRdrElt's don't have any 'GREInfo'
-- attached to them. This is useful to avoid space leaks, see Note [IfGlobalRdrEnv].
type IfGlobalRdrEnv = GlobalRdrEnvX ()

-- | Parametrises 'GlobalRdrEnv' over the presence or absence of 'GREInfo'.
--
-- See Note [IfGlobalRdrEnv].
type GlobalRdrEnvX info = OccEnv [GlobalRdrEltX info]

-- | Global Reader Element
--
-- Something in scope in the renamer; usually a member of the 'GlobalRdrEnv'.
-- See Note [GlobalRdrElt provenance].

type GlobalRdrElt   = GlobalRdrEltX GREInfo

-- | A 'GlobalRdrElt' in which we stripped out the 'GREInfo' field,
-- in order to avoid space leaks.
--
-- See Note [IfGlobalRdrEnv].
type IfGlobalRdrElt = GlobalRdrEltX ()

-- | Global Reader Element
--
-- Something in scope in the renamer; usually a member of the 'GlobalRdrEnv'.
-- See Note [GlobalRdrElt provenance].
--
-- Why do we parametrise over the 'gre_info' field? See Note [IfGlobalRdrEnv].
data GlobalRdrEltX info
  = GRE { forall info. GlobalRdrEltX info -> Name
gre_name :: !Name
        , forall info. GlobalRdrEltX info -> Parent
gre_par  :: !Parent            -- ^ See Note [Parents]
        , forall info. GlobalRdrEltX info -> Bool
gre_lcl  :: !Bool              -- ^ True <=> the thing was defined locally
        , forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp  :: !(Bag ImportSpec)  -- ^ In scope through these imports
  -- See Note [GlobalRdrElt provenance] for the relation between gre_lcl and gre_imp.

        , forall info. GlobalRdrEltX info -> info
gre_info :: info
            -- ^ Information the renamer knows about this particular 'Name'.
            --
            -- Careful about forcing this field! Forcing it can trigger
            -- the loading of interface files.
            --
            -- Note [Retrieving the GREInfo from interfaces] in GHC.Types.GREInfo.
    } deriving (Typeable (GlobalRdrEltX info)
Typeable (GlobalRdrEltX info) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> GlobalRdrEltX info
 -> c (GlobalRdrEltX info))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (GlobalRdrEltX info))
-> (GlobalRdrEltX info -> Constr)
-> (GlobalRdrEltX info -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (GlobalRdrEltX info)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (GlobalRdrEltX info)))
-> ((forall b. Data b => b -> b)
    -> GlobalRdrEltX info -> GlobalRdrEltX info)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> GlobalRdrEltX info -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> GlobalRdrEltX info -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> GlobalRdrEltX info -> m (GlobalRdrEltX info))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> GlobalRdrEltX info -> m (GlobalRdrEltX info))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> GlobalRdrEltX info -> m (GlobalRdrEltX info))
-> Data (GlobalRdrEltX info)
GlobalRdrEltX info -> Constr
GlobalRdrEltX info -> DataType
(forall b. Data b => b -> b)
-> GlobalRdrEltX info -> GlobalRdrEltX info
forall info. Data info => Typeable (GlobalRdrEltX info)
forall info. Data info => GlobalRdrEltX info -> Constr
forall info. Data info => GlobalRdrEltX info -> DataType
forall info.
Data info =>
(forall b. Data b => b -> b)
-> GlobalRdrEltX info -> GlobalRdrEltX info
forall info u.
Data info =>
Int -> (forall d. Data d => d -> u) -> GlobalRdrEltX info -> u
forall info u.
Data info =>
(forall d. Data d => d -> u) -> GlobalRdrEltX info -> [u]
forall info r r'.
Data info =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r
forall info r r'.
Data info =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r
forall info (m :: * -> *).
(Data info, Monad m) =>
(forall d. Data d => d -> m d)
-> GlobalRdrEltX info -> m (GlobalRdrEltX info)
forall info (m :: * -> *).
(Data info, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> GlobalRdrEltX info -> m (GlobalRdrEltX info)
forall info (c :: * -> *).
Data info =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GlobalRdrEltX info)
forall info (c :: * -> *).
Data info =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> GlobalRdrEltX info
-> c (GlobalRdrEltX info)
forall info (t :: * -> *) (c :: * -> *).
(Data info, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (GlobalRdrEltX info))
forall info (t :: * -> * -> *) (c :: * -> *).
(Data info, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GlobalRdrEltX info))
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) -> GlobalRdrEltX info -> u
forall u. (forall d. Data d => d -> u) -> GlobalRdrEltX info -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> GlobalRdrEltX info -> m (GlobalRdrEltX info)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GlobalRdrEltX info -> m (GlobalRdrEltX info)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GlobalRdrEltX info)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> GlobalRdrEltX info
-> c (GlobalRdrEltX info)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (GlobalRdrEltX info))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GlobalRdrEltX info))
$cgfoldl :: forall info (c :: * -> *).
Data info =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> GlobalRdrEltX info
-> c (GlobalRdrEltX info)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> GlobalRdrEltX info
-> c (GlobalRdrEltX info)
$cgunfold :: forall info (c :: * -> *).
Data info =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GlobalRdrEltX info)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GlobalRdrEltX info)
$ctoConstr :: forall info. Data info => GlobalRdrEltX info -> Constr
toConstr :: GlobalRdrEltX info -> Constr
$cdataTypeOf :: forall info. Data info => GlobalRdrEltX info -> DataType
dataTypeOf :: GlobalRdrEltX info -> DataType
$cdataCast1 :: forall info (t :: * -> *) (c :: * -> *).
(Data info, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (GlobalRdrEltX info))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (GlobalRdrEltX info))
$cdataCast2 :: forall info (t :: * -> * -> *) (c :: * -> *).
(Data info, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GlobalRdrEltX info))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GlobalRdrEltX info))
$cgmapT :: forall info.
Data info =>
(forall b. Data b => b -> b)
-> GlobalRdrEltX info -> GlobalRdrEltX info
gmapT :: (forall b. Data b => b -> b)
-> GlobalRdrEltX info -> GlobalRdrEltX info
$cgmapQl :: forall info r r'.
Data info =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r
$cgmapQr :: forall info r r'.
Data info =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r
$cgmapQ :: forall info u.
Data info =>
(forall d. Data d => d -> u) -> GlobalRdrEltX info -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> GlobalRdrEltX info -> [u]
$cgmapQi :: forall info u.
Data info =>
Int -> (forall d. Data d => d -> u) -> GlobalRdrEltX info -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> GlobalRdrEltX info -> u
$cgmapM :: forall info (m :: * -> *).
(Data info, Monad m) =>
(forall d. Data d => d -> m d)
-> GlobalRdrEltX info -> m (GlobalRdrEltX info)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> GlobalRdrEltX info -> m (GlobalRdrEltX info)
$cgmapMp :: forall info (m :: * -> *).
(Data info, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> GlobalRdrEltX info -> m (GlobalRdrEltX info)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GlobalRdrEltX info -> m (GlobalRdrEltX info)
$cgmapMo :: forall info (m :: * -> *).
(Data info, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> GlobalRdrEltX info -> m (GlobalRdrEltX info)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GlobalRdrEltX info -> m (GlobalRdrEltX info)
Data)

instance NFData a => NFData (GlobalRdrEltX a) where
  rnf :: GlobalRdrEltX a -> ()
rnf (GRE Name
name Parent
par Bool
_ Bag ImportSpec
imp a
info) = Name -> ()
forall a. NFData a => a -> ()
rnf Name
name () -> () -> ()
forall a b. a -> b -> b
`seq` Parent -> ()
forall a. NFData a => a -> ()
rnf Parent
par () -> () -> ()
forall a b. a -> b -> b
`seq` Bag ImportSpec -> ()
forall a. NFData a => a -> ()
rnf Bag ImportSpec
imp () -> () -> ()
forall a b. a -> b -> b
`seq` a -> ()
forall a. NFData a => a -> ()
rnf a
info


{- Note [IfGlobalRdrEnv]
~~~~~~~~~~~~~~~~~~~~~~~~
Information pertinent to the renamer about a 'Name' is stored in the fields of
'GlobalRdrElt'. The 'gre_info' field, described in Note [GREInfo] in GHC.Types.GREInfo,
is a bit special: as Note [Retrieving the GREInfo from interfaces] in GHC.Types.GREInfo
describes, for imported 'Name's it is usually obtained by a look up in a type environment,
and forcing can cause the interface file for the module defining the 'Name' to be
loaded. As described in Note [Forcing GREInfo] in GHC.Types.GREInfo, keeping it
a thunk can cause space leaks, while forcing it can cause extra work to be done.
So it's best to discard it when we don't need it, for example when we are about
to store it in a 'ModIface'.

We thus parametrise 'GlobalRdrElt' (and 'GlobalRdrEnv') over the presence or
absence of the 'GREInfo' field.

  - When we are about to stash the 'GlobalRdrElt' in a long-lived data structure,
    e.g. a 'ModIface', we force it by setting all the 'GREInfo' fields to '()'.
    See 'forceGlobalRdrEnv'.
  - To go back the other way, we use 'hydrateGlobalRdrEnv', which sets the
    'gre_info' fields back to lazy lookups.

This parametrisation also helps ensure that we don't accidentally force the
GREInfo field (which can cause unnecessary loading of interface files).
In particular, the 'lookupGRE' function is statically guaranteed to not consult
the 'GREInfo' field when using 'SameNameSpace', which is important
as we sometimes need to use this function with an 'IfaceGlobalRdrEnv' in which
the 'GREInfo' fields have been stripped.
-}

-- | A 'FieldGlobalRdrElt' is a 'GlobalRdrElt'
-- in which the 'gre_info' field is 'IAmRecField'.
type FieldGlobalRdrElt = GlobalRdrElt

greName :: GlobalRdrEltX info -> Name
greName :: forall info. GlobalRdrEltX info -> Name
greName = GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
gre_name

greNameSpace :: GlobalRdrEltX info -> NameSpace
greNameSpace :: forall info. GlobalRdrEltX info -> NameSpace
greNameSpace = Name -> NameSpace
nameNameSpace (Name -> NameSpace)
-> (GlobalRdrEltX info -> Name) -> GlobalRdrEltX info -> NameSpace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName

greParent :: GlobalRdrEltX info -> Parent
greParent :: forall info. GlobalRdrEltX info -> Parent
greParent = GlobalRdrEltX info -> Parent
forall info. GlobalRdrEltX info -> Parent
gre_par

greInfo :: GlobalRdrElt -> GREInfo
greInfo :: GlobalRdrElt -> GREInfo
greInfo = GlobalRdrElt -> GREInfo
forall info. GlobalRdrEltX info -> info
gre_info

-- | See Note [Parents]
data Parent = NoParent
            | ParentIs  { Parent -> Name
par_is :: !Name }
            deriving (Parent -> Parent -> Bool
(Parent -> Parent -> Bool)
-> (Parent -> Parent -> Bool) -> Eq Parent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Parent -> Parent -> Bool
== :: Parent -> Parent -> Bool
$c/= :: Parent -> Parent -> Bool
/= :: Parent -> Parent -> Bool
Eq, Typeable Parent
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 -> Constr
Parent -> DataType
(forall b. Data b => b -> b) -> Parent -> Parent
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Parent -> u
forall u. (forall d. Data d => d -> u) -> Parent -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Parent
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Parent -> c Parent
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Parent)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Parent -> c Parent
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Parent -> c Parent
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Parent
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Parent
$ctoConstr :: Parent -> Constr
toConstr :: Parent -> Constr
$cdataTypeOf :: Parent -> DataType
dataTypeOf :: Parent -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Parent)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Parent)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent)
$cgmapT :: (forall b. Data b => b -> b) -> Parent -> Parent
gmapT :: (forall b. Data b => b -> b) -> Parent -> Parent
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Parent -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Parent -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Parent -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Parent -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Parent -> m Parent
Data)

instance Outputable Parent where
   ppr :: Parent -> SDoc
ppr Parent
NoParent        = SDoc
forall doc. IsOutput doc => doc
empty
   ppr (ParentIs Name
n)    = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"parent:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
n

instance NFData Parent where
  rnf :: Parent -> ()
rnf Parent
NoParent = ()
  rnf (ParentIs Name
n) = Name -> ()
forall a. NFData a => a -> ()
rnf Name
n

plusParent :: Parent -> Parent -> Parent
-- See Note [Combining parents]
plusParent :: Parent -> Parent -> Parent
plusParent p1 :: Parent
p1@(ParentIs Name
_)    Parent
p2 = Parent -> Parent -> Parent
hasParent Parent
p1 Parent
p2
plusParent Parent
p1 p2 :: Parent
p2@(ParentIs Name
_)    = Parent -> Parent -> Parent
hasParent Parent
p2 Parent
p1
plusParent Parent
NoParent Parent
NoParent     = Parent
NoParent

hasParent :: Parent -> Parent -> Parent
#if defined(DEBUG)
hasParent p NoParent = p
hasParent p p'
  | p /= p' = pprPanic "hasParent" (ppr p <+> ppr p')  -- Parents should agree
#endif
hasParent :: Parent -> Parent -> Parent
hasParent Parent
p Parent
_  = Parent
p


{- Note [GlobalRdrElt provenance]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The gre_lcl and gre_imp fields of a GlobalRdrElt describe its "provenance",
i.e. how the Name came to be in scope.  It can be in scope in one of the following
three ways:

  A. The Name was locally bound, in the current module.
     gre_lcl = True

     The renamer adds this Name to the GlobalRdrEnv after renaming the binding.
     See the calls to "extendGlobalRdrEnvRn" in GHC.Rename.Module.rnSrcDecls.

  B. The Name was imported
     gre_imp = Just imps <=> brought into scope by the imports "imps"

     The renamer adds this Name to the GlobalRdrEnv after processing the imports.
     See GHC.Rename.Names.filterImports and GHC.Tc.Module.tcRnImports.

  C. We followed an exact reference (i.e. an Exact or Orig RdrName)
     gre_lcl = False, gre_imp = Nothing

     In this case, we directly fetch a Name and its GREInfo from direct reference.
     We don't add it to the GlobalRdrEnv. See "GHC.Rename.Env.lookupExactOrOrig".

It is just about possible to have *both* gre_lcl = True and gre_imp = Just imps.
This can happen with module loops: a Name is defined locally in A, and also
brought into scope by importing a module that SOURCE-imported A.

Example (#7672):

 A.hs-boot   module A where
               data T

 B.hs        module B(Decl.T) where
               import {-# SOURCE #-} qualified A as Decl

 A.hs        module A where
               import qualified B
               data T = Z | S B.T

In A.hs, 'T' is locally bound, *and* imported as B.T.


Note [Parents]
~~~~~~~~~~~~~~~~~
The children of a Name are the things that are abbreviated by the ".." notation
in export lists.

~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  Parent           Children
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  data T           Data constructors
                   Record-field ids

  data family T    Data constructors and record-field ids
                   of all visible data instances of T

  class C          Class operations
                   Associated type constructors

~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  Constructor      Meaning
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  NoParent         Not bundled with a type constructor.
  ParentIs n       Bundled with the type constructor corresponding to n.

Pattern synonym constructors (and their record fields, if any) are unusual:
their gre_par is NoParent in the module in which they are defined.  However, a
pattern synonym can be bundled with a type constructor on export, in which case
whenever the pattern synonym is imported the gre_par will be ParentIs.

Thus the gre_name and gre_par fields are independent, because a normal datatype
introduces FieldGlobalRdrElts using ParentIs, but a record pattern synonym can
introduce FieldGlobalRdrElts that use NoParent. (In the past we represented
fields using an additional constructor of the Parent type, which could not
adequately represent this situation.) See also
Note [Representing pattern synonym fields in AvailInfo] in GHC.Types.Avail.

Note [Combining parents]
~~~~~~~~~~~~~~~~~~~~~~~~
With an associated type we might have
   module M where
     class C a where
       data T a
       op :: T a -> a
     instance C Int where
       data T Int = TInt
     instance C Bool where
       data T Bool = TBool

Then:   C is the parent of T
        T is the parent of TInt and TBool
So: in an export list
    C(..) is short for C( op, T )
    T(..) is short for T( TInt, TBool )

Module M exports everything, so its exports will be
   AvailTC C [C,T,op]
   AvailTC T [T,TInt,TBool]
On import we convert to GlobalRdrElt and then combine
those.  For T that will mean we have
  one GRE with Parent C
  one GRE with NoParent
That's why plusParent picks the "best" case.
-}

mkGRE :: (Name -> Maybe ImportSpec) -> GREInfo -> Parent -> Name -> GlobalRdrElt
mkGRE :: (Name -> Maybe ImportSpec)
-> GREInfo -> Parent -> Name -> GlobalRdrElt
mkGRE Name -> Maybe ImportSpec
prov_fn GREInfo
info Parent
par Name
n =
  case Name -> Maybe ImportSpec
prov_fn Name
n of
      -- Nothing => bound locally
      -- Just is => imported from 'is'
    Maybe ImportSpec
Nothing -> GRE { gre_name :: Name
gre_name = Name
n, gre_par :: Parent
gre_par = Parent
par
                   , gre_lcl :: Bool
gre_lcl = Bool
True, gre_imp :: Bag ImportSpec
gre_imp = Bag ImportSpec
forall a. Bag a
emptyBag
                   , gre_info :: GREInfo
gre_info = GREInfo
info }
    Just ImportSpec
is -> GRE { gre_name :: Name
gre_name = Name
n, gre_par :: Parent
gre_par = Parent
par
                   , gre_lcl :: Bool
gre_lcl = Bool
False, gre_imp :: Bag ImportSpec
gre_imp = ImportSpec -> Bag ImportSpec
forall a. a -> Bag a
unitBag ImportSpec
is
                   , gre_info :: GREInfo
gre_info = GREInfo
info }

mkExactGRE :: Name -> GREInfo -> GlobalRdrElt
mkExactGRE :: Name -> GREInfo -> GlobalRdrElt
mkExactGRE Name
nm GREInfo
info =
  GRE { gre_name :: Name
gre_name = Name
nm, gre_par :: Parent
gre_par = Parent
NoParent
      , gre_lcl :: Bool
gre_lcl = Bool
False, gre_imp :: Bag ImportSpec
gre_imp = Bag ImportSpec
forall a. Bag a
emptyBag
      , gre_info :: GREInfo
gre_info = GREInfo
info }

mkLocalGRE :: GREInfo -> Parent -> Name -> GlobalRdrElt
mkLocalGRE :: GREInfo -> Parent -> Name -> GlobalRdrElt
mkLocalGRE = (Name -> Maybe ImportSpec)
-> GREInfo -> Parent -> Name -> GlobalRdrElt
mkGRE (Maybe ImportSpec -> Name -> Maybe ImportSpec
forall a b. a -> b -> a
const Maybe ImportSpec
forall a. Maybe a
Nothing)

mkLocalVanillaGRE :: Parent -> Name -> GlobalRdrElt
mkLocalVanillaGRE :: Parent -> Name -> GlobalRdrElt
mkLocalVanillaGRE = GREInfo -> Parent -> Name -> GlobalRdrElt
mkLocalGRE GREInfo
Vanilla

-- | Create a local 'GlobalRdrElt' for a 'TyCon'.
mkLocalTyConGRE :: TyConFlavour Name
              -> Name
              -> GlobalRdrElt
mkLocalTyConGRE :: TyConFlavour Name -> Name -> GlobalRdrElt
mkLocalTyConGRE TyConFlavour Name
flav Name
nm = GREInfo -> Parent -> Name -> GlobalRdrElt
mkLocalGRE (TyConFlavour Name -> GREInfo
IAmTyCon TyConFlavour Name
flav) Parent
par Name
nm
  where
    par :: Parent
par = case TyConFlavour Name -> Maybe Name
forall tc. TyConFlavour tc -> Maybe tc
tyConFlavourAssoc_maybe TyConFlavour Name
flav of
      Maybe Name
Nothing -> Parent
NoParent
      Just Name
p  -> Name -> Parent
ParentIs Name
p

mkLocalConLikeGRE :: Parent -> (ConLikeName, ConInfo) -> GlobalRdrElt
mkLocalConLikeGRE :: Parent -> (ConLikeName, ConInfo) -> GlobalRdrElt
mkLocalConLikeGRE Parent
p (ConLikeName
con_nm, ConInfo
con_info) =
  GREInfo -> Parent -> Name -> GlobalRdrElt
mkLocalGRE (ConInfo -> GREInfo
IAmConLike ConInfo
con_info) Parent
p (ConLikeName -> Name
conLikeName_Name ConLikeName
con_nm )

mkLocalFieldGREs :: Parent -> [(ConLikeName, ConInfo)] -> [GlobalRdrElt]
mkLocalFieldGREs :: Parent -> [(ConLikeName, ConInfo)] -> [GlobalRdrElt]
mkLocalFieldGREs Parent
p [(ConLikeName, ConInfo)]
cons =
  [ GREInfo -> Parent -> Name -> GlobalRdrElt
mkLocalGRE (RecFieldInfo -> GREInfo
IAmRecField RecFieldInfo
fld_info) Parent
p Name
fld_nm
  | (S.Arg Name
fld_nm FieldLabel
fl, UniqSet ConLikeName
fl_cons) <- [(Arg Name FieldLabel, UniqSet ConLikeName)]
flds
  , let fld_info :: RecFieldInfo
fld_info = RecFieldInfo { recFieldLabel :: FieldLabel
recFieldLabel = FieldLabel
fl
                                , recFieldCons :: UniqSet ConLikeName
recFieldCons  = UniqSet ConLikeName
fl_cons } ]
  where
    -- We are given a map taking a constructor to its fields, but we want
    -- a map taking a field to the contructors which have it.
    -- We thus need to convert [(Con, [Field])] into [(Field, [Con])].
    flds :: [(Arg Name FieldLabel, UniqSet ConLikeName)]
flds = Map (Arg Name FieldLabel) (UniqSet ConLikeName)
-> [(Arg Name FieldLabel, UniqSet ConLikeName)]
forall k a. Map k a -> [(k, a)]
Map.toList
         (Map (Arg Name FieldLabel) (UniqSet ConLikeName)
 -> [(Arg Name FieldLabel, UniqSet ConLikeName)])
-> Map (Arg Name FieldLabel) (UniqSet ConLikeName)
-> [(Arg Name FieldLabel, UniqSet ConLikeName)]
forall a b. (a -> b) -> a -> b
$ (UniqSet ConLikeName -> UniqSet ConLikeName -> UniqSet ConLikeName)
-> [(Arg Name FieldLabel, UniqSet ConLikeName)]
-> Map (Arg Name FieldLabel) (UniqSet ConLikeName)
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith UniqSet ConLikeName -> UniqSet ConLikeName -> UniqSet ConLikeName
forall a. UniqSet a -> UniqSet a -> UniqSet a
unionUniqSets
         [ (Name -> FieldLabel -> Arg Name FieldLabel
forall a b. a -> b -> Arg a b
S.Arg (FieldLabel -> Name
flSelector FieldLabel
fl) FieldLabel
fl, ConLikeName -> UniqSet ConLikeName
forall a. Uniquable a => a -> UniqSet a
unitUniqSet ConLikeName
con)
         | (ConLikeName
con, ConInfo
con_info) <- [(ConLikeName, ConInfo)]
cons
         , ConHasRecordFields NonEmpty FieldLabel
fls <- [ConInfo
con_info]
         , FieldLabel
fl <- NonEmpty FieldLabel -> [FieldLabel]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty FieldLabel
fls ]

instance HasOccName (GlobalRdrEltX info) where
  occName :: GlobalRdrEltX info -> OccName
occName = GlobalRdrEltX info -> OccName
forall info. GlobalRdrEltX info -> OccName
greOccName

greOccName :: GlobalRdrEltX info -> OccName
greOccName :: forall info. GlobalRdrEltX info -> OccName
greOccName ( GRE { gre_name :: forall info. GlobalRdrEltX info -> Name
gre_name = Name
nm } ) = Name -> OccName
nameOccName Name
nm

-- | The SrcSpan of the name pointed to by the GRE.
greDefinitionSrcSpan :: GlobalRdrEltX info -> SrcSpan
greDefinitionSrcSpan :: forall info. GlobalRdrEltX info -> SrcSpan
greDefinitionSrcSpan = Name -> SrcSpan
nameSrcSpan (Name -> SrcSpan)
-> (GlobalRdrEltX info -> Name) -> GlobalRdrEltX info -> SrcSpan
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName

-- | The module in which the name pointed to by the GRE is defined.
greDefinitionModule :: GlobalRdrEltX info -> Maybe Module
greDefinitionModule :: forall info. GlobalRdrEltX info -> Maybe Module
greDefinitionModule = Name -> Maybe Module
nameModule_maybe (Name -> Maybe Module)
-> (GlobalRdrEltX info -> Name)
-> GlobalRdrEltX info
-> Maybe Module
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName

greQualModName :: Outputable info => GlobalRdrEltX info -> ModuleName
-- Get a suitable module qualifier for the GRE
-- (used in mkPrintUnqualified)
-- Precondition: the gre_name is always External
greQualModName :: forall info. Outputable info => GlobalRdrEltX info -> ModuleName
greQualModName gre :: GlobalRdrEltX info
gre@(GRE { gre_lcl :: forall info. GlobalRdrEltX info -> Bool
gre_lcl = Bool
lcl, gre_imp :: forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp = Bag ImportSpec
iss })
 | Bool
lcl, Just Module
mod <- GlobalRdrEltX info -> Maybe Module
forall info. GlobalRdrEltX info -> Maybe Module
greDefinitionModule GlobalRdrEltX info
gre = Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
mod
 | Just ImportSpec
is <- Bag ImportSpec -> Maybe ImportSpec
forall a. Bag a -> Maybe a
headMaybe Bag ImportSpec
iss                 = ImpDeclSpec -> ModuleName
is_as (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is)
 | Bool
otherwise                                = String -> SDoc -> ModuleName
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"greQualModName" (GlobalRdrEltX info -> SDoc
forall a. Outputable a => a -> SDoc
ppr GlobalRdrEltX info
gre)

greRdrNames :: GlobalRdrEltX info -> [RdrName]
greRdrNames :: forall info. GlobalRdrEltX info -> [RdrName]
greRdrNames gre :: GlobalRdrEltX info
gre@GRE{ gre_lcl :: forall info. GlobalRdrEltX info -> Bool
gre_lcl = Bool
lcl, gre_imp :: forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp = Bag ImportSpec
iss }
  = Bag RdrName -> [RdrName]
forall a. Bag a -> [a]
bagToList (Bag RdrName -> [RdrName]) -> Bag RdrName -> [RdrName]
forall a b. (a -> b) -> a -> b
$ (if Bool
lcl then RdrName -> Bag RdrName
forall a. a -> Bag a
unitBag RdrName
unqual else Bag RdrName
forall a. Bag a
emptyBag) Bag RdrName -> Bag RdrName -> Bag RdrName
forall a. Bag a -> Bag a -> Bag a
`unionBags` (ImpDeclSpec -> Bag RdrName) -> Bag ImpDeclSpec -> Bag RdrName
forall a b. (a -> Bag b) -> Bag a -> Bag b
concatMapBag ImpDeclSpec -> Bag RdrName
do_spec ((ImportSpec -> ImpDeclSpec) -> Bag ImportSpec -> Bag ImpDeclSpec
forall a b. (a -> b) -> Bag a -> Bag b
mapBag ImportSpec -> ImpDeclSpec
is_decl Bag ImportSpec
iss)
  where
    occ :: OccName
occ    = GlobalRdrEltX info -> OccName
forall info. GlobalRdrEltX info -> OccName
greOccName GlobalRdrEltX info
gre
    unqual :: RdrName
unqual = OccName -> RdrName
Unqual OccName
occ
    do_spec :: ImpDeclSpec -> Bag RdrName
do_spec ImpDeclSpec
decl_spec
        | ImpDeclSpec -> Bool
is_qual ImpDeclSpec
decl_spec = RdrName -> Bag RdrName
forall a. a -> Bag a
unitBag RdrName
qual
        | Bool
otherwise         = [RdrName] -> Bag RdrName
forall a. [a] -> Bag a
listToBag [RdrName
unqual,RdrName
qual]
        where qual :: RdrName
qual = ModuleName -> OccName -> RdrName
Qual (ImpDeclSpec -> ModuleName
is_as ImpDeclSpec
decl_spec) OccName
occ

-- the SrcSpan that pprNameProvenance prints out depends on whether
-- the Name is defined locally or not: for a local definition the
-- definition site is used, otherwise the location of the import
-- declaration.  We want to sort the export locations in
-- exportClashErr by this SrcSpan, we need to extract it:
greSrcSpan :: Outputable info => GlobalRdrEltX info -> SrcSpan
greSrcSpan :: forall info. Outputable info => GlobalRdrEltX info -> SrcSpan
greSrcSpan gre :: GlobalRdrEltX info
gre@(GRE { gre_lcl :: forall info. GlobalRdrEltX info -> Bool
gre_lcl = Bool
lcl, gre_imp :: forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp = Bag ImportSpec
iss } )
  | Bool
lcl           = GlobalRdrEltX info -> SrcSpan
forall info. GlobalRdrEltX info -> SrcSpan
greDefinitionSrcSpan GlobalRdrEltX info
gre
  | Just ImportSpec
is <- Bag ImportSpec -> Maybe ImportSpec
forall a. Bag a -> Maybe a
headMaybe Bag ImportSpec
iss = ImpDeclSpec -> SrcSpan
is_dloc (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is)
  | Bool
otherwise     = String -> SDoc -> SrcSpan
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"greSrcSpan" (GlobalRdrEltX info -> SDoc
forall a. Outputable a => a -> SDoc
ppr GlobalRdrEltX info
gre)

mkParent :: Name -> AvailInfo -> Parent
mkParent :: Name -> AvailInfo -> Parent
mkParent Name
_ (Avail Name
_)                 = Parent
NoParent
mkParent Name
n (AvailTC Name
m [Name]
_) | Name
n Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
m    = Parent
NoParent
                         | Bool
otherwise = Name -> Parent
ParentIs Name
m

availParent :: AvailInfo -> Parent
availParent :: AvailInfo -> Parent
availParent (AvailTC Name
m [Name]
_) = Name -> Parent
ParentIs Name
m
availParent (Avail {})    = Parent
NoParent


greParent_maybe :: GlobalRdrEltX info -> Maybe Name
greParent_maybe :: forall info. GlobalRdrEltX info -> Maybe Name
greParent_maybe GlobalRdrEltX info
gre = case GlobalRdrEltX info -> Parent
forall info. GlobalRdrEltX info -> Parent
gre_par GlobalRdrEltX info
gre of
                        Parent
NoParent      -> Maybe Name
forall a. Maybe a
Nothing
                        ParentIs Name
n    -> Name -> Maybe Name
forall a. a -> Maybe a
Just Name
n

gresToNameSet :: [GlobalRdrEltX info] -> NameSet
gresToNameSet :: forall info. [GlobalRdrEltX info] -> NameSet
gresToNameSet [GlobalRdrEltX info]
gres = (GlobalRdrEltX info -> NameSet -> NameSet)
-> NameSet -> [GlobalRdrEltX info] -> NameSet
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr GlobalRdrEltX info -> NameSet -> NameSet
forall {info}. GlobalRdrEltX info -> NameSet -> NameSet
add NameSet
emptyNameSet [GlobalRdrEltX info]
gres
  where add :: GlobalRdrEltX info -> NameSet -> NameSet
add GlobalRdrEltX info
gre NameSet
set = NameSet -> Name -> NameSet
extendNameSet NameSet
set (GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrEltX info
gre)

-- | Takes a list of distinct GREs and folds them
-- into AvailInfos. This is more efficient than mapping each individual
-- GRE to an AvailInfo and then folding using `plusAvail`, but needs the
-- uniqueness assumption.
gresToAvailInfo :: forall info. [GlobalRdrEltX info] -> [AvailInfo]
gresToAvailInfo :: forall info. [GlobalRdrEltX info] -> [AvailInfo]
gresToAvailInfo [GlobalRdrEltX info]
gres
  = NameEnv AvailInfo -> [AvailInfo]
forall a. NameEnv a -> [a]
nonDetNameEnvElts NameEnv AvailInfo
avail_env
  where
    avail_env :: NameEnv AvailInfo -- Keyed by the parent
    (NameEnv AvailInfo
avail_env, NameSet
_) = ((NameEnv AvailInfo, NameSet)
 -> GlobalRdrEltX info -> (NameEnv AvailInfo, NameSet))
-> (NameEnv AvailInfo, NameSet)
-> [GlobalRdrEltX info]
-> (NameEnv AvailInfo, NameSet)
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (NameEnv AvailInfo, NameSet)
-> GlobalRdrEltX info -> (NameEnv AvailInfo, NameSet)
add (NameEnv AvailInfo
forall a. NameEnv a
emptyNameEnv, NameSet
emptyNameSet) [GlobalRdrEltX info]
gres

    add :: (NameEnv AvailInfo, NameSet)
        -> GlobalRdrEltX info
        -> (NameEnv AvailInfo, NameSet)
    add :: (NameEnv AvailInfo, NameSet)
-> GlobalRdrEltX info -> (NameEnv AvailInfo, NameSet)
add (NameEnv AvailInfo
env, NameSet
done) GlobalRdrEltX info
gre
      | Name
name Name -> NameSet -> Bool
`elemNameSet` NameSet
done
      = (NameEnv AvailInfo
env, NameSet
done)  -- Don't insert twice into the AvailInfo
      | Bool
otherwise
      = ( (GlobalRdrEltX info -> AvailInfo -> AvailInfo)
-> (GlobalRdrEltX info -> AvailInfo)
-> NameEnv AvailInfo
-> Name
-> GlobalRdrEltX info
-> NameEnv AvailInfo
forall a b.
(a -> b -> b) -> (a -> b) -> NameEnv b -> Name -> a -> NameEnv b
extendNameEnv_Acc GlobalRdrEltX info -> AvailInfo -> AvailInfo
comb GlobalRdrEltX info -> AvailInfo
forall info. GlobalRdrEltX info -> AvailInfo
availFromGRE NameEnv AvailInfo
env Name
key GlobalRdrEltX info
gre
        , NameSet
done NameSet -> Name -> NameSet
`extendNameSet` Name
name )
      where
        name :: Name
name = GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrEltX info
gre
        key :: Name
key = case GlobalRdrEltX info -> Maybe Name
forall info. GlobalRdrEltX info -> Maybe Name
greParent_maybe GlobalRdrEltX info
gre of
                 Just Name
parent -> Name
parent
                 Maybe Name
Nothing     -> GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrEltX info
gre

        -- We want to insert the child `k` into a list of children but
        -- need to maintain the invariant that the parent is first.
        --
        -- We also use the invariant that `k` is not already in `ns`.
        insertChildIntoChildren :: Name -> [Name] -> Name -> [Name]
        insertChildIntoChildren :: Name -> [Name] -> Name -> [Name]
insertChildIntoChildren Name
_ [] Name
k = [Name
k]
        insertChildIntoChildren Name
p (Name
n:[Name]
ns) 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 :: GlobalRdrEltX info -> AvailInfo -> AvailInfo
        comb :: GlobalRdrEltX info -> AvailInfo -> AvailInfo
comb GlobalRdrEltX info
_   (Avail Name
n) = Name -> AvailInfo
Avail Name
n -- Duplicated name, should not happen
        comb GlobalRdrEltX info
gre (AvailTC Name
m [Name]
ns)
          = case GlobalRdrEltX info -> Parent
forall info. GlobalRdrEltX info -> Parent
gre_par GlobalRdrEltX info
gre of
              Parent
NoParent    -> Name -> [Name] -> AvailInfo
AvailTC Name
m (GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrEltX info
greName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[Name]
ns) -- Not sure this ever happens
              ParentIs {} -> Name -> [Name] -> AvailInfo
AvailTC Name
m (Name -> [Name] -> Name -> [Name]
insertChildIntoChildren Name
m [Name]
ns (GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrEltX info
gre))

availFromGRE :: GlobalRdrEltX info -> AvailInfo
availFromGRE :: forall info. GlobalRdrEltX info -> AvailInfo
availFromGRE (GRE { gre_name :: forall info. GlobalRdrEltX info -> Name
gre_name = Name
child, gre_par :: forall info. GlobalRdrEltX info -> Parent
gre_par = Parent
parent })
  = case Parent
parent of
      ParentIs Name
p
        -> Name -> [Name] -> AvailInfo
AvailTC Name
p [Name
child]
      Parent
NoParent
        | Name -> Bool
isTyConName Name
child -- NB: don't force the GREInfo field unnecessarily.
        -> Name -> [Name] -> AvailInfo
AvailTC Name
child [Name
child]
        | Bool
otherwise
        -> Name -> AvailInfo
Avail Name
child

emptyGlobalRdrEnv :: GlobalRdrEnvX info
emptyGlobalRdrEnv :: forall info. GlobalRdrEnvX info
emptyGlobalRdrEnv = OccEnv [GlobalRdrEltX info]
forall a. OccEnv a
emptyOccEnv

globalRdrEnvElts :: GlobalRdrEnvX info -> [GlobalRdrEltX info]
globalRdrEnvElts :: forall info. GlobalRdrEnvX info -> [GlobalRdrEltX info]
globalRdrEnvElts GlobalRdrEnvX info
env = ([GlobalRdrEltX info]
 -> [GlobalRdrEltX info] -> [GlobalRdrEltX info])
-> [GlobalRdrEltX info]
-> GlobalRdrEnvX info
-> [GlobalRdrEltX info]
forall a b. (a -> b -> b) -> b -> OccEnv a -> b
nonDetFoldOccEnv [GlobalRdrEltX info]
-> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall a. [a] -> [a] -> [a]
(++) [] GlobalRdrEnvX info
env

-- | Drop all 'GREInfo' fields in a 'GlobalRdrEnv' in order to
-- avoid space leaks.
-- See Note [Forcing GREInfo] in GHC.Types.GREInfo.
forceGlobalRdrEnv :: GlobalRdrEnvX info -> IfGlobalRdrEnv
forceGlobalRdrEnv :: forall info. GlobalRdrEnvX info -> IfGlobalRdrEnv
forceGlobalRdrEnv GlobalRdrEnvX info
rdrs =
  ([GlobalRdrEltX info] -> [GlobalRdrEltX ()])
-> GlobalRdrEnvX info -> IfGlobalRdrEnv
forall a b. (a -> b) -> OccEnv a -> OccEnv b
strictMapOccEnv ((GlobalRdrEltX info -> GlobalRdrEltX ())
-> [GlobalRdrEltX info] -> [GlobalRdrEltX ()]
forall a b. (a -> b) -> [a] -> [b]
strictMap (\ GlobalRdrEltX info
gre -> GlobalRdrEltX info
gre { gre_info = ()})) GlobalRdrEnvX info
rdrs

-- | Hydrate a previously dehydrated 'GlobalRdrEnv',
-- by (lazily!) looking up the 'GREInfo' using the provided function.
--
-- See Note [Forcing GREInfo] in GHC.Types.GREInfo.
hydrateGlobalRdrEnv :: forall info noInfo
                    .  (Name -> IO info)
                    -> GlobalRdrEnvX noInfo -> GlobalRdrEnvX info
hydrateGlobalRdrEnv :: forall info noInfo.
(Name -> IO info) -> GlobalRdrEnvX noInfo -> GlobalRdrEnvX info
hydrateGlobalRdrEnv Name -> IO info
f = ([GlobalRdrEltX noInfo] -> [GlobalRdrEltX info])
-> OccEnv [GlobalRdrEltX noInfo] -> OccEnv [GlobalRdrEltX info]
forall a b. (a -> b) -> OccEnv a -> OccEnv b
mapOccEnv ((GlobalRdrEltX noInfo -> GlobalRdrEltX info)
-> [GlobalRdrEltX noInfo] -> [GlobalRdrEltX info]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GlobalRdrEltX noInfo -> GlobalRdrEltX info
g)
  where
    g :: GlobalRdrEltX noInfo -> GlobalRdrEltX info
g GlobalRdrEltX noInfo
gre = GlobalRdrEltX noInfo
gre { gre_info = unsafePerformIO $ f (greName gre) }
    -- NB: use unsafePerformIO to delay the lookup until it is forced.
    -- See also 'GHC.Rename.Env.lookupGREInfo'.

instance Outputable info => Outputable (GlobalRdrEltX info) where
  ppr :: GlobalRdrEltX info -> SDoc
ppr GlobalRdrEltX info
gre = SDoc -> Int -> SDoc -> SDoc
hang (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrEltX info
gre) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Parent -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GlobalRdrEltX info -> Parent
forall info. GlobalRdrEltX info -> Parent
gre_par GlobalRdrEltX info
gre) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> info -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GlobalRdrEltX info -> info
forall info. GlobalRdrEltX info -> info
gre_info GlobalRdrEltX info
gre))
               Int
2 (GlobalRdrEltX info -> SDoc
forall info. GlobalRdrEltX info -> SDoc
pprNameProvenance GlobalRdrEltX info
gre)

pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc
pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc
pprGlobalRdrEnv Bool
locals_only GlobalRdrEnv
env
  = [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"GlobalRdrEnv" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen Bool
locals_only (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(locals only)")
             SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
forall doc. IsLine doc => doc
lbrace
         , Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ [GlobalRdrElt] -> SDoc
forall {info}. Outputable info => [GlobalRdrEltX info] -> SDoc
pp ([GlobalRdrElt] -> [GlobalRdrElt]
remove_locals [GlobalRdrElt]
gre_list) | [GlobalRdrElt]
gre_list <- GlobalRdrEnv -> [[GlobalRdrElt]]
forall a. OccEnv a -> [a]
nonDetOccEnvElts GlobalRdrEnv
env ]
             SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
forall doc. IsLine doc => doc
rbrace) ]
  where
    remove_locals :: [GlobalRdrElt] -> [GlobalRdrElt]
remove_locals [GlobalRdrElt]
gres | Bool
locals_only = (GlobalRdrElt -> Bool) -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. (a -> Bool) -> [a] -> [a]
filter GlobalRdrElt -> Bool
forall info. GlobalRdrEltX info -> Bool
isLocalGRE [GlobalRdrElt]
gres
                       | Bool
otherwise   = [GlobalRdrElt]
gres
    pp :: [GlobalRdrEltX info] -> SDoc
pp []   = SDoc
forall doc. IsOutput doc => doc
empty
    pp gres :: [GlobalRdrEltX info]
gres@(GlobalRdrEltX info
gre:[GlobalRdrEltX info]
_) = SDoc -> Int -> SDoc -> SDoc
hang (OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
colon)
                         Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((GlobalRdrEltX info -> SDoc) -> [GlobalRdrEltX info] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map GlobalRdrEltX info -> SDoc
forall a. Outputable a => a -> SDoc
ppr [GlobalRdrEltX info]
gres))
      where
        occ :: OccName
occ = Name -> OccName
nameOccName (GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrEltX info
gre)

{-
Note [NoFieldSelectors]
~~~~~~~~~~~~~~~~~~~~~~~
The NoFieldSelectors extension allows record fields to be defined without
bringing the corresponding selector functions into scope.  However, such fields
may still be used in contexts such as record construction, pattern matching or
update. This requires us to distinguish contexts in which selectors are required
from those in which any field may be used.  For example:

  {-# LANGUAGE NoFieldSelectors #-}
  module M (T(foo), foo) where  -- T(foo) refers to the field,
                                -- unadorned foo to the value binding
    data T = MkT { foo :: Int }
    foo = ()

    bar = foo -- refers to the value binding, field ignored

  module N where
    import M (T(..))
    baz = MkT { foo = 3 } -- refers to the field
    oops = foo -- an error: the field is in scope but the value binding is not

Each 'FieldLabel' indicates (in the 'flHasFieldSelector' field) whether the
FieldSelectors extension was enabled in the defining module.  This allows them
to be filtered out by 'filterFieldGREs'.

Even when NoFieldSelectors is in use, we still generate selector functions
internally. For example, the expression
   getField @"foo" t
or (with dot-notation)
   t.foo
extracts the `foo` field of t::T, and hence needs the selector function
(see Note [HasField instances] in GHC.Tc.Instance.Class).

In many of the name lookup functions in this module we pass a FieldsOrSelectors
value, indicating what we are looking for:

 * WantNormal: fields are in scope only if they have an accompanying selector
   function, e.g. we are looking up a variable in an expression
   (lookupExprOccRn).

 * WantBoth: any name or field will do, regardless of whether the selector
   function is available, e.g. record updates (lookupRecUpdFields) with
   NoDisambiguateRecordFields.

 * WantField: any field will do, regardless of whether the selector function is
   available, but ignoring any non-field names, e.g. record updates
   (lookupRecUpdFields with DisambiguateRecordFields.

-----------------------------------------------------------------------------------
  Context                                  FieldsOrSelectors
-----------------------------------------------------------------------------------
  Record construction/pattern match        WantField, but unless DisambiguateRecordFields
  e.g. MkT { foo = 3 }                     is in effect, also look up using WantBoth
  Record update, e.g. e { foo = 3 }        to report when a non-field clashes with a field.

  :info in GHCi                            WantBoth

  Variable occurrence in expression        WantNormal
  Type variable, data constructor
  Pretty much everything else
-----------------------------------------------------------------------------------
-}

fieldGRE_maybe :: GlobalRdrElt -> Maybe FieldGlobalRdrElt
fieldGRE_maybe :: GlobalRdrElt -> Maybe GlobalRdrElt
fieldGRE_maybe GlobalRdrElt
gre = do
  Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (GlobalRdrElt -> Bool
forall info. GlobalRdrEltX info -> Bool
isRecFldGRE GlobalRdrElt
gre)
  GlobalRdrElt -> Maybe GlobalRdrElt
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return GlobalRdrElt
gre

fieldGRELabel :: HasDebugCallStack => FieldGlobalRdrElt -> FieldLabel
fieldGRELabel :: (() :: Constraint) => GlobalRdrElt -> FieldLabel
fieldGRELabel = RecFieldInfo -> FieldLabel
recFieldLabel (RecFieldInfo -> FieldLabel)
-> (GlobalRdrElt -> RecFieldInfo) -> GlobalRdrElt -> FieldLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (() :: Constraint) => GlobalRdrElt -> RecFieldInfo
GlobalRdrElt -> RecFieldInfo
fieldGREInfo

fieldGREInfo :: HasDebugCallStack => FieldGlobalRdrElt -> RecFieldInfo
fieldGREInfo :: (() :: Constraint) => GlobalRdrElt -> RecFieldInfo
fieldGREInfo GlobalRdrElt
gre
  = Bool -> SDoc -> RecFieldInfo -> RecFieldInfo
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (GlobalRdrElt -> Bool
forall info. GlobalRdrEltX info -> Bool
isRecFldGRE GlobalRdrElt
gre) (GlobalRdrElt -> SDoc
forall a. Outputable a => a -> SDoc
ppr GlobalRdrElt
gre) (RecFieldInfo -> RecFieldInfo) -> RecFieldInfo -> RecFieldInfo
forall a b. (a -> b) -> a -> b
$
    case GlobalRdrElt -> GREInfo
greInfo GlobalRdrElt
gre of
      IAmRecField RecFieldInfo
info -> RecFieldInfo
info
      GREInfo
info -> String -> SDoc -> RecFieldInfo
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"fieldGREInfo" (SDoc -> RecFieldInfo) -> SDoc -> RecFieldInfo
forall a b. (a -> b) -> a -> b
$
        [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"gre_name:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GlobalRdrElt -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrElt
gre)
             , String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"info:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> GREInfo -> SDoc
forall a. Outputable a => a -> SDoc
ppr GREInfo
info ]

recFieldConLike_maybe :: HasDebugCallStack => GlobalRdrElt -> Maybe ConInfo
recFieldConLike_maybe :: (() :: Constraint) => GlobalRdrElt -> Maybe ConInfo
recFieldConLike_maybe GlobalRdrElt
gre =
  case GlobalRdrElt -> GREInfo
greInfo GlobalRdrElt
gre of
    IAmConLike ConInfo
info -> ConInfo -> Maybe ConInfo
forall a. a -> Maybe a
Just ConInfo
info
    GREInfo
_               -> Maybe ConInfo
forall a. Maybe a
Nothing

recFieldInfo_maybe :: HasDebugCallStack => GlobalRdrElt -> Maybe RecFieldInfo
recFieldInfo_maybe :: (() :: Constraint) => GlobalRdrElt -> Maybe RecFieldInfo
recFieldInfo_maybe GlobalRdrElt
gre =
  case GlobalRdrElt -> GREInfo
greInfo GlobalRdrElt
gre of
    IAmRecField RecFieldInfo
info -> Bool -> SDoc -> Maybe RecFieldInfo -> Maybe RecFieldInfo
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (GlobalRdrElt -> Bool
forall info. GlobalRdrEltX info -> Bool
isRecFldGRE GlobalRdrElt
gre) (GlobalRdrElt -> SDoc
forall a. Outputable a => a -> SDoc
ppr GlobalRdrElt
gre) (Maybe RecFieldInfo -> Maybe RecFieldInfo)
-> Maybe RecFieldInfo -> Maybe RecFieldInfo
forall a b. (a -> b) -> a -> b
$ RecFieldInfo -> Maybe RecFieldInfo
forall a. a -> Maybe a
Just RecFieldInfo
info
    GREInfo
_                -> Maybe RecFieldInfo
forall a. Maybe a
Nothing

-- | When looking up GREs, we may or may not want to include fields that were
-- defined in modules with @NoFieldSelectors@ enabled.  See Note
-- [NoFieldSelectors].
data FieldsOrSelectors
    = WantNormal -- ^ Include normal names, and fields with selectors, but
                 -- ignore fields without selectors.
    | WantBoth   -- ^ Include normal names and all fields (regardless of whether
                 -- they have selectors).
    | WantField  -- ^ Include only fields, with or without selectors, ignoring
                 -- any non-fields in scope.
  deriving (FieldsOrSelectors -> FieldsOrSelectors -> Bool
(FieldsOrSelectors -> FieldsOrSelectors -> Bool)
-> (FieldsOrSelectors -> FieldsOrSelectors -> Bool)
-> Eq FieldsOrSelectors
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldsOrSelectors -> FieldsOrSelectors -> Bool
== :: FieldsOrSelectors -> FieldsOrSelectors -> Bool
$c/= :: FieldsOrSelectors -> FieldsOrSelectors -> Bool
/= :: FieldsOrSelectors -> FieldsOrSelectors -> Bool
Eq, Int -> FieldsOrSelectors -> ShowS
[FieldsOrSelectors] -> ShowS
FieldsOrSelectors -> String
(Int -> FieldsOrSelectors -> ShowS)
-> (FieldsOrSelectors -> String)
-> ([FieldsOrSelectors] -> ShowS)
-> Show FieldsOrSelectors
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldsOrSelectors -> ShowS
showsPrec :: Int -> FieldsOrSelectors -> ShowS
$cshow :: FieldsOrSelectors -> String
show :: FieldsOrSelectors -> String
$cshowList :: [FieldsOrSelectors] -> ShowS
showList :: [FieldsOrSelectors] -> ShowS
Show)

filterFieldGREs :: FieldsOrSelectors -> [GlobalRdrElt] -> [GlobalRdrElt]
filterFieldGREs :: FieldsOrSelectors -> [GlobalRdrElt] -> [GlobalRdrElt]
filterFieldGREs FieldsOrSelectors
WantBoth = [GlobalRdrElt] -> [GlobalRdrElt]
forall a. a -> a
id
filterFieldGREs FieldsOrSelectors
fos = (GlobalRdrElt -> Bool) -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. (a -> Bool) -> [a] -> [a]
filter (FieldsOrSelectors -> GlobalRdrElt -> Bool
allowGRE FieldsOrSelectors
fos)

allowGRE :: FieldsOrSelectors -> GlobalRdrElt -> Bool
allowGRE :: FieldsOrSelectors -> GlobalRdrElt -> Bool
allowGRE FieldsOrSelectors
WantBoth   GlobalRdrElt
_
  = Bool
True
allowGRE FieldsOrSelectors
WantNormal GlobalRdrElt
gre
  -- NB: we only need to consult the GREInfo for record field GREs,
  -- to check whether they define field selectors.
  -- By checking 'isRecFldGRE' first, which only consults the NameSpace,
  -- we avoid forcing the GREInfo for things that aren't record fields.
  | GlobalRdrElt -> Bool
forall info. GlobalRdrEltX info -> Bool
isRecFldGRE GlobalRdrElt
gre
  = FieldLabel -> FieldSelectors
flHasFieldSelector ((() :: Constraint) => GlobalRdrElt -> FieldLabel
GlobalRdrElt -> FieldLabel
fieldGRELabel GlobalRdrElt
gre) FieldSelectors -> FieldSelectors -> Bool
forall a. Eq a => a -> a -> Bool
== FieldSelectors
FieldSelectors
  | Bool
otherwise
  = Bool
True
allowGRE FieldsOrSelectors
WantField GlobalRdrElt
gre
  = GlobalRdrElt -> Bool
forall info. GlobalRdrEltX info -> Bool
isRecFldGRE GlobalRdrElt
gre

-- | What should we look up in a 'GlobalRdrEnv'? Should we only look up
-- names with the exact same 'OccName', or do we allow different 'NameSpace's?
--
-- Depending on the answer, we might need more or less information from the
-- 'GlobalRdrEnv', e.g. if we want to include matching record fields we need
-- to know if the corresponding record fields define field selectors, for which
-- we need to consult the 'GREInfo'. This is why this datatype is a GADT.
--
-- See Note [IfGlobalRdrEnv].
data LookupGRE info where
  -- | Look for this specific 'OccName', with the exact same 'NameSpace',
  -- in the 'GlobalRdrEnv'.
  LookupOccName :: OccName -- ^ the 'OccName' to look up
                -> WhichGREs info
                    -- ^ information about other relevant 'NameSpace's
                -> LookupGRE info

  -- | Look up the 'OccName' of this 'RdrName' in the 'GlobalRdrEnv',
  -- filtering out those whose qualification matches that of the 'RdrName'.
  --
  -- Lookup returns an empty result for 'Exact' or 'Orig' 'RdrName's.
  LookupRdrName :: RdrName -- ^ the 'RdrName' to look up
                -> WhichGREs info
                    -- ^ information about other relevant 'NameSpace's
                -> LookupGRE info

  -- | Look for 'GRE's with the same unique as the given 'Name'
  -- in the 'GlobalRdrEnv'.
  LookupExactName
    :: { forall info. LookupGRE info -> Name
lookupExactName :: Name
          -- ^ the 'Name' to look up
       , forall info. LookupGRE info -> Bool
lookInAllNameSpaces :: Bool
          -- ^ whether to look in *all* 'NameSpace's, or just
          -- in the 'NameSpace' of the 'Name'
          -- See Note [Template Haskell ambiguity]
       }
    -> LookupGRE info

  -- | Look up children 'GlobalRdrElt's with a given 'Parent'.
  LookupChildren
    :: OccName  -- ^ the 'OccName' to look up
    -> LookupChild
         -- ^ information to decide which 'GlobalRdrElt's
         -- are valid children after looking up
    -> LookupGRE info

-- | How should we look up in a 'GlobalRdrEnv'?
-- Which 'NameSpace's are considered relevant for a given lookup?
data WhichGREs info where
  -- | Only consider 'GlobalRdrElt's with the exact 'NameSpace' we look up.
  SameNameSpace :: WhichGREs info
  -- | Allow 'GlobalRdrElt's with different 'NameSpace's, e.g. allow looking up
  -- record fields from the variable 'NameSpace', or looking up a 'TyCon' from
  -- the data constructor 'NameSpace'.
  RelevantGREs
    :: { WhichGREs GREInfo -> FieldsOrSelectors
includeFieldSelectors :: !FieldsOrSelectors
        -- ^ how should we handle looking up variables?
        --
        --   - should we include record fields defined with @-XNoFieldSelectors@?
        --   - should we include non-fields?
        --
        -- See Note [NoFieldSelectors].
       , WhichGREs GREInfo -> Bool
lookupVariablesForFields :: !Bool
          -- ^ when looking up a record field, should we also look up plain variables?
       , WhichGREs GREInfo -> Bool
lookupTyConsAsWell :: !Bool
          -- ^ when looking up a variable, field or data constructor, should we
          -- also try the type constructor 'NameSpace'?
       }
    -> WhichGREs GREInfo

instance Outputable (WhichGREs info) where
  ppr :: WhichGREs info -> SDoc
ppr WhichGREs info
SameNameSpace = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"SameNameSpace"
  ppr (RelevantGREs { includeFieldSelectors :: WhichGREs GREInfo -> FieldsOrSelectors
includeFieldSelectors = FieldsOrSelectors
sel
                    , lookupVariablesForFields :: WhichGREs GREInfo -> Bool
lookupVariablesForFields = Bool
vars
                    , lookupTyConsAsWell :: WhichGREs GREInfo -> Bool
lookupTyConsAsWell = Bool
tcs_too })
    = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hsep
       [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"RelevantGREs"
       , String -> SDoc
forall doc. IsLine doc => String -> doc
text (FieldsOrSelectors -> String
forall a. Show a => a -> String
show FieldsOrSelectors
sel)
       , if Bool
vars then String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[vars]" else SDoc
forall doc. IsOutput doc => doc
empty
       , if Bool
tcs_too then String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[tcs]" else SDoc
forall doc. IsOutput doc => doc
empty ]

-- | Look up as many possibly relevant 'GlobalRdrElt's as possible.
pattern AllRelevantGREs :: WhichGREs GREInfo
pattern $mAllRelevantGREs :: forall {r}. WhichGREs GREInfo -> ((# #) -> r) -> ((# #) -> r) -> r
$bAllRelevantGREs :: WhichGREs GREInfo
AllRelevantGREs =
  RelevantGREs { includeFieldSelectors = WantBoth
               , lookupVariablesForFields = True
               , lookupTyConsAsWell = True }

-- | Look up relevant GREs, taking into account the interaction between the
-- variable and field 'NameSpace's as determined by the 'FieldsOrSelector'
-- argument.
pattern RelevantGREsFOS :: FieldsOrSelectors -> WhichGREs GREInfo
pattern $mRelevantGREsFOS :: forall {r}.
WhichGREs GREInfo -> (FieldsOrSelectors -> r) -> ((# #) -> r) -> r
$bRelevantGREsFOS :: FieldsOrSelectors -> WhichGREs GREInfo
RelevantGREsFOS fos <- RelevantGREs { includeFieldSelectors = fos }
  where
    RelevantGREsFOS FieldsOrSelectors
fos =
      RelevantGREs { includeFieldSelectors :: FieldsOrSelectors
includeFieldSelectors = FieldsOrSelectors
fos
                   , lookupVariablesForFields :: Bool
lookupVariablesForFields = FieldsOrSelectors
fos FieldsOrSelectors -> FieldsOrSelectors -> Bool
forall a. Eq a => a -> a -> Bool
== FieldsOrSelectors
WantBoth
                   , lookupTyConsAsWell :: Bool
lookupTyConsAsWell = Bool
False }

data LookupChild
  = LookupChild
  { LookupChild -> Name
wantedParent :: Name
     -- ^ the parent we are looking up children of
  , LookupChild -> Bool
lookupDataConFirst :: Bool
     -- ^ for type constructors, should we look in the data constructor
     -- namespace first?
  , LookupChild -> Bool
prioritiseParent :: Bool
    -- ^ should we prioritise getting the right 'Parent'?
    --
    --  - @True@: prioritise getting the right 'Parent'
    --  - @False@: prioritise getting the right 'NameSpace'
    --
    -- See Note [childGREPriority].
  }

instance Outputable LookupChild where
  ppr :: LookupChild -> SDoc
ppr (LookupChild { wantedParent :: LookupChild -> Name
wantedParent = Name
par
                   , lookupDataConFirst :: LookupChild -> Bool
lookupDataConFirst = Bool
dc
                   , prioritiseParent :: LookupChild -> Bool
prioritiseParent = Bool
prio_parent })
    = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hsep
        [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LookupChild"
        , SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"parent:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
par)
        , if Bool
dc then String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[dc_first]" else SDoc
forall doc. IsOutput doc => doc
empty
        , if Bool
prio_parent then String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[prio_parent]" else SDoc
forall doc. IsOutput doc => doc
empty
        ]

-- | After looking up something with the given 'NameSpace', is the resulting
-- 'GlobalRdrElt' we have obtained relevant, according to the 'RelevantGREs'
-- specification of which 'NameSpace's are relevant?
greIsRelevant :: WhichGREs GREInfo -- ^ specification of which 'GlobalRdrElt's to consider relevant
              -> NameSpace    -- ^ the 'NameSpace' of the thing we are looking up
              -> GlobalRdrElt -- ^ the 'GlobalRdrElt' we have looked up, in a
                              -- potentially different 'NameSpace' than we wanted
              -> Bool
greIsRelevant :: WhichGREs GREInfo -> NameSpace -> GlobalRdrElt -> Bool
greIsRelevant WhichGREs GREInfo
which_gres NameSpace
ns GlobalRdrElt
gre
  | NameSpace
ns NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
other_ns
  = Bool
True
  | Bool
otherwise
  = case WhichGREs GREInfo
which_gres of
      WhichGREs GREInfo
SameNameSpace -> Bool
False
      RelevantGREs { includeFieldSelectors :: WhichGREs GREInfo -> FieldsOrSelectors
includeFieldSelectors = FieldsOrSelectors
fos
                   , lookupVariablesForFields :: WhichGREs GREInfo -> Bool
lookupVariablesForFields = Bool
vars_for_flds
                   , lookupTyConsAsWell :: WhichGREs GREInfo -> Bool
lookupTyConsAsWell = Bool
tycons_too }
        | NameSpace
ns NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
varName
        -> (NameSpace -> Bool
isFieldNameSpace NameSpace
other_ns Bool -> Bool -> Bool
&& FieldsOrSelectors -> GlobalRdrElt -> Bool
allowGRE FieldsOrSelectors
fos GlobalRdrElt
gre) Bool -> Bool -> Bool
|| Bool
tc_too
        | NameSpace -> Bool
isFieldNameSpace NameSpace
ns
        -> Bool
vars_for_flds Bool -> Bool -> Bool
&&
          (  NameSpace
other_ns NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
varName
          Bool -> Bool -> Bool
|| (NameSpace -> Bool
isFieldNameSpace NameSpace
other_ns Bool -> Bool -> Bool
&& FieldsOrSelectors -> GlobalRdrElt -> Bool
allowGRE FieldsOrSelectors
fos GlobalRdrElt
gre)
          Bool -> Bool -> Bool
|| Bool
tc_too )
        | NameSpace -> Bool
isDataConNameSpace NameSpace
ns
        -> Bool
tc_too
        | Bool
otherwise
        -> Bool
False
        where
          tc_too :: Bool
tc_too = Bool
tycons_too Bool -> Bool -> Bool
&& NameSpace -> Bool
isTcClsNameSpace NameSpace
other_ns
  where
    other_ns :: NameSpace
other_ns = GlobalRdrElt -> NameSpace
forall info. GlobalRdrEltX info -> NameSpace
greNameSpace GlobalRdrElt
gre

{- Note [childGREPriority]
~~~~~~~~~~~~~~~~~~~~~~~~~~
There are currently two places in the compiler where we look up GlobalRdrElts
which have a given Parent. These are the two calls to lookupSubBndrOcc_helper:

  A. Looking up children in an export item, e.g.

       module M ( T(MkT, D) ) where { data T = MkT; data D = D }

  B. Looking up binders in a class or instance declaration, e.g.
     the operator +++ in the fixity declaration:

       class C a where { type (+++) :: a -> a ->; infixl 6 +++ }
       (+++) :: Int -> Int -> Int; (+++) = (+)

In these two situations, there are two competing metrics for finding the "best"
'GlobalRdrElt' that a particular 'OccName' resolves to:

  - does the resolved 'GlobalRdrElt' have the correct parent?
  - does the resolved 'GlobalRdrElt' have the same 'NameSpace' as the 'OccName'?

(A) and (B) have competing requirements.

For the example of (A) above, we know that the child 'D' of 'T' must live
in the data namespace, so we look up the OccName 'OccName DataName "D"' and
prioritise the lookup results based on the 'NameSpace'.
This means we get an error message of the form:

  The type constructor 'T' is not the parent of the data constructor 'D'.

as opposed to the rather unhelpful and confusing:

  The type constructor 'T' is not the parent of the type constructor 'D'.

See test case T11970.

For the example of (B) above, the fixity declaration for +++ lies inside the
class, so we should prioritise looking up 'GlobalRdrElt's whose parent is 'C'.
Not doing so led to #23664.
-}

-- | Scoring priority function for looking up children 'GlobalRdrElt'.
--
-- We score by 'Parent' and 'NameSpace', with higher priorities having lower
-- numbers. Which lexicographic order we use ('Parent' or 'NameSpace' first)
-- is determined by the first argument; see Note [childGREPriority].
childGREPriority :: LookupChild -- ^ what kind of child do we want,
                                -- e.g. what should its parent be?
                 -> NameSpace   -- ^ what 'NameSpace' are we originally looking in?
                 -> GlobalRdrEltX info
                                -- ^ the result of looking up; it might be in a different
                                -- 'NameSpace', which is used to determine the score
                                -- (in the first component)
                 -> Maybe (Int, Int)
childGREPriority :: forall info.
LookupChild -> NameSpace -> GlobalRdrEltX info -> Maybe (Int, Int)
childGREPriority (LookupChild { wantedParent :: LookupChild -> Name
wantedParent = Name
wanted_parent
                              , lookupDataConFirst :: LookupChild -> Bool
lookupDataConFirst = Bool
try_dc_first
                              , prioritiseParent :: LookupChild -> Bool
prioritiseParent = Bool
par_first })
  NameSpace
ns GlobalRdrEltX info
gre =
    case NameSpace -> Maybe Int
child_ns_prio (NameSpace -> Maybe Int) -> NameSpace -> Maybe Int
forall a b. (a -> b) -> a -> b
$ GlobalRdrEltX info -> NameSpace
forall info. GlobalRdrEltX info -> NameSpace
greNameSpace GlobalRdrEltX info
gre of
      Maybe Int
Nothing -> Maybe (Int, Int)
forall a. Maybe a
Nothing
      Just Int
ns_prio ->
        let par_prio :: Int
par_prio = Parent -> Int
parent_prio (Parent -> Int) -> Parent -> Int
forall a b. (a -> b) -> a -> b
$ GlobalRdrEltX info -> Parent
forall info. GlobalRdrEltX info -> Parent
greParent GlobalRdrEltX info
gre
        in (Int, Int) -> Maybe (Int, Int)
forall a. a -> Maybe a
Just ((Int, Int) -> Maybe (Int, Int)) -> (Int, Int) -> Maybe (Int, Int)
forall a b. (a -> b) -> a -> b
$ if Bool
par_first
                  then (Int
par_prio, Int
ns_prio)
                  else (Int
ns_prio, Int
par_prio)
          -- See Note [childGREPriority].

  where
      -- Pick out the possible 'NameSpace's in order of priority.
      child_ns_prio :: (NameSpace -> Maybe Int)
      child_ns_prio :: NameSpace -> Maybe Int
child_ns_prio NameSpace
other_ns
        | NameSpace
other_ns NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
ns
        = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0
        | NameSpace -> Bool
isTermVarOrFieldNameSpace NameSpace
ns
        , NameSpace -> Bool
isTermVarOrFieldNameSpace NameSpace
other_ns
        = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0
        | NameSpace -> Bool
isValNameSpace NameSpace
varName
        , NameSpace
other_ns NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
tcName
        -- When looking up children, we sometimes want a value name
        -- to resolve to a type constructor.
        -- For example, for an infix declaration "infixr 3 +!" or "infix 2 `Fun`"
        -- inside a class declaration, we want to account for the possibility
        -- that the identifier refers to an associated type (type constructor
        -- NameSpace), when otherwise "+!" would be in the term-level variable
        -- NameSpace, and "Fun" would be in the term-level data constructor
        -- NameSpace.  See tests T10816, T23664, T24037.
        = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1
        | NameSpace
ns NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
tcName
        , NameSpace
other_ns NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
dataName
        , Bool
try_dc_first -- try data namespace before type/class namespace?
        = Int -> Maybe Int
forall a. a -> Maybe a
Just (-Int
1)
        | Bool
otherwise
        = Maybe Int
forall a. Maybe a
Nothing

      parent_prio :: Parent -> Int
      parent_prio :: Parent -> Int
parent_prio (ParentIs Name
other_parent)
        | Name
other_parent Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
wanted_parent = Int
0
        | Bool
otherwise                     = Int
1
      parent_prio Parent
NoParent              = Int
0

-- | Look something up in the Global Reader Environment.
--
-- The 'LookupGRE' argument specifies what to look up, and in particular
-- whether there should there be any lee-way if the 'NameSpace's don't
-- exactly match.
lookupGRE :: GlobalRdrEnvX info -> LookupGRE info -> [GlobalRdrEltX info]
lookupGRE :: forall info.
GlobalRdrEnvX info -> LookupGRE info -> [GlobalRdrEltX info]
lookupGRE GlobalRdrEnvX info
env = \case
  LookupOccName OccName
occ WhichGREs info
which_gres ->
    case WhichGREs info
which_gres of
      WhichGREs info
SameNameSpace ->
        Maybe [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (Maybe [GlobalRdrEltX info] -> [GlobalRdrEltX info])
-> Maybe [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall a b. (a -> b) -> a -> b
$ GlobalRdrEnvX info -> OccName -> Maybe [GlobalRdrEltX info]
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv GlobalRdrEnvX info
env OccName
occ
      rel :: WhichGREs info
rel@(RelevantGREs{}) ->
        (GlobalRdrEltX info -> Bool)
-> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall a. (a -> Bool) -> [a] -> [a]
filter (WhichGREs GREInfo -> NameSpace -> GlobalRdrElt -> Bool
greIsRelevant WhichGREs info
WhichGREs GREInfo
rel (OccName -> NameSpace
occNameSpace OccName
occ)) ([GlobalRdrEltX info] -> [GlobalRdrEltX info])
-> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall a b. (a -> b) -> a -> b
$
          [[GlobalRdrEltX info]] -> [GlobalRdrEltX info]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[GlobalRdrEltX info]] -> [GlobalRdrEltX info])
-> [[GlobalRdrEltX info]] -> [GlobalRdrEltX info]
forall a b. (a -> b) -> a -> b
$ GlobalRdrEnvX info -> OccName -> [[GlobalRdrEltX info]]
forall a. OccEnv a -> OccName -> [a]
lookupOccEnv_AllNameSpaces GlobalRdrEnvX info
env OccName
occ
  LookupRdrName RdrName
rdr WhichGREs info
rel ->
    RdrName -> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall info.
RdrName -> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
pickGREs RdrName
rdr ([GlobalRdrEltX info] -> [GlobalRdrEltX info])
-> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall a b. (a -> b) -> a -> b
$ GlobalRdrEnvX info -> LookupGRE info -> [GlobalRdrEltX info]
forall info.
GlobalRdrEnvX info -> LookupGRE info -> [GlobalRdrEltX info]
lookupGRE GlobalRdrEnvX info
env (OccName -> WhichGREs info -> LookupGRE info
forall info. OccName -> WhichGREs info -> LookupGRE info
LookupOccName (RdrName -> OccName
rdrNameOcc RdrName
rdr) WhichGREs info
rel)
  LookupExactName { lookupExactName :: forall info. LookupGRE info -> Name
lookupExactName = Name
nm
                  , lookInAllNameSpaces :: forall info. LookupGRE info -> Bool
lookInAllNameSpaces = Bool
all_ns } ->
      [ GlobalRdrEltX info
gre | GlobalRdrEltX info
gre <- [GlobalRdrEltX info]
lkup, GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrEltX info
gre Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
nm ]
    where
      occ :: OccName
occ = Name -> OccName
nameOccName Name
nm
      lkup :: [GlobalRdrEltX info]
lkup | Bool
all_ns    = [[GlobalRdrEltX info]] -> [GlobalRdrEltX info]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[GlobalRdrEltX info]] -> [GlobalRdrEltX info])
-> [[GlobalRdrEltX info]] -> [GlobalRdrEltX info]
forall a b. (a -> b) -> a -> b
$ GlobalRdrEnvX info -> OccName -> [[GlobalRdrEltX info]]
forall a. OccEnv a -> OccName -> [a]
lookupOccEnv_AllNameSpaces GlobalRdrEnvX info
env OccName
occ
           | Bool
otherwise = [GlobalRdrEltX info]
-> Maybe [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [GlobalRdrEltX info] -> [GlobalRdrEltX info])
-> Maybe [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall a b. (a -> b) -> a -> b
$ GlobalRdrEnvX info -> OccName -> Maybe [GlobalRdrEltX info]
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv GlobalRdrEnvX info
env OccName
occ
  LookupChildren OccName
occ LookupChild
which_child ->
    let ns :: NameSpace
ns = OccName -> NameSpace
occNameSpace OccName
occ
        all_gres :: [GlobalRdrEltX info]
all_gres = [[GlobalRdrEltX info]] -> [GlobalRdrEltX info]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[GlobalRdrEltX info]] -> [GlobalRdrEltX info])
-> [[GlobalRdrEltX info]] -> [GlobalRdrEltX info]
forall a b. (a -> b) -> a -> b
$ GlobalRdrEnvX info -> OccName -> [[GlobalRdrEltX info]]
forall a. OccEnv a -> OccName -> [a]
lookupOccEnv_AllNameSpaces GlobalRdrEnvX info
env OccName
occ
    in (GlobalRdrEltX info -> Maybe (Int, Int))
-> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall gre prio. Ord prio => (gre -> Maybe prio) -> [gre] -> [gre]
highestPriorityGREs (LookupChild -> NameSpace -> GlobalRdrEltX info -> Maybe (Int, Int)
forall info.
LookupChild -> NameSpace -> GlobalRdrEltX info -> Maybe (Int, Int)
childGREPriority LookupChild
which_child NameSpace
ns) [GlobalRdrEltX info]
all_gres

-- | Collect the 'GlobalRdrElt's with the highest priority according
-- to the given function (lower value <=> higher priority).
--
-- This allows us to first look in e.g. the data 'NameSpace', and then fall back
-- to the type/class 'NameSpace'.
highestPriorityGREs :: forall gre prio
                    .  Ord prio
                    => (gre -> Maybe prio)
                      -- ^ priority function
                      -- lower value <=> higher priority
                    -> [gre] -> [gre]
highestPriorityGREs :: forall gre prio. Ord prio => (gre -> Maybe prio) -> [gre] -> [gre]
highestPriorityGREs gre -> Maybe prio
priority [gre]
gres =
  [NonEmpty (Arg prio gre)] -> [gre]
take_highest_prio ([NonEmpty (Arg prio gre)] -> [gre])
-> [NonEmpty (Arg prio gre)] -> [gre]
forall a b. (a -> b) -> a -> b
$ [Arg prio gre] -> [NonEmpty (Arg prio gre)]
forall (f :: * -> *) a. (Foldable f, Eq a) => f a -> [NonEmpty a]
NE.group ([Arg prio gre] -> [NonEmpty (Arg prio gre)])
-> [Arg prio gre] -> [NonEmpty (Arg prio gre)]
forall a b. (a -> b) -> a -> b
$ [Arg prio gre] -> [Arg prio gre]
forall a. Ord a => [a] -> [a]
sort
    [ prio -> gre -> Arg prio gre
forall a b. a -> b -> Arg a b
S.Arg prio
prio gre
gre
    | gre
gre <- [gre]
gres
    , prio
prio <- Maybe prio -> [prio]
forall a. Maybe a -> [a]
maybeToList (Maybe prio -> [prio]) -> Maybe prio -> [prio]
forall a b. (a -> b) -> a -> b
$ gre -> Maybe prio
priority gre
gre ]
  where
    take_highest_prio :: [NE.NonEmpty (S.Arg prio gre)] -> [gre]
    take_highest_prio :: [NonEmpty (Arg prio gre)] -> [gre]
take_highest_prio [] = []
    take_highest_prio (NonEmpty (Arg prio gre)
fs:[NonEmpty (Arg prio gre)]
_) = (Arg prio gre -> gre) -> [Arg prio gre] -> [gre]
forall a b. (a -> b) -> [a] -> [b]
map (\ (S.Arg prio
_ gre
gre) -> gre
gre) ([Arg prio gre] -> [gre]) -> [Arg prio gre] -> [gre]
forall a b. (a -> b) -> a -> b
$ NonEmpty (Arg prio gre) -> [Arg prio gre]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (Arg prio gre)
fs
{-# INLINEABLE highestPriorityGREs #-}

-- | Look for precisely this 'Name' in the environment,
-- in the __same 'NameSpace'__ as the 'Name'.
--
-- This tests whether it is in scope, ignoring anything
-- else that might be in scope which doesn't have the same 'Unique'.
lookupGRE_Name :: Outputable info => GlobalRdrEnvX info -> Name -> Maybe (GlobalRdrEltX info)
lookupGRE_Name :: forall info.
Outputable info =>
GlobalRdrEnvX info -> Name -> Maybe (GlobalRdrEltX info)
lookupGRE_Name GlobalRdrEnvX info
env Name
name =
  case GlobalRdrEnvX info -> LookupGRE info -> [GlobalRdrEltX info]
forall info.
GlobalRdrEnvX info -> LookupGRE info -> [GlobalRdrEltX info]
lookupGRE GlobalRdrEnvX info
env (LookupExactName { lookupExactName :: Name
lookupExactName = Name
name
                                      , lookInAllNameSpaces :: Bool
lookInAllNameSpaces = Bool
False }) of
      []    -> Maybe (GlobalRdrEltX info)
forall a. Maybe a
Nothing
      [GlobalRdrEltX info
gre] -> GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
forall a. a -> Maybe a
Just GlobalRdrEltX info
gre
      [GlobalRdrEltX info]
gres  -> String -> SDoc -> Maybe (GlobalRdrEltX info)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"lookupGRE_Name"
                        (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Name -> OccName
nameOccName Name
name) SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ [GlobalRdrEltX info] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [GlobalRdrEltX info]
gres)
               -- See INVARIANT 1 on GlobalRdrEnv

-- | Look for a particular record field selector in the environment.
lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe FieldGlobalRdrElt
lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt
lookupGRE_FieldLabel GlobalRdrEnv
env FieldLabel
fl =
  case GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
forall info.
Outputable info =>
GlobalRdrEnvX info -> Name -> Maybe (GlobalRdrEltX info)
lookupGRE_Name GlobalRdrEnv
env (FieldLabel -> Name
flSelector FieldLabel
fl) of
    Maybe GlobalRdrElt
Nothing -> Maybe GlobalRdrElt
forall a. Maybe a
Nothing
    Just GlobalRdrElt
gre ->
      Bool -> SDoc -> Maybe GlobalRdrElt -> Maybe GlobalRdrElt
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (GlobalRdrElt -> Bool
forall info. GlobalRdrEltX info -> Bool
isRecFldGRE GlobalRdrElt
gre)
        ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"lookupGre_FieldLabel:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> FieldLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr FieldLabel
fl ]) (Maybe GlobalRdrElt -> Maybe GlobalRdrElt)
-> Maybe GlobalRdrElt -> Maybe GlobalRdrElt
forall a b. (a -> b) -> a -> b
$
        GlobalRdrElt -> Maybe GlobalRdrElt
forall a. a -> Maybe a
Just GlobalRdrElt
gre

getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]]
-- Returns all the qualifiers by which 'x' is in scope
-- Nothing means "the unqualified version is in scope"
-- [] means the thing is not in scope at all
getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]]
getGRE_NameQualifier_maybes GlobalRdrEnv
env Name
name
  = case GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
forall info.
Outputable info =>
GlobalRdrEnvX info -> Name -> Maybe (GlobalRdrEltX info)
lookupGRE_Name GlobalRdrEnv
env Name
name of
      Just GlobalRdrElt
gre -> [GlobalRdrElt -> Maybe [ModuleName]
forall {info}. GlobalRdrEltX info -> Maybe [ModuleName]
qualifier_maybe GlobalRdrElt
gre]
      Maybe GlobalRdrElt
Nothing  -> []
  where
    qualifier_maybe :: GlobalRdrEltX info -> Maybe [ModuleName]
qualifier_maybe (GRE { gre_lcl :: forall info. GlobalRdrEltX info -> Bool
gre_lcl = Bool
lcl, gre_imp :: forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp = Bag 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) (Bag ImportSpec -> [ImportSpec]
forall a. Bag a -> [a]
bagToList Bag ImportSpec
iss)

-- | Is this 'GlobalRdrElt' defined locally?
isLocalGRE :: GlobalRdrEltX info -> Bool
isLocalGRE :: forall info. GlobalRdrEltX info -> Bool
isLocalGRE (GRE { gre_lcl :: forall info. GlobalRdrEltX info -> Bool
gre_lcl = Bool
lcl }) = Bool
lcl

-- | Is this 'GlobalRdrElt' imported?
--
-- Not just the negation of 'isLocalGRE', because it might be an Exact or
-- Orig name reference. See Note [GlobalRdrElt provenance].
isImportedGRE :: GlobalRdrEltX info -> Bool
isImportedGRE :: forall info. GlobalRdrEltX info -> Bool
isImportedGRE (GRE { gre_imp :: forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp = Bag ImportSpec
imps }) = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Bag ImportSpec -> Bool
forall a. Bag a -> Bool
isEmptyBag Bag ImportSpec
imps

-- | Is this a record field GRE?
--
-- Important: does /not/ consult the 'GreInfo' field.
isRecFldGRE :: GlobalRdrEltX info -> Bool
isRecFldGRE :: forall info. GlobalRdrEltX info -> Bool
isRecFldGRE (GRE { gre_name :: forall info. GlobalRdrEltX info -> Name
gre_name = Name
nm }) = Name -> Bool
isFieldName Name
nm

isDuplicateRecFldGRE :: GlobalRdrElt -> Bool
-- ^ Is this a record field defined with DuplicateRecordFields?
isDuplicateRecFldGRE :: GlobalRdrElt -> Bool
isDuplicateRecFldGRE =
    Bool -> (FieldLabel -> Bool) -> Maybe FieldLabel -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False ((DuplicateRecordFields
DuplicateRecordFields DuplicateRecordFields -> DuplicateRecordFields -> Bool
forall a. Eq a => a -> a -> Bool
==) (DuplicateRecordFields -> Bool)
-> (FieldLabel -> DuplicateRecordFields) -> FieldLabel -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLabel -> DuplicateRecordFields
flHasDuplicateRecordFields) (Maybe FieldLabel -> Bool)
-> (GlobalRdrElt -> Maybe FieldLabel) -> GlobalRdrElt -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Maybe FieldLabel
greFieldLabel_maybe

isNoFieldSelectorGRE :: GlobalRdrElt -> Bool
-- ^ Is this a record field defined with NoFieldSelectors?
-- (See Note [NoFieldSelectors] in GHC.Rename.Env)
isNoFieldSelectorGRE :: GlobalRdrElt -> Bool
isNoFieldSelectorGRE =
    Bool -> (FieldLabel -> Bool) -> Maybe FieldLabel -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False ((FieldSelectors
NoFieldSelectors FieldSelectors -> FieldSelectors -> Bool
forall a. Eq a => a -> a -> Bool
==) (FieldSelectors -> Bool)
-> (FieldLabel -> FieldSelectors) -> FieldLabel -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLabel -> FieldSelectors
flHasFieldSelector) (Maybe FieldLabel -> Bool)
-> (GlobalRdrElt -> Maybe FieldLabel) -> GlobalRdrElt -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Maybe FieldLabel
greFieldLabel_maybe

isFieldSelectorGRE :: GlobalRdrElt -> Bool
-- ^ Is this a record field defined with FieldSelectors?
-- (See Note [NoFieldSelectors] in GHC.Rename.Env)
isFieldSelectorGRE :: GlobalRdrElt -> Bool
isFieldSelectorGRE =
    Bool -> (FieldLabel -> Bool) -> Maybe FieldLabel -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False ((FieldSelectors
FieldSelectors FieldSelectors -> FieldSelectors -> Bool
forall a. Eq a => a -> a -> Bool
==) (FieldSelectors -> Bool)
-> (FieldLabel -> FieldSelectors) -> FieldLabel -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLabel -> FieldSelectors
flHasFieldSelector) (Maybe FieldLabel -> Bool)
-> (GlobalRdrElt -> Maybe FieldLabel) -> GlobalRdrElt -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Maybe FieldLabel
greFieldLabel_maybe

greFieldLabel_maybe :: GlobalRdrElt -> Maybe FieldLabel
-- ^ Returns the field label of this GRE, if it has one
greFieldLabel_maybe :: GlobalRdrElt -> Maybe FieldLabel
greFieldLabel_maybe = (GlobalRdrElt -> FieldLabel)
-> Maybe GlobalRdrElt -> Maybe FieldLabel
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (() :: Constraint) => GlobalRdrElt -> FieldLabel
GlobalRdrElt -> FieldLabel
fieldGRELabel (Maybe GlobalRdrElt -> Maybe FieldLabel)
-> (GlobalRdrElt -> Maybe GlobalRdrElt)
-> GlobalRdrElt
-> Maybe FieldLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrElt -> Maybe GlobalRdrElt
fieldGRE_maybe

unQualOK :: GlobalRdrEltX info -> Bool
-- ^ Test if an unqualified version of this thing would be in scope
unQualOK :: forall info. GlobalRdrEltX info -> Bool
unQualOK (GRE {gre_lcl :: forall info. GlobalRdrEltX info -> Bool
gre_lcl = Bool
lcl, gre_imp :: forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp = Bag ImportSpec
iss })
  | Bool
lcl = Bool
True
  | Bool
otherwise = (ImportSpec -> Bool) -> Bag ImportSpec -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ImportSpec -> Bool
unQualSpecOK Bag ImportSpec
iss

{- Note [GRE filtering]
~~~~~~~~~~~~~~~~~~~~~~~
(pickGREs rdr gres) takes a list of GREs which have the same OccName
as 'rdr', say "x".  It does two things:

(a) filters the GREs to a subset that are in scope
    * Qualified,   as 'M.x'  if want_qual    is Qual M _
    * Unqualified, as 'x'    if want_unqual  is Unqual _

(b) for that subset, filter the provenance field (gre_lcl and gre_imp)
    to ones that brought it into scope qualified or unqualified resp.

Example:
      module A ( f ) where
      import qualified Foo( f )
      import Baz( f )
      f = undefined

Let's suppose that Foo.f and Baz.f are the same entity really, but the local
'f' is different, so there will be two GREs matching "f":
   gre1:  gre_lcl = True,  gre_imp = []
   gre2:  gre_lcl = False, gre_imp = [ imported from Foo, imported from Bar ]

The use of "f" in the export list is ambiguous because it's in scope
from the local def and the import Baz(f); but *not* the import qualified Foo.
pickGREs returns two GRE
   gre1:   gre_lcl = True,  gre_imp = []
   gre2:   gre_lcl = False, gre_imp = [ imported from Bar ]

Now the "ambiguous occurrence" message can correctly report how the
ambiguity arises.
-}

pickGREs :: RdrName -> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
-- ^ Takes a list of GREs which have the right OccName 'x'
-- Pick those GREs that are in scope
--    * Qualified,   as 'M.x'  if want_qual    is Qual M _
--    * Unqualified, as 'x'    if want_unqual  is Unqual _
--
-- Return each such GRE, with its ImportSpecs filtered, to reflect
-- how it is in scope qualified or unqualified respectively.
-- See Note [GRE filtering]
pickGREs :: forall info.
RdrName -> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
pickGREs (Unqual {})  [GlobalRdrEltX info]
gres = (GlobalRdrEltX info -> Maybe (GlobalRdrEltX info))
-> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
forall info. GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
pickUnqualGRE     [GlobalRdrEltX info]
gres
pickGREs (Qual ModuleName
mod OccName
_) [GlobalRdrEltX info]
gres = (GlobalRdrEltX info -> Maybe (GlobalRdrEltX info))
-> [GlobalRdrEltX info] -> [GlobalRdrEltX info]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (ModuleName -> GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
forall info.
ModuleName -> GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
pickQualGRE ModuleName
mod) [GlobalRdrEltX info]
gres
pickGREs RdrName
_            [GlobalRdrEltX info]
_    = []  -- I don't think this actually happens

pickUnqualGRE :: GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
pickUnqualGRE :: forall info. GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
pickUnqualGRE gre :: GlobalRdrEltX info
gre@(GRE { gre_lcl :: forall info. GlobalRdrEltX info -> Bool
gre_lcl = Bool
lcl, gre_imp :: forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp = Bag ImportSpec
iss })
  | Bool -> Bool
not Bool
lcl, Bag ImportSpec -> Bool
forall a. Bag a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Bag ImportSpec
iss' = Maybe (GlobalRdrEltX info)
forall a. Maybe a
Nothing
  | Bool
otherwise          = GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
forall a. a -> Maybe a
Just (GlobalRdrEltX info
gre { gre_imp = iss' })
  where
    iss' :: Bag ImportSpec
iss' = (ImportSpec -> Bool) -> Bag ImportSpec -> Bag ImportSpec
forall a. (a -> Bool) -> Bag a -> Bag a
filterBag ImportSpec -> Bool
unQualSpecOK Bag ImportSpec
iss

pickQualGRE :: ModuleName -> GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
pickQualGRE :: forall info.
ModuleName -> GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
pickQualGRE ModuleName
mod gre :: GlobalRdrEltX info
gre@(GRE { gre_lcl :: forall info. GlobalRdrEltX info -> Bool
gre_lcl = Bool
lcl, gre_imp :: forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp = Bag ImportSpec
iss })
  | Bool -> Bool
not Bool
lcl', Bag ImportSpec -> Bool
forall a. Bag a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Bag ImportSpec
iss' = Maybe (GlobalRdrEltX info)
forall a. Maybe a
Nothing
  | Bool
otherwise           = GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
forall a. a -> Maybe a
Just (GlobalRdrEltX info
gre { gre_lcl = lcl', gre_imp = iss' })
  where
    iss' :: Bag ImportSpec
iss' = (ImportSpec -> Bool) -> Bag ImportSpec -> Bag ImportSpec
forall a. (a -> Bool) -> Bag a -> Bag a
filterBag (ModuleName -> ImportSpec -> Bool
qualSpecOK ModuleName
mod) Bag ImportSpec
iss
    lcl' :: Bool
lcl' = Bool
lcl Bool -> Bool -> Bool
&& ModuleName -> Bool
name_is_from ModuleName
mod

    name_is_from :: ModuleName -> Bool
    name_is_from :: ModuleName -> Bool
name_is_from ModuleName
mod = case GlobalRdrEltX info -> Maybe Module
forall info. GlobalRdrEltX info -> Maybe Module
greDefinitionModule GlobalRdrEltX info
gre of
                         Just Module
n_mod -> Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
n_mod ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName
mod
                         Maybe Module
Nothing    -> Bool
False

pickGREsModExp :: ModuleName -> [GlobalRdrEltX info] -> [(GlobalRdrEltX info,GlobalRdrEltX info)]
-- ^ Pick GREs that are in scope *both* qualified *and* unqualified
-- Return each GRE that is, as a pair
--    (qual_gre, unqual_gre)
-- These two GREs are the original GRE with imports filtered to express how
-- it is in scope qualified an unqualified respectively
--
-- Used only for the 'module M' item in export list;
--   see 'GHC.Tc.Gen.Export.exports_from_avail'
pickGREsModExp :: forall info.
ModuleName
-> [GlobalRdrEltX info]
-> [(GlobalRdrEltX info, GlobalRdrEltX info)]
pickGREsModExp ModuleName
mod [GlobalRdrEltX info]
gres = (GlobalRdrEltX info
 -> Maybe (GlobalRdrEltX info, GlobalRdrEltX info))
-> [GlobalRdrEltX info]
-> [(GlobalRdrEltX info, GlobalRdrEltX info)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (ModuleName
-> GlobalRdrEltX info
-> Maybe (GlobalRdrEltX info, GlobalRdrEltX info)
forall info.
ModuleName
-> GlobalRdrEltX info
-> Maybe (GlobalRdrEltX info, GlobalRdrEltX info)
pickBothGRE ModuleName
mod) [GlobalRdrEltX info]
gres

-- | isBuiltInSyntax filter out names for built-in syntax They
-- just clutter up the environment (esp tuples), and the
-- parser will generate Exact RdrNames for them, so the
-- cluttered envt is no use.  Really, it's only useful for
-- GHC.Base and GHC.Tuple.
pickBothGRE :: ModuleName -> GlobalRdrEltX info -> Maybe (GlobalRdrEltX info, GlobalRdrEltX info)
pickBothGRE :: forall info.
ModuleName
-> GlobalRdrEltX info
-> Maybe (GlobalRdrEltX info, GlobalRdrEltX info)
pickBothGRE ModuleName
mod GlobalRdrEltX info
gre
  | Name -> Bool
isBuiltInSyntax (GlobalRdrEltX info -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrEltX info
gre)
  = Maybe (GlobalRdrEltX info, GlobalRdrEltX info)
forall a. Maybe a
Nothing
  | Just GlobalRdrEltX info
gre1 <- ModuleName -> GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
forall info.
ModuleName -> GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
pickQualGRE ModuleName
mod GlobalRdrEltX info
gre
  , Just GlobalRdrEltX info
gre2 <- GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
forall info. GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
pickUnqualGRE   GlobalRdrEltX info
gre
  = (GlobalRdrEltX info, GlobalRdrEltX info)
-> Maybe (GlobalRdrEltX info, GlobalRdrEltX info)
forall a. a -> Maybe a
Just (GlobalRdrEltX info
gre1, GlobalRdrEltX info
gre2)
  | Bool
otherwise
  = Maybe (GlobalRdrEltX info, GlobalRdrEltX info)
forall a. Maybe a
Nothing

-- Building GlobalRdrEnvs

plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
plusGlobalRdrEnv GlobalRdrEnv
env1 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 a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE) GlobalRdrEnv
env1 GlobalRdrEnv
env2

mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv
mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv
mkGlobalRdrEnv [GlobalRdrElt]
gres
  = (GlobalRdrElt -> GlobalRdrEnv -> GlobalRdrEnv)
-> GlobalRdrEnv -> [GlobalRdrElt] -> GlobalRdrEnv
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr GlobalRdrElt -> GlobalRdrEnv -> GlobalRdrEnv
add GlobalRdrEnv
forall info. GlobalRdrEnvX info
emptyGlobalRdrEnv [GlobalRdrElt]
gres
  where
    add :: GlobalRdrElt -> GlobalRdrEnv -> GlobalRdrEnv
add GlobalRdrElt
gre 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]
Utils.singleton GlobalRdrEnv
env
                                   (GlobalRdrElt -> OccName
forall info. GlobalRdrEltX info -> OccName
greOccName GlobalRdrElt
gre)
                                   GlobalRdrElt
gre

insertGRE :: GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE :: GlobalRdrElt -> [GlobalRdrElt] -> [GlobalRdrElt]
insertGRE GlobalRdrElt
new_g [] = [GlobalRdrElt
new_g]
insertGRE GlobalRdrElt
new_g (GlobalRdrElt
old_g : [GlobalRdrElt]
old_gs)
        | GlobalRdrElt -> Name
forall info. GlobalRdrEltX info -> Name
greName GlobalRdrElt
new_g Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== GlobalRdrElt -> Name
forall info. GlobalRdrEltX info -> Name
greName 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
-- Used when the gre_name fields match
plusGRE :: GlobalRdrElt -> GlobalRdrElt -> GlobalRdrElt
plusGRE GlobalRdrElt
g1 GlobalRdrElt
g2
  = GRE { gre_name :: Name
gre_name = GlobalRdrElt -> Name
forall info. GlobalRdrEltX info -> Name
gre_name GlobalRdrElt
g1
        , gre_lcl :: Bool
gre_lcl  = GlobalRdrElt -> Bool
forall info. GlobalRdrEltX info -> Bool
gre_lcl GlobalRdrElt
g1 Bool -> Bool -> Bool
|| GlobalRdrElt -> Bool
forall info. GlobalRdrEltX info -> Bool
gre_lcl GlobalRdrElt
g2
        , gre_imp :: Bag ImportSpec
gre_imp  = GlobalRdrElt -> Bag ImportSpec
forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp GlobalRdrElt
g1 Bag ImportSpec -> Bag ImportSpec -> Bag ImportSpec
forall a. Bag a -> Bag a -> Bag a
`unionBags` GlobalRdrElt -> Bag ImportSpec
forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp GlobalRdrElt
g2
        , gre_par :: Parent
gre_par  = GlobalRdrElt -> Parent
forall info. GlobalRdrEltX info -> Parent
gre_par GlobalRdrElt
g1 Parent -> Parent -> Parent
`plusParent` GlobalRdrElt -> Parent
forall info. GlobalRdrEltX info -> Parent
gre_par GlobalRdrElt
g2
        , gre_info :: GREInfo
gre_info = GlobalRdrElt -> GREInfo
forall info. GlobalRdrEltX info -> info
gre_info GlobalRdrElt
g1 GREInfo -> GREInfo -> GREInfo
`plusGREInfo` GlobalRdrElt -> GREInfo
forall info. GlobalRdrEltX info -> info
gre_info GlobalRdrElt
g2 }

transformGREs :: (GlobalRdrElt -> GlobalRdrElt)
              -> [OccName]
              -> GlobalRdrEnv -> GlobalRdrEnv
-- ^ Apply a transformation function to the GREs for these OccNames
transformGREs :: (GlobalRdrElt -> GlobalRdrElt)
-> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv
transformGREs GlobalRdrElt -> GlobalRdrElt
trans_gre [OccName]
occs GlobalRdrEnv
rdr_env
  = (OccName -> GlobalRdrEnv -> GlobalRdrEnv)
-> GlobalRdrEnv -> [OccName] -> GlobalRdrEnv
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr OccName -> GlobalRdrEnv -> GlobalRdrEnv
trans GlobalRdrEnv
rdr_env [OccName]
occs
  where
    trans :: OccName -> GlobalRdrEnv -> GlobalRdrEnv
trans OccName
occ GlobalRdrEnv
env
      = case GlobalRdrEnv -> OccName -> Maybe [GlobalRdrElt]
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv GlobalRdrEnv
env OccName
occ of
           Just [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)
           Maybe [GlobalRdrElt]
Nothing   -> GlobalRdrEnv
env

extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
extendGlobalRdrEnv GlobalRdrEnv
env 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]
Utils.singleton GlobalRdrEnv
env
                     (GlobalRdrElt -> OccName
forall info. GlobalRdrEltX info -> OccName
greOccName GlobalRdrElt
gre) GlobalRdrElt
gre

{- Note [GlobalRdrEnv shadowing]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Before adding new names to the GlobalRdrEnv we nuke some existing entries;
this is "shadowing".  The actual work is done by GHC.Types.Name.Reader.shadowNames.
Suppose

   env' = shadowNames env { f } `extendGlobalRdrEnv` { M.f }

Then:
   * Looking up (Unqual f) in env' should succeed, returning M.f,
     even if env contains existing unqualified bindings for f.
     They are shadowed

   * Looking up (Qual M.f) in env' should succeed, returning M.f

   * Looking up (Qual X.f) in env', where X /= M, should be the same as
     looking up (Qual X.f) in env.

     That is, shadowNames does /not/ delete earlier qualified bindings

There are two reasons for shadowing:

* The GHCi REPL

  - Ids bought into scope on the command line (eg let x = True) have
    External Names, like Ghci4.x.  We want a new binding for 'x' (say)
    to override the existing binding for 'x'.  Example:

           ghci> :load M    -- Brings `x` and `M.x` into scope
           ghci> x
           ghci> "Hello"
           ghci> M.x
           ghci> "hello"
           ghci> let x = True  -- Shadows `x`
           ghci> x             -- The locally bound `x`
                               -- NOT an ambiguous reference
           ghci> True
           ghci> M.x           -- M.x is still in scope!
           ghci> "Hello"

    So when we add `x = True` we must not delete the `M.x` from the
    `GlobalRdrEnv`; rather we just want to make it "qualified only";
    hence the `set_qual` in `shadowNames`.  See also Note
    [Interactively-bound Ids in GHCi] in GHC.Runtime.Context

  - Data types also have External Names, like Ghci4.T; but we still want
    'T' to mean the newly-declared 'T', not an old one.

* Nested Template Haskell declaration brackets
  See Note [Top-level Names in Template Haskell decl quotes] in GHC.Rename.Names

  Consider a TH decl quote:
      module M where
        f x = h [d| f = ...f...M.f... |]
  We must shadow the outer unqualified binding of 'f', else we'll get
  a complaint when extending the GlobalRdrEnv, saying that there are
  two bindings for 'f'.  There are several tricky points:

    - This shadowing applies even if the binding for 'f' is in a
      where-clause, and hence is in the *local* RdrEnv not the *global*
      RdrEnv.  This is done in lcl_env_TH in extendGlobalRdrEnvRn.

    - The External Name M.f from the enclosing module must certainly
      still be available.  So we don't nuke it entirely; we just make
      it seem like qualified import.

    - We only shadow *External* names (which come from the main module),
      or from earlier GHCi commands. Do not shadow *Internal* names
      because in the bracket
          [d| class C a where f :: a
              f = 4 |]
      rnSrcDecls will first call extendGlobalRdrEnvRn with C[f] from the
      class decl, and *separately* extend the envt with the value binding.
      At that stage, the class op 'f' will have an Internal name.

Wrinkle [Shadowing namespaces]

  In the following GHCi session:

    > data A = MkA { foo :: Int }
    > foo = False
    > bar = foo

  We expect the variable 'foo' to shadow the record field 'foo', even though
  they are in separate namespaces, so that the occurrence of 'foo' in the body
  of 'bar' is not ambiguous.

-}

shadowNames :: Bool -- ^ discard names that are only available qualified?
            -> GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
-- Remove certain old GREs that share the same OccName as this new Name.
-- See Note [GlobalRdrEnv shadowing] for details
shadowNames :: Bool -> GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
shadowNames Bool
drop_only_qualified GlobalRdrEnv
env GlobalRdrEnv
new_gres = (UniqFM NameSpace [GlobalRdrElt]
 -> UniqFM NameSpace [GlobalRdrElt]
 -> UniqFM NameSpace [GlobalRdrElt])
-> GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
forall a b.
(UniqFM NameSpace a -> UniqFM NameSpace b -> UniqFM NameSpace a)
-> OccEnv a -> OccEnv b -> OccEnv a
minusOccEnv_C_Ns UniqFM NameSpace [GlobalRdrElt]
-> UniqFM NameSpace [GlobalRdrElt]
-> UniqFM NameSpace [GlobalRdrElt]
do_shadowing GlobalRdrEnv
env GlobalRdrEnv
new_gres
  where

    do_shadowing :: UniqFM NameSpace [GlobalRdrElt]
                 -> UniqFM NameSpace [GlobalRdrElt]
                 -> UniqFM NameSpace [GlobalRdrElt]
    do_shadowing :: UniqFM NameSpace [GlobalRdrElt]
-> UniqFM NameSpace [GlobalRdrElt]
-> UniqFM NameSpace [GlobalRdrElt]
do_shadowing UniqFM NameSpace [GlobalRdrElt]
olds UniqFM NameSpace [GlobalRdrElt]
news =
      -- Start off by accumulating all 'NameSpace's shadowed
      -- by the entire collection of new GREs.
      let shadowed_gres :: ShadowedGREs
          shadowed_gres :: ShadowedGREs
shadowed_gres =
            ([GlobalRdrElt] -> ShadowedGREs -> ShadowedGREs)
-> ShadowedGREs -> UniqFM NameSpace [GlobalRdrElt] -> ShadowedGREs
forall elt a key. (elt -> a -> a) -> a -> UniqFM key elt -> a
nonDetFoldUFM (\ [GlobalRdrElt]
gres ShadowedGREs
shads -> (GlobalRdrElt -> ShadowedGREs) -> [GlobalRdrElt] -> ShadowedGREs
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap GlobalRdrElt -> ShadowedGREs
greShadowedNameSpaces [GlobalRdrElt]
gres ShadowedGREs -> ShadowedGREs -> ShadowedGREs
forall a. Semigroup a => a -> a -> a
S.<> ShadowedGREs
shads)
              ShadowedGREs
forall a. Monoid a => a
mempty UniqFM NameSpace [GlobalRdrElt]
news

      -- Then shadow the old 'GlobalRdrElt's, now that we know which 'NameSpace's
      -- should be shadowed.
          shadow_list :: Unique -> [GlobalRdrElt] -> Maybe [GlobalRdrElt]
          shadow_list :: Unique -> [GlobalRdrElt] -> Maybe [GlobalRdrElt]
shadow_list Unique
old_ns [GlobalRdrElt]
old_gres =
            case Unique -> ShadowedGREs -> IsShadowed
namespace_is_shadowed Unique
old_ns ShadowedGREs
shadowed_gres of
              IsShadowed
IsNotShadowed -> [GlobalRdrElt] -> Maybe [GlobalRdrElt]
forall a. a -> Maybe a
Just [GlobalRdrElt]
old_gres
              IsShadowed
IsShadowed    -> [GlobalRdrElt] -> Maybe [GlobalRdrElt]
forall a. [a] -> Maybe [a]
guard_nonEmpty ([GlobalRdrElt] -> Maybe [GlobalRdrElt])
-> [GlobalRdrElt] -> Maybe [GlobalRdrElt]
forall a b. (a -> b) -> a -> b
$ (GlobalRdrElt -> Maybe GlobalRdrElt)
-> [GlobalRdrElt] -> [GlobalRdrElt]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe GlobalRdrElt -> Maybe GlobalRdrElt
shadow [GlobalRdrElt]
old_gres
              IsShadowed
IsShadowedIfFieldSelector ->
                [GlobalRdrElt] -> Maybe [GlobalRdrElt]
forall a. [a] -> Maybe [a]
guard_nonEmpty ([GlobalRdrElt] -> Maybe [GlobalRdrElt])
-> [GlobalRdrElt] -> Maybe [GlobalRdrElt]
forall a b. (a -> b) -> a -> b
$
                (GlobalRdrElt -> Maybe GlobalRdrElt)
-> [GlobalRdrElt] -> [GlobalRdrElt]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\ GlobalRdrElt
old_gre -> if GlobalRdrElt -> Bool
isFieldSelectorGRE GlobalRdrElt
old_gre then GlobalRdrElt -> Maybe GlobalRdrElt
shadow GlobalRdrElt
old_gre else GlobalRdrElt -> Maybe GlobalRdrElt
forall a. a -> Maybe a
Just GlobalRdrElt
old_gre)
                  [GlobalRdrElt]
old_gres

      -- Now do all of the shadowing in a single go. This avoids traversing
      -- the old GlobalRdrEnv multiple times over.
      in (Unique -> [GlobalRdrElt] -> Maybe [GlobalRdrElt])
-> UniqFM NameSpace [GlobalRdrElt]
-> UniqFM NameSpace [GlobalRdrElt]
forall elt1 elt2 key.
(Unique -> elt1 -> Maybe elt2)
-> UniqFM key elt1 -> UniqFM key elt2
mapMaybeWithKeyUFM Unique -> [GlobalRdrElt] -> Maybe [GlobalRdrElt]
shadow_list UniqFM NameSpace [GlobalRdrElt]
olds

    guard_nonEmpty :: [a] -> Maybe [a]
    guard_nonEmpty :: forall a. [a] -> Maybe [a]
guard_nonEmpty [a]
xs | [a] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
xs   = Maybe [a]
forall a. Maybe a
Nothing
                      | Bool
otherwise = [a] -> Maybe [a]
forall a. a -> Maybe a
Just [a]
xs

    -- Shadow a single GRE, by either qualifying it or removing it entirely.
    shadow :: GlobalRdrElt-> Maybe GlobalRdrElt
    shadow :: GlobalRdrElt -> Maybe GlobalRdrElt
shadow old_gre :: GlobalRdrElt
old_gre@(GRE { gre_lcl :: forall info. GlobalRdrEltX info -> Bool
gre_lcl = Bool
lcl, gre_imp :: forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp = Bag ImportSpec
iss }) =
      case GlobalRdrElt -> Maybe Module
forall info. GlobalRdrEltX info -> Maybe Module
greDefinitionModule GlobalRdrElt
old_gre of
        Maybe Module
Nothing -> GlobalRdrElt -> Maybe GlobalRdrElt
forall a. a -> Maybe a
Just GlobalRdrElt
old_gre   -- Old name is Internal; do not shadow
        Just Module
old_mod
           |  Bag ImportSpec -> Bool
forall a. Bag a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Bag ImportSpec
iss'            -- Nothing remains
           Bool -> Bool -> Bool
|| Bool
drop_only_qualified
           -> Maybe GlobalRdrElt
forall a. Maybe a
Nothing

           | Bool
otherwise
           -> GlobalRdrElt -> Maybe GlobalRdrElt
forall a. a -> Maybe a
Just (GlobalRdrElt
old_gre { gre_lcl = False, gre_imp = iss' })

           where
             iss' :: Bag ImportSpec
iss' = Bag ImportSpec
lcl_imp Bag ImportSpec -> Bag ImportSpec -> Bag ImportSpec
forall a. Bag a -> Bag a -> Bag a
`unionBags` (ImportSpec -> ImportSpec) -> Bag ImportSpec -> Bag ImportSpec
forall a b. (a -> b) -> Bag a -> Bag b
mapBag ImportSpec -> ImportSpec
set_qual Bag ImportSpec
iss
             lcl_imp :: Bag ImportSpec
lcl_imp | Bool
lcl       = ImportSpec -> Bag ImportSpec
forall a. a -> Bag a
unitBag (ImportSpec -> Bag ImportSpec) -> ImportSpec -> Bag ImportSpec
forall a b. (a -> b) -> a -> b
$ GlobalRdrElt -> Module -> ImportSpec
forall {info}. GlobalRdrEltX info -> Module -> ImportSpec
mk_fake_imp_spec GlobalRdrElt
old_gre Module
old_mod
                     | Bool
otherwise = Bag ImportSpec
forall a. Bag a
emptyBag

    mk_fake_imp_spec :: GlobalRdrEltX info -> Module -> ImportSpec
mk_fake_imp_spec GlobalRdrEltX info
old_gre Module
old_mod    -- Urgh!
      = ImpDeclSpec -> ImpItemSpec -> ImportSpec
ImpSpec ImpDeclSpec
id_spec ImpItemSpec
ImpAll
      where
        old_mod_name :: ModuleName
old_mod_name = Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
old_mod
        id_spec :: ImpDeclSpec
id_spec      = ImpDeclSpec { is_mod :: Module
is_mod = Module
old_mod
                                   , is_as :: ModuleName
is_as = ModuleName
old_mod_name
                                   , is_qual :: Bool
is_qual = Bool
True
                                   , is_dloc :: SrcSpan
is_dloc = GlobalRdrEltX info -> SrcSpan
forall info. GlobalRdrEltX info -> SrcSpan
greDefinitionSrcSpan GlobalRdrEltX info
old_gre }

    set_qual :: ImportSpec -> ImportSpec
    set_qual :: ImportSpec -> ImportSpec
set_qual ImportSpec
is = ImportSpec
is { is_decl = (is_decl is) { is_qual = True } }

-- | @greClashesWith new_gre old_gre@ computes whether @new_gre@ clashes
-- with @old_gre@ (assuming they both have the same underlying 'occNameFS').
greClashesWith :: GlobalRdrElt -> (GlobalRdrElt -> Bool)
greClashesWith :: GlobalRdrElt -> GlobalRdrElt -> Bool
greClashesWith GlobalRdrElt
new_gre GlobalRdrElt
old_gre =
  GlobalRdrElt
old_gre GlobalRdrElt -> ShadowedGREs -> Bool
`greIsShadowed` GlobalRdrElt -> ShadowedGREs
greShadowedNameSpaces GlobalRdrElt
new_gre

-- | Is the given 'GlobalRdrElt' shadowed, as specified by the 'ShadowedNameSpace's?
greIsShadowed :: GlobalRdrElt -> ShadowedGREs -> Bool
greIsShadowed :: GlobalRdrElt -> ShadowedGREs -> Bool
greIsShadowed GlobalRdrElt
old_gre ShadowedGREs
shadowed =
  case NameSpace -> Unique
forall a. Uniquable a => a -> Unique
getUnique NameSpace
old_ns Unique -> ShadowedGREs -> IsShadowed
`namespace_is_shadowed` ShadowedGREs
shadowed of
    IsShadowed
IsShadowed                -> Bool
True
    IsShadowed
IsNotShadowed             -> Bool
False
    IsShadowed
IsShadowedIfFieldSelector -> GlobalRdrElt -> Bool
isFieldSelectorGRE GlobalRdrElt
old_gre
  where
    old_ns :: NameSpace
old_ns = OccName -> NameSpace
occNameSpace (OccName -> NameSpace) -> OccName -> NameSpace
forall a b. (a -> b) -> a -> b
$ GlobalRdrElt -> OccName
forall info. GlobalRdrEltX info -> OccName
greOccName GlobalRdrElt
old_gre


-- | Whether a 'GlobalRdrElt' is definitely shadowed, definitely not shadowed,
-- or conditionally shadowed based on more information beyond the 'NameSpace'.
data IsShadowed
  -- | The GRE is not shadowed.
  = IsNotShadowed
  -- | The GRE is shadowed.
  | IsShadowed
  -- | The GRE is shadowed iff it is a record field GRE
  -- which defines a field selector (i.e. FieldSelectors is enabled in its
  -- defining module).
  | IsShadowedIfFieldSelector

-- | Internal function: is a 'GlobalRdrElt' with the 'NameSpace' with given
-- 'Unique' shadowed by the specified 'ShadowedGREs'?
namespace_is_shadowed :: Unique -> ShadowedGREs -> IsShadowed
namespace_is_shadowed :: Unique -> ShadowedGREs -> IsShadowed
namespace_is_shadowed Unique
old_ns (ShadowedGREs UniqSet NameSpace
shadowed_nonflds ShadowedFieldGREs
shadowed_flds)
  | Unique -> Bool
isFldNSUnique Unique
old_ns
  = case ShadowedFieldGREs
shadowed_flds of
      ShadowedFieldGREs
ShadowAllFieldGREs -> IsShadowed
IsShadowed
      ShadowFieldSelectorsAnd UniqSet NameSpace
shadowed
        | Unique
old_ns Unique -> UniqSet NameSpace -> Bool
forall a. Unique -> UniqSet a -> Bool
`elemUniqSet_Directly` UniqSet NameSpace
shadowed
        -> IsShadowed
IsShadowed
        | Bool
otherwise
        -> IsShadowed
IsShadowedIfFieldSelector
      ShadowFieldNameSpaces UniqSet NameSpace
shadowed
        | Unique
old_ns Unique -> UniqSet NameSpace -> Bool
forall a. Unique -> UniqSet a -> Bool
`elemUniqSet_Directly` UniqSet NameSpace
shadowed
        -> IsShadowed
IsShadowed
        | Bool
otherwise
        -> IsShadowed
IsNotShadowed
  | Unique
old_ns Unique -> UniqSet NameSpace -> Bool
forall a. Unique -> UniqSet a -> Bool
`elemUniqSet_Directly` UniqSet NameSpace
shadowed_nonflds
  = IsShadowed
IsShadowed
  | Bool
otherwise
  = IsShadowed
IsNotShadowed

-- | What are all the 'GlobalRdrElt's that are shadowed by this new 'GlobalRdrElt'?
greShadowedNameSpaces :: GlobalRdrElt -> ShadowedGREs
greShadowedNameSpaces :: GlobalRdrElt -> ShadowedGREs
greShadowedNameSpaces GlobalRdrElt
gre = UniqSet NameSpace -> ShadowedFieldGREs -> ShadowedGREs
ShadowedGREs UniqSet NameSpace
shadowed_nonflds ShadowedFieldGREs
shadowed_flds
  where
    ns :: NameSpace
ns = OccName -> NameSpace
occNameSpace (OccName -> NameSpace) -> OccName -> NameSpace
forall a b. (a -> b) -> a -> b
$ GlobalRdrElt -> OccName
forall info. GlobalRdrEltX info -> OccName
greOccName GlobalRdrElt
gre
    !shadowed_nonflds :: UniqSet NameSpace
shadowed_nonflds
      | NameSpace -> Bool
isFieldNameSpace NameSpace
ns
      -- A new record field shadows variables if it defines a field selector.
      = if GlobalRdrElt -> Bool
isFieldSelectorGRE GlobalRdrElt
gre
        then NameSpace -> UniqSet NameSpace
forall a. Uniquable a => a -> UniqSet a
unitUniqSet NameSpace
varName
        else UniqSet NameSpace
forall a. UniqSet a
emptyUniqSet
      | Bool
otherwise
      = NameSpace -> UniqSet NameSpace
forall a. Uniquable a => a -> UniqSet a
unitUniqSet NameSpace
ns
    !shadowed_flds :: ShadowedFieldGREs
shadowed_flds
      | NameSpace
ns NameSpace -> NameSpace -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace
varName
      -- A new variable shadows record fields with field selectors.
      = UniqSet NameSpace -> ShadowedFieldGREs
ShadowFieldSelectorsAnd UniqSet NameSpace
forall a. UniqSet a
emptyUniqSet
      | NameSpace -> Bool
isFieldNameSpace NameSpace
ns
      -- A new record field shadows record fields unless it is a duplicate record field.
      = if GlobalRdrElt -> Bool
isDuplicateRecFldGRE GlobalRdrElt
gre
        then UniqSet NameSpace -> ShadowedFieldGREs
ShadowFieldNameSpaces (NameSpace -> UniqSet NameSpace
forall a. Uniquable a => a -> UniqSet a
unitUniqSet NameSpace
ns)
        -- NB: we must still shadow fields with the same constructor name.
        else ShadowedFieldGREs
ShadowAllFieldGREs
      | Bool
otherwise
      = UniqSet NameSpace -> ShadowedFieldGREs
ShadowFieldNameSpaces UniqSet NameSpace
forall a. UniqSet a
emptyUniqSet

-- | A description of which 'GlobalRdrElt's are shadowed.
data ShadowedGREs
  = ShadowedGREs
    { ShadowedGREs -> UniqSet NameSpace
shadowedNonFieldNameSpaces :: !(UniqSet NameSpace)
      -- ^ These specific non-field 'NameSpace's are shadowed.
    , ShadowedGREs -> ShadowedFieldGREs
shadowedFieldGREs :: !ShadowedFieldGREs
      -- ^ These field 'GlobalRdrElt's are shadowed.
    }

-- | A description of which record field 'GlobalRdrElt's are shadowed.
data ShadowedFieldGREs
  -- | All field 'GlobalRdrElt's are shadowed.
  = ShadowAllFieldGREs
  -- | Record field GREs defining field selectors, as well as those
  -- with the explicitly specified field 'NameSpace's, are shadowed.
  | ShadowFieldSelectorsAnd { ShadowedFieldGREs -> UniqSet NameSpace
shadowedFieldNameSpaces :: !(UniqSet NameSpace) }
  -- | These specific field 'NameSpace's are shadowed.
  | ShadowFieldNameSpaces { shadowedFieldNameSpaces :: !(UniqSet NameSpace) }

instance Monoid ShadowedFieldGREs where
  mempty :: ShadowedFieldGREs
mempty = ShadowFieldNameSpaces { shadowedFieldNameSpaces :: UniqSet NameSpace
shadowedFieldNameSpaces = UniqSet NameSpace
forall a. UniqSet a
emptyUniqSet }

instance Semigroup ShadowedFieldGREs where
  ShadowedFieldGREs
ShadowAllFieldGREs <> :: ShadowedFieldGREs -> ShadowedFieldGREs -> ShadowedFieldGREs
<> ShadowedFieldGREs
_ = ShadowedFieldGREs
ShadowAllFieldGREs
  ShadowedFieldGREs
_ <> ShadowedFieldGREs
ShadowAllFieldGREs = ShadowedFieldGREs
ShadowAllFieldGREs
  ShadowFieldSelectorsAnd UniqSet NameSpace
ns1 <> ShadowFieldSelectorsAnd UniqSet NameSpace
ns2 =
    UniqSet NameSpace -> ShadowedFieldGREs
ShadowFieldSelectorsAnd (UniqSet NameSpace
ns1 UniqSet NameSpace -> UniqSet NameSpace -> UniqSet NameSpace
forall a. Semigroup a => a -> a -> a
S.<> UniqSet NameSpace
ns2)
  ShadowFieldSelectorsAnd UniqSet NameSpace
ns1 <> ShadowFieldNameSpaces UniqSet NameSpace
ns2 =
    UniqSet NameSpace -> ShadowedFieldGREs
ShadowFieldSelectorsAnd (UniqSet NameSpace
ns1 UniqSet NameSpace -> UniqSet NameSpace -> UniqSet NameSpace
forall a. Semigroup a => a -> a -> a
S.<> UniqSet NameSpace
ns2)
  ShadowFieldNameSpaces UniqSet NameSpace
ns1 <> ShadowFieldSelectorsAnd UniqSet NameSpace
ns2 =
    UniqSet NameSpace -> ShadowedFieldGREs
ShadowFieldSelectorsAnd (UniqSet NameSpace
ns1 UniqSet NameSpace -> UniqSet NameSpace -> UniqSet NameSpace
forall a. Semigroup a => a -> a -> a
S.<> UniqSet NameSpace
ns2)
  ShadowFieldNameSpaces UniqSet NameSpace
ns1 <> ShadowFieldNameSpaces UniqSet NameSpace
ns2 =
    UniqSet NameSpace -> ShadowedFieldGREs
ShadowFieldNameSpaces (UniqSet NameSpace
ns1 UniqSet NameSpace -> UniqSet NameSpace -> UniqSet NameSpace
forall a. Semigroup a => a -> a -> a
S.<> UniqSet NameSpace
ns2)

instance Monoid ShadowedGREs where
  mempty :: ShadowedGREs
mempty =
    ShadowedGREs
      { shadowedNonFieldNameSpaces :: UniqSet NameSpace
shadowedNonFieldNameSpaces = UniqSet NameSpace
forall a. UniqSet a
emptyUniqSet
      , shadowedFieldGREs :: ShadowedFieldGREs
shadowedFieldGREs = ShadowedFieldGREs
forall a. Monoid a => a
mempty }

instance Semigroup ShadowedGREs where
  ShadowedGREs UniqSet NameSpace
nonflds1 ShadowedFieldGREs
flds1 <> :: ShadowedGREs -> ShadowedGREs -> ShadowedGREs
<> ShadowedGREs UniqSet NameSpace
nonflds2 ShadowedFieldGREs
flds2 =
    UniqSet NameSpace -> ShadowedFieldGREs -> ShadowedGREs
ShadowedGREs (UniqSet NameSpace
nonflds1 UniqSet NameSpace -> UniqSet NameSpace -> UniqSet NameSpace
forall a. Semigroup a => a -> a -> a
S.<> UniqSet NameSpace
nonflds2) (ShadowedFieldGREs
flds1 ShadowedFieldGREs -> ShadowedFieldGREs -> ShadowedFieldGREs
forall a. Semigroup a => a -> a -> a
S.<> ShadowedFieldGREs
flds2)

{-
************************************************************************
*                                                                      *
                        ImportSpec
*                                                                      *
************************************************************************
-}

-- | Import Specification
--
-- The 'ImportSpec' of something says how it came to be imported
-- It's quite elaborate so that we can give accurate unused-name warnings.
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
$c== :: ImportSpec -> ImportSpec -> Bool
== :: ImportSpec -> ImportSpec -> Bool
$c/= :: ImportSpec -> ImportSpec -> Bool
/= :: ImportSpec -> ImportSpec -> Bool
Eq, Typeable ImportSpec
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 -> Constr
ImportSpec -> DataType
(forall b. Data b => b -> b) -> ImportSpec -> ImportSpec
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ImportSpec -> u
forall u. (forall d. Data d => d -> u) -> ImportSpec -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportSpec
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImportSpec -> c ImportSpec
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportSpec)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImportSpec -> c ImportSpec
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImportSpec -> c ImportSpec
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportSpec
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportSpec
$ctoConstr :: ImportSpec -> Constr
toConstr :: ImportSpec -> Constr
$cdataTypeOf :: ImportSpec -> DataType
dataTypeOf :: ImportSpec -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportSpec)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportSpec)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec)
$cgmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec
gmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImportSpec -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ImportSpec -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ImportSpec -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImportSpec -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImportSpec -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec
Data )

instance NFData ImportSpec where
  rnf :: ImportSpec -> ()
rnf = ImportSpec -> ()
forall a. a -> ()
rwhnf -- All fields are strict, so we don't need to do anything

-- | Import Declaration Specification
--
-- Describes a particular import declaration and is
-- shared among all the 'Provenance's for that decl
data ImpDeclSpec
  = ImpDeclSpec {
        ImpDeclSpec -> Module
is_mod      :: !Module,     -- ^ Module imported, e.g. @import Muggle@
                                   -- Note the @Muggle@ may well not be
                                   -- the defining module for this thing!

                                   -- TODO: either should be Module, or there
                                   -- should be a Maybe UnitId here too.
        ImpDeclSpec -> ModuleName
is_as       :: !ModuleName, -- ^ Import alias, e.g. from @as M@ (or @Muggle@ if there is no @as@ clause)
        ImpDeclSpec -> Bool
is_qual     :: !Bool,       -- ^ Was this import qualified?
        ImpDeclSpec -> SrcSpan
is_dloc     :: !SrcSpan     -- ^ The location of the entire import declaration
    } deriving (ImpDeclSpec -> ImpDeclSpec -> Bool
(ImpDeclSpec -> ImpDeclSpec -> Bool)
-> (ImpDeclSpec -> ImpDeclSpec -> Bool) -> Eq ImpDeclSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImpDeclSpec -> ImpDeclSpec -> Bool
== :: ImpDeclSpec -> ImpDeclSpec -> Bool
$c/= :: ImpDeclSpec -> ImpDeclSpec -> Bool
/= :: ImpDeclSpec -> ImpDeclSpec -> Bool
Eq, Typeable ImpDeclSpec
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 -> Constr
ImpDeclSpec -> DataType
(forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u
forall u. (forall d. Data d => d -> u) -> ImpDeclSpec -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpDeclSpec
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpDeclSpec)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpDeclSpec
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpDeclSpec
$ctoConstr :: ImpDeclSpec -> Constr
toConstr :: ImpDeclSpec -> Constr
$cdataTypeOf :: ImpDeclSpec -> DataType
dataTypeOf :: ImpDeclSpec -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpDeclSpec)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpDeclSpec)
$cgmapT :: (forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec
gmapT :: (forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ImpDeclSpec -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ImpDeclSpec -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec
Data)

-- | Import Item Specification
--
-- Describes import info a particular Name
data ImpItemSpec
  = ImpAll              -- ^ The import had no import list,
                        -- or had a hiding list

  | ImpSome {
        ImpItemSpec -> Bool
is_explicit :: !Bool,
        ImpItemSpec -> SrcSpan
is_iloc     :: !SrcSpan  -- Location of the import item
    }   -- ^ The import had an import list.
        -- The 'is_explicit' field is @True@ iff the thing was named
        -- /explicitly/ in the import specs rather
        -- than being imported as part of a "..." group. Consider:
        --
        -- > import C( T(..) )
        --
        -- Here the constructors of @T@ are not named explicitly;
        -- only @T@ is named explicitly.
  deriving (ImpItemSpec -> ImpItemSpec -> Bool
(ImpItemSpec -> ImpItemSpec -> Bool)
-> (ImpItemSpec -> ImpItemSpec -> Bool) -> Eq ImpItemSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImpItemSpec -> ImpItemSpec -> Bool
== :: ImpItemSpec -> ImpItemSpec -> Bool
$c/= :: ImpItemSpec -> ImpItemSpec -> Bool
/= :: ImpItemSpec -> ImpItemSpec -> Bool
Eq, Typeable ImpItemSpec
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 -> Constr
ImpItemSpec -> DataType
(forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u
forall u. (forall d. Data d => d -> u) -> ImpItemSpec -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpItemSpec
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpItemSpec)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpItemSpec
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImpItemSpec
$ctoConstr :: ImpItemSpec -> Constr
toConstr :: ImpItemSpec -> Constr
$cdataTypeOf :: ImpItemSpec -> DataType
dataTypeOf :: ImpItemSpec -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpItemSpec)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImpItemSpec)
$cgmapT :: (forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec
gmapT :: (forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ImpItemSpec -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ImpItemSpec -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec
Data)

bestImport :: NE.NonEmpty ImportSpec -> ImportSpec
-- See Note [Choosing the best import declaration]
bestImport :: NonEmpty ImportSpec -> ImportSpec
bestImport NonEmpty ImportSpec
iss = NonEmpty ImportSpec -> ImportSpec
forall a. NonEmpty a -> a
NE.head (NonEmpty ImportSpec -> ImportSpec)
-> NonEmpty ImportSpec -> ImportSpec
forall a b. (a -> b) -> a -> b
$ (ImportSpec -> ImportSpec -> Ordering)
-> NonEmpty ImportSpec -> NonEmpty ImportSpec
forall a. (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
NE.sortBy ImportSpec -> ImportSpec -> Ordering
best NonEmpty ImportSpec
iss
  where
    best :: ImportSpec -> ImportSpec -> Ordering
    -- Less means better
    -- Unqualified always wins over qualified; then
    -- import-all wins over import-some; then
    -- earlier declaration wins over later
    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
forall a. Semigroup a => a -> a -> a
S.<> ImpItemSpec -> ImpItemSpec -> Ordering
best_item ImpItemSpec
item1 ImpItemSpec
item2 Ordering -> Ordering -> Ordering
forall a. Semigroup a => a -> a -> a
S.<>
        SrcSpan -> SrcSpan -> Ordering
SrcLoc.leftmost_smallest (ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
d1) (ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
d2)

    best_item :: ImpItemSpec -> ImpItemSpec -> Ordering
    best_item :: ImpItemSpec -> ImpItemSpec -> Ordering
best_item ImpItemSpec
ImpAll ImpItemSpec
ImpAll = Ordering
EQ
    best_item ImpItemSpec
ImpAll (ImpSome {}) = Ordering
LT
    best_item (ImpSome {}) ImpItemSpec
ImpAll = Ordering
GT
    best_item (ImpSome { is_explicit :: ImpItemSpec -> Bool
is_explicit = Bool
e1 })
              (ImpSome { is_explicit :: ImpItemSpec -> Bool
is_explicit = Bool
e2 }) = Bool
e1 Bool -> Bool -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Bool
e2
     -- False < True, so if e1 is explicit and e2 is not, we get GT

{- Note [Choosing the best import declaration]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
When reporting unused import declarations we use the following rules.
   (see [wiki:commentary/compiler/unused-imports])

Say that an import-item is either
  * an entire import-all decl (eg import Foo), or
  * a particular item in an import list (eg import Foo( ..., x, ...)).
The general idea is that for each /occurrence/ of an imported name, we will
attribute that use to one import-item. Once we have processed all the
occurrences, any import items with no uses attributed to them are unused,
and are warned about. More precisely:

1. For every RdrName in the program text, find its GlobalRdrElt.

2. Then, from the [ImportSpec] (gre_imp) of that GRE, choose one
   the "chosen import-item", and mark it "used". This is done
   by 'bestImport'

3. After processing all the RdrNames, bleat about any
   import-items that are unused.
   This is done in GHC.Rename.Names.warnUnusedImportDecls.

The function 'bestImport' returns the dominant import among the
ImportSpecs it is given, implementing Step 2.  We say import-item A
dominates import-item B if we choose A over B. In general, we try to
choose the import that is most likely to render other imports
unnecessary.  Here is the dominance relationship we choose:

    a) import Foo dominates import qualified Foo.

    b) import Foo dominates import Foo(x).

    c) Otherwise choose the textually first one.

Rationale for (a).  Consider
   import qualified M  -- Import #1
   import M( x )       -- Import #2
   foo = M.x + x

The unqualified 'x' can only come from import #2.  The qualified 'M.x'
could come from either, but bestImport picks import #2, because it is
more likely to be useful in other imports, as indeed it is in this
case (see #5211 for a concrete example).

But the rules are not perfect; consider
   import qualified M  -- Import #1
   import M( x )       -- Import #2
   foo = M.x + M.y

The M.x will use import #2, but M.y can only use import #1.
-}


unQualSpecOK :: ImportSpec -> Bool
-- ^ Is in scope unqualified?
unQualSpecOK :: ImportSpec -> Bool
unQualSpecOK ImportSpec
is = Bool -> Bool
not (ImpDeclSpec -> Bool
is_qual (ImportSpec -> ImpDeclSpec
is_decl ImportSpec
is))

qualSpecOK :: ModuleName -> ImportSpec -> Bool
-- ^ Is in scope qualified with the given module?
qualSpecOK :: ModuleName -> ImportSpec -> Bool
qualSpecOK ModuleName
mod 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 ImpDeclSpec
decl ImpItemSpec
ImpAll) = ImpDeclSpec -> SrcSpan
is_dloc ImpDeclSpec
decl
importSpecLoc (ImpSpec ImpDeclSpec
_    ImpItemSpec
item)   = ImpItemSpec -> SrcSpan
is_iloc ImpItemSpec
item

importSpecModule :: ImportSpec -> ModuleName
importSpecModule :: ImportSpec -> ModuleName
importSpecModule = Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName (Module -> ModuleName)
-> (ImportSpec -> Module) -> ImportSpec -> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImpDeclSpec -> Module
is_mod (ImpDeclSpec -> Module)
-> (ImportSpec -> ImpDeclSpec) -> ImportSpec -> Module
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImportSpec -> ImpDeclSpec
is_decl

isExplicitItem :: ImpItemSpec -> Bool
isExplicitItem :: ImpItemSpec -> Bool
isExplicitItem ImpItemSpec
ImpAll                        = Bool
False
isExplicitItem (ImpSome {is_explicit :: ImpItemSpec -> Bool
is_explicit = Bool
exp}) = Bool
exp

pprNameProvenance :: GlobalRdrEltX info -> SDoc
-- ^ Print out one place where the name was define/imported
-- (With -dppr-debug, print them all)
pprNameProvenance :: forall info. GlobalRdrEltX info -> SDoc
pprNameProvenance (GRE { gre_name :: forall info. GlobalRdrEltX info -> Name
gre_name = Name
name, gre_lcl :: forall info. GlobalRdrEltX info -> Bool
gre_lcl = Bool
lcl, gre_imp :: forall info. GlobalRdrEltX info -> Bag ImportSpec
gre_imp = Bag ImportSpec
iss })
  = SDoc -> SDoc -> SDoc
forall doc. IsOutput doc => doc -> doc -> doc
ifPprDebug ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [SDoc]
pp_provs)
               ([SDoc] -> SDoc
forall a. HasCallStack => [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 (Bag ImportSpec -> [ImportSpec]
forall a. Bag a -> [a]
bagToList Bag ImportSpec
iss)
    pp_lcl :: [SDoc]
pp_lcl = if Bool
lcl then [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"defined at" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SrcLoc -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Name -> SrcLoc
nameSrcLoc Name
name)]
                    else []
    pp_is :: ImportSpec -> SDoc
pp_is ImportSpec
is = [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [ImportSpec -> SDoc
forall a. Outputable a => a -> SDoc
ppr ImportSpec
is, ImportSpec -> Name -> SDoc
ppr_defn_site ImportSpec
is Name
name]

-- If we know the exact definition point (which we may do with GHCi)
-- then show that too.  But not if it's just "imported from X".
ppr_defn_site :: ImportSpec -> Name -> SDoc
ppr_defn_site :: ImportSpec -> Name -> SDoc
ppr_defn_site ImportSpec
imp_spec Name
name
  | Bool
same_module Bool -> Bool -> Bool
&& Bool -> Bool
not (SrcSpan -> Bool
isGoodSrcSpan SrcSpan
loc)
  = SDoc
forall doc. IsOutput doc => doc
empty              -- Nothing interesting to say
  | Bool
otherwise
  = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"and originally defined" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_mod)
                Int
2 (SrcSpan -> SDoc
pprLoc SrcSpan
loc)
  where
    loc :: SrcSpan
loc = Name -> SrcSpan
nameSrcSpan Name
name
    defining_mod :: Module
defining_mod = Bool -> SDoc -> Module -> Module
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (Name -> Bool
isExternalName Name
name) (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name) (Module -> Module) -> Module -> Module
forall a b. (a -> b) -> a -> b
$ (() :: Constraint) => Name -> Module
Name -> Module
nameModule Name
name
    same_module :: Bool
same_module = ImportSpec -> ModuleName
importSpecModule ImportSpec
imp_spec ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
defining_mod
    pp_mod :: SDoc
pp_mod | Bool
same_module = SDoc
forall doc. IsOutput doc => doc
empty
           | Bool
otherwise   = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"in" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
defining_mod)


instance Outputable ImportSpec where
   ppr :: ImportSpec -> SDoc
ppr ImportSpec
imp_spec
     = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"imported" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
qual
        SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"from" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ImportSpec -> ModuleName
importSpecModule ImportSpec
imp_spec))
        SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> 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
forall doc. IsLine doc => String -> doc
text String
"qualified"
            | Bool
otherwise                  = SDoc
forall doc. IsOutput doc => doc
empty

pprLoc :: SrcSpan -> SDoc
pprLoc :: SrcSpan -> SDoc
pprLoc (RealSrcSpan RealSrcSpan
s Maybe BufSpan
_)  = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"at" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> RealSrcSpan -> SDoc
forall a. Outputable a => a -> SDoc
ppr RealSrcSpan
s
pprLoc (UnhelpfulSpan {}) = SDoc
forall doc. IsOutput doc => doc
empty

-- | Indicate if the given name is the "@" operator
opIsAt :: RdrName -> Bool
opIsAt :: RdrName -> Bool
opIsAt RdrName
e = RdrName
e RdrName -> RdrName -> Bool
forall a. Eq a => a -> a -> Bool
== NameSpace -> FastString -> RdrName
mkUnqual NameSpace
varName (String -> FastString
fsLit String
"@")