On Tue, Sep 26, 2000 at 09:56:18AM -0700, Peter Achten wrote:
> At 11:18 25-9-00 -0300, Prof. José Romildo Malaquias wrote:
> 
> [...skip...]
> >And then how would I define data types based on Fn ? The math expressions
> >my system has to deal is expressed as something like
> >
> >         data Expr = Int
> >                   | App Fn [Expr]
> >
> >I cannot just define
> >
> >         data (FnExt fn) => Expr fn = Int
> >                                    | App fn [Expr fn]
> >
> >because the second value constructor would not be general enough
> >and the values of the second form would be all sums, or all products,
> >and so on.
> 
> [...skip...]
> 
> >Anny comments?
> 
> 
> The trick is to construct all of your recursive data structures also in an 
> overloaded fassion. [...]
> 
> The interesting case is obviously (APP fn expr). As you can see below, you 
> express to what type constructor classes the parameters should belong.
> [...]
> ==========================================================
> -- (1) for Fn
> class FnExt a where
>       -- Define your class member functions here
> -- (2)
> data Sum = Sum
> data Pro  = Pro
> data Pow  = Pow
> -- (3)
> instance FnExt Sum where fn x = x
> instance FnExt Pro where fn x = x
> instance FnExt Pow where fn x = x
> 
> -- (1) for Expr
> class ExprExt a where
>       -- Define your class member functions here
> -- (2)
> data INT         = INT Integer
> data CTE         = CTE String
> data VAR         = VAR String
> data APP fn expr = APP fn expr
> -- (3)
> instance ExprExt INT where ...
> instance ExprExt CTE where ...
> instance ExprExt VAR where ...
> instance (FnExt fn,ExprExt expr) => ExprExt (APP fn expr) where ...
> 
> -- Convenient types when constructing lists and pairs:
> 
> data List expr      -- Lists for convenience when you do have expressions 
> of same type
>      = List [expr]
> infixr 9 :^:        -- This is basically a tuple, but you can leave out 
> brackets
> data Pair expr1 expr2
>      = expr1 :^: expr2
> 
> instance (ExprExt e) => ExprExt (List e) where ...
> instance (ExprExt e1,ExprExt e2) => ExprExt (Pair e1 e2) where ...

This solution works great for the data type, but, at least
to me, it seems to make it too dificult to write functions
over ExprExt.

Consider for example the original version of the addition
operation (somehow simplified) on the original Expr data type

  data Fn = Sum | Pro | Pow

  data Expr = Int Integer | Cte String | Var String | App Fn [Expr]

  add :: Expr -> Expr -> Expr
  add (Int x) (Int y) = Int (x + y)
  add (Int 0) x       = x
  add x       (Int 0) = x
  add x       y       = App Sum [x,y]

The problem now is how to code the above algorithm using
the overloaded version of the data Expr data type.
Clearly the type of add should be

  add :: (ExprExt a, ExprExt b, ExprExt c) => a -> b -> c

I could not see how to implement it. I could define a
class

  class (ExprExt a, ExprExt b, ExprExt c) => AddOp a b c where
    add :: a -> b -> c

But how the instances should be defined? One rule for
each possible combination of INT, CTE, VAR and APP for
a, b and c:

  instance AddOp INT INT INT where
    add (Int x) (Int y) = Int (x + y)

  instance AddOp INT CTE ????? where
    add (Int 0) x = x
    add x       y = App Sum (x :^: y)

  instance AddOp INT VAR ????? where
    add (Int 0) x = x
    add x       y = App Sum (x :^: y)

  instance AddOp INT APP APP where
    add (Int 0) x = x
    add x       y = App Sum (x :^: y)

  instance AddOp CTE INT ????? where
    add (Int 0) x = x
    add x       y = App Sum (x :^: y)

  ...

Some of these definitions will not type check.

Any clues?

The use of an existentialy quantified variable
would solve this,

  data Expr =                          Int Integer
            |                          Cte String
            |                          Var String
            | forall a . (FnExt fn) => App fn Expr

but would make it to difficult to extend the
data type with new value constructors.

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

Reply via email to