ghc-8.4.3: The GHC API

Safe HaskellNone
LanguageHaskell2010

HsExtension

Synopsis

Documentation

data GhcPass (c :: Pass) Source #

Used as a data type index for the hsSyn AST

Instances
Eq (GhcPass c) Source # 
Instance details

Defined in HsExtension

Methods

(==) :: GhcPass c -> GhcPass c -> Bool #

(/=) :: GhcPass c -> GhcPass c -> Bool #

Typeable c => Data (GhcPass c) Source # 
Instance details

Defined in HsExtension

Methods

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

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

toConstr :: GhcPass c -> Constr Source #

dataTypeOf :: GhcPass c -> DataType Source #

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

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

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

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

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

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

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

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

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

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

type XHsDoublePrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsDoublePrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsDoublePrim GhcPs Source # 
Instance details

Defined in HsExtension

type XHsFloatPrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsFloatPrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsFloatPrim GhcPs Source # 
Instance details

Defined in HsExtension

type XHsRat GhcTc Source # 
Instance details

Defined in HsExtension

type XHsRat GhcTc = ()
type XHsRat GhcRn Source # 
Instance details

Defined in HsExtension

type XHsRat GhcRn = ()
type XHsRat GhcPs Source # 
Instance details

Defined in HsExtension

type XHsRat GhcPs = ()
type XHsInteger GhcTc Source # 
Instance details

Defined in HsExtension

type XHsInteger GhcRn Source # 
Instance details

Defined in HsExtension

type XHsInteger GhcPs Source # 
Instance details

Defined in HsExtension

type XHsWord64Prim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsWord64Prim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsWord64Prim GhcPs Source # 
Instance details

Defined in HsExtension

type XHsInt64Prim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsInt64Prim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsInt64Prim GhcPs Source # 
Instance details

Defined in HsExtension

type XHsWordPrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsWordPrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsWordPrim GhcPs Source # 
Instance details

Defined in HsExtension

type XHsIntPrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsIntPrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsIntPrim GhcPs Source # 
Instance details

Defined in HsExtension

type XHsInt GhcTc Source # 
Instance details

Defined in HsExtension

type XHsInt GhcTc = ()
type XHsInt GhcRn Source # 
Instance details

Defined in HsExtension

type XHsInt GhcRn = ()
type XHsInt GhcPs Source # 
Instance details

Defined in HsExtension

type XHsInt GhcPs = ()
type XHsStringPrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsStringPrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsStringPrim GhcPs Source # 
Instance details

Defined in HsExtension

type XHsString GhcTc Source # 
Instance details

Defined in HsExtension

type XHsString GhcRn Source # 
Instance details

Defined in HsExtension

type XHsString GhcPs Source # 
Instance details

Defined in HsExtension

type XHsCharPrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsCharPrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsCharPrim GhcPs Source # 
Instance details

Defined in HsExtension

type XHsChar GhcTc Source # 
Instance details

Defined in HsExtension

type XHsChar GhcRn Source # 
Instance details

Defined in HsExtension

type XHsChar GhcPs Source # 
Instance details

Defined in HsExtension

type IdP GhcTc Source # 
Instance details

Defined in HsExtension

type IdP GhcTc = Id
type IdP GhcRn Source # 
Instance details

Defined in HsExtension

type IdP GhcRn = Name
type IdP GhcPs Source # 
Instance details

Defined in HsExtension

type PostRn GhcTc ty Source # 
Instance details

Defined in HsExtension

type PostRn GhcTc ty = ty
type PostRn GhcRn ty Source # 
Instance details

Defined in HsExtension

type PostRn GhcRn ty = ty
type PostRn GhcPs ty Source # 
Instance details

Defined in HsExtension

type PostTc GhcTc ty Source # 
Instance details

Defined in HsExtension

type PostTc GhcTc ty = ty
type PostTc GhcRn ty Source # 
Instance details

Defined in HsExtension

type PostTc GhcPs ty Source # 
Instance details

Defined in HsExtension

data Pass Source #

Constructors

Parsed 
Renamed 
Typechecked 
Instances
Data Pass Source # 
Instance details

Defined in HsExtension

Methods

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

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

toConstr :: Pass -> Constr Source #

dataTypeOf :: Pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

type family PostTc x ty Source #

Types that are not defined until after type checking

Instances
type PostTc GhcTc ty Source # 
Instance details

Defined in HsExtension

type PostTc GhcTc ty = ty
type PostTc GhcRn ty Source # 
Instance details

Defined in HsExtension

type PostTc GhcPs ty Source # 
Instance details

Defined in HsExtension

type family PostRn x ty Source #

Types that are not defined until after renaming

Instances
type PostRn GhcTc ty Source # 
Instance details

Defined in HsExtension

type PostRn GhcTc ty = ty
type PostRn GhcRn ty Source # 
Instance details

Defined in HsExtension

type PostRn GhcRn ty = ty
type PostRn GhcPs ty Source # 
Instance details

Defined in HsExtension

type family IdP p Source #

Maps the "normal" id type for a given pass

Instances
type IdP GhcTc Source # 
Instance details

Defined in HsExtension

type IdP GhcTc = Id
type IdP GhcRn Source # 
Instance details

Defined in HsExtension

type IdP GhcRn = Name
type IdP GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsChar x Source #

Instances
type XHsChar GhcTc Source # 
Instance details

Defined in HsExtension

type XHsChar GhcRn Source # 
Instance details

Defined in HsExtension

type XHsChar GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsCharPrim x Source #

Instances
type XHsCharPrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsCharPrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsCharPrim GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsString x Source #

Instances
type XHsString GhcTc Source # 
Instance details

Defined in HsExtension

type XHsString GhcRn Source # 
Instance details

Defined in HsExtension

type XHsString GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsStringPrim x Source #

Instances
type XHsStringPrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsStringPrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsStringPrim GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsInt x Source #

Instances
type XHsInt GhcTc Source # 
Instance details

Defined in HsExtension

type XHsInt GhcTc = ()
type XHsInt GhcRn Source # 
Instance details

Defined in HsExtension

type XHsInt GhcRn = ()
type XHsInt GhcPs Source # 
Instance details

Defined in HsExtension

type XHsInt GhcPs = ()

type family XHsIntPrim x Source #

Instances
type XHsIntPrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsIntPrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsIntPrim GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsWordPrim x Source #

Instances
type XHsWordPrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsWordPrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsWordPrim GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsInt64Prim x Source #

Instances
type XHsInt64Prim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsInt64Prim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsInt64Prim GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsWord64Prim x Source #

Instances
type XHsWord64Prim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsWord64Prim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsWord64Prim GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsInteger x Source #

Instances
type XHsInteger GhcTc Source # 
Instance details

Defined in HsExtension

type XHsInteger GhcRn Source # 
Instance details

Defined in HsExtension

type XHsInteger GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsRat x Source #

Instances
type XHsRat GhcTc Source # 
Instance details

Defined in HsExtension

type XHsRat GhcTc = ()
type XHsRat GhcRn Source # 
Instance details

Defined in HsExtension

type XHsRat GhcRn = ()
type XHsRat GhcPs Source # 
Instance details

Defined in HsExtension

type XHsRat GhcPs = ()

type family XHsFloatPrim x Source #

Instances
type XHsFloatPrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsFloatPrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsFloatPrim GhcPs Source # 
Instance details

Defined in HsExtension

type family XHsDoublePrim x Source #

Instances
type XHsDoublePrim GhcTc Source # 
Instance details

Defined in HsExtension

type XHsDoublePrim GhcRn Source # 
Instance details

Defined in HsExtension

type XHsDoublePrim GhcPs Source # 
Instance details

Defined in HsExtension

type ForallX (c :: * -> Constraint) (x :: *) = (c (XHsChar x), c (XHsCharPrim x), c (XHsString x), c (XHsStringPrim x), c (XHsInt x), c (XHsIntPrim x), c (XHsWordPrim x), c (XHsInt64Prim x), c (XHsWord64Prim x), c (XHsInteger x), c (XHsRat x), c (XHsFloatPrim x), c (XHsDoublePrim x)) Source #

Helper to apply a constraint to all extension points. It has one entry per extension point type family.

class HasSourceText a where Source #

The SourceText fields have been moved into the extension fields, thus placing a requirement in the extension field to contain a SourceText so that the pretty printing and round tripping of source can continue to operate.

The HasSourceText class captures this requirement for the relevant fields.

Minimal complete definition

noSourceText, sourceText, setSourceText, getSourceText

type SourceTextX x = (HasSourceText (XHsChar x), HasSourceText (XHsCharPrim x), HasSourceText (XHsString x), HasSourceText (XHsStringPrim x), HasSourceText (XHsIntPrim x), HasSourceText (XHsWordPrim x), HasSourceText (XHsInt64Prim x), HasSourceText (XHsWord64Prim x), HasSourceText (XHsInteger x)) Source #

Provide a summary constraint that lists all the extension points requiring the HasSourceText class, so that it can be changed in one place as the named extensions change throughout the AST.

class HasDefault a where Source #

Defaults for each annotation, used to simplify creation in arbitrary contexts

Minimal complete definition

def

Methods

def :: a Source #

Instances
HasDefault () Source # 
Instance details

Defined in HsExtension

Methods

def :: () Source #

HasDefault SourceText Source # 
Instance details

Defined in HsExtension

type HasDefaultX x = ForallX HasDefault x Source #

Provide a single constraint that captures the requirement for a default across all the extension points.

class Convertable a b | a -> b where Source #

Conversion of annotations from one type index to another. This is required where the AST is converted from one pass to another, and the extension values need to be brought along if possible. So for example a SourceText is converted via id, but needs a type signature to keep the type checker happy.

Minimal complete definition

convert

Methods

convert :: a -> b Source #

Instances
Convertable a a Source # 
Instance details

Defined in HsExtension

Methods

convert :: a -> a Source #

type ConvertIdX a b = (XHsDoublePrim a ~ XHsDoublePrim b, XHsFloatPrim a ~ XHsFloatPrim b, XHsRat a ~ XHsRat b, XHsInteger a ~ XHsInteger b, XHsWord64Prim a ~ XHsWord64Prim b, XHsInt64Prim a ~ XHsInt64Prim b, XHsWordPrim a ~ XHsWordPrim b, XHsIntPrim a ~ XHsIntPrim b, XHsInt a ~ XHsInt b, XHsStringPrim a ~ XHsStringPrim b, XHsString a ~ XHsString b, XHsCharPrim a ~ XHsCharPrim b, XHsChar a ~ XHsChar b) Source #

A constraint capturing all the extension points that can be converted via instance Convertable a a

type OutputableBndrId id = (OutputableBndr (NameOrRdrName (IdP id)), OutputableBndr (IdP id)) Source #

Constraint type to bundle up the requirement for OutputableBndr on both the id and the NameOrRdrName type for it