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

Safe HaskellSafe
LanguageHaskell2010

Language.Symantic.Interpreting.Dup

Contents

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 repr either using NoMonomorphismRestriction when writing an EDSL, or with a forall repr. within a data type when writing a DSL; as is done when parsing Term in this library; it is thus mainly here for the sake of curiosity.

Synopsis
  • data Dup repr1 repr2 a = Dup {}
  • dup0 :: (cl x, cl y) => (forall repr. cl repr => repr a) -> Dup x y a
  • dup1 :: (cl x, cl y) => (forall repr. cl repr => repr a -> repr b) -> Dup x y a -> Dup x y b
  • dup2 :: (cl x, cl y) => (forall repr. cl repr => repr a -> repr b -> repr c) -> Dup x y a -> Dup x y b -> Dup x y c
  • dup3 :: (cl x, cl y) => (forall repr. cl repr => repr a -> repr b -> repr c -> repr d) -> Dup x y a -> Dup x y b -> Dup x y c -> Dup x y d
  • dupList :: [Dup x y a] -> ([x a], [y a])

Type Dup

data Dup repr1 repr2 a infixl 2 Source #

Duplicate an implicitly generated representation.

Useful to combine two symantic interpreters into one.

Constructors

Dup infixl 2 

Fields

Instances
(Functor x, Functor y) => Functor (Dup x y) Source # 
Instance details

Defined in Language.Symantic.Interpreting.Dup

Methods

fmap :: (a -> b) -> Dup x y a -> Dup x y b #

(<$) :: a -> Dup x y b -> Dup x y a #

(Applicative x, Applicative y) => Applicative (Dup x y) Source # 
Instance details

Defined in Language.Symantic.Interpreting.Dup

Methods

pure :: a -> Dup x y a #

(<*>) :: Dup x y (a -> b) -> Dup x y a -> Dup x y b #

liftA2 :: (a -> b -> c) -> Dup x y a -> Dup x y b -> Dup x y c #

(*>) :: Dup x y a -> Dup x y b -> Dup x y b #

(<*) :: Dup x y a -> Dup x y b -> Dup x y a #

(Alternative x, Alternative y) => Alternative (Dup x y) Source # 
Instance details

Defined in Language.Symantic.Interpreting.Dup

Methods

empty :: Dup x y a #

(<|>) :: Dup x y a -> Dup x y a -> Dup x y a #

some :: Dup x y a -> Dup x y [a] #

many :: Dup x y a -> Dup x y [a] #

(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 #

Helpers

dup0 :: (cl x, cl y) => (forall repr. cl repr => repr a) -> Dup x y a Source #

To be used with the TypeApplications language extension: dup0 @Sym_Foo foo

dup1 :: (cl x, cl y) => (forall repr. cl repr => repr a -> repr b) -> Dup x y a -> Dup x y b Source #

dup2 :: (cl x, cl y) => (forall repr. cl repr => repr a -> repr b -> repr c) -> Dup x y a -> Dup x y b -> Dup x y c Source #

dup3 :: (cl x, cl y) => (forall repr. cl repr => repr a -> repr b -> repr c -> repr d) -> Dup x y a -> Dup x y b -> Dup x y c -> Dup x y d Source #

dupList :: [Dup x y a] -> ([x a], [y a]) Source #