ghc-lib-parser-8.8.1.20191204: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

HsImpExp

Synopsis

Documentation

type LImportDecl pass Source #

Arguments

 = Located (ImportDecl pass)

When in a list this may have

Located Import Declaration

data ImportDecl pass Source #

Import Declaration

A single Haskell import declaration.

Constructors

ImportDecl 

Fields

XImportDecl (XXImportDecl pass)

AnnKeywordIds

Instances
Data (ImportDecl GhcTc) Source # 
Instance details

Defined in HsInstances

Methods

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

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

toConstr :: ImportDecl GhcTc -> Constr #

dataTypeOf :: ImportDecl GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ImportDecl GhcRn) Source # 
Instance details

Defined in HsInstances

Methods

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

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

toConstr :: ImportDecl GhcRn -> Constr #

dataTypeOf :: ImportDecl GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ImportDecl GhcPs) Source # 
Instance details

Defined in HsInstances

Methods

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

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

toConstr :: ImportDecl GhcPs -> Constr #

dataTypeOf :: ImportDecl GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

(p ~ GhcPass pass, OutputableBndrId p) => Outputable (ImportDecl p) Source # 
Instance details

Defined in HsImpExp

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
Eq name => Eq (IEWrappedName name) Source # 
Instance details

Defined in HsImpExp

Methods

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

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

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

Defined in HsImpExp

Methods

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

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

toConstr :: IEWrappedName name -> Constr #

dataTypeOf :: IEWrappedName name -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in HsImpExp

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

Defined in HsImpExp

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

Defined in HsImpExp

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
Eq (IE GhcTc) Source # 
Instance details

Defined in HsInstances

Methods

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

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

Eq (IE GhcRn) Source # 
Instance details

Defined in HsInstances

Methods

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

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

Eq (IE GhcPs) Source # 
Instance details

Defined in HsInstances

Methods

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

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

Data (IE GhcTc) Source # 
Instance details

Defined in HsInstances

Methods

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

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

toConstr :: IE GhcTc -> Constr #

dataTypeOf :: IE GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (IE GhcRn) Source # 
Instance details

Defined in HsInstances

Methods

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

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

toConstr :: IE GhcRn -> Constr #

dataTypeOf :: IE GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (IE GhcPs) Source # 
Instance details

Defined in HsInstances

Methods

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

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

toConstr :: IE GhcPs -> Constr #

dataTypeOf :: IE GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in HsImpExp

Methods

ppr :: IE p -> SDoc Source #

pprPrec :: Rational -> IE p -> SDoc Source #

data IEWildcard Source #

Imported or Exported Wildcard

Constructors

NoIEWildcard 
IEWildcard Int 
Instances
Eq IEWildcard Source # 
Instance details

Defined in HsImpExp

Data IEWildcard Source # 
Instance details

Defined in HsImpExp

Methods

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

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

toConstr :: IEWildcard -> Constr #

dataTypeOf :: IEWildcard -> DataType #

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

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

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

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

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

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

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

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

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

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

ieName :: IE pass -> IdP pass Source #

ieNames :: IE pass -> [IdP pass] Source #

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