
Before anything else, I want to point out that I have no intention to confront your community, or denigrate Haskell. A few days ago I answered an email from a Clean programmer on something related to Clean. He was worried that Clean team could give up its good work, and Clean could disappear; therefore, he was thinking about switching to Haskell. Since I thought that my email could be of interest for the Clean community, I posted it in the -- small-- Clean list :-(Clean is not as popular as Haskell). I received a lot of furious and offensive private emails for suggesting the Clean programmer to stick with Clean. However, I also received a very polite, humorous, and illuminating private email from a person who seems to work at Microsoft. His name is Simon Peyton-Jones. He urged me to post my comments on a Haskell cafe. He also filed one of my comments as a bug in a Haskell bug track. Here is a couple of snippets from his email: --- I think it's v bad that a straightforward program runs so slowly, and it's certainly true that this is an area we could pay more attention to. --- Meanwhile, I'm curious: are the arrays in Philippos's program strict? Or lazy? If strict, that's a pretty big difference. Therefore, here are my comments, with a lot of code. A few months ago I came accross an unpublished article about a novel genetic programming system. The system was coded in Larceny Scheme. I translated it to Clean and to Haskell. Unhappily, I cannot post the program here because it is very large, and the authors of the original Lisp program don't want me to divulge it before they see in in a printed page of a Journal. Therefore, I wrote an empty genetic programming framework, just to compare languages. Comparing Clean and Haskell, I noticed: 1 -- Clean compiler almost never let me do very stupid things, like trying to unbox a tree, or to write in a closed file (I will post an example of this in a near future). For instance, Clean compiler would never swallow something like the code below: import Control.Monad.ST import Data.Array.ST import Data.Array.Base import System.Random data Op = AND | OR | NOT; data Tree= L Double | T Op [Tree] main = print $ runST (do arr <- newArray (1,2000000) (L 0.0) :: ST s (STArray s Int Tree) go arr 2000000 0.0 ) go :: STArray s Int Tree -> Int -> Double -> ST s Double go a i acc | i < 1 = return acc | otherwise=do b <- unsafeRead a i {- readArray a i -} writeArray a i (setDouble ((getDouble b)+3.0)) c <- readArray a i go a (i-1) (acc+ (getDouble c)) -- What I really need is a random index in Haskell. getDouble (L r)= r getDouble _ = 0.0 setDouble r= L r 2 -- Safety does not cost much in Clean. For instance, removing array boundary check does not seem to affect Clean. I believe that it does not affect Haskell either, but I have not verified this point. 3 -- Haskell seems to loop more often than Clean. For instance, Haskell may loop if I change function mutate to mutate e (L i) xs = (e, xs) mutate e t (y:ys) = ins t (rnLen t y, ys) where ins (T p (L i:xs)) (0, st)=(T p (e:xs), st) ins (T p (t:xs)) (n,(r1:rs)) | n > 0= let (T p mt, s2)= ins (T p xs)(n-1, rs) in (T p (t:mt), s2) ins (T p (t:xs)) (n,(r1:rs)) | rn 2 r1== 0= (T p (e:xs), rs) | rn 2 r1== 1= let (xpr, st)= mutate e t rs in (T p (xpr:xs), st) This might be a bug in my implementation of show Tree. It would be great if you people could "show" me what I did wrong. 4 -- On the plus side, there are libraries in Haskell that seem to behave better than the Clean equivalent libraries. This could be explained by the fact that there are a lot of people coding Haskell libraries, while Clean team seems to be reluctant in accepting libraries from outsiders. For instance, lethevert made a very important improvement in ObjectIO (changing fonts in edit text field), but it was never incorporated into Clean (yes, I wrote a lot of emails to Clean team about it). Last year, when I was learning Clean, I discovered that many of my professors and teachers are presbyopic. Therefore, it would be a good policy to use very large fonts for homework. I only succeeded in doing it thanks to lethevert. In the case of the program below, Haskell System.Random library seems to work much better than Clean MersenneTwister. 5 --- Any improvement in the program below will be welcome. The program is already very fast thanks to suggestions I received from the bug track people, and from Peyton-Jones. Function "show" seems to loop if I replace mutate in item 3 for mutate in the code below. {- ghc gp.hs -O2 --make -} {- Execute: gp.exe +RTS -sstderr -} import Control.Monad.ST import Data.Array.ST import Data.Array.Base import System.Random data Op = AND | OR | NOT; data Tree= L Int | T Op [Tree] psz= 20000 thr=4.0 gates= [AND, NOT, OR] table= [ (False, False, False), (True, False, True), (True, True, False), (False, True, True)] prt NOT= "NOT" prt OR= "OR" prt AND= "AND" instance Show Tree where show (L i) = "L"++(show i) show (T p xs) = (prt p)++(show xs) main = do xs <- (rnList (1, 20000)) print $ runST $ do arr <- newArray_ (1,psz) :: ST s (STArray s Int Tree) (arr, xs1) <- gen0 arr psz xs g1 <- evolve 30 arr (L 0) xs1; return $ g1 gen0 a i xs = if i<=0 then return(a,xs) else do (tree, rs) <- return(rndXpr gates 5 xs) writeArray a i tree gen0 a (i-1) rs mutate e (L i) xs = (e, xs) mutate e t (y:ys) = ins t (rnLen t y, ys) where ins (T p (L i:xs)) (0, st)=(T p (e:xs), st) ins (T p (t:xs)) (n,(r1:rs)) | n > 0= let (T p mt, s2)= ins (T p xs)(n-1, rs) in (T p (t:mt), s2) ins (T p (t:xs)) (n,(r1:rs)) | rn 2 r1== 0= (T p (e:xs), rs) | rn 2 r1== 1= let (xpr, st)= mutate e t rs in (T p (xpr:xs), st) fxy NOT r= T NOT [L (rn 2 r)] fxy AND st = T AND [L 0, L 1] fxy OR st = T OR [L 0, L 1] rndXpr fs beastSz xs= loop beastSz xs where rth s r= s!!(rn (length s) r) loop n (r1:r2:rs) | n<1 = (fxy (rth fs r1) r1, rs) |otherwise= mutate (fxy (rth fs r1) r2) f1 rs where (f1, ys)= loop (n-1) rs run (L 0) x y= x -- Interpreter run (L 1) x y= y run (T AND xs) x y = and [run c x y | c <- xs] run (T OR xs) x y= or [run c x y | c <- xs] run (T NOT (t:_)) x y= not (run t x y) rn n r= (abs r) `rem` n rnLen (T _ s) r= rn (length s) r rnList :: (Int, Int) -> IO [Int] rnList r=getStdGen>>=(\x->return(randomRs r x)) frag (L i) st = (L i, st) frag (T p xs) (r1:r2:rs) | rn 2 r2==0= (xpr, rs) | otherwise= frag xpr rs where xpr= xs!!(rnLen (T p xs) r1) crossover e1 e2 rs = ([c2, c1], rs4) where (g1, rs1) = frag e1 rs (g2, rs2) = frag e2 rs1 (c1, rs3) = mutate g1 e2 rs2 (c2, rs4) = mutate g2 e1 rs3 nGates (L i)= 0.0 nGates (T p xs) = (-0.1) + sum [nGates g | g <- xs] fitness tt gt = (ng + 1.0 + sum [ft t | t <- tt]) where ng= nGates gt ft (out, t1, t2) | run gt t1 t2 == out= 1.0 ft _ = 0.0 evolve n p b xs | n < 1 = do (arr, xs1) <- gen0 p psz xs evolve 30 arr b xs1 evolve n p b (r1:r2:rs) = do n1 <- return $ 1+(rn psz r1) n2 <- return $ 1+(rn psz r2) g1 <- readArray p n1; g2 <- readArray p n2 ([c1,c2], rs) <- return $ crossover g1 g2 rs insrt c1 p 1 psz insrt c2 p 1 psz res <- best 1 b p fitn <- return $ fitness table res if fitn > thr then return res else evolve (n-1) p res rs best i res p | i >= psz= return res best i fg p= do g <- readArray p i if (fitness table fg) > (fitness table g) then best (i+1) fg p else best (i+1) g p insrt g v i sz | i >= sz = return () insrt g v i sz = do a <- readArray v i fg <- return $ fitness table g fa <- return $ fitness table a if fa > fg then insrt g v (i+1) sz else do writeArray v i g __________________________________________________________________ Connect with friends from any web browser - no download required. Try the new Yahoo! Canada Messenger for the Web BETA at http://ca.messenger.yahoo.com/webmessengerpromo.php