Safe Haskell | Safe |
---|---|
Language | Haskell98 |
- type family GTAnnot l
- type family GTBindVar l
- type family GTBoundVar l
- type family GTBindCon l
- type family GTBoundCon l
- type family GTPrim l
- data GType l
- data GTyCon l
- = TyConVoid
- | TyConUnit
- | TyConFun
- | TyConUnion !(GType l)
- | TyConBot !(GType l)
- | TyConForall !(GType l)
- | TyConExists !(GType l)
- | TyConPrim !(GTPrim l)
- | TyConBound !(GTBoundCon l)
- pattern TFun :: forall t. GType t -> GType t -> GType t
- pattern TUnit :: forall t. GType t
- pattern TVoid :: forall t. GType t
- pattern TBot :: forall t. GType t -> GType t
- pattern TPrim :: forall t. GTPrim t -> GType t
- makeTApps :: GType l -> [GType l] -> GType l
- takeTApps :: GType l -> [GType l]
- makeTFun :: GType l -> GType l -> GType l
- makeTFuns :: [GType l] -> GType l -> GType l
- takeTFun :: GType l -> Maybe (GType l, GType l)
- takeTFuns :: GType l -> ([GType l], GType l)
- takeTFuns' :: GType l -> [GType l]
- makeTForall :: Anon l => l -> GType l -> (GType l -> GType l) -> GType l
- takeTForall :: GType l -> Maybe (GType l, GTBindVar l, GType l)
- makeTExists :: Anon l => l -> GType l -> (GType l -> GType l) -> GType l
- takeTExists :: GType l -> Maybe (GType l, GTBindVar l, GType l)
- class Binding l where
- class Anon l where
- type ShowGType l = (Show l, Show (GTAnnot l), Show (GTBindVar l), Show (GTBoundVar l), Show (GTBindCon l), Show (GTBoundCon l), Show (GTPrim l))
Abstract Syntax
Type Families
type family GTBoundVar l Source #
Yield the type of bound occurrences of variables.
type GTBoundVar Flat Source # | |
type family GTBoundCon l Source #
Yield the type of bound occurrences of constructors.
type GTBoundCon Flat Source # | |
Core Syntax
Generic type expression representation.
Wrapper for primitive constructors that adds the ones common to SystemFω based languages.
TyConVoid | The void constructor. |
TyConUnit | The unit constructor. |
TyConFun | The function constructor. |
TyConUnion !(GType l) | Take the least upper bound at the given kind. |
TyConBot !(GType l) | The least element of the given kind. |
TyConForall !(GType l) | The universal quantifier with a parameter of the given kind. |
TyConExists !(GType l) | The existential quantifier with a parameter of the given kind. |
TyConPrim !(GTPrim l) | Primitive constructor. |
TyConBound !(GTBoundCon l) | Bound constructor. |
Syntactic Sugar
pattern TFun :: forall t. GType t -> GType t -> GType t Source #
Representation of the function type.
pattern TBot :: forall t. GType t -> GType t Source #
Representation of the bottom type at a given kind.
pattern TPrim :: forall t. GTPrim t -> GType t Source #
Representation of primitive type constructors.
Compounds
Type Applications
takeTApps :: GType l -> [GType l] Source #
Flatten a sequence of type applications into the function part and arguments, if any.
Function Types
makeTFun :: GType l -> GType l -> GType l infixr 9 Source #
Construct a function type with the given parameter and result type.
makeTFuns :: [GType l] -> GType l -> GType l Source #
Like makeFun
but taking a list of parameter types.
takeTFun :: GType l -> Maybe (GType l, GType l) Source #
Destruct a function type into its parameter and result types,
returning Nothing
if this isn't a function type.
takeTFuns :: GType l -> ([GType l], GType l) Source #
Destruct a function type into into all its parameters and result type, returning an empty parameter list if this isn't a function type.
takeTFuns' :: GType l -> [GType l] Source #
Like takeFuns
, but yield the parameter and return types in the same list.
Forall Types
makeTForall :: Anon l => l -> GType l -> (GType l -> GType l) -> GType l Source #
Construct a forall quantified type using an anonymous binder.
takeTForall :: GType l -> Maybe (GType l, GTBindVar l, GType l) Source #
Destruct a forall quantified type, if this is one.
The kind we return comes from the abstraction rather than the Forall constructor.
Exists Types
makeTExists :: Anon l => l -> GType l -> (GType l -> GType l) -> GType l Source #
Construct an exists quantified type using an anonymous binder.
takeTExists :: GType l -> Maybe (GType l, GTBindVar l, GType l) Source #
Destruct an exists quantified type, if this is one.
The kind we return comes from the abstraction rather than the Exists constructor.
Type Classes
class Binding l where Source #
Class of languages that include name binding.
boundOfBind :: l -> GTBindVar l -> GTBoundVar l Source #
Get the bound occurrence that matches the given binding occurrence.
boundMatchesBind :: l -> GTBindVar l -> GTBoundVar l -> Bool Source #
Check if the given bound occurence matches a binding occurrence.
Class of languages that support anonymous binding.
withBinding :: l -> (GTBindVar l -> GTBoundVar l -> a) -> a Source #
Evaluate a function given a new anonymous binding and matching bound occurrence.
withBindings :: l -> Int -> ([GTBindVar l] -> [GTBoundVar l] -> a) -> a Source #