[Haskell-cafe] Re: Monad.Reader with updates

Ryan Ingram ryani.spam at gmail.com
Thu Nov 6 14:04:34 EST 2008


Hi Mauricio.  What you want actually already exists in QuickCheck as
the "Gen" monad.
>From http://hackage.haskell.org/packages/archive/QuickCheck/1.1.0.0/doc/html/src/Test-QuickCheck.html#Gen

newtype Gen a
  = Gen (Int -> StdGen -> a)

instance Monad Gen where
  return a    = Gen (\n r -> a)
  Gen m >>= k =
    Gen (\n r0 -> let (r1,r2) = split r0
                      Gen m'  = k (m n r1)
                   in m' n r2)

This has an additional "size" parameter in the environment, but other
than that it sounds like exactly what you are asking for.  There is
the problem, as others have pointed out, that it doesn't strictly
follow the monad laws; (m >>= return) is not the same as (m).

You can make a "fast and loose" argument that the whole point is that
each view of the generator is supposed to get a random source, so the
fact that it is a different random source shouldn't matter.  I'm not
sure how one would go about a formal analysis of this property.  But
it doesn't seem to have caused any problems for the QuickCheck folks.

You could also implement this as a variation on the State monad if you
wanted to avoid using split:

import Control.Monad.State
advance :: RNG -> RNG  -- supplied by you

newtype GenA a = GenA (State RNG a)
runGenA (GenA m) = m

instance Monad GenA where
    return a = GenA $ return a
    m >>= k = GenA $ do
        a <- runGenA m
        modify advance
        runGenA (k a)

(The obvious extension to StateT applies to make GenAT).

  -- ryan

On Thu, Nov 6, 2008 at 6:18 AM, Mauricio <briqueabraque at yahoo.com> wrote:
>>>>> Is there  some abstraction in  current ghc library  that implements
>>>>> something like  Reader, but where  the value of the  environment is
>>>>> updated at every "step"?
>>>>
>> It doesn't  quite make sense,  because one "step" isn't  well defined.
>> How many  "steps" is "return (f  x)" ? how  about "return x >>=  \y ->
>> return (f y)" ? (...)
>>
>
> I  understand.  But  do  you  think something  like  the (obviously  not
> working)  code below  could  respect  monad laws,  if  I could  consider
> (environment->a) a monad over a?
>
>  update = snd . next ; -- this updates a random number generator
>
>  instance RandomGen environment => Monad ( environment -> a ) where {
>
>   -- below, f :: g1 -> ( environment -> g2 )
>   p >>= f = p2 where { p2 e = ( f . p $ e ) . update } ;
>
>   return = const ;
>
>  }
>
> Then I would do something like:
>
>  getStdGen >>= ( return . do { a >>= b >>= c } )
>
>>
>> So I think you'd have to make the steps explicit. (...)
>>
>> advance :: m () -- your primitive which changes the environment
>>
>> a >>* b = a >> advance >> b
>> a >>*= f = do { r <- a; advance; f r }
>>
>
> The problem is that I need 'a' or 'b' above to sometimes also change the
> environment. I think with this method I could not get that.
>
> Thanks,
> Maurício
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list