[Haskell-cafe] Lazy Evaluation in Monads

Albert Y. C. Lai trebla at vex.net
Wed Jun 1 02:26:09 CEST 2011


On a tangent, not doing IO, but food for thought:

{-# LANGUAGE FlexibleContexts #-}

import Control.Monad.State.Lazy as N
import Control.Monad.State.Strict as S

gen :: (MonadState [()] m) => m ()
gen = do
   gen
   modify (() :)

many = take 3 (N.execState gen [])
none = take 3 (S.execState gen [])




More information about the Haskell-Cafe mailing list