
In the following, why does testA work and testB diverge? Where is the strictness coming from? Thanks, Yitz module Test where import Control.Monad.State import Control.Monad.Identity repeatM :: Monad m => m a -> m [a] repeatM = sequence . repeat testA = take 5 $ flip evalState [1..10] $ repeatM $ do x <- gets head modify tail return x testB = take 5 $ runIdentity $ flip evalStateT [1..10] $ repeatM $ do x <- gets head modify tail return x

Yitzchak Gale wrote:
In the following, why does testA work and testB diverge? Where is the strictness coming from?
My guess: from strict pattern matching in (>>=). The following StateT variant uses lazy (irrefutable) pattern match instead. Regards, Roberto Zunino. ==== newtype StT s m a = StT { runStT :: s -> m (a,s) } instance (Monad m) => Monad (StT s m) where return a = StT $ \s -> return (a, s) m >>= k = StT $ \s -> do -- was: (a, s') <- runStT m s ~(a, s') <- runStT m s runStT (k a) s' fail str = StT $ \_ -> fail str stGet :: Monad m => StT s m s stGet = StT $ \s -> return (s,s) stPut :: Monad m => s -> StT s m () stPut s = StT $ \_ -> return ((),s) evalStT :: Monad m => StT s m a -> s -> m a evalStT m s = do (x,_) <- runStT m s ; return x repeatM :: Monad m => m a -> m [a] repeatM = sequence . repeat testC = take 5 $ runIdentity $ flip evalStT [1..10] $ repeatM $ do s <- stGet let x = head s stPut $ tail s return x ====

Am Montag, 21. November 2005 16:09 schrieb Roberto Zunino:
Yitzchak Gale wrote:
In the following, why does testA work and testB diverge? Where is the strictness coming from?
My guess: from strict pattern matching in (>>=).
This is a problem I came across some months ago. State uses lazy pattern matching (implicitely via a let expression) while StateT uses strict pattern matching (inside a do statement). Both should definitely use lazy pattern matching, in my opinion.
[...]
The following StateT variant uses lazy (irrefutable) pattern match instead.
Good! :-)
Regards, Roberto Zunino.
[...]
Best wishes, Wolfgang
participants (3)
-
Roberto Zunino
-
Wolfgang Jeltsch
-
Yitzchak Gale