[Haskell-cafe] Monad strictness

Yitzchak Gale gale at sefer.org
Mon Nov 21 06:49:31 EST 2005


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


More information about the Haskell-Cafe mailing list