ghc-8.2.1: The GHC API

Safe HaskellNone
LanguageHaskell2010

HsImpExp

Synopsis

Documentation

type LImportDecl name Source #

Arguments

 = Located (ImportDecl name)

When in a list this may have

Located Import Declaration

data ImportDecl name Source #

Import Declaration

A single Haskell import declaration.

Constructors

ImportDecl

AnnKeywordIds

Fields

Instances

Data name => Data (ImportDecl name) Source # 

Methods

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

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

toConstr :: ImportDecl name -> Constr #

dataTypeOf :: ImportDecl name -> DataType #

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

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

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

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

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

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

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

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

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

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

(OutputableBndr name, HasOccName name) => Outputable (ImportDecl name) Source # 

Methods

ppr :: ImportDecl name -> SDoc Source #

pprPrec :: Rational -> ImportDecl name -> SDoc Source #

data IEWrappedName name Source #

A name in an import or export specfication 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 # 

Methods

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

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

Data name => Data (IEWrappedName name) Source # 

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, HasOccName name) => OutputableBndr (IEWrappedName name) Source # 
(HasOccName name, OutputableBndr name) => Outputable (IEWrappedName name) Source # 
HasOccName name => HasOccName (IEWrappedName name) Source # 

type LIEWrappedName name = Located (IEWrappedName name) Source #

Located name with possible adornment - AnnKeywordIds : AnnType, AnnPattern

type LIE name Source #

Arguments

 = Located (IE name)

When in a list this may have

Located Import or Export

data IE name Source #

Imported or exported entity.

Constructors

IEVar (LIEWrappedName name)

Imported or Exported Variable

IEThingAbs (LIEWrappedName name)

Imported or exported Thing with Absent list

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

IEThingAll (LIEWrappedName name)

Imported or exported Thing with All imported or exported

The thing is a ClassType and the All refers to methodsconstructors

IEThingWith (LIEWrappedName name) IEWildcard [LIEWrappedName name] [Located (FieldLbl name)]

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 (Located ModuleName)

Imported or exported module contents

(Export Only)

IEGroup Int HsDocString

Doc section heading

IEDoc HsDocString

Some documentation

IEDocNamed String

Reference to named doc

Instances

Eq name => Eq (IE name) Source # 

Methods

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

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

Data name => Data (IE name) Source # 

Methods

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

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

toConstr :: IE name -> Constr #

dataTypeOf :: IE name -> DataType #

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

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

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

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

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

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

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

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

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

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

(HasOccName name, OutputableBndr name) => Outputable (IE name) Source # 

Methods

ppr :: IE name -> SDoc Source #

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

data IEWildcard Source #

Imported or Exported Wildcard

Constructors

NoIEWildcard 
IEWildcard Int 

Instances

Eq IEWildcard Source # 
Data IEWildcard Source # 

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 name -> name Source #

ieNames :: IE a -> [a] Source #

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