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

2008-11-07 Thread Mauricio

> Hi Mauricio.  What you want actually already exists in QuickCheck as
> the "Gen" monad.
>
> 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)
>
> (...)

Nice. I think that's exactly what I was trying to do.

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

Yes.  After Brent's explanation I finally realized State was the perfect
option. Maybe  it should  also be better  for QuickCheck. I  just didn't
know it…  There are  many things  in the standard  library that  do nice
things, but  I don't understand them  until I write a  few hundred lines
trying to do what they do :)

Thanks for your support and patience,
Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-11-07 Thread Brent Yorgey
On Fri, Nov 07, 2008 at 10:41:01AM +0100, Achim Schneider wrote:
> 
> But then, you either want a ReaderT r State s or StateT s Reader r,
> depending on how you want to write your code... the main thing that
> confuses me right now is that nesting order doesn't seem to matter that
> much in this case which makes me wonder if I really understood how
> those two nest.

>From the mtl documentation ([1], [2]):

  Reader r a  =~  r -> a
  State s a   =~  s -> (a, s)

  StateT s m a  =~ s -> m (a, s)
  ReaderT r m a =~ r -> m a

where =~ indicates isomorphism of types (up to newtype tags).

So,
  
  ReaderT r (State s) a  =~   r -> State s a  =~  r -> s -> (a,s)

and

  StateT s (Reader r) a  =~  s -> Reader r (a,s)  =~  s -> r -> (a,s)

which are clearly isomorphic, just a simple function argument
reordering.  For some combinations of monad transformers (for
example, StateT and MaybeT), the order of composition really does
matter, but not for Reader and State.

Moreover, if you make your new composed monad using a newtype with
generalized deriving [3], the choice actually doesn't matter since you
can write exactly the same code:

  newtype MyMonad a = My { unMy :: ReaderT r (State s) a }
deriving (Functor, Monad, MonadReader r, MonadState s)

You could also write the newtype the other way around, and still use
it with the same code: you can just treat MyMonad as if it is both a
Reader monad (ask, asks, local...) and a State monad (get, gets, put,
modify...) with no icky lifts in sight.

I don't know what this thread was originally about, but just thought
I'd jump in to clarify. =)

-Brent

[1] 
http://hackage.haskell.org/packages/archive/mtl/1.1.0.1/doc/html/Control-Monad-State-Lazy.html
[2] 
http://hackage.haskell.org/packages/archive/mtl/1.1.0.1/doc/html/Control-Monad-Reader.html
[3] http://cale.yi.org/index.php/How_To_Use_Monad_Transformers
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-11-07 Thread Achim Schneider
Maurcio <[EMAIL PROTECTED]> wrote:

> > 
> >> [...]
> >>
> > Are you sure you don't want to use monad transformers?
> > 
> 
> No. Do you have a sugestion on how could I do
> it in this situation?
> 
Not really, mainly because if monad transformers don't confuse you you
should double-check if you aren't one of these SPJ clones he spawned to
make Haskell succeed...

But then, you either want a ReaderT r State s or StateT s Reader r,
depending on how you want to write your code... the main thing that
confuses me right now is that nesting order doesn't seem to matter that
much in this case which makes me wonder if I really understood how
those two nest.

As another idea, you might want to use Parsec, you can regard it as a
Reader on steroids and it also supports state, though you'll be
conjuring up evil spirits if you try to influence parsing behaviour
with it instead of just your return values. Two or even more passes
are the way to go in such cases.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-11-06 Thread Ryan Ingram
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 <[EMAIL PROTECTED]> 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@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-11-06 Thread Jules Bean

Mauricio wrote:

 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.


I no longer understand what you want.

I thought you wanted an environment which automatically changed every 
"step".


I showed you how you can do that, although it requires making explicit 
what a "step" is, which you could do with custom combinators.


Now you want any part of the action to change the environment?

In this case, use the state monad, not the reader monad. That is what 
it's for.


Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-11-06 Thread Maurí­cio



[...]


Are you sure you don't want to use monad transformers?



No. Do you have a sugestion on how could I do
it in this situation?

Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-11-06 Thread Achim Schneider
Mauricio <[EMAIL PROTECTED]> wrote:

> [...]
>
Are you sure you don't want to use monad transformers?

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-11-06 Thread Mauricio

 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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-11-06 Thread Jules Bean

Mauricio 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"?


do-it-yourself? you can start from reader definition and add what you
need. you just need to make "initial state" consisting from state
itself and update function so `run` will have just one initialization 
argument




Sure. I've done a few versions, trying to change
the way (>>=) is defined, and learned a lot with
that. But I wanted to know if there's already the
"right way to do it" instead of my "newbie way to
do it" :)


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)" ?


Because the monad laws guarantee those two things should be the same, 
and yet the first is zero steps and the second is one step, going by the 
crude "counting >>=s" method I'm guess you were thinking of.


So I think you'd have to make the steps explicit.

You could do this with a custom version of (>>) and (>>=) which 
automatically do a step, for example.


So

advance :: m () -- your primitive which changes the environment

a >>* b = a >> advance >> b
a >>*= f = do { r <- a; advance; f r }

Does that help?

Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-11-06 Thread Bulat Ziganshin
Hello Mauricio,

Thursday, November 6, 2008, 2:52:16 PM, you wrote:

> that. But I wanted to know if there's already the
> "right way to do it" instead of my "newbie way to
> do it" :)

"All about monads" doesn't mention it, at least :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-11-06 Thread Mauricio

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"?


do-it-yourself? you can start from reader definition and add what you
need. you just need to make "initial state" consisting from state
itself and update function so `run` will have just one initialization argument



Sure. I've done a few versions, trying to change
the way (>>=) is defined, and learned a lot with
that. But I wanted to know if there's already the
"right way to do it" instead of my "newbie way to
do it" :)

Thanks,
Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe