
On 8/16/06, Casey Hawthorne
The Q Programming Language can do symbolic manipulation -- Haskell?
The Q Programming Language can do the following:
sqr X = X*X
==>sqr 5 25
==>sqr (X+1) (X+1)*(X+1)
Can Haskell do symbolic manipulation?
Or are term-rewriting and the lambda calculus sufficiently far enough apart concepts?
You can do (if you don't mind cheating) : Compiling Sym ( Sym.hs, interpreted ) :Ok, modules loaded: Sym. *Sym> :!cat Sym.hs module Sym where data Sym a = Const a | Var String | Sym a `Mult` Sym a | Sym a `Plus` Sym a | Sym a `Minus` Sym a deriving (Eq,Show) instance Num a => Num (Sym a) where (+) = Plus (*) = Mult abs = id signum = id fromInteger = Const . fromInteger sqr x = x*x *Sym> sqr 5 25 *Sym> sqr (Var "X" + 1) (Var "X" Plus Const 1) Mult (Var "X" Plus Const 1) -- Cheers, Lemmih