
Hello, I have written a Haskell program that runs much more efficiently without optimisations than with optimisations. Compiled without optimisations it finishes in about 15 seconds and runs in constant space (< 3 MB), with optimisations (both -O and -O2) it consumed all my RAM in less than 30 seconds before I killed it. The program contains four occurrences of the identity function 'id'. All of them are superflous from a declarative point of view. If I remove any of them (one is enough) then the program finishes in about 10 seconds and runs in constant space (< 3 MB) with optimisations. The (attached) program is a condensed version of a program that uses newtypes. Originally, the identity functions where newtype con- and destructors. The original program consumes a lot of memory both with and without optimisations. A version where I have inlined some newtypes runs in constant space. I have used GHC 6.10.1 on Mac OS X. Is this behaviour intended, is it a known/fixed issue of GHC 6.10.1 or should I file a bug report? Cheers, Sebastian ------- {-# LANGUAGE RankNTypes #-} newtype S a = S { unS :: forall b . (a -> Int -> [b]) -> Int -> [b] } ret x = S (\c -> c x) a `bind` f = S (\c -> unS a (\x -> unS (f x) c)) zero = S (\c _ -> []) plus a b = S (\c -> id (\d -> if d==0 then [] else id (unS a c) (d-1) ++ id (unS b c) (d-1))) runS :: S a -> [a] runS a = concatMap (\d -> id (run a) d) [10000] run :: S a -> Int -> [a] run a = unS a (\x _ -> [x]) natSum :: S Int natSum = anyof [1..] `bind` \x -> anyof [1..] `bind` \y -> ret (x+y) where anyof = foldr plus zero . map ret main = print . length $ runS natSum ------- -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)