[Haskell-cafe] Multiple State Monads

Phil pbeadling at mail2web.com
Tue Jan 13 17:29:02 EST 2009


Many thanks for the replies.

Using 'modify' cleans the syntax up nicely.

With regard to using 'iterate' as shown by David here:

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

My only concern with using this method is - Will 'iterate' not create a full
list of type [Double] and then take the final position once the list has
been fully realized?  For my application this would be undesirable as the
list may be millions of items long, and you only ever care about the last
iteration (It's a crude Monte Carlo simulator to give it some context).  If
Haskell is smart enough to look ahead and see as we only need the last
element as it is creating the list, therefore garbage collecting earlier
items then this would work fine - by I'm guessing that is a step to far for
the compiler?

I had originally implemented this similar to the above (although I didn't
know about the 'iterate' keyword - which makes things tidier - a useful
tip!), I moved to using the state monad and replicateM_ for the first
truncate(endTime/timeStep)-1 elements so that everything but the last result
is thrown away, and a final bind to getEvolution would return the result.

Now that the code has been modified so that no result is passed back, using
modify and execState, this can be simplified to "replicateM_
truncate(endTime/timeStep)" with no final bind needed.  I've tried this and
it works fine.

The key reason for using the Monad was to tell Haskell to discard all but
the current state.  If I'm wrong about please let me know, as I don't want
to be guilty of overcomplicating my algorithm, and more importantly it means
I'm not yet totally grasping the power of Haskell!

Thanks again,

Phil.




On 13/01/2009 03:13, "David Menendez" <dave at zednenem.com> wrote:

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



More information about the Haskell-Cafe mailing list