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

Safe HaskellNone
LanguageHaskell2010

Language.Symantic.Compiling.Read

Contents

Synopsis

Type ReadTerm

type ReadTerm src ss ts = Source src => SourceInj (TypeVT src) src => SourceInj (KindK src) src => SourceInj (AST_Type src) src => Constable (->) => CtxTy src ts -> AST_Term src ss -> Either (Error_Term src) (TermVT src ss ts) Source #

Convenient type alias for readTerm and related functions.

readTerm :: forall src ss ts. ReadTerm src ss ts Source #

Read a TermVT from and AST_Term.

teVar :: forall ss src ts. Source src => NameTe -> CtxTy src ts -> Either (Error_Term src) (TermVT src ss ts) Source #

teApp :: Source src => Constable (->) => Term src ss ts '[Proxy (a :: Type), Proxy (b :: Type)] (() #> ((a -> b) -> a -> b)) Source #

reduceTeApp :: AST_Term src ss -> AST_Term src ss Source #

Reduce number of Token_Term_App in given AST_Term by converting them into BinTree2.

NOTE: Token_Term_App exists only to handle unifix operators applied to arguments.

Type ReadTermCF

newtype ReadTermCF src ss Source #

Like ReadTerm, but CtxTe-free.

Useful in readTermWithCtx to help GHC's type solver, which "Cannot instantiate unification variable with a type involving foralls".

Constructors

ReadTermCF 

Fields

readTermWithCtx :: Foldable f => Source src => SourceInj (TypeVT src) src => SourceInj (KindK src) src => SourceInj (AST_Type src) src => Constable (->) => f (NameTe, TermT src ss '[] '[]) -> AST_Term src ss -> Either (Error_Term src) (TermVT src ss '[]) Source #

Like readTerm but with given context, and no more.

readTermWithCtxPush :: Foldable f => f (NameTe, TermT src ss '[] '[]) -> (forall ts'. ReadTerm src ss ts') -> ReadTerm src ss ts Source #

Like readTerm but with given context.

readTermWithCtxPush1 :: (NameTe, TermT src ss '[] '[]) -> (forall ts'. ReadTerm src ss ts') -> ReadTerm src ss ts Source #

Like readTerm but with given TermT pushed onto CtxTy and CtxTe.

readTermWithCtxClose :: (forall ts'. ReadTerm src ss ts') -> Source src => SourceInj (TypeVT src) src => SourceInj (KindK src) src => SourceInj (AST_Type src) src => Constable (->) => AST_Term src ss -> Either (Error_Term src) (TermVT src ss '[]) Source #

Close a ReadTerm context.

Type CtxTy

data CtxTy src ts where Source #

Typing context accumulating at each lambda abstraction the Type of the introduced variable. It is built top-down from the closest including lambda abstraction to the farest. It determines the Types of CtxTe.

Constructors

CtxTyZ :: CtxTy src '[] 
CtxTyS :: NameTe -> Type src '[] t -> CtxTy src ts -> CtxTy src (t ': ts) infixr 5 

appendCtxTy :: CtxTy src ts0 -> CtxTy src ts1 -> CtxTy src (ts0 ++ ts1) Source #

Type Error_Term

data Error_Term src Source #

Instances

(Eq src, Source src) => Eq (Error_Term src) Source # 

Methods

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

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

(Show src, Source src) => Show (Error_Term src) Source # 

Methods

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

show :: Error_Term src -> String #

showList :: [Error_Term src] -> ShowS #

ErrorInj (Con_Kind src) (Error_Term src) Source # 

Methods

errorInj :: Con_Kind src -> Error_Term src #

ErrorInj (Error_Type src) (Error_Term src) Source # 

Methods

errorInj :: Error_Type src -> Error_Term src #

ErrorInj (Error_Beta src) (Error_Term src) Source # 

Methods

errorInj :: Error_Beta src -> Error_Term src #

Type SrcTe

data SrcTe inp ss Source #

A Source usable when using readTerm.

Constructors

SrcTe_Less 
SrcTe_Input (Span inp) 
SrcTe_AST_Term (AST_Term (SrcTe inp ss) ss) 
SrcTe_AST_Type (AST_Type (SrcTe inp ss)) 
SrcTe_Kind (KindK (SrcTe inp ss)) 
SrcTe_Type (TypeVT (SrcTe inp ss)) 
SrcTe_Term 

Instances

SourceInj (Span inp) (SrcTe inp ss) Source # 

Methods

sourceInj :: Span inp -> SrcTe inp ss #

SourceInj (KindK (SrcTe inp ss)) (SrcTe inp ss) Source # 

Methods

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

SourceInj (TypeVT (SrcTe inp ss)) (SrcTe inp ss) Source # 

Methods

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

SourceInj (AST_Type (SrcTe inp ss)) (SrcTe inp ss) Source # 

Methods

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

Eq inp => Eq (SrcTe inp ss) Source # 

Methods

(==) :: SrcTe inp ss -> SrcTe inp ss -> Bool #

(/=) :: SrcTe inp ss -> SrcTe inp ss -> Bool #

Show inp => Show (SrcTe inp ss) Source # 

Methods

showsPrec :: Int -> SrcTe inp ss -> ShowS #

show :: SrcTe inp ss -> String #

showList :: [SrcTe inp ss] -> ShowS #

Source (SrcTe inp ss) Source # 

Methods

noSource :: SrcTe inp ss #

SourceInj (AST_Term (SrcTe inp ss) ss) (SrcTe inp ss) Source # 

Methods

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

type Source_Input (SrcTe inp ss) Source # 
type Source_Input (SrcTe inp ss) = inp