Multiple State Monads

Hi, I¹ve been reading the Monads aren¹t evil posts with interest I¹m a 2nd week Haskell newbie and I¹m doing my best to use them where (I hope) it is appropriate. Typically I¹m writing my code out without using Monads (normally using list recursion), and then when I get them working, I delve into the Monad world.... This has been going well so far with a bit of help from you guys, but I¹ve hit a snag. In the code below I¹m using a state Monad (getEvolution), but unlike simpler cases I¹m passing around two items of state, and one of these states is also ultimately a result although I don¹t care about the result until I reach an end state. My implementation is a bit ugly to say the least and clearly I¹m forcing round pegs into square holes here reading a bit online I get the impression that I can solve the two-state issue using Monad Transformers, by wrapping a StateT around a regular State object (or even two StateT Monads around an Identity Monad??). I think I understand the theory here, but any attempt to implement it leads to a horrible mess that typically doesn¹t compile. The other problem of having a state that is also a result, I¹m sure what to do about this. Was wondering if anyone could give me a push in the right direction how can I rework my state monad so that it looks less wildly. Many thanks, Phil. mcSimulate :: Double -> Double -> Word64 -> [Double] mcSimulate startStock endTime seedForSeed = expiryStock : mcSimulate startStock endTime newSeedForSeed where expiryStock = evalState ( do replicateM_ (truncate(endTime/timeStep)-1) getEvolution; getEvolution ) $ (startStock,ranq1Init seedForSeed) newSeedForSeed = seedForSeed + 246524 discount :: Double -> Double -> Double -> Double discount stock r t = stock * exp (-r)*t payOff :: Double -> Double -> Double payOff strike stock | (stock - strike) > 0 = stock - strike | otherwise = 0 -- Monad Implementation -- Yuk! evolveUnderlying :: (Double, Word64) -> ( Double, (Double, Word64) ) evolveUnderlying (stock, state) = ( newStock, ( newStock, newState ) ) where newState = ranq1Increment state newStock = stock * exp ( ( ir - (0.5*(vol*vol)) )*timeStep + ( vol*sqrt(timeStep)*normalFromRngState(state) ) ) getEvolution :: State (Double, Word64) Double getEvolution = State evolveUnderlying

2009/1/12 Phil
Hi,
I've been reading the Monads aren't evil posts with interest – I'm a 2nd week Haskell newbie and I'm doing my best to use them where (I hope) it is appropriate. Typically I'm writing my code out without using Monads (normally using list recursion), and then when I get them working, I delve into the Monad world.... This has been going well so far with a bit of help from you guys, but I've hit a snag.
In the code below I'm using a state Monad (getEvolution), but unlike simpler cases I'm passing around two items of state, and one of these states is also ultimately a result – although I don't care about the result until I reach an end state. My implementation is a bit ugly to say the least and clearly I'm forcing round pegs into square holes here – reading a bit online I get the impression that I can solve the two-state issue using Monad Transformers, by wrapping a StateT around a regular State object (or even two StateT Monads around an Identity Monad??). I think I understand the theory here, but any attempt to implement it leads to a horrible mess that typically doesn't compile. The other problem of having a state that is also a result, I'm sure what to do about this.
Was wondering if anyone could give me a push in the right direction – how can I rework my state monad so that it looks less wildly.
Many thanks,
Phil.
mcSimulate :: Double -> Double -> Word64 -> [Double] mcSimulate startStock endTime seedForSeed = expiryStock : mcSimulate startStock endTime newSeedForSeed where expiryStock = evalState ( do replicateM_ (truncate(endTime/timeStep)-1) getEvolution; getEvolution ) $ (startStock,ranq1Init seedForSeed) newSeedForSeed = seedForSeed + 246524
discount :: Double -> Double -> Double -> Double discount stock r t = stock * exp (-r)*t
payOff :: Double -> Double -> Double payOff strike stock | (stock - strike) > 0 = stock - strike | otherwise = 0
-- Monad Implementation
-- Yuk! evolveUnderlying :: (Double, Word64) -> ( Double, (Double, Word64) ) evolveUnderlying (stock, state) = ( newStock, ( newStock, newState ) ) where newState = ranq1Increment state newStock = stock * exp ( ( ir - (0.5*(vol*vol)) )*timeStep + ( vol*sqrt(timeStep)*normalFromRngState(state) ) )
getEvolution :: State (Double, Word64) Double getEvolution = State evolveUnderlying
Hi, the evolveUnderlying can simply manipulate the state, so you can do evolveUnderlying -- state (not your state, but the tuple) changes here r <- gets fst -- query the state for the first element of the tuple return r -- simply return what you want Note that if you want to combine your state and the stock, you simply end with a new kind of state : the tuple (thus, no need to compose two State) Note also, since evolveUnderlying only manipulates the internal state of the State monad, it returns (). Depending on how you want to structure your code, you can also use execState instead of evalState : it returns the state on which you can use fst. hope it helps, Thu

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. I
guess given that (), as I understand, is just like 'void' in C, it should
not affect program performance, and the fact that I'm using replicateM_
means that the result is being ignored for all but my last iteration.
As an exercise I assume I could have approached the problem using the StateT
transformer, although for the purposes below carrying two states in a tuple
is probably clearer and more performant?
Thanks again,
Phil.
mcSimulate :: Double -> Double -> Word64 -> [Double]
mcSimulate startStock endTime seedForSeed = fst expiryStock : mcSimulate
startStock endTime newSeedForSeed
where
expiryStock = execState ( do replicateM_ (truncate(endTime/timeStep)-1)
getEvolution; getEvolution )
$ (startStock,ranq1Init seedForSeed)
newSeedForSeed = seedForSeed + 246524
-- Monad Implementation
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 = State evolveUnderlying
On 12/01/2009 20:49, "minh thu"
2009/1/12 Phil
: Hi,
I've been reading the Monads aren't evil posts with interest I'm a 2nd week Haskell newbie and I'm doing my best to use them where (I hope) it is appropriate. Typically I'm writing my code out without using Monads (normally using list recursion), and then when I get them working, I delve into the Monad world.... This has been going well so far with a bit of help from you guys, but I've hit a snag.
In the code below I'm using a state Monad (getEvolution), but unlike simpler cases I'm passing around two items of state, and one of these states is also ultimately a result although I don't care about the result until I reach an end state. My implementation is a bit ugly to say the least and clearly I'm forcing round pegs into square holes here reading a bit online I get the impression that I can solve the two-state issue using Monad Transformers, by wrapping a StateT around a regular State object (or even two StateT Monads around an Identity Monad??). I think I understand the theory here, but any attempt to implement it leads to a horrible mess that typically doesn't compile. The other problem of having a state that is also a result, I'm sure what to do about this.
Was wondering if anyone could give me a push in the right direction how can I rework my state monad so that it looks less wildly.
Many thanks,
Phil.
mcSimulate :: Double -> Double -> Word64 -> [Double] mcSimulate startStock endTime seedForSeed = expiryStock : mcSimulate startStock endTime newSeedForSeed where expiryStock = evalState ( do replicateM_ (truncate(endTime/timeStep)-1) getEvolution; getEvolution ) $ (startStock,ranq1Init seedForSeed) newSeedForSeed = seedForSeed + 246524
discount :: Double -> Double -> Double -> Double discount stock r t = stock * exp (-r)*t
payOff :: Double -> Double -> Double payOff strike stock | (stock - strike) > 0 = stock - strike | otherwise = 0
-- Monad Implementation
-- Yuk! evolveUnderlying :: (Double, Word64) -> ( Double, (Double, Word64) ) evolveUnderlying (stock, state) = ( newStock, ( newStock, newState ) ) where newState = ranq1Increment state newStock = stock * exp ( ( ir - (0.5*(vol*vol)) )*timeStep + ( vol*sqrt(timeStep)*normalFromRngState(state) ) )
getEvolution :: State (Double, Word64) Double getEvolution = State evolveUnderlying
Hi,
the evolveUnderlying can simply manipulate the state, so you can
do evolveUnderlying -- state (not your state, but the tuple) changes here r <- gets fst -- query the state for the first element of the tuple return r -- simply return what you want
Note that if you want to combine your state and the stock, you simply end with a new kind of state : the tuple (thus, no need to compose two State)
Note also, since evolveUnderlying only manipulates the internal state of the State monad, it returns ().
Depending on how you want to structure your code, you can also use execState instead of evalState : it returns the state on which you can use fst.
hope it helps, Thu

On Mon, Jan 12, 2009 at 6:34 PM, Phil
-- Monad Implementation
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) ) )
How about: evolveUnderlying :: (Double, Word64) -> (Double, Word64) evolveUnderlying (stock, state) = (newStock, newState) where ... getEvolution = modify evolveUnderlying Luke

On Mon, Jan 12, 2009 at 8:34 PM, Phil
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

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"
On Mon, Jan 12, 2009 at 8:34 PM, Phil
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) ) )

On Tue, Jan 13, 2009 at 3:29 PM, Phil
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?
No, doing this type of thing is very typical Haskell, and the garbage collector *will* incrementally throw away early elements of the list.
I had originally implemented this similar to the above (although I didn't know about the 'iterate' keyword
FWIW, iterate is just a function, not a keyword. Could just be terminology mismatch. So, while the garbage collector will do the right thing, for a list millions of elements long, I suspect you will get stack overflows and/or bad memory performance because the computation is too lazy. One solution is to use a stricter version of !!, which evaluates elements of the list as it whizzes by them. Because the function you're iterating is strict to begin with, you do not lose performance by doing this: strictIdx :: Int -> [a] -> a strictIdx _ [] = error "empty list" strictIdx 0 (x:xs) = x strictIdx n (x:xs) = x `seq` strictIdx (n-1) xs (Note that I flipped the arguments, to an order that is nicer for currying) The reason is that iterate f x0 constructs a list like this: [ x0, f x0, f (f x0), f (f (f x0)), ... ] But shares the intermediate elements, so if we were to evaluate the first f x0 to, say, 42, then the thunks are overwritten and become: [ x0, 42, f 42, f (f 42), ... ] So iterate f x0 !! 1000000 is f (f (f (f ( ... a million times ... f x0)))), which will be a stack overflow because of each of the calls. What strictIdx does is to evaluate each element as it traverses it, so that each call is only one function deep, then we move on to the next one. This is the laziness abstraction leaking. Intuition about it develops with time and experience. It would be great if this leak could be patched by some brilliant theorist somewhere. Luke - 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"
wrote: Thanks Minh - I've updated my code as you suggested. This looks better
On Mon, Jan 12, 2009 at 8:34 PM, Phil
wrote: 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) ) )
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ahh, I see so using the State monad is arguably overcomplicating this.
This is very helpful.
The use of keyword¹ was just an unfortunate use of terminology my bad.
Very useful explanation about the laziness resulting in stack overflows too
when I crank up the numbers I have been seeing this, I had been
temporarily ignoring the issue and just increasing the stack size at
runtime, but I suspected something was awry.
One last question on this function:
In the definition:
mcSimulate :: Double -> Double -> Word64 -> [Double]
mcSimulate startStock endTime seedForSeed = fst expiryStock : mcSimulate
startStock endTime newSeedForSeed
It is abundantly clear that the startStock and endTime are just being passed
around from call to call unchanged that is their value is constant
throughout the the simulation. For the purposes here when I¹m only passing
2 constants¹ around it doesn¹t strike me as too odd, but my list of
constants¹ is likely to grow as I bolt more functionality onto this. For
readability, I understand that I can create new types to encapsulate complex
data types into a single type , but I can¹t help thinking that passing say 9
or 10 constants¹ around and around like this feels wrong¹. If I sit back
and think about it, it doesn¹t strike me as implausible that the compiler
will recognize what I¹m doing and optimize this out for me, and what I¹m
doing is thinking about the whole think like a C++ programmer (which I
traditionally am) would.
However before I allayed my own concerns I wanted to check that in the
Haskell world passing around lots of parameters isn¹t a bad thing that is,
I¹m not missing a trick here to make my code more readable or more
importantly more performant.
Thanks again,
Phil.
On 13/01/2009 23:24, "Luke Palmer"
On Tue, Jan 13, 2009 at 3:29 PM, Phil
wrote: 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?
No, doing this type of thing is very typical Haskell, and the garbage collector will incrementally throw away early elements of the list.
I had originally implemented this similar to the above (although I didn't know about the 'iterate' keyword
FWIW, iterate is just a function, not a keyword. Could just be terminology mismatch.
So, while the garbage collector will do the right thing, for a list millions of elements long, I suspect you will get stack overflows and/or bad memory performance because the computation is too lazy. One solution is to use a stricter version of !!, which evaluates elements of the list as it whizzes by them. Because the function you're iterating is strict to begin with, you do not lose performance by doing this:
strictIdx :: Int -> [a] -> a strictIdx _ [] = error "empty list" strictIdx 0 (x:xs) = x strictIdx n (x:xs) = x `seq` strictIdx (n-1) xs
(Note that I flipped the arguments, to an order that is nicer for currying)
The reason is that iterate f x0 constructs a list like this:
[ x0, f x0, f (f x0), f (f (f x0)), ... ]
But shares the intermediate elements, so if we were to evaluate the first f x0 to, say, 42, then the thunks are overwritten and become:
[ x0, 42, f 42, f (f 42), ... ]
So iterate f x0 !! 1000000 is f (f (f (f ( ... a million times ... f x0)))), which will be a stack overflow because of each of the calls. What strictIdx does is to evaluate each element as it traverses it, so that each call is only one function deep, then we move on to the next one.
This is the laziness abstraction leaking. Intuition about it develops with time and experience. It would be great if this leak could be patched by some brilliant theorist somewhere.
Luke
- 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"
wrote: Thanks Minh - I've updated my code as you suggested. This looks better
On Mon, Jan 12, 2009 at 8:34 PM, Phil
wrote: 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) ) )
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Jan 13, 2009 at 5:45 PM, Phil
mcSimulate :: Double -> Double -> Word64 -> [Dou ble] mcSimulate startStock endTime seedForSeed = fst expiryStock : mcSimulate startStock endTime newSeedForSeed
It is abundantly clear that the startStock and endTime are just being passed around from call to call unchanged – that is their value is constant throughout the the simulation. For the purposes here when I'm only passing 2 'constants' around it doesn't strike me as too odd, but my list of 'constants' is likely to grow as I bolt more functionality onto this. For readability, I understand that I can create new types to encapsulate complex data types into a single type , but I can't help thinking that passing say 9 or 10 'constants' around and around like this 'feels wrong'. If I sit back and think about it, it doesn't strike me as implausible that the compiler will recognize what I'm doing and optimize this out for me, and what I'm doing is thinking about the whole think like a C++ programmer (which I traditionally am) would.
You can factor out constants in a couple ways. If you are just passing constants between a recursive call to the same function, you can factor out the recursive bit into a separate function: something param1 param2 = go where go = ... param1 ... param2 ... etc ... go ... etc = ... Where go takes only the parameters that change, and the rest is handled by its enclosing scope. You might buy a little performance this way too, depending on the compiler's cleverness (I'm not sure how it optimizes these things). If you are passing around many constants between functions, first package them all up in a record data type: data Params = Params { parmFoo :: Int, parmBar :: Double, ... } At this point it is pretty easy just to pass a Parms object around. If you really hate the explicit style, though, you can throw your computation into a Reader Parms (Reader is the monad precisely for this: adding a constant parameter to every function), and then use eg. asks parmFoo to get parameters out. And if none of those strike your fancy, you can look into GHC's "implicit arguments" extension. But that seems to be in the process of a phase out by the community (nothing explicit, it's just that nobody is using them anymore). Luke
However before I allayed my own concerns I wanted to check that in the Haskell world passing around lots of parameters isn't a bad thing – that is, I'm not missing a trick here to make my code more readable or more importantly more performant.
Thanks again,
Phil.
On 13/01/2009 23:24, "Luke Palmer"
wrote: On Tue, Jan 13, 2009 at 3:29 PM, Phil
wrote: 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?
No, doing this type of thing is very typical Haskell, and the garbage collector *will* incrementally throw away early elements of the list.
I had originally implemented this similar to the above (although I didn't know about the 'iterate' keyword
FWIW, iterate is just a function, not a keyword. Could just be terminology mismatch.
So, while the garbage collector will do the right thing, for a list millions of elements long, I suspect you will get stack overflows and/or bad memory performance because the computation is too lazy. One solution is to use a stricter version of !!, which evaluates elements of the list as it whizzes by them. Because the function you're iterating is strict to begin with, you do not lose performance by doing this:
strictIdx :: Int -> [a] -> a strictIdx _ [] = error "empty list" strictIdx 0 (x:xs) = x strictIdx n (x:xs) = x `seq` strictIdx (n-1) xs
(Note that I flipped the arguments, to an order that is nicer for currying)
The reason is that iterate f x0 constructs a list like this:
[ x0, f x0, f (f x0), f (f (f x0)), ... ]
But shares the intermediate elements, so if we were to evaluate the first f x0 to, say, 42, then the thunks are overwritten and become:
[ x0, 42, f 42, f (f 42), ... ]
So iterate f x0 !! 1000000 is f (f (f (f ( ... a million times ... f x0)))), which will be a stack overflow because of each of the calls. What strictIdx does is to evaluate each element as it traverses it, so that each call is only one function deep, then we move on to the next one.
This is the laziness abstraction leaking. Intuition about it develops with time and experience. It would be great if this leak could be patched by some brilliant theorist somewhere.
Luke
- 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"
wrote: Thanks Minh - I've updated my code as you suggested. This looks better
On Mon, Jan 12, 2009 at 8:34 PM, Phil
wrote: 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) ) )
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Inline....
On 14/01/2009 01:08, "Luke Palmer"
On Tue, Jan 13, 2009 at 5:45 PM, Phil
wrote: mcSimulate :: Double -> Double -> Word64 -> [Dou ble] mcSimulate startStock endTime seedForSeed = fst expiryStock : mcSimulate startStock endTime newSeedForSeed
It is abundantly clear that the startStock and endTime are just being passed around from call to call unchanged that is their value is constant throughout the the simulation. For the purposes here when I'm only passing 2 'constants' around it doesn't strike me as too odd, but my list of 'constants' is likely to grow as I bolt more functionality onto this. For readability, I understand that I can create new types to encapsulate complex data types into a single type , but I can't help thinking that passing say 9 or 10 'constants' around and around like this 'feels wrong'. If I sit back and think about it, it doesn't strike me as implausible that the compiler will recognize what I'm doing and optimize this out for me, and what I'm doing is thinking about the whole think like a C++ programmer (which I traditionally am) would.
You can factor out constants in a couple ways. If you are just passing constants between a recursive call to the same function, you can factor out the recursive bit into a separate function:
something param1 param2 = go where go = ... param1 ... param2 ... etc ... go ... etc = ...
Where go takes only the parameters that change, and the rest is handled by its enclosing scope. You might buy a little performance this way too, depending on the compiler's cleverness (I'm not sure how it optimizes these things).
[PHIL] Firstly thanks for your advice.
When I say constants, I should be clear these are parameters passed in by the user, but they remain constant throughout the recursive call. I think the example above is only relevant if they are constants at compile time? If not I¹m not sure I follow the example. If we have something like
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
Here startStock and endTime are not altered from iteration to iteration, but they are not known at compile time. I see that I can reduce this to something like
test seedForSeed = fst expiryStock : test newSeedForSeed where expiryStock = iterate evolveUnderlying (_startStock, ranq1Init seedForSeed) !! truncate (_endTime/timeStep) newSeedForSeed = seedForSeed + 246524
But don¹t understand how I feed¹ the _startStock and _endTime in?
Could you explain this in detail, or confirm my suspicions that it only works for compile-time constants?
Thanks again,
Phil.

On Thu, Jan 15, 2009 at 3:34 PM, Phil
On 14/01/2009 01:08, "Luke Palmer"
wrote: On Tue, Jan 13, 2009 at 5:45 PM, Phil
wrote: mcSimulate :: Double -> Double -> Word64 -> [Dou ble] mcSimulate startStock endTime seedForSeed = fst expiryStock : mcSimulate startStock endTime newSeedForSeed
It is abundantly clear that the startStock and endTime are just being passed around from call to call unchanged – that is their value is constant throughout the the simulation. For the purposes here when I'm only passing 2 'constants' around it doesn't strike me as too odd, but my list of 'constants' is likely to grow as I bolt more functionality onto this. For readability, I understand that I can create new types to encapsulate complex data types into a single type , but I can't help thinking that passing say 9 or 10 'constants' around and around like this 'feels wrong'. If I sit back and think about it, it doesn't strike me as implausible that the compiler will recognize what I'm doing and optimize this out for me, and what I'm doing is thinking about the whole think like a C++ programmer (which I traditionally am) would.
You can factor out constants in a couple ways. If you are just passing constants between a recursive call to the same function, you can factor out the recursive bit into a separate function:
something param1 param2 = go where go = ... param1 ... param2 ... etc ... go ... etc = ...
Where go takes only the parameters that change, and the rest is handled by its enclosing scope. You might buy a little performance this way too, depending on the compiler's cleverness (I'm not sure how it optimizes these things).
[PHIL] Firstly – thanks for your advice.
When I say constants, I should be clear – these are parameters passed in by the user, but they remain constant throughout the recursive call. I think the example above is only relevant if they are constants at compile time? If not I'm not sure I follow the example. If we have something like
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
Here startStock and endTime are not altered from iteration to iteration, but they are not known at compile time. I see that I can reduce this to something like
test seedForSeed = fst expiryStock : test newSeedForSeed where expiryStock = iterate evolveUnderlying (_startStock, ranq1Init seedForSeed) !! truncate (_endTime/timeStep) newSeedForSeed = seedForSeed + 246524
But don't understand how I 'feed' the _startStock and _endTime in?
Could you explain this in detail, or confirm my suspicions that it only works for compile-time constants?
Compile-time constants could be handled by simple top-level bindings. This technique is specifically for the case you are after: mcSimulate :: Double -> Double -> Word64 -> [Double] mcSimulate startStock endTime seedForSeed = go seedForSeed where go = fst expiryStock : go newSeedForSeed where expiryStock = iterate evolveUnderlying (startStock, ranq1Init seedForSeed) !! truncate (endTime/timeStep) newSeedForSeed = seedForSeed + 246524 See what's going on there? I don't know about that nested where. In Real Life I would probably use a let instead for expiryStock and newSeedForSeed. Luke

On 16/01/2009 01:28, "Luke Palmer"
Compile-time constants could be handled by simple top-level bindings. This technique is specifically for the case you are after:
mcSimulate :: Double -> Double -> Word64 -> [Double] mcSimulate startStock endTime seedForSeed = go seedForSeed where go = fst expiryStock : go newSeedForSeed where expiryStock = iterate evolveUnderlying (startStock, ranq1Init seedForSeed) !! truncate (endTime/timeStep) newSeedForSeed = seedForSeed + 246524
See what's going on there?
I don't know about that nested where. In Real Life I would probably use a let instead for expiryStock and newSeedForSeed.
Luke
Ahh, I get it now, that¹s pretty neat - go¹ is only updating the seedForSeed and the expiryStock, the inner where¹ clause keeps everything else constant each time it is called.
Thanks again! Phil.

Hi,
I¹ve been thinking about factoring constants out of iterations and have
spotted another place in my code where I can make use of this.
See the two examples below the first example iterates over the mcSimulate
function this has changed a little bit but essentially still recurses
around passing in
two constants, and two variables that are changed each time it is called
it has the following form:
mcSimulate (startStock, endTime, seedForSeed, runningSum) = ( startStock,
endTime, newSeedForSeed, newRunningSum )
I figured I¹m passing around the constants startStock and endTime so looked
factor these out producing the second example below.
My concern is that although iterate function now only handles two variables,
it¹s still passing around 1 tuple, which under the bonnet is likely to be
represented in machine code as a pointer? Humor me here a little I know
I¹m thinking of this in terms of C++, but I¹m guessing the final byte code
will adhere to this:
Thus each time mcSimulate is called a machine code subroutine will be
passed a memory address to the input data. Now, the crux of this is, will
it make a COPY of the old input data, BUT with the newSeedForSeed and
newRunningSum, to pass to the next iteration? If this is the case each
iteration does two useless copies of startStock and endTime? Here the
second example should produce better code because nothing constant is copied
from 1 iteration to the next. However if the compiler is smarter and simply
REPLACES the modified data the second example buys us nothing.
However, again, depending very much on the compiler, the second example may
actually be less efficient. Let¹s say the compiler is super smart and
doesn¹t copy around the startStock and endTime on each iteration in the
first example. Then we¹ve gained nothing. However the second example Will
call 3 functions each iteration:
mcWrapper -> mcSimulate -> getStateInfo
In the second example we probably have something like 6 JMP¹ statements in
machine code 3 to jump in to each function, and 3 to jump back out. In
the first we have 2 one to jump us into mcSimulate and one to return. So
each iteration executes 4 more JMPs in the second example. All others
things being equal this will produce slightly less efficient code.
Now I know I¹m speculating like crazy, and perhaps I¹m drunk with efficiency
here, but it would seem to me that whatever way it works there will be a
certain critical mass of constant data that you can carry around that once
breached (i.e. When the copy operations exceed the CPU time taken for the 4
extra JMPs) you will be better off factoring the constant data out..... That
is assuming any of my analysis is correct :-)
If anyone has any insight into how this might looked once compiled down to
machine code, or has an opinion one which example below makes for better
Haskell, I¹d be grateful for any comments, advice or discussion.
Cheers,
Phil.
Note: I recognize the use of getSum and getStateInfo could be polished
using data structures instead, and the use of !! will not produce strict
evaluation.
-------------
getSum :: (Double, Double, Word64, Double) -> Double
getSum (startStock, endTime, seedForSeed, runningSum) = runningSum
getAveragePayoff :: Double -> Double -> Int -> Word64 -> Double
getAveragePayoff startStock endTime iterations seedForSeed = average
where
average = (getSum $ (iterate mcSimulate (startStock, endTime,
seedForSeed, 0)) !! iterations ) / fromIntegral iterations
---------------
getStateInfo :: (Double, Double, Word64, Double) -> (Word64,Double)
getStateInfo (startStock, endTime, seedForSeed, runningSum) = (seedForSeed,
runningSum)
getAveragePayoff :: Double -> Double -> Int -> Word64 -> Double
getAveragePayoff startStock endTime iterations seedForSeed = average
where
average = (snd $ (iterate mcWrapper (seedForSeed,0)) !! iterations ) /
fromIntegral iterations
where
mcWrapper = \(seed,runningSum) -> getStateInfo $ mcSimulate (
startStock, endTime, seed, runningSum )
On 16/01/2009 01:41, "Phil"
On 16/01/2009 01:28, "Luke Palmer"
wrote: Compile-time constants could be handled by simple top-level bindings. This technique is specifically for the case you are after:
mcSimulate :: Double -> Double -> Word64 -> [Double] mcSimulate startStock endTime seedForSeed = go seedForSeed where go = fst expiryStock : go newSeedForSeed where expiryStock = iterate evolveUnderlying (startStock, ranq1Init seedForSeed) !! truncate (endTime/timeStep) newSeedForSeed = seedForSeed + 246524
See what's going on there?
I don't know about that nested where. In Real Life I would probably use a let instead for expiryStock and newSeedForSeed.
Luke
Ahh, I get it now, that¹s pretty neat - go¹ is only updating the seedForSeed and the expiryStock, the inner where¹ clause keeps everything else constant each time it is called.
Thanks again!
Phil.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Jan 17, 2009 at 9:46 AM, Phil
In the second example we probably have something like 6 'JMP' statements in machine code – 3 to jump in to each function, and 3 to jump back out. In the first we have 2 – one to jump us into mcSimulate and one to return. So each iteration executes 4 more JMPs in the second example. All others things being equal this will produce slightly less efficient code.
Wow. I strongly suggest you forget about efficiency completely and become a proficient high-level haskeller, and then dive back in. Laziness changes many runtime properties, and renders your old ways of thinking about efficiency almost useless. If you are interested, though, you can use the ghc-core tool on hackage to look at the core (lowish-level intermediate language) and even the generated assembly for minimal cases. It's dense, but interesting if you have the time to study it. Others will know more about this specific speculation than I. Luke

On 17/01/2009 16:55, "Luke Palmer"

A very short time ago Simon Marlow (if I recall correctly) commented
on this topic: he told that this transformation usually improves
efficiency pretty much, but sometimes it leads to some problems and it
shouldn't be done by the compiler automatically. Search the recent
messages for 'map' and one of them will have an answer :)
2009/1/17 Phil
On 17/01/2009 16:55, "Luke Palmer"
wrote: Wow. I strongly suggest you forget about efficiency completely and become a proficient high-level haskeller, and then dive back in. Laziness changes many runtime properties, and renders your old ways of thinking about efficiency almost useless. If you are interested, though, you can use the ghc-core tool on hackage to look at the core (lowish-level intermediate language) and even the generated assembly for minimal cases. It's dense, but interesting if you have the time to study it.
Others will know more about this specific speculation than I.
Luke
[Phil] Heh heh – totally accept what your saying, I am obsessing over details here. I've ran some empirical tests to get some crude insight (just using the linux's time program), I expected the differences to be small for the amount of data I was passing around, but I was surprised. I modified the code ever so slightly to use data structures to pass around the data. Thus got rid of the getSum and getStateInfo functions. In the first unfactored example everything was passed around in one structure. In the second example I had two structures; one for constant data and one for state date. Thus doesn't really change the problem it just means that in the unfactored example mcSimulate takes one parameter (holding data constant and variable state data) and in the factored example it takes two parameters. The rest of the code remained more-or-less identical to my original post.
Running both programs at the same time on an otherwise unloaded CPU gave a very consistent result over numerous trials that for 1 million calls to mcSimulate, the unfactored example took approx 1m44s and the factored example took 1m38 – which is a fairly significant difference.
So whilst I can't offer any exact explanation, it is clear that factoring out even a few parameters taking up little memory produces a significant performance increase. This would suggest that my 'JMP' analysis is not right and that the compiler is able to optimize the factored version better.
If anyone else fancies offering up their 2 cents on what the compiler is doing, I'd still be interested, but the empirical evidence alone is enough for me to be swayed to factoring all static parameters in an iteration out of the iteration and into a wrapper.
Phil.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 17/01/2009 20:45, "Eugene Kirpichov"
A very short time ago Simon Marlow (if I recall correctly) commented on this topic: he told that this transformation usually improves efficiency pretty much, but sometimes it leads to some problems and it shouldn't be done by the compiler automatically. Search the recent messages for 'map' and one of them will have an answer :)
Thanks for the tip - I'll have a look for this.
I've also tried a third test using the two possibilities below, both have
separate structures for variable and constant data, but the second example
explicitly factors out passing this around as in previous examples. Here
there is no discernable difference between the two methods' timed results,
if anything the first one which is not explicitly factored out had a slight
edge in tests.
Therefore it would seem that providing you separate the constant and
variable data out into the separate parameters, the compiler will do the
rest for you. This suggests that the compiler is indeed smart; the
staticData is not copied from iteration to iteration providing the whole
structure is constant, but when you mix and match within a structure itself
the compiler isn't smart enough to factor out the constant members. I
suppose a conclusive test would be to add a very large amount of constant
data to the structure to see if results were still similar.
Note: strictIdx is just a strict version of !!:
getAveragePayoff :: Double -> Double -> Int -> Word64 -> Double
getAveragePayoff startStock endTime iterations seedForSeed = average
where
staticData = MCStatic startStock endTime
average = ( runningSum $ snd $ strictIdx
iterations ( iterate mcSimulate (staticData, (MCState
seedForSeed 0)) ) )
/ fromIntegral iterations
_______
getAveragePayoff :: Double -> Double -> Int -> Word64 -> Double
getAveragePayoff startStock endTime iterations seedForSeed = average
where
staticData = MCStatic startStock endTime
average = ( runningSum $ strictIdx
iterations ( iterate mcWrapper (MCState seedForSeed 0) ) )
/ fromIntegral iterations
where
mcWrapper = \stateData -> snd $ mcSimulate (staticData, stateData)
On 17/01/2009 20:45, "Eugene Kirpichov"
A very short time ago Simon Marlow (if I recall correctly) commented on this topic: he told that this transformation usually improves efficiency pretty much, but sometimes it leads to some problems and it shouldn't be done by the compiler automatically. Search the recent messages for 'map' and one of them will have an answer :)

On Tue, Jan 13, 2009 at 5:29 PM, Phil
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?
iterate creates the elements of the list as they are requested, and !! will discard everything until it hits the answer it wants. That being said, it's not the best way to repeatedly apply a function, as Luke pointed out. A better way would probably be something like this, applyNTimes :: Int -> (a -> a) -> a -> a applyNTimes n f a | n <= 0 = a | otherwise = applyNTimes (n-1) $! f a That ($!) is there to make sure "f a" gets evaluated before calling applyNTimes again.
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!
I'm not entirely sure what you mean by "discard all but the current
state", but Haskell implementations are pretty good about discarding
values that are no longer needed.
That being said, here's one way I might implement your algorithm. It's
a sketch, and I haven't tested it, but the general idea should be
clear.
mcSimulate stock endTime seed = map (evolve n stock) $ iterate
(+246524) seed
where
n = truncate (endTime / timeStep)
evolve :: Int -> Double -> Word64 -> Double
evolve n stock seed
| n <= 0 = stock
| otherwise = evolve (n-1) (evolveStock stock seed)
(ranq1Increment seed)
evolveStock :: Double -> Word64 -> Double
evolveStock stock seed = stock * exp (a + b * normalFromRngState seed)
where
a = (ir - 0.5 * vol * vol) * timeStep
b = vol * sqrt timeStep
--
Dave Menendez
participants (5)
-
David Menendez
-
Eugene Kirpichov
-
Luke Palmer
-
minh thu
-
Phil