1 -- | Interpreter to duplicate the representation of an expression
2 -- in order to evaluate it with different interpreters.
4 -- NOTE: this is a more verbose, less clear,
5 -- and maybe less efficient alternative
6 -- to maintaining the universal polymorphism of @repr@ at parsing time
7 -- as done with 'Forall_Repr_with_Context';
8 -- it is mainly here for the sake of curiosity.
9 module Language.Symantic.Repr.Dup where
11 import Language.Symantic.Expr
13 -- | Interpreter's data.
14 data Dup repr1 repr2 a
23 ) => Sym_Bool (Dup r1 r2) where
24 bool x = bool x `Dup` bool x
25 not (x1 `Dup` x2) = not x1 `Dup` not x2
26 (&&) (x1 `Dup` x2) (y1 `Dup` y2) = (&&) x1 y1 `Dup` (&&) x2 y2
27 (||) (x1 `Dup` x2) (y1 `Dup` y2) = (||) x1 y1 `Dup` (||) x2 y2
28 xor (x1 `Dup` x2) (y1 `Dup` y2) = xor x1 y1 `Dup` xor x2 y2
32 ) => Sym_Int (Dup r1 r2) where
33 int x = int x `Dup` int x
34 abs (x1 `Dup` x2) = abs x1 `Dup` abs x2
35 negate (x1 `Dup` x2) = negate x1 `Dup` negate x2
36 (+) (x1 `Dup` x2) (y1 `Dup` y2) = (+) x1 y1 `Dup` (+) x2 y2
37 (-) (x1 `Dup` x2) (y1 `Dup` y2) = (-) x1 y1 `Dup` (-) x2 y2
38 (*) (x1 `Dup` x2) (y1 `Dup` y2) = (*) x1 y1 `Dup` (*) x2 y2
39 mod (x1 `Dup` x2) (y1 `Dup` y2) = mod x1 y1 `Dup` mod x2 y2
43 ) => Sym_Eq (Dup r1 r2) where
44 (==) (x1 `Dup` x2) (y1 `Dup` y2) = (==) x1 y1 `Dup` (==) x2 y2
48 ) => Sym_Ord (Dup r1 r2) where
49 compare (x1 `Dup` x2) (y1 `Dup` y2) =
50 compare x1 y1 `Dup` compare x2 y2
54 ) => Sym_If (Dup r1 r2) where
55 if_ (c1 `Dup` c2) (ok1 `Dup` ok2) (ko1 `Dup` ko2) =
56 if_ c1 ok1 ko1 `Dup` if_ c2 ok2 ko2
60 ) => Sym_When (Dup r1 r2) where
61 when (c1 `Dup` c2) (ok1 `Dup` ok2) =
62 when c1 ok1 `Dup` when c2 ok2
66 ) => Sym_List (Dup r1 r2) where
67 list_empty = list_empty `Dup` list_empty
68 list_cons (a1 `Dup` a2) (l1 `Dup` l2) = list_cons a1 l1 `Dup` list_cons a2 l2
71 foldr (\(x1 `Dup` x2) (xs1, xs2) ->
72 (x1:xs1, x2:xs2)) ([], []) l in
74 instance -- Sym_List_Lam
77 ) => Sym_List_Lam lam (Dup r1 r2) where
78 list_filter (f1 `Dup` f2) (l1 `Dup` l2) =
79 list_filter f1 l1 `Dup` list_filter f2 l2
83 ) => Sym_Maybe (Dup r1 r2) where
84 nothing = nothing `Dup` nothing
85 just (a1 `Dup` a2) = just a1 `Dup` just a2
86 instance -- Sym_Maybe_Lam
87 ( Sym_Maybe_Lam lam r1
88 , Sym_Maybe_Lam lam r2
89 ) => Sym_Maybe_Lam lam (Dup r1 r2) where
90 maybe (m1 `Dup` m2) (n1 `Dup` n2) (j1 `Dup` j2) =
93 instance -- Sym_Lambda
96 ) => Sym_Lambda lam (Dup r1 r2) where
97 type Lambda_from_Repr (Dup r1 r2) = Lambda_from_Repr r1
98 app (f1 `Dup` f2) (x1 `Dup` x2) = app f1 x1 `Dup` app f2 x2
99 inline f = dup1 (inline f) `Dup` dup2 (inline f)
100 val f = dup1 (val f) `Dup` dup2 (val f)
101 lazy f = dup1 (lazy f) `Dup` dup2 (lazy f)
102 instance -- Sym_Tuple2
105 ) => Sym_Tuple2 (Dup r1 r2) where
106 tuple2 (a1 `Dup` a2) (b1 `Dup` b2) =
107 tuple2 a1 b1 `Dup` tuple2 a2 b2
111 ) => Sym_Map (Dup r1 r2) where
112 map_from_list (l1 `Dup` l2) =
113 map_from_list l1 `Dup` map_from_list l2
114 instance -- Sym_Map_Lam
117 ) => Sym_Map_Lam lam (Dup r1 r2) where
118 map_map (f1 `Dup` f2) (m1 `Dup` m2) =
119 map_map f1 m1 `Dup` map_map f2 m2