space leak due to optimisations and/or newtypes

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.)

It sounds like a bad performance bug to me! Newtypes should not cost efficiency. Please to submit a Trac bug report. What would really help is a self-contained program that demonstrates the problem. Maybe that's what you've supplied. I'm confused though. You say 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. Are you also saying this? If I leave all of them in, then the program takes ages and uses lots of space, if I use -O. But it's fine without -O. Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Sebastian Fischer | Sent: 03 June 2009 22:27 | To: glasgow-haskell-users@haskell.org | Subject: space leak due to optimisations and/or newtypes | | 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.) | | | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Jun 4, 2009, at 10:05 AM, Simon Peyton-Jones wrote:
What would really help is a self-contained program that demonstrates the problem. Maybe that's what you've supplied. I'm confused though. You say 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.
Are you also saying this? If I leave all of them in, then the program takes ages and uses lots of space, if I use -O. But it's fine without -O.
Yes exactly, that is what happens with the program I attached. Morover, my original program uses lots of memory with and without -O (but it's fine without newtypes). I'll file a Trac bug report and supply both the condensed and the original program. Cheers, Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

On 03/06/2009 22:26, Sebastian Fischer wrote:
------- {-# 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 -------
Those two [1..] ring alarm bells. GHC will happily combine them with CSE and possibly also lift them to the top-level; both transformations might have a big impact on space behaviour. Try with -fno-full-laziness and/or -fno-cse. Cheers, Simon

On Jun 4, 2009, at 11:42 AM, Simon Marlow wrote:
Those two [1..] ring alarm bells. GHC will happily combine them with CSE and possibly also lift them to the top-level; both transformations might have a big impact on space behaviour.
Try with -fno-full-laziness and/or -fno-cse.
I did and found no difference when using any or both of these flags. I have just submitted a ticket: http://hackage.haskell.org/trac/ghc/ticket/3273 It seems the problem is not related to newtypes. Also in the original program with newtypes the memory requirements only depend on whether I use -O. Cheers, Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

On Jun 4, 2009, at 2:33 PM, Sebastian Fischer wrote:
Try with -fno-full-laziness and/or -fno-cse.
I did and found no difference when using any or both of these flags.
As "int-e" pointed out on the ticket that was my fault (spuriously abstracting from command-line argument order). -fno-full-laziness does avoid the space leak. Now that I am aware of let-floating I wonder why removing any of the occurrences of 'id' happens to avoid it. Cheers, Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)
participants (3)
-
Sebastian Fischer
-
Simon Marlow
-
Simon Peyton-Jones