
Hi, Does anyone know of a package for genetic programming for Haskell? I tried some links from Haskell wiki and some I found on google, and found many interesting papers, but none of them pointed to downloadable code. Does anyone know where can I find a good implementation (even an experimental one)? Thanks, Maurício

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? -- Regards, Casey

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

On Aug 15, 2006, at 11:43 PM, Casey Hawthorne wrote:
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?
Well, there's always the sledgehammer (http://www.haskell.org/ghc/ docs/latest/html/users_guide/template-haskell.html)
Or are term-rewriting and the lambda calculus sufficiently far enough apart concepts? -- Regards, Casey _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

Casey Hawthorne wrote:
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?
Typeful symbolic differentiation of compiled functions http://www.haskell.org/pipermail/haskell/2004-November/014939.html

Greg Buchholz wrote:
Casey Hawthorne wrote:
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?
Typeful symbolic differentiation of compiled functions
http://www.haskell.org/pipermail/haskell/2004-November/014939.html
And a GADT version of differentiation: http://haskell.org/hawiki/ShortExamples_2fSymbolDifferentiation which also does some simplifications. I have a version that I did not post that uses the hs-plugins: It can take a function like f x = x * log x + 7 * (-x) + (2**x) - (sin x) and compute the derivative, simplify it, emit the haskell code for it, compile it via hs-plugins, and be able to use it. Of course, you can't INLINE a new function like that, but the performance is still very good.
participants (6)
-
Casey Hawthorne
-
Chris Kuklewicz
-
Greg Buchholz
-
Lemmih
-
Maurício
-
Robert Dockins