[Haskell-cafe] Multiple State Monads

David Menendez dave at zednenem.com
Mon Jan 12 22:13:33 EST 2009


On Mon, Jan 12, 2009 at 8:34 PM, Phil <pbeadling at mail2web.com> wrote:
> Thanks Minh - I've updated my code as you suggested.  This looks better than
> my first attempt!
>
> Is it possible to clean this up any more?  I find:
>
> ( (), (Double, Word64) )
>
> a bit odd syntactically, although I understand this is just to fit the type
> to the State c'tor so that we don't have to write our own Monad longhand.

If you have a function which transforms the state, you can lift it
into the state monad using "modify".

> evolveUnderlying :: (Double, Word64) -> (Double, Word64)
> evolveUnderlying (stock, state) = ( newStock, newState )
>  where
>    newState = ranq1Increment state
>    newStock = stock * exp ( ( ir - (0.5*(vol*vol)) )*timeStep + (
> vol*sqrt(timeStep)*normalFromRngState(state) ) )
>
> getEvolution :: State (Double, Word64) ()
> getEvolution = modify evolveUnderlying

Now, I don't know the full context of what you're doing, but the
example you posted isn't really gaining anything from the state monad.
Specifically,

  execState (replicateM_ n (modify f))
= execState (modify f >> modify f >> ... >> modify f)
= execState (modify (f . f . ... . f))
= f . f . ... . f

So you could just write something along these lines,

> mcSimulate :: Double -> Double -> Word64 -> [Double]
> mcSimulate startStock endTime seedForSeed = fst expiryStock : mcSimulate
> startStock endTime newSeedForSeed
>  where
>    expiryStock = iterate evolveUnderlying (startStock, ranq1Init seedForSeed) !! truncate (endTime/timeStep)
>    newSeedForSeed = seedForSeed + 246524


Coming back to your original question, it is possible to work with
nested state monad transformers. The trick is to use "lift" to make
sure you are working with the appropriate state.

get :: StateT s1 (State s2) s1
put :: s1 -> StateT s1 (State s2) ()

lift get :: StateT s1 (State s2) s2
lift put :: s2 -> StateT s1 (State s2) ()

A more general piece of advice is to try breaking things into smaller
pieces. For example:

getRanq1 :: MonadState Word64 m => m Word64
getRanq1 = do
    seed <- get
    put (ranq1Increment seed)
    return seed

getEvolution :: StateT Double (State Word64) ()
getEvolution = do
    seed <- lift getRanq1
    modify $ \stock -> stock * exp ( ( ir - (0.5*(vol*vol)) )*timeStep
+ ( vol*sqrt(timeStep)*normalFromRngState(seed) ) )


-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list