stack overflow when using ST monad

Hi, I have a program, abstracted from a larger application that I am writing for a customer, that persistently overflows its stack. The program is a simulation of the communication protocol of a sensor tag. The code is below. The program mimics a hardware state machine. In the example below, the internal state is just a counter and a another register that holds what is called the tag's "state": Syncing, Listening or Sleeping. The simulation just advances the tags internal state until the counter reaches zero. (In the real application, there are external inputs that can change the state, but that's not needed to see the problem.) The simulation crashes, running out of stack space after only about 400000 cycles on my machine (OS X 10.4.7 ppc). Both hugs and ghci show it: hugs -98 Test2.hs Hugs mode: Restart with command line option +98 for Haskell 98 mode Type :? for help Main> main ERROR - Garbage collection fails to reclaim sufficient space Main> and ghci: Prelude> :load "/Users/gwright/src/haskell/simulator/test2.hs" Compiling Main ( /Users/gwright/src/haskell/simulator/ test2.hs, interpreted ) Ok, modules loaded: Main. *Main> main FrozenTag {ft_tagID = 1, ft_state = *** Exception: stack overflow *Main> Searches through old mailing lists warn me that it can be hard to tell if evaluation is truly tail recursive, and I saw a discussion of this in the context of "monadic loops", but I never saw a solution. Perhaps in my sleep deprived condition I am missing the obvious, but any help would be appreciated. Best, Greg -- -- Test the state transformer calculation. -- -- 21 August 2006 -- module Main where import Control.Monad.ST import Control.Monad.Writer import Data.STRef import Maybe data TagState = Syncing | Listening | Sleeping deriving (Eq, Show) -- A structure with internal state: -- data Tag s = Tag { tagID :: Int, state :: STRef s TagState, count :: STRef s Integer } data FrozenTag = FrozenTag { ft_tagID :: Int, ft_state :: TagState, ft_count :: Integer } deriving Show -- Repeat a computation until it returns Nothing: -- until_ :: Monad m => m (Maybe a) -> m () until_ action = do result <- action if isNothing result then return () else until_ action -- Here is a toy stateful computation: -- runTag :: ST s (FrozenTag) runTag = do tag <- initialize until_ (step tag) freezeTag tag initialize :: ST s (Tag s) initialize = do init_count <- newSTRef 1000000 init_state <- newSTRef Syncing return (Tag { tagID = 1, state = init_state, count = init_count }) step :: Tag s -> ST s (Maybe Integer) step t = do c <- readSTRef (count t) s <- readSTRef (state t) writeSTRef (count t) (c - 1) writeSTRef (state t) (nextState s) if (c <= 0) then return Nothing else return (Just c) nextState :: TagState -> TagState nextState s = case s of Syncing -> Listening Listening -> Sleeping Sleeping -> Syncing freezeTag :: Tag s -> ST s (FrozenTag) freezeTag t = do frozen_count <- readSTRef (count t) frozen_state <- readSTRef (state t) return (FrozenTag { ft_tagID = tagID t, ft_count = frozen_count, ft_state = frozen_state }) main :: IO () main = do putStrLn (show (runST runTag))

Hi Gregory, Gregory Wright wrote:
step :: Tag s -> ST s (Maybe Integer) step t = do c <- readSTRef (count t) s <- readSTRef (state t) writeSTRef (count t) (c - 1) writeSTRef (state t) (nextState s) if (c <= 0) then return Nothing else return (Just c)
just looking at the program, this seems to be the problem: writeSTRef does not force the evaluation of the stored value. So after repeated calculation, you end up storing not the current counter and state, but something like (nextState (...(nextState (nextState initState))...)). The counter is evaluated for the conditional at the end, so it doesn't exhibit this problem. Your computation runs to its end, then that deeply nested expression is evaluated and exhausts the control stack. Try this instead:
writeSTRef (state t) $! nextState s
If TagState is a more complicated data type, you may also need strict fields in there. [This comes up so often, shouldn't there be an FAQ about it somewhere? It could even offer a guideline along the lines of "Whenever you repeatedly update some value, chances are that you want to force strict evaluation."] Udo.

Hi Udo, On Aug 24, 2006, at 7:22 AM, Udo Stenzel wrote:
Hi Gregory,
Gregory Wright wrote:
step :: Tag s -> ST s (Maybe Integer) step t = do c <- readSTRef (count t) s <- readSTRef (state t) writeSTRef (count t) (c - 1) writeSTRef (state t) (nextState s) if (c <= 0) then return Nothing else return (Just c)
just looking at the program, this seems to be the problem: writeSTRef does not force the evaluation of the stored value. So after repeated calculation, you end up storing not the current counter and state, but something like (nextState (...(nextState (nextState initState))...)). The counter is evaluated for the conditional at the end, so it doesn't exhibit this problem. Your computation runs to its end, then that deeply nested expression is evaluated and exhausts the control stack. Try this instead:
writeSTRef (state t) $! nextState s
If TagState is a more complicated data type, you may also need strict fields in there.
[This comes up so often, shouldn't there be an FAQ about it somewhere? It could even offer a guideline along the lines of "Whenever you repeatedly update some value, chances are that you want to force strict evaluation."]
I agree this should be a FAQ. Perhaps I should write it up for the performance section of the wiki? Looking back I see my mental error was that I thought I was doing what you and everyone else correctly suggested: writeSTRef (state t) $! nextState s but what I actually typed was writeSTRef (state t) (nextState $! s) which of course doesn't help. Another telling example of the fact that coffee is not an entirely adequate substitute for sleep. Best, Greg
Udo. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Gregory, Thursday, August 24, 2006, 4:43:57 PM, you wrote:
I agree this should be a FAQ.
we already have something like this on performance/strictness wikipage. although adding your example of misusing $! may be helpful - peoples are always better learned on (good and bad) examples rather on bare theory
Perhaps I should write it up for the performance section of the wiki? Looking back I see my mental error was that I thought I was doing what you and everyone else correctly suggested:
writeSTRef (state t) $! nextState s
but what I actually typed was
writeSTRef (state t) (nextState $! s)
which of course doesn't help. Another telling example of the fact that coffee is not an entirely adequate substitute for sleep.
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

The write*Ref functions, like many "write into data structure" have the common problem of being much lazier than you want. The nextState calls form a lazy thunk. In fact it tries form 10^6 nested thunks to call nextState. So you have to use something like seq to reduce the laziness:
step :: Tag s -> ST s (Maybe Integer) step t = do c <- readSTRef (count t) s <- readSTRef (state t) writeSTRef (count t) (c - 1) let state'=nextState s state' `seq` writeSTRef (state t) state' if (c <= 0) then return Nothing else return (Just c)

Hello Gregory, Thursday, August 24, 2006, 2:29:15 PM, you wrote:
step t = do c <- readSTRef (count t) s <- readSTRef (state t) writeSTRef (count t) (c - 1) writeSTRef (state t) (nextState s) if (c <= 0) then return Nothing else return (Just c)
as Chris said, you are write unevaluated chunks. add $! to evaluate values before writing: writeSTRef (count t) $! (c - 1) writeSTRef (state t) $! (nextState s) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat, On Aug 24, 2006, at 7:52 AM, Bulat Ziganshin wrote:
Hello Gregory,
Thursday, August 24, 2006, 2:29:15 PM, you wrote:
step t = do c <- readSTRef (count t) s <- readSTRef (state t) writeSTRef (count t) (c - 1) writeSTRef (state t) (nextState s) if (c <= 0) then return Nothing else return (Just c)
as Chris said, you are write unevaluated chunks.
add $! to evaluate values before writing:
writeSTRef (count t) $! (c - 1) writeSTRef (state t) $! (nextState s)
That fixed it exactly. Thank you Bulat and Chris! Best Wishes, Greg
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Gregory Wright wrote:
-- A structure with internal state: -- data Tag s = Tag { tagID :: Int, state :: STRef s TagState, count :: STRef s Integer }
data FrozenTag = FrozenTag { ft_tagID :: Int, ft_state :: TagState, ft_count :: Integer } deriving Show
I would make all the fields strict here, to be sure that no lazyness can creep about unseen eg: data Tag s = Tag { tagID :: !Int, state :: !(STRef s TagState), count :: !(STRef s Integer) } -- ditto for FrozenTag (And use (writeSTRef ref $! value) as others have suggested) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Hello Brian, Thursday, August 24, 2006, 4:16:41 PM, you wrote:
I would make all the fields strict here, to be sure that no lazyness can creep about unseen eg:
data Tag s = Tag { tagID :: !Int, state :: !(STRef s TagState), count :: !(STRef s Integer) }
perhaps better: data Tag s = Tag { tagID :: !Int, state :: STRef s !TagState, count :: STRef s !Integer } although i don't even sure that this will compile (in this case we can request it as wishful feature). in theory, this should allow to omit '$!' from writeRef calls also, one can implement strict write operations: writeRef r x = writeSTRef r $! x or use my unboxed references (but not with Integer) - http://haskell.org/haskellwiki/Library/ArrayRef -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat! On Aug 24, 2006, at 1:07 PM, Bulat Ziganshin wrote:
Hello Brian,
Thursday, August 24, 2006, 4:16:41 PM, you wrote:
I would make all the fields strict here, to be sure that no lazyness can creep about unseen eg:
data Tag s = Tag { tagID :: !Int, state :: !(STRef s TagState), count :: !(STRef s Integer) }
perhaps better:
data Tag s = Tag { tagID :: !Int, state :: STRef s !TagState, count :: STRef s !Integer }
although i don't even sure that this will compile (in this case we can request it as wishful feature). in theory, this should allow to omit '$!' from writeRef calls
Alas, at the moment the last gives (in ghc-6.4.2), Unexpected strictness annotation: !TagState In the data type declaration for `Tag' Failed, modules loaded: none. Prelude>
also, one can implement strict write operations:
writeRef r x = writeSTRef r $! x
or use my unboxed references (but not with Integer) - http://haskell.org/haskellwiki/Library/ArrayRef
I will look at this. Thanks! Best Wishes, Greg
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (5)
-
Brian Hulley
-
Bulat Ziganshin
-
Chris Kuklewicz
-
Gregory Wright
-
Udo Stenzel