Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type AST_Type src = BinTree (Token_Type src)
- data Token_Type src
- = Token_Type_Const (TypeTLen src)
- | Token_Type_Var (At src NameVar)
- type ModulesTy src = Map (Mod NameTy) (TypeTLen src)
- newtype TypeTLen src = TypeTLen (forall vs. Len vs -> TypeT src vs)
- typeTLen :: forall c src. Source src => Constable c => KindInjP (Ty_of_Type (K c)) => K c ~ Type_of_Ty (Ty_of_Type (K c)) => src -> TypeTLen src
- class ModulesTyInj ts where
- class (Gram_Terminal g, Gram_Rule g, Gram_Alt g, Gram_Try g, Gram_App g, Gram_AltApp g, Gram_RegL g, Gram_CF g, Gram_Comment g, Gram_Op g) => Gram_Mod g where
- class (Gram_Terminal g, Gram_Rule g, Gram_Alt g, Gram_Try g, Gram_App g, Gram_AltApp g, Gram_RegL g, Gram_CF g, Gram_Comment g, Gram_Op g, Gram_Mod g) => Gram_Type_Name g where
- class (Gram_Source src g, Gram_Terminal g, Gram_Rule g, Gram_Alt g, Gram_Try g, Gram_App g, Gram_AltApp g, Gram_CF g, Gram_Comment g, Gram_Op g, Gram_Type_Name g, Gram_Error (Error_Type src) g, Gram_State (Imports NameTy, ModulesTy src) g, Constable (->), Constable [], Constable (,)) => Gram_Type src g where
- readTyName :: Source src => Imports NameTy -> ModulesTy src -> src -> Mod NameTy -> Either (Error_Type src) (TypeTLen src)
- data Error_Type src
- = Error_Type_Constant_unknown (At src (Mod NameTy))
- | Error_Type_Con_Kind (Con_Kind src)
- gram_type :: Gram_Type () g => [CF g (AST_Type ())]
Type AST_Type
type AST_Type src = BinTree (Token_Type src) Source #
Abstract Syntax Tree of Token_Type
.
Type Token_Type
data Token_Type src Source #
Token_Type_Const (TypeTLen src) | |
Token_Type_Var (At src NameVar) |
Type ModulesTy
Type TypeTLen
typeTLen :: forall c src. Source src => Constable c => KindInjP (Ty_of_Type (K c)) => K c ~ Type_of_Ty (Ty_of_Type (K c)) => src -> TypeTLen src Source #
Class ModulesTyInj
class ModulesTyInj ts where Source #
modulesTyInj :: Source src => ModulesTy src Source #
ModulesTyInj [k] ([] k) Source # | |
(KindInjP (Ty_of_Type (K k c)), (~) * (K k c) (Type_of_Ty (Ty_of_Type (K k c))), Constable k c, ModulesTyInj [*] ts) => ModulesTyInj [*] ((:) * (Proxy k c) ts) Source # | |
Class Gram_Mod
class (Gram_Terminal g, Gram_Rule g, Gram_Alt g, Gram_Try g, Gram_App g, Gram_AltApp g, Gram_RegL g, Gram_CF g, Gram_Comment g, Gram_Op g) => Gram_Mod g where Source #
Class Gram_Type_Name
class (Gram_Terminal g, Gram_Rule g, Gram_Alt g, Gram_Try g, Gram_App g, Gram_AltApp g, Gram_RegL g, Gram_CF g, Gram_Comment g, Gram_Op g, Gram_Mod g) => Gram_Type_Name g where Source #
Class Gram_Type
class (Gram_Source src g, Gram_Terminal g, Gram_Rule g, Gram_Alt g, Gram_Try g, Gram_App g, Gram_AltApp g, Gram_CF g, Gram_Comment g, Gram_Op g, Gram_Type_Name g, Gram_Error (Error_Type src) g, Gram_State (Imports NameTy, ModulesTy src) g, Constable (->), Constable [], Constable (,)) => Gram_Type src g where Source #
Read an AST_Type
from a textual source.
g_type :: CF g (AST_Type src) Source #
g_type_fun :: CF g (AST_Type src) Source #
g_type_list :: CF g (AST_Type src) Source #
g_type_tuple2 :: CF g (AST_Type src) Source #
g_type_app :: CF g (AST_Type src) Source #
g_type_atom :: CF g (AST_Type src) Source #
g_type_name_const :: CF g (AST_Type src) Source #
g_type_name_var :: CF g (AST_Type src) Source #
(Gram_Source src RuleEBNF, Constable (* -> * -> *) (->), Constable (* -> * -> *) (,), Constable (* -> *) []) => Gram_Type src RuleEBNF Source # | |
(Gram_Source src EBNF, Constable (* -> * -> *) (->), Constable (* -> * -> *) (,), Constable (* -> *) []) => Gram_Type src EBNF Source # | |
Gram_Type src g => Gram_Type src (CF g) Source # | |
readTyName :: Source src => Imports NameTy -> ModulesTy src -> src -> Mod NameTy -> Either (Error_Type src) (TypeTLen src) Source #
Type Error_Type
data Error_Type src Source #
Error_Type_Constant_unknown (At src (Mod NameTy)) | |
Error_Type_Con_Kind (Con_Kind src) |
Eq src => Eq (Error_Type src) Source # | |
Show src => Show (Error_Type src) Source # | |
ErrorInj (Con_Kind src) (Error_Type src) Source # | |
ErrorInj (Error_Type src) (Error_Type src) Source # | |
ErrorInj (Error_Type src) (Error_Term src) # | |