ghc-8.0.0.20160204: The GHC API

Safe HaskellNone
LanguageHaskell2010

HsImpExp

Synopsis

Documentation

type LImportDecl name Source

Arguments

 = Located (ImportDecl name)

When in a list this may have

data ImportDecl name Source

A single Haskell import declaration.

Constructors

ImportDecl

AnnKeywordIds

Fields

Instances

Data name => Data (ImportDecl name) 

Methods

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

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

toConstr :: ImportDecl name -> Constr Source

dataTypeOf :: ImportDecl name -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl name)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl name)) Source

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

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

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

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

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

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

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

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

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

Methods

ppr :: ImportDecl name -> SDoc Source

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

type LIE name Source

Arguments

 = Located (IE name)

When in a list this may have

data IE name Source

Imported or exported entity.

Constructors

IEVar (Located name)
IEThingAbs (Located name)

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

IEThingAll (Located name)

ClassType plus all methodsconstructors

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

ClassType plus some methodsconstructors and record fields; see Note [IEThingWith] - AnnKeywordIds : AnnOpen, AnnClose, AnnComma, AnnType

IEModuleContents (Located ModuleName)

(Export Only)

IEGroup Int HsDocString

Doc section heading

IEDoc HsDocString

Some documentation

IEDocNamed String

Reference to named doc

Instances

Eq name => Eq (IE name) 

Methods

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

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

Data name => Data (IE name) 

Methods

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

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

toConstr :: IE name -> Constr Source

dataTypeOf :: IE name -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (IE name)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE name)) Source

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

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

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

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

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

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

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

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

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

Methods

ppr :: IE name -> SDoc Source

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

data IEWildcard Source

Constructors

NoIEWildcard 
IEWildcard Int 

Instances

Eq IEWildcard 
Data IEWildcard 

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 (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c IEWildcard) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) 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 :: (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

ieName :: IE name -> name Source

ieNames :: IE a -> [a] Source

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