I have been trying to write a DSL for Povray (see www.povray.org) in Haskell, using the technique of: http://okmij.org/ftp/papers/tagless-final-APLAS.pdf with some inspiration taken from http://okmij.org/ftp/Haskell/DSLSharing.hs
The Povray Scene Description Language is a very declarative language, with few high level constructs (even loops take a bit of work) -- which is why I'm putting it in Haskell. At one point, I needed a "varargs" function for the DSL, a function f :: b -> a -> b dressed up to take a variable number of 'a's, known at compile time. This was easy enough: > data Nil a = Nil > data Cons b a = a ::: b a > infixr 1 ::: > > class VarArgs v where > apply_args :: (s -> a -> s) -> s -> v a -> s > > instance VarArgs Nil where > apply_args _ start _ = start > > instance VarArgs b => VarArgs (Cons b) where > apply_args f start (a ::: b) = apply_args f (f start a) b The solution is quite workable: I can simply write the following, and I believe the summation is expanded out at compile-time: > apply_args (+) 0 (2 ::: 3 ::: 8 ::: 1 ::: (-3) ::: Nil) But I found I also needed a function to take a union type -- that is, the function would either take an argument of type T1, or of type T2, known at compile time. I tried a similar technique as I tried with varargs, and unfortunately ended up with this: > data LeftOf a b = L a > data RightOf a b = R b > > class Union u where > apply_union :: (a -> c) -> (b -> c) -> (u a b) -> c > > instance Union LeftOf where > apply_union f _ (L a) = f a > > instance Union RightOf where > apply_union _ g (R b) = g b > > type A = Integer > type B = String > type C = () > > type Union_ABC u1 u2 = u1 A (u2 B C) > > f_A = show . (+ 3) > f_B = reverse > f_C = const "unit" > > f :: (Union u1, Union u2) => Union_ABC u1 u2 -> String > f = apply_union f_A (apply_union f_B f_C) > > main = do > putStrLn $ f $ (L 6 :: Union_ABC LeftOne LeftOne) > putStrLn $ f $ R (L "hello, world") > putStrLn $ f $ R (R ()) Notice a lot of ugliness in my example: e.g., the definition of f, the type signature of f (I can't move the context into the type-synonym Union_ABC), creating objects of the union type, and the unpleasant surprise that I needed to provide the type of 'L 6'. This solution is very not-scalable: the Povray SDL is a "messy" language, and for my DSL I would need approximately 20 or 30 such unions, each a union of about 20 types (admittedly with a lot of overlap from union to union). I think the solution is to abandon the lofty ideal of statically determining argument types; instead have a universal type with tags to distinguish types dynamically: > data Universal = UA A | UB B | UC C > f :: Universal -> String > f (UA a) = f_A a > f (UB b) = f_B b > f (UC c) = f_C c > > main2 = do > putStrLn $ f $ UA 6 > putStrLn $ f $ UB "hello, world" > putStrLn $ f $ UC () ...but I'm not ready to give up hope yet. Suggestions please? Eric _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe