On Thu, Sep 28, 2000 at 12:00:11PM +0100, Chris Angus wrote:
> How about defining a Datatype Fn which defines all functions
> and building in terms of this
> 
> data Expr = Int Integer
>           | Cte String
>           | Var String
>           | App Fn [Expr] deriving (Show)
> 
> data Fn = Fn String
>         | Combiner String
>         | Compose Fn Fn deriving (Show)
> 
> class (Show a) => Fns a where
>  mkFn :: a -> Fn
>  mkFn x = Fn (show x)
> data Basic = Negate deriving (Show)
> data Combining = Sum | Prod deriving (Show)
> data Trig  = Sin | Cos | Tan deriving (Show)
> 
> instance Fns Trig
> instance Fns Basic
> instance Fns Combining where
>  mkFn x = Combiner (show x)
> 
> sine    = mkFn Sin
> cosine  = mkFn Cos
> tangent = mkFn Tan
> neg  = mkFn Negate
> 
> compose :: Fn -> Fn -> Fn
> compose x y = Compose x y
> 
> match (Fn x) (Fn y) = x == y
> match (Combiner x) (Combiner y) = x == y
> match (Compose x y) (Compose a b) = match x a && ma
> match _ _ = False

Your solution should work, but the match operation, would be
too common in my system (it would be needed in order to
check the class of applications) and as it is based on
string (list of characters) equality, it would made the
system inefficient. If it was easy to keep this
structure, but obtain an unique integer (instead of
string) for each functor, this solution would be good enough
for me, as integer comparisons are much more efficient
than string comparison.

> diff :: Fn -> Fn
> diff fn | match fn sine   = cosine
> diff fn | match fn cosine = neg `compose` cosine

You forgot to differentiate the arguments of the function:

  data Diff = Diff deriving Show

  instance Fns Diff

  diffE :: Expr -> Expr -> Expr
  diffE (Int _) _ = Int 0
  diffE (Cte _) _ = Int 0
  diffE (Var x) (Var y)
     | x == y    = Int 1
     | otherwise = Int 0
  diffE (App fn xs) (Var y) = App (diff fn) (map diffE xs)
  diffE x y = App Diff [x,y]

would be better (yeat too simplistic).

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

Reply via email to