1 {-# LANGUAGE ConstraintKinds #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE NoImplicitPrelude #-}
6 {-# LANGUAGE Rank2Types #-}
7 {-# LANGUAGE TypeFamilies #-}
8 {-# LANGUAGE UndecidableInstances #-}
9 -- | Interpreter to duplicate the representation of an expression
10 -- in order to evaluate it with different interpreters.
12 -- NOTE: this is a more verbose, less clear,
13 -- and maybe less efficient alternative
14 -- to maintaining the universal polymorphism of @repr@ at parsing time
15 -- as done with 'Forall_Repr_with_Context';
16 -- it is mainly here for the sake of curiosity.
17 module Language.Symantic.Interpreting.Dup where
21 -- | Interpreter's data.
22 data DupI repr1 repr2 a
31 -> (forall repr. cl repr => repr a)
33 dupI0 _cl f = f `DupI` f
38 -> (forall repr. cl repr => repr a -> repr b)
41 dupI1 _cl f (a1 `DupI` a2) =
47 -> (forall repr. cl repr => repr a -> repr b -> repr c)
51 dupI2 _cl f (a1 `DupI` a2) (b1 `DupI` b2) =
52 f a1 b1 `DupI` f a2 b2
57 -> (forall repr. cl repr => repr a -> repr b -> repr c -> repr d)
62 dupI3 _cl f (a1 `DupI` a2) (b1 `DupI` b2) (c1 `DupI` c2) =
63 f a1 b1 c1 `DupI` f a2 b2 c2