Stack usage with a state monad

2003-12-30 Thread Joe Thornber
Hi,

I was wondering if anyone could give me some help with this problem ?

I'm trying to hold some state in a StateMonad whilst I iterate over a
large tree, and finding that I'm running out of stack space very
quickly.  The simplified program below exhibits the same problem.

This is the first time I've hit space problems in Haskell, I hope
judicial use of 'seq' or '$!' would be enough to fix it, but I don't
know where to start.

Any ideas as to what I'm doing wrong would be much appreciated.

Thanks,

- Joe




module Main (main) where

-- Program to count the leaf nodes in a rose tree.  Written to try and
-- reproduce a stack space leak present in a larger program.

-- How can I use a state monad to count the leaves without eating all
-- the stack ?

import Control.Monad.State

data Tree = Tree [Tree] | Leaf

buildTree :: Int - Int - Tree
buildTree order = buildTree'
where
buildTree' 0 = Leaf
buildTree' depth = Tree $ map (buildTree') $ take order $ repeat (depth - 1)

countLeaves1 :: Tree - Int
countLeaves1 (Tree xs) = sum $ map (countLeaves1) xs
countLeaves1 (Leaf) = 1

incCount :: State Int ()
incCount = do {c - get;
   put (c + 1);
   return ();
  }

countLeaves2   :: Tree - Int
countLeaves2 t = execState (aux t) 0
where
aux :: Tree - State Int ()
aux (Tree xs) = foldr1 () $ map (aux) xs
aux (Leaf) = incCount

main :: IO ()B
main = print $ countLeaves2 $ buildTree 15 6
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Stack usage with a state monad

2003-12-30 Thread Tomasz Zielonka
On Tue, Dec 30, 2003 at 02:12:15PM +, Joe Thornber wrote:
 Hi,
 
 I was wondering if anyone could give me some help with this problem ?

 I'm trying to hold some state in a StateMonad whilst I iterate over a
 large tree, and finding that I'm running out of stack space very
 quickly.  The simplified program below exhibits the same problem.

If you are using Hugs, try compiling your program with GHC (with -O2).

With GHC it seems to work, but it is still rather slow. After 4 minutes
of waiting a killed the process.

Correction: I had an environment option GHCRTS=-K64M, so it just took
more time before the stack exhausted.

I've optimised you program a bit and now it completes after 4 seconds
using only 2 megabytes of memory. After adding strictness annotations,
increasing sharing in the tree generated by buildTree the program still
was quite resource hungry, so I tried using an unboxed tuple (GHC's
extension) in the state monad - it helped a lot.

I am sorry, if I only confused you. My english is not great and time is
running. Got to go :)

Best regards,
Tom

{-# OPTIONS -fglasgow-exts #-}

module Main (module Main) where

-- Program to count the leaf nodes in a rose tree.  Written to try and
-- reproduce a stack space leak present in a larger program.

-- How can I use a state monad to count the leaves without eating all
-- the stack ?

import Control.Monad.State

newtype UnboxedState s a = UnboxedState { runUnboxedState :: s - (# a, s #) }

instance Monad (UnboxedState s) where
return a = UnboxedState $ \s - (# a, s #)
m = k  = UnboxedState $ \s -
case runUnboxedState m s of
(# a, s' #) - runUnboxedState (k a) s'

instance MonadState s (UnboxedState s) where
get   = UnboxedState $ \s - (# s, s #)
put s = UnboxedState $ \_ - (# (), s #)

execUnboxedState m s = case runUnboxedState m s of
(# _, s' #) - s'

data Tree = Tree [Tree] | Leaf

buildTree :: Int - Int - Tree
buildTree order depth =
head $ drop depth $ iterate (\t - Tree (replicate order t)) Leaf

countLeaves1 :: Tree - Int
countLeaves1 (Tree xs) = sum $ map (countLeaves1) xs
countLeaves1 (Leaf) = 1

incCount :: UnboxedState Int ()
incCount = do {c - get;
   put $! (c + 1);
  }

countLeaves2   :: Tree - Int
countLeaves2 t = execUnboxedState (aux t) 0
where
aux (Tree xs) = mapM_ aux xs
aux (Leaf) = incCount

main :: IO ()
main = print $ countLeaves2 $ buildTree 15 6


-- 
.signature: Too many levels of symbolic links
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Stack usage with a state monad

2003-12-30 Thread Koji Nakahara
Hi,

I think the problem is in the State Monad itself;
State Monad is lazy to compute its state.

I am not a haskell expert, and there may be better ideas.  But anyhow,
when I use these = and  instead of = and , 
your example runs fine.  I hope it becomes some help.

m = k = State $ \s - let (a, s') = runState m s
in  s `seq` runState (k a) s' -- force evaluation of the 
state

m  k = m = \_ - k

--
Koji Nakahara
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Stack usage with a state monad

2003-12-30 Thread Tomasz Zielonka
On Wed, Dec 31, 2003 at 02:54:18AM +0900, Koji Nakahara wrote:
 Hi,
 
 I think the problem is in the State Monad itself;
 State Monad is lazy to compute its state.
 
 I am not a haskell expert, and there may be better ideas.  But anyhow,
 when I use these = and  instead of = and , 
 your example runs fine.  I hope it becomes some help.
 
 m = k = State $ \s - let (a, s') = runState m s
   in  s `seq` runState (k a) s' -- force evaluation of the 
 state
 
 m  k = m = \_ - k

Ahh, right. So I didn't have to use UnboxedState. StrictState would do.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Stack usage with a state monad

2003-12-30 Thread Joe Thornber
On Tue, Dec 30, 2003 at 08:28:11PM +0100, Tomasz Zielonka wrote:
 On Wed, Dec 31, 2003 at 02:54:18AM +0900, Koji Nakahara wrote:
  Hi,
  
  I think the problem is in the State Monad itself;
  State Monad is lazy to compute its state.
  
  I am not a haskell expert, and there may be better ideas.  But anyhow,
  when I use these = and  instead of = and , 
  your example runs fine.  I hope it becomes some help.
  
  m = k = State $ \s - let (a, s') = runState m s
  in  s `seq` runState (k a) s' -- force evaluation of the 
  state
  
  m  k = m = \_ - k
 
 Ahh, right. So I didn't have to use UnboxedState. StrictState would do.


Thankyou both for your help, I wouldn't have thought of changing the
State monad itself.  I guess I've got lots more to learn :)

- Joe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe