Safe Haskell | None |
---|---|
Language | Haskell98 |
Documentation
mapAllEq :: Monad m => (e1 tp -> m (e2 tp)) -> Natural n -> List e1 (AllEq tp n) -> m (List e2 (AllEq tp n)) Source #
data Function fun sig where Source #
GetFunType fun => GetFunType (Function fun) Source # | |
GEq ([Type], Type) fun => Eq (Function fun sig) Source # | |
GShow ([Type], Type) fun => Show (Function fun sig) Source # | |
GCompare ([Type], Type) fun => GCompare ([Type], Type) (Function fun) Source # | |
GEq ([Type], Type) fun => GEq ([Type], Type) (Function fun) Source # | |
GShow ([Type], Type) fun => GShow ([Type], Type) (Function fun) Source # | |
data AnyFunction fun where Source #
AnyFunction :: Function fun '(arg, t) -> AnyFunction fun |
data ArithOpInt Source #
data LetBinding v e t Source #
data Quantifier Source #
data Expression v qv fun fv lv e res where Source #
Var :: v res -> Expression v qv fun fv lv e res | Free variable. |
QVar :: qv res -> Expression v qv fun fv lv e res | Quantified variable, i.e. a variable that's bound by a forall/exists quantor. |
FVar :: fv res -> Expression v qv fun fv lv e res | A function argument variable. Only used in function bodies. |
LVar :: lv res -> Expression v qv fun fv lv e res | A variable bound by a let binding. |
App :: Function fun '(arg, res) -> List e arg -> Expression v qv fun fv lv e res | Function application |
Const :: Value a -> Expression v qv fun fv lv e a | Constant |
AsArray :: Function fun '(arg, res) -> Expression v qv fun fv lv e (ArrayType arg res) | AsArray converts a function into an array by using the function arguments as array indices and the return type as array element. |
Quantification :: Quantifier -> List qv arg -> e BoolType -> Expression v qv fun fv lv e BoolType | Bind variables using a forall or exists quantor. |
Let :: List (LetBinding lv e) arg -> e res -> Expression v qv fun fv lv e res | Bind variables to expressions. |
functionType :: Monad m => (forall arg t. fun '(arg, t) -> m (List Repr arg, Repr t)) -> Function fun '(arg, res) -> m (List Repr arg, Repr res) Source #
expressionType :: (Monad m, Functor m) => (forall t. v t -> m (Repr t)) -> (forall t. qv t -> m (Repr t)) -> (forall arg t. fun '(arg, t) -> m (List Repr arg, Repr t)) -> (forall t. fv t -> m (Repr t)) -> (forall t. lv t -> m (Repr t)) -> (forall t. e t -> m (Repr t)) -> Expression v qv fun fv lv e res -> m (Repr res) Source #
:: (Functor m, Monad m) | |
=> (forall t. v1 t -> m (v2 t)) | How to translate variables |
-> (forall t. qv1 t -> m (qv2 t)) | How to translate quantified variables |
-> (forall arg t. fun1 '(arg, t) -> m (fun2 '(arg, t))) | How to translate functions |
-> (forall t. fv1 t -> m (fv2 t)) | How to translate function variables |
-> (forall t. lv1 t -> m (lv2 t)) | How to translate let variables |
-> (forall t. e1 t -> m (e2 t)) | How to translate sub-expressions |
-> Expression v1 qv1 fun1 fv1 lv1 e1 r | The expression to translate |
-> m (Expression v2 qv2 fun2 fv2 lv2 e2 r) |
mapFunction :: (Functor m, Monad m) => (forall arg t. fun1 '(arg, t) -> m (fun2 '(arg, t))) -> Function fun1 '(arg, res) -> m (Function fun2 '(arg, res)) Source #
data RenderMode Source #
renderExprDefault :: (GetType qv, GShow v, GShow qv, GShow fun, GShow fv, GShow lv, GShow e) => RenderMode -> Expression v qv fun fv lv e tp -> ShowS Source #
renderExpr :: GetType qv => RenderMode -> (forall tp. v tp -> ShowS) -> (forall tp. qv tp -> ShowS) -> (forall arg res. fun '(arg, res) -> ShowS) -> (forall tp. fv tp -> ShowS) -> (forall tp. lv tp -> ShowS) -> (forall tp. e tp -> ShowS) -> Expression v qv fun fv lv e tp -> ShowS Source #
renderValue :: RenderMode -> Value tp -> ShowS Source #
renderFunction :: RenderMode -> (forall arg res. fun '(arg, res) -> ShowS) -> Function fun '(arg, res) -> ShowS Source #
renderType :: RenderMode -> Repr tp -> ShowS Source #