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

Safe HaskellSafe
LanguageHaskell2010

Language.Symantic.Interpreting.Dup

Description

Interpreter to duplicate the representation of an expression in order to evaluate it with different interpreters.

NOTE: this is a more verbose, less clear, and maybe less efficient alternative to maintaining the universal polymorphism of term at parsing time as done with Term; it is mainly here for the sake of curiosity.

Synopsis
  • data Dup term1 term2 a = Dup {}
  • dup0 :: (cl r, cl s) => (forall term. cl term => term a) -> Dup r s a
  • dup1 :: (cl r, cl s) => (forall term. cl term => term a -> term b) -> Dup r s a -> Dup r s b
  • dup2 :: (cl r, cl s) => (forall term. cl term => term a -> term b -> term c) -> Dup r s a -> Dup r s b -> Dup r s c
  • dup3 :: (cl r, cl s) => (forall term. cl term => term a -> term b -> term c -> term d) -> Dup r s a -> Dup r s b -> Dup r s c -> Dup r s d

Documentation

data Dup term1 term2 a Source #

Interpreter's data.

Constructors

Dup 

Fields

Instances
(Sym_Lambda r1, Sym_Lambda r2) => Sym_Lambda (Dup r1 r2) Source # 
Instance details

Defined in Language.Symantic.Compiling.Term

Methods

apply :: Dup r1 r2 ((a -> b) -> a -> b) Source #

app :: Dup r1 r2 (a -> b) -> Dup r1 r2 a -> Dup r1 r2 b Source #

lam :: (Dup r1 r2 a -> Dup r1 r2 b) -> Dup r1 r2 (a -> b) Source #

let_ :: Dup r1 r2 var -> (Dup r1 r2 var -> Dup r1 r2 res) -> Dup r1 r2 res Source #

lam1 :: (Dup r1 r2 a -> Dup r1 r2 b) -> Dup r1 r2 (a -> b) Source #

qual :: proxy q -> Dup r1 r2 t -> Dup r1 r2 (q #> t) Source #

dup0 :: (cl r, cl s) => (forall term. cl term => term a) -> Dup r s a Source #

dup1 :: (cl r, cl s) => (forall term. cl term => term a -> term b) -> Dup r s a -> Dup r s b Source #

dup2 :: (cl r, cl s) => (forall term. cl term => term a -> term b -> term c) -> Dup r s a -> Dup r s b -> Dup r s c Source #

dup3 :: (cl r, cl s) => (forall term. cl term => term a -> term b -> term c -> term d) -> Dup r s a -> Dup r s b -> Dup r s c -> Dup r s d Source #