Bug in Control.Monad.State

Yitzchak Gale gale at sefer.org
Tue Nov 22 21:38:26 EST 2005


> ...I did not understand the example you posted,
> as it contains functions that are not defined...

Sorry. I actually think you understood it quite
well, from what you wrote in reply. But OK, I will
put in some more annotation below.

> but here is something you can do (...using
> monadLib...).  Letme know if this helps.

Well, I like using infinite lists - where a
sequence is completely decoupled from its end
conditions - as opposed to while-loop-like
constructs. And other such lazy paradigms when
appropriate. And I also like using monads when
they make my code more clear - which is usually.

And I like using these things together when they
happen to coincide. I gave Udo an example of a
common kind of situation in which that happens.

You wrote that you introduced some limited kind of
strictness in your state monad. My question was:
Can I still use infinite lists and state monads
together in monadLib?  I think your answer is
"No." Am I correct?

Regards,
Yitz

Iavor's code:

> import Monad.StateT
> import Monad.Id
> import Random
> 
> type M        = StateT (StdGen,[Int]) Id
> 
> randomItem   :: M ()
> randomItem    = do (g,xs) <- peek
>                    let (x,g') = random g
>                    poke_ (g',mod x 5 : xs)
> 
> needMoreItems :: M Bool
> needMoreItems = do (_,xs) <- peek
>                    return (sum xs < 50)
> 
> whileM p b    = do x <- p
>                    if x then b >> whileM p b else return ()
> 
> test          = do g <- newStdGen
>                    print $ runId $ evalState (g,[])
>                                  $ do whileM needMoreItems randomItem
>                                       (_,xs) <- peek
>                                       return xs

My code (that I wrote to Udo), with additional annotation:

import System.Random
import Control.Monad.State

createItems :: RandomGen g => State g [Item]
createItems =
  liftM catMaybes $ runListT $
  flip evalStateT initialState $ runMaybeT $
  do
    item <- liftRandom $ repeatM randomItem
    updateState item
    needMoreItems >>= guard
    return item
  where
    liftRandom = lift . lift . lift

-- The type of the items we need to create.
type Item = Int

-- Create one random item.
randomItem :: RandomGen g => State g Item
randomItem = State $ randomR (1, 5)

-- The type of the state we need to keep while
-- computing whether we have enough items yet.
type MyState = Int

-- The initial state while computing whether we
-- have enough items yet.
initialState :: MyState
initialState = 0

-- Update the state after creating an Item.
updateState :: MonadState MyState m => Item -> m ()
updateState = modify . (+)

--Do we need any more items?
needMoreItems :: MonadState MyState m => m Bool
needMoreItems = gets (< 50)

-- repeatM is still missing from Control.Monad.
-- I hope they will put it in soon.
repeatM :: Monad m => m a -> m [a]
repeatM = sequence . repeat

-- MaybeT is still missing from mtl.
-- I hope they will put it in soon.
newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)}
instance Monad m => Monad (MaybeT m) where ...
instance Monad m => MonadPlus (MaybeT m) where ...
instance MonadState s m => MonadState s (MaybeT m) where ...


More information about the Libraries mailing list