ghc-9.6.1: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Haskell.Syntax.ImpExp

Synopsis

Documentation

type LImportDecl pass Source #

Arguments

 = XRec pass (ImportDecl pass)

When in a list this may have

Located Import Declaration

data ImportDeclQualifiedStyle Source #

If/how an import is qualified.

Constructors

QualifiedPre

qualified appears in prepositive position.

QualifiedPost

qualified appears in postpositive position.

NotQualified

Not qualified.

Instances

Instances details
Data ImportDeclQualifiedStyle Source # 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDeclQualifiedStyle -> c ImportDeclQualifiedStyle Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle Source #

toConstr :: ImportDeclQualifiedStyle -> Constr Source #

dataTypeOf :: ImportDeclQualifiedStyle -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportDeclQualifiedStyle) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDeclQualifiedStyle -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDeclQualifiedStyle -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle Source #

Eq ImportDeclQualifiedStyle Source # 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

data IsBootInterface Source #

Indicates whether a module name is referring to a boot interface (hs-boot file) or regular module (hs file). We need to treat boot modules specially when building compilation graphs, since they break cycles. Regular source files and signature files are treated equivalently.

Constructors

NotBoot 
IsBoot 

Instances

Instances details
Data IsBootInterface Source # 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IsBootInterface Source #

toConstr :: IsBootInterface -> Constr Source #

dataTypeOf :: IsBootInterface -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IsBootInterface) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsBootInterface) Source #

gmapT :: (forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IsBootInterface -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface Source #

Show IsBootInterface Source # 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

Binary IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

Eq IsBootInterface Source # 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

Ord IsBootInterface Source # 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

data ImportDecl pass Source #

Import Declaration

A single Haskell import declaration.

Constructors

ImportDecl 

Fields

XImportDecl !(XXImportDecl pass)

AnnKeywordIds

Instances

Instances details
Data (ImportDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcPs -> c (ImportDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcPs) Source #

toConstr :: ImportDecl GhcPs -> Constr Source #

dataTypeOf :: ImportDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcPs -> ImportDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source #

Data (ImportDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcRn -> c (ImportDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcRn) Source #

toConstr :: ImportDecl GhcRn -> Constr Source #

dataTypeOf :: ImportDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcRn -> ImportDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source #

Data (ImportDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcTc -> c (ImportDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcTc) Source #

toConstr :: ImportDecl GhcTc -> Constr Source #

dataTypeOf :: ImportDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcTc -> ImportDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source #

(OutputableBndrId p, Outputable (Anno (IE (GhcPass p))), Outputable (ImportDeclPkgQual (GhcPass p))) => Outputable (ImportDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: ImportDecl (GhcPass p) -> SDoc Source #

type Anno (ImportDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

data ImportListInterpretation Source #

Whether the import list is exactly what to import, or whether hiding was used, and therefore everything but what was listed should be imported

Constructors

Exactly 
EverythingBut 

Instances

Instances details
Data ImportListInterpretation Source # 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportListInterpretation -> c ImportListInterpretation Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportListInterpretation Source #

toConstr :: ImportListInterpretation -> Constr Source #

dataTypeOf :: ImportListInterpretation -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImportListInterpretation) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportListInterpretation) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportListInterpretation -> ImportListInterpretation Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportListInterpretation -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportListInterpretation -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportListInterpretation -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportListInterpretation -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportListInterpretation -> m ImportListInterpretation Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportListInterpretation -> m ImportListInterpretation Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportListInterpretation -> m ImportListInterpretation Source #

Eq ImportListInterpretation Source # 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

type LIE pass Source #

Arguments

 = XRec pass (IE pass)

When in a list this may have

Located Import or Export

data IE pass Source #

Imported or exported entity.

Constructors

IEVar (XIEVar pass) (LIEWrappedName pass)

Imported or Exported Variable

IEThingAbs (XIEThingAbs pass) (LIEWrappedName pass)

Imported or exported Thing with Absent list

The thing is a Class/Type (can't tell) - AnnKeywordIds : AnnPattern, AnnType,AnnVal

IEThingAll (XIEThingAll pass) (LIEWrappedName pass)

Imported or exported Thing with All imported or exported

The thing is a ClassType and the All refers to methodsconstructors

IEThingWith (XIEThingWith pass) (LIEWrappedName pass) IEWildcard [LIEWrappedName pass]

Imported or exported Thing With given imported or exported

The thing is a Class/Type and the imported or exported things are methods/constructors and record fields; see Note [IEThingWith] - AnnKeywordIds : AnnOpen, AnnClose, AnnComma, AnnType

IEModuleContents (XIEModuleContents pass) (XRec pass ModuleName)

Imported or exported module contents

(Export Only)

IEGroup (XIEGroup pass) Int (LHsDoc pass)

Doc section heading

IEDoc (XIEDoc pass) (LHsDoc pass)

Some documentation

IEDocNamed (XIEDocNamed pass) String

Reference to named doc

XIE !(XXIE pass) 

Instances

Instances details
Data (IE GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcPs -> c (IE GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcPs) Source #

toConstr :: IE GhcPs -> Constr Source #

dataTypeOf :: IE GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> IE GhcPs -> IE GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IE GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source #

Data (IE GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcRn -> c (IE GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcRn) Source #

toConstr :: IE GhcRn -> Constr Source #

dataTypeOf :: IE GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> IE GhcRn -> IE GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IE GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source #

Data (IE GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcTc -> c (IE GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcTc) Source #

toConstr :: IE GhcTc -> Constr Source #

dataTypeOf :: IE GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> IE GhcTc -> IE GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IE GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source #

OutputableBndrId p => Outputable (IE (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: IE (GhcPass p) -> SDoc Source #

Eq (IE GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

(==) :: IE GhcPs -> IE GhcPs -> Bool #

(/=) :: IE GhcPs -> IE GhcPs -> Bool #

Eq (IE GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

(==) :: IE GhcRn -> IE GhcRn -> Bool #

(/=) :: IE GhcRn -> IE GhcRn -> Bool #

Eq (IE GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

(==) :: IE GhcTc -> IE GhcTc -> Bool #

(/=) :: IE GhcTc -> IE GhcTc -> Bool #

type Anno (LocatedA (IE (GhcPass p))) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (IE (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (IE (GhcPass p)) = SrcSpanAnnA
type Anno [LocatedA (IE (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.ImpExp

data IEWildcard Source #

Wildcard in an import or export sublist, like the .. in import Mod ( T(Mk1, Mk2, ..) ).

Constructors

NoIEWildcard

no wildcard in this list

IEWildcard Int

wildcard after the given # of items in this list The Int is in the range [0..n], where n is the length of the list.

Instances

Instances details
Data IEWildcard Source # 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWildcard -> c IEWildcard Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IEWildcard Source #

toConstr :: IEWildcard -> Constr Source #

dataTypeOf :: IEWildcard -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IEWildcard) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard) Source #

gmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWildcard -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWildcard -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IEWildcard -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWildcard -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard Source #

Eq IEWildcard Source # 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

data IEWrappedName p Source #

A name in an import or export specification which may have adornments. Used primarily for accurate pretty printing of ParsedSource, and API Annotation placement. The Annotation is the location of the adornment in the original source.

Constructors

IEName (XIEName p) (LIdP p)

no extra

IEPattern (XIEPattern p) (LIdP p)

pattern X

IEType (XIEType p) (LIdP p)

type (:+:)

XIEWrappedName !(XXIEWrappedName p) 

Instances

Instances details
Data (IEWrappedName GhcPs) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName GhcPs -> c (IEWrappedName GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName GhcPs) Source #

toConstr :: IEWrappedName GhcPs -> Constr Source #

dataTypeOf :: IEWrappedName GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> IEWrappedName GhcPs -> IEWrappedName GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName GhcPs -> m (IEWrappedName GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcPs -> m (IEWrappedName GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcPs -> m (IEWrappedName GhcPs) Source #

Data (IEWrappedName GhcRn) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName GhcRn -> c (IEWrappedName GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName GhcRn) Source #

toConstr :: IEWrappedName GhcRn -> Constr Source #

dataTypeOf :: IEWrappedName GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> IEWrappedName GhcRn -> IEWrappedName GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName GhcRn -> m (IEWrappedName GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcRn -> m (IEWrappedName GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcRn -> m (IEWrappedName GhcRn) Source #

Data (IEWrappedName GhcTc) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName GhcTc -> c (IEWrappedName GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName GhcTc) Source #

toConstr :: IEWrappedName GhcTc -> Constr Source #

dataTypeOf :: IEWrappedName GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> IEWrappedName GhcTc -> IEWrappedName GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName GhcTc -> m (IEWrappedName GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcTc -> m (IEWrappedName GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcTc -> m (IEWrappedName GhcTc) Source #

(HasOccName (IdP (GhcPass p)), OutputableBndrId p) => HasOccName (IEWrappedName (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

OutputableBndrId p => Outputable (IEWrappedName (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

OutputableBndrId p => OutputableBndr (IEWrappedName (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Eq (IEWrappedName GhcPs) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Eq (IEWrappedName GhcRn) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Eq (IEWrappedName GhcTc) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (IEWrappedName (GhcPass _1)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type LIEWrappedName p = XRec p (IEWrappedName p) Source #

Located name with possible adornment - AnnKeywordIds : AnnType, AnnPattern