symantic-6.3.4.20190712: Library for Typed Tagless-Final Higher-Order Composable DSL

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Typing.Grammar

Contents

Synopsis

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 #

Instances
Source src => Eq (Token_Type src) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Language.Symantic.Compiling.Read

Methods

sourceInj :: AST_Type (SrcTe inp ss) -> SrcTe inp ss #

Type ModulesTy

type ModulesTy src = Map (Mod NameTy) (TypeTLen src) Source #

Type TypeTLen

newtype TypeTLen src Source #

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.

Constructors

TypeTLen (forall vs. Len vs -> TypeT src vs) 
Instances
Source src => Eq (TypeTLen src) Source # 
Instance details

Defined in Language.Symantic.Typing.Grammar

Methods

(==) :: TypeTLen src -> TypeTLen src -> Bool #

(/=) :: TypeTLen src -> TypeTLen src -> Bool #

(Source src, Show (TypeT src ([] :: [Type]))) => Show (TypeTLen src) Source # 
Instance details

Defined in Language.Symantic.Typing.Grammar

Methods

showsPrec :: Int -> TypeTLen src -> ShowS #

show :: TypeTLen src -> String #

showList :: [TypeTLen src] -> ShowS #

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 #

Derive a ModulesTy from the given type-level list of Proxy-fied type constants.

Methods

modulesTyInj :: Source src => ModulesTy src Source #

Instances
ModulesTyInj ([] :: [k]) Source # 
Instance details

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 # 
Instance details

Defined in Language.Symantic.Typing.Grammar

Methods

modulesTyInj :: Source src => ModulesTy src Source #

Class Gram_Mod

Class Gram_Type_Name

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

Instances
(Gram_Source src RuleEBNF, Constable ((->) :: Type -> Type -> Type), Constable (,), Constable []) => Gram_Type src RuleEBNF Source # 
Instance details

Defined in Language.Symantic.Typing.Grammar

(Gram_Source src EBNF, Constable ((->) :: Type -> Type -> Type), Constable (,), Constable []) => Gram_Type src EBNF Source # 
Instance details

Defined in Language.Symantic.Typing.Grammar

Gram_Type src g => Gram_Type src (CF g) Source # 
Instance details

Defined in Language.Symantic.Typing.Grammar

readTyName :: Source src => Imports NameTy -> ModulesTy src -> src -> Mod NameTy -> Either (Error_Type src) (TypeTLen src) Source #

Lookup a TyConst or Type synonym associated with given NameTy in given ModulesTy, building it for a vs of given Len.

Type Error_Type

data Error_Type src Source #

Instances
Eq src => Eq (Error_Type src) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Language.Symantic.Typing.Grammar

Methods

errorInj :: Con_Kind src -> Error_Type src #

ErrorInj (Error_Type src) (Error_Type src) Source # 
Instance details

Defined in Language.Symantic.Typing.Grammar

Methods

errorInj :: Error_Type src -> Error_Type src #

ErrorInj (Error_Type src) (Error_Term src) Source # 
Instance details

Defined in Language.Symantic.Compiling.Read

Methods

errorInj :: Error_Type src -> Error_Term src #

gram_type :: Gram_Type () g => [CF g (AST_Type ())] Source #

List of the rules of Gram_Type.