[Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread michael rice
Given the first program, it seems that the unchanging first element of the 
tuple could be handled by a Reader monad, leading to the second program, where 
b becomes the state, but how do I get the constant a from the Reader monad?

Michael 

==

import Control.Monad.State

type GeneratorState = State (Double,Double)

sqrtST :: GeneratorState Double
sqrtST = do (a,b0) - get
    let b1 = (b0**2.0+a)/(2.0*b0)
    (if (abs (a-b1**2.0))  0.01
  then
    return b1
  else do
    put (a,b1)
    sqrtST)

mySqrt a = let b = a/2.0
   in fst ( runState sqrtST (a,b) )

{-
*Main mySqrt 2.0
1.4142135623746899
-}

==

import Control.Monad.Reader
import Control.Monad.State

type GeneratorState = State Double

sqrtST :: GeneratorState Double
sqrtST = do b0 - get
    let a = ?
    b1 = (b0**2.0+a)/(2.0*b0)
    (if (abs (a-b1**2.0))  0.01
  then
    return b1
  else do
    put b1
    sqrtST)


mySqrt a = let b = a/2.0
   in runReaderT (runState sqrtST b) a




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


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread Thomas Davie
Is the idea here merely an exercise in using the state monad?  This can be 
easily performed using pure code.

Bob

On 3 Feb 2011, at 19:18, michael rice wrote:

 Given the first program, it seems that the unchanging first element of the 
 tuple could be handled by a Reader monad, leading to the second program, 
 where b becomes the state, but how do I get the constant a from the Reader 
 monad?
 
 Michael 
 
 ==
 
 import Control.Monad.State
 
 type GeneratorState = State (Double,Double)
 
 sqrtST :: GeneratorState Double
 sqrtST = do (a,b0) - get
 let b1 = (b0**2.0+a)/(2.0*b0)
 (if (abs (a-b1**2.0))  0.01
   then
 return b1
   else do
 put (a,b1)
 sqrtST)
 
 mySqrt a = let b = a/2.0
in fst ( runState sqrtST (a,b) )
 
 {-
 *Main mySqrt 2.0
 1.4142135623746899
 -}
 
 ==
 
 import Control.Monad.Reader
 import Control.Monad.State
 
 type GeneratorState = State Double
 
 sqrtST :: GeneratorState Double
 sqrtST = do b0 - get
 let a = ?
 b1 = (b0**2.0+a)/(2.0*b0)
 (if (abs (a-b1**2.0))  0.01
   then
 return b1
   else do
 put b1
 sqrtST)
 
 
 mySqrt a = let b = a/2.0
in runReaderT (runState sqrtST b) a
 
 
 ___
 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] Reader monad wrapping State monad

2011-02-03 Thread Daniel Fischer
On Thursday 03 February 2011 20:18:43, michael rice wrote:
 Given the first program, it seems that the unchanging first element of
 the tuple could be handled by a Reader monad, leading to the second
 program, where b becomes the state, but how do I get the constant a from
 the Reader monad?

You need a monad-transformer to use both, Reader and State.
You can use either

ReaderT Double (State Double)

or

StateT Double (Reader Double)

(they're isomorphic).

Then you can query the modifiable state with get (from the MonadState 
class) and the immutable with ask (from the MonadReader class)

type Heron = StateT Double (Reader Double)

sqrtH :: Heron Double
sqrtH = do
  a - ask
  b - get
  let c = 0.5*(b + a/b)
  if (good enough)
then return c
else put c  sqrtH

mySqrt a = runReader (evalStateT sqrtH (a*0.5)) a


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


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread Ozgur Akgun
On 3 February 2011 19:18, michael rice nowg...@yahoo.com wrote:

 but how do I get the constant a from the Reader monad?


http://hackage.haskell.org/packages/archive/transformers/latest/doc/html/Control-Monad-Trans-Reader.html#v:ask

You also need to change the type to use ReaderT.

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


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread michael rice
Hi Daniel,

Ok, but what I was looking for was ReaderT on top, State on the bottom. This is 
very confusing material, with no apparent conceptual commonality (ad hoc comes 
to mind) among the many examples I've looked at. Sometimes lift is used, other 
times a lift helper function, and in this case no use of lift at all.

Michael

--- On Thu, 2/3/11, Daniel Fischer daniel.is.fisc...@googlemail.com wrote:

From: Daniel Fischer daniel.is.fisc...@googlemail.com
Subject: Re: [Haskell-cafe] Reader monad wrapping State monad
To: haskell-cafe@haskell.org
Cc: michael rice nowg...@yahoo.com
Date: Thursday, February 3, 2011, 2:54 PM

On Thursday 03 February 2011 20:18:43, michael rice wrote:
 Given the first program, it seems that the unchanging first element of
 the tuple could be handled by a Reader monad, leading to the second
 program, where b becomes the state, but how do I get the constant a from
 the Reader monad?

You need a monad-transformer to use both, Reader and State.
You can use either

ReaderT Double (State Double)

or

StateT Double (Reader Double)

(they're isomorphic).

Then you can query the modifiable state with get (from the MonadState 
class) and the immutable with ask (from the MonadReader class)

type Heron = StateT Double (Reader Double)

sqrtH :: Heron Double
sqrtH = do
  a - ask
  b - get
  let c = 0.5*(b + a/b)
  if (good enough)
    then return c
    else put c  sqrtH

mySqrt a = runReader (evalStateT sqrtH (a*0.5)) a




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


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread Daniel Fischer
On Thursday 03 February 2011 21:40:13, michael rice wrote:
 Hi Daniel,

 Ok, but what I was looking for was ReaderT on top, State on the bottom.

No problem, just change the definition of the Heron type synonym and swap 
the applcations of runReader[T] and evalState[T] in mySqrt, the monadic 
sqrtH can remain unchanged :)

 This is very confusing material, with no apparent conceptual commonality
 (ad hoc comes to mind) among the many examples I've looked at. Sometimes
 lift is used, other times a lift helper function, and in this case no
 use of lift at all.

That's because only methods of the MonadState and the MonadReader class are 
used and instances of MonadState are propagated/lifted through ReaderT, 
instance of MonadReader are propagated/lifted through StateT.

(
instance MonadReader r m = MonadReader r (StateT s m) where
ask = lift ask
local = ...
instance MonadState s m = MonadState (ReaderT r m) where
get = lift get
put = ...
)

If you use a function on the inner monad which is not propagated to the 
entire transformer stack via class instances, you have to use lift (if you 
have a MonadTrans instance) or something similar.


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


Re: [Haskell-cafe] Reader monad wrapping State monad

2011-02-03 Thread michael rice
And swap the arguments.



Thanks for going the extra mile.



Michael


--- On Thu, 2/3/11, Daniel Fischer daniel.is.fisc...@googlemail.com wrote:

From: Daniel Fischer daniel.is.fisc...@googlemail.com
Subject: Re: [Haskell-cafe] Reader monad wrapping State monad
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Thursday, February 3, 2011, 4:15 PM

On Thursday 03 February 2011 21:40:13, michael rice wrote:
 Hi Daniel,

 Ok, but what I was looking for was ReaderT on top, State on the bottom.

No problem, just change the definition of the Heron type synonym and swap 
the applcations of runReader[T] and evalState[T] in mySqrt, the monadic 
sqrtH can remain unchanged :)

 This is very confusing material, with no apparent conceptual commonality
 (ad hoc comes to mind) among the many examples I've looked at. Sometimes
 lift is used, other times a lift helper function, and in this case no
 use of lift at all.

That's because only methods of the MonadState and the MonadReader class are 
used and instances of MonadState are propagated/lifted through ReaderT, 
instance of MonadReader are propagated/lifted through StateT.

(
instance MonadReader r m = MonadReader r (StateT s m) where
    ask = lift ask
    local = ...
instance MonadState s m = MonadState (ReaderT r m) where
    get = lift get
    put = ...
)

If you use a function on the inner monad which is not propagated to the 
entire transformer stack via class instances, you have to use lift (if you 
have a MonadTrans instance) or something similar.




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