Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Symantic.Typing.Grammar
Contents
Synopsis
- type AST_Type src = BinTree (Token_Type src)
- data Token_Type src
- = Token_Type_Const (TypeTLen src)
- | Token_Type_Var (Sourced 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
- modulesTyInj :: Source src => ModulesTy src
- class (Gram_Char 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_Char 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
- g_ModNameTy :: CF g (Mod NameTy)
- g_ModNameTyId :: CF g (Mod NameTy)
- g_NameTyId :: CF g NameTy
- g_ModNameTyOp :: CF g (Mod NameTy)
- g_NameTyOp :: CF g NameTy
- class (Gram_Source src g, Gram_Char 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
- g_type :: CF g (AST_Type src)
- g_type_fun :: CF g (AST_Type src)
- g_type_list :: CF g (AST_Type src)
- g_type_tuple2 :: CF g (AST_Type src)
- g_type_app :: CF g (AST_Type src)
- g_type_atom :: CF g (AST_Type src)
- g_type_const :: CF g (AST_Type src)
- g_type_var :: CF g (AST_Type src)
- readTyName :: Source src => Imports NameTy -> ModulesTy src -> src -> Mod NameTy -> Either (Error_Type src) (TypeTLen src)
- data Error_Type src
- = Error_Type_Constant_unknown (Sourced 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 #
Constructors
Token_Type_Const (TypeTLen src) | |
Token_Type_Var (Sourced src NameVar) |
Instances
Source src => Eq (Token_Type src) Source # | |
Defined in Language.Symantic.Typing.Grammar Methods (==) :: Token_Type src -> Token_Type src -> Bool # (/=) :: Token_Type src -> Token_Type src -> Bool # | |
(Source src, Show (TypeT src ([] :: [Type]))) => Show (Token_Type src) Source # | |
Defined in Language.Symantic.Typing.Grammar Methods showsPrec :: Int -> Token_Type src -> ShowS # show :: Token_Type src -> String # showList :: [Token_Type src] -> ShowS # | |
SourceInj (AST_Type (SrcTe inp ss)) (SrcTe inp ss) Source # | |
Type
ModulesTy
Type
TypeTLen
Like TypeT
, but needing a (
Len
vs)
to be built.
Useful to build a ModulesTy
which can be used
whatever will be the (
Len
vs)
given to readTyVars
.
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 #
Methods
modulesTyInj :: Source src => ModulesTy src Source #
Instances
ModulesTyInj ([] :: [k]) Source # | |
Defined in Language.Symantic.Typing.Grammar Methods modulesTyInj :: Source src => ModulesTy src Source # | |
(KindInjP (Ty_of_Type (K c)), K c ~ Type_of_Ty (Ty_of_Type (K c)), Constable c, ModulesTyInj ts) => ModulesTyInj (Proxy c ': ts :: [Type]) Source # | |
Defined in Language.Symantic.Typing.Grammar Methods modulesTyInj :: Source src => ModulesTy src Source # |
Class
Gram_Mod
class (Gram_Char 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 #
Minimal complete definition
Nothing
Class
Gram_Type_Name
class (Gram_Char 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 #
Minimal complete definition
Nothing
Methods
g_ModNameTy :: CF g (Mod NameTy) Source #
g_ModNameTyId :: CF g (Mod NameTy) Source #
g_NameTyId :: CF g NameTy Source #
g_ModNameTyOp :: CF g (Mod NameTy) Source #
g_NameTyOp :: CF g NameTy Source #
Instances
Gram_Type_Name EBNF Source # | |
Gram_Type_Name RuleEBNF Source # | |
Gram_Type_Name g => Gram_Type_Name (CF g) Source # | |
Class
Gram_Type
class (Gram_Source src g, Gram_Char 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.
Minimal complete definition
Nothing
Methods
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_const :: CF g (AST_Type src) Source #
g_type_var :: CF g (AST_Type src) Source #
Instances
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 #
Constructors
Error_Type_Constant_unknown (Sourced src (Mod NameTy)) | |
Error_Type_Con_Kind (Con_Kind src) |
Instances
Eq src => Eq (Error_Type src) Source # | |
Defined in Language.Symantic.Typing.Grammar Methods (==) :: Error_Type src -> Error_Type src -> Bool # (/=) :: Error_Type src -> Error_Type src -> Bool # | |
Show src => Show (Error_Type src) Source # | |
Defined in Language.Symantic.Typing.Grammar Methods showsPrec :: Int -> Error_Type src -> ShowS # show :: Error_Type src -> String # showList :: [Error_Type src] -> ShowS # | |
ErrorInj (Con_Kind src) (Error_Type src) Source # | |
Defined in Language.Symantic.Typing.Grammar Methods errorInj :: Con_Kind src -> Error_Type src # | |
ErrorInj (Error_Type src) (Error_Type src) Source # | |
Defined in Language.Symantic.Typing.Grammar Methods errorInj :: Error_Type src -> Error_Type src # | |
ErrorInj (Error_Type src) (Error_Term src) Source # | |
Defined in Language.Symantic.Compiling.Read Methods errorInj :: Error_Type src -> Error_Term src # |