]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Repr/Dup.hs
factorizing Type1_From ast Type0
[haskell/symantic.git] / Language / Symantic / Repr / Dup.hs
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.
11 --
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.Repr.Dup where
18
19 import Data.Proxy
20
21 -- | Interpreter's data.
22 data Repr_Dup repr1 repr2 a
23 = Repr_Dup
24 { repr_dup_1 :: repr1 a
25 , repr_dup_2 :: repr2 a
26 }
27
28 repr_dup0
29 :: (cl r, cl s)
30 => Proxy cl
31 -> (forall repr. cl repr => repr a)
32 -> Repr_Dup r s a
33 repr_dup0 _cl f = f `Repr_Dup` f
34
35 repr_dup1
36 :: (cl r, cl s)
37 => Proxy cl
38 -> (forall repr. cl repr => repr a -> repr b)
39 -> Repr_Dup r s a
40 -> Repr_Dup r s b
41 repr_dup1 _cl f (a1 `Repr_Dup` a2) =
42 f a1 `Repr_Dup` f a2
43
44 repr_dup2
45 :: (cl r, cl s)
46 => Proxy cl
47 -> (forall repr. cl repr => repr a -> repr b -> repr c)
48 -> Repr_Dup r s a
49 -> Repr_Dup r s b
50 -> Repr_Dup r s c
51 repr_dup2 _cl f (a1 `Repr_Dup` a2) (b1 `Repr_Dup` b2) =
52 f a1 b1 `Repr_Dup` f a2 b2
53
54 repr_dup3
55 :: (cl r, cl s)
56 => Proxy cl
57 -> (forall repr. cl repr => repr a -> repr b -> repr c -> repr d)
58 -> Repr_Dup r s a
59 -> Repr_Dup r s b
60 -> Repr_Dup r s c
61 -> Repr_Dup r s d
62 repr_dup3 _cl f (a1 `Repr_Dup` a2) (b1 `Repr_Dup` b2) (c1 `Repr_Dup` c2) =
63 f a1 b1 c1 `Repr_Dup` f a2 b2 c2