Hi Oleg,

(cc'ed the haskell-cafe as it may be of interest to other readers)

On Tue, 9 Mar 2010 o...@okmij.org wrote:


Hi, Bruno!

        Of course I know the EMGM paper and approach -- we discuss it
at great length in the paper we are both editing, don't we? What I had
in mind about tagless final is different from EMGM, without the mediation
by an isomorphism.

The isomorphism has no role in extensibility there: it is completely orthogonal to this issue. The isomorphism is used for the generic programming part. If we apply the tecnique directly to the expression
problem this is what we get:

http://www.haskell.org/pipermail/haskell-cafe/2008-July/045028.html

Whether it is more direct or not is in the eye of
the beholder.

        I guess you probably won't be at the Spring School.

No I am not going to be there, unfortunatelly :(.

So, I'm
sending you the code that might hopefully clarify what I meant. The
original code was written in Haskell; I am sending you the OCaml
translation. Somehow I thought you might like it better (and also tell
if it translatable to Scala).

I must say that my OCaml is not as good as my Haskell or Scala :). However, if I understand the code correctly I don't see where the difference to the code in the link above is.

Regarding whether it is translatable to Scala. The answer for your question is answered here:

Modular Visitor Components: A Practical Solution to the Expression Families Problem
Bruno C. d. S. Oliveira
In Sophia Drossopoulou, editor, LNCS 5653, Proceedings of the 23rd European Conference on Object Oriented Programming (ECOOP). June 2009.

Link: http://ropas.snu.ac.kr/%7Ebruno/papers/ModularVisitor.pdf


        I was a little bit surprised that you ended up in Korea. That
was quite a big jump and quite a lot of hassle moving, I imagine. On
the other hand, it makes a lot of sense: governments on that side of
the world seem to have real money, and they are intent in investing
them in science, including basic science. How is your Korean?

It is worse than my OCaml :).

Bruno

        Cheers,
        Oleg

(* Tagless Final using dictionary passing *)

(* Compare with Haskell's ExpSYM *)
class type ['repr] expSYM  = object
 method lit : int -> 'repr
 method neg : 'repr -> 'repr
 method add : 'repr -> 'repr -> 'repr
end;;

(* Constructor functions *)
let lit n = fun ro -> ro#lit n;;
let neg e = fun ro -> ro#neg (e ro);;
let add e1 e2 = fun ro -> ro#add (e1 ro) (e2 ro);;

(* Unit is for the sake of value restriction *)
(* The term is exactly the same as that in Intro2.hs *)
let tf1 () = add (lit 8) (neg (add (lit 1) (lit 2)));;

(* We can write interepreters of expSYM *)
(* and evaluate exp in several ways. The code for the interpreters
  is quite like the one we have seen already
*)
class eval = object
 method lit n = (n:int)
 method neg e = - e
 method add e1 e2 = e1 + e2
end;;

let eval = new eval;;

let 5  = tf1 () eval;;

class view = object
 method lit n = string_of_int n
 method neg e = "(-" ^ e ^ ")"
 method add e1 e2 = "(" ^ e1 ^ " + " ^ e2 ^ ")"
end;;

let view = new view;;

let "(8 + (-(1 + 2)))" = tf1 () view;;

(* We can extend our expression adding a new expression form *)
class type ['repr] mulSYM = object
 method mul : 'repr -> 'repr -> 'repr
end;;

let mul e1 e2 = fun ro -> ro#mul (e1 ro) (e2 ro);;


(* Extended sample expressions *)
(* Again, the code is the same as before, modulo the occasional () *)
(* Value restriction is indeed annoying ... *)
let tfm1 () = add (lit 7) (neg (mul (lit 1) (lit 2)));;

let tfm2 () = mul (lit 7) (tf1 ());;

class evalM = object
 inherit eval
 method mul e1 e2 = e1 * e2
end;;

let evalM = new evalM;;

class viewM = object
 inherit view
 method mul e1 e2 = "(" ^ e1 ^ " * " ^ e2 ^ ")"
end;;

let viewM = new viewM;;

(* can use the extended evaluator to evaluate old expressions *)
let 5  = tf1 () evalM;;

(* Of course we can't use the old evaluator to evaluate extended
  expressions
let 5 = tfm1 () eval;;
Error: This expression has type eval but an expression was expected of type
        < add : 'a -> 'b -> 'c; lit : int -> 'a; mul : 'a -> 'a -> 'd;
          neg : 'd -> 'b; .. >
      The first object type has no method mul
*)

let 5 = tfm1 () evalM;;

let 35 = tfm2 () evalM;;

let "(7 + (-(1 * 2)))" = tfm1 () viewM;;

let "(7 * (8 + (-(1 + 2))))" = tfm2 () viewM;;

(* The expressions are first-class: we can put them into the same list *)

let tl1 () = [lit 1; tf1 ()];;

(* and add the extended objects afterwards *)

let tl2 () = tfm1 () :: tfm2 () :: tl1 ();;

let [5; 35; 1; 5] = List.map (fun x -> x evalM) (tl2 ());;

let ["(7 + (-(1 * 2)))"; "(7 * (8 + (-(1 + 2))))"; "1"; "(8 + (-(1 + 2)))"]
   = List.map (fun x -> x viewM) (tl2 ());;

Printf.printf "\nAll done\n";;

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to