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

GHC.Hs.ImpExp

Synopsis

Documentation

type LImportDecl pass Source #

Arguments

 = Located (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 GHC.Hs.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 GHC.Hs.ImpExp

importDeclQualifiedStyle :: Maybe (Located a) -> Maybe (Located a) -> ImportDeclQualifiedStyle Source #

Given two possible located qualified tokens, compute a style (in a conforming Haskell program only one of the two can be not Nothing). This is called from GHC.Parser.

isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool Source #

Convenience function to answer the question if an import decl. is qualified.

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 (ImportDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

data IEWrappedName name 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.

Constructors

IEName (Located name)

no extra

IEPattern (Located name)

pattern X

IEType (Located name)

type (:+:)

Instances

Instances details
Data name => Data (IEWrappedName name) 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 name -> c (IEWrappedName name) Source #

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

toConstr :: IEWrappedName name -> Constr Source #

dataTypeOf :: IEWrappedName name -> DataType Source #

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

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

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

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

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

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

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

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

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

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

HasOccName name => HasOccName (IEWrappedName name) Source # 
Instance details

Defined in GHC.Hs.ImpExp

OutputableBndr name => Outputable (IEWrappedName name) Source # 
Instance details

Defined in GHC.Hs.ImpExp

OutputableBndr name => OutputableBndr (IEWrappedName name) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Eq name => Eq (IEWrappedName name) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Methods

(==) :: IEWrappedName name -> IEWrappedName name -> Bool #

(/=) :: IEWrappedName name -> IEWrappedName name -> Bool #

type LIEWrappedName name = Located (IEWrappedName name) Source #

Located name with possible adornment - AnnKeywordIds : AnnType, AnnPattern

type LIE pass Source #

Arguments

 = Located (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 (IdP pass))

Imported or Exported Variable

IEThingAbs (XIEThingAbs pass) (LIEWrappedName (IdP 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 (IdP 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 (IdP pass)) IEWildcard [LIEWrappedName (IdP pass)] [Located (FieldLbl (IdP 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) (Located ModuleName)

Imported or exported module contents

(Export Only)

IEGroup (XIEGroup pass) Int HsDocString

Doc section heading

IEDoc (XIEDoc pass) HsDocString

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 #

pprPrec :: Rational -> 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 #

data IEWildcard Source #

Imported or Exported Wildcard

Constructors

NoIEWildcard 
IEWildcard Int 

Instances

Instances details
Data IEWildcard 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) -> 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 GHC.Hs.ImpExp

ieNames :: IE (GhcPass p) -> [IdP (GhcPass p)] Source #

pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc Source #