Re: [Haskell-cafe] State Monad - using the updated state

2009-01-08 Thread Kurt Hutchinson
Ryan gave some great advice about restructuring your program to do
what you want, but I wanted to give a small explanation of why that's
necessary.

2009/1/7 Phil pbeadl...@mail2web.com:
  I want to be able to do:

 Get_a_random_number

  a whole load of other stuff 

 Get the next number as defined by the updated state in the first call

 some more stuff

 Get another number, and so on.

The issue you're having is that you're trying to do the other stuff
in your 'main', but main isn't inside the State monad. The only State
computation you're calling from main is getRanq1, but you really need
another State computation that does other stuff and calls getRanq1
itself. That's what Ryan's first suggestion implements. You need all
your other stuff to be done inside the State monad so that it has
read/update access to the current random state. So all your main does
is run a State computation. That computation calls getRanq1 itself and
then other stuff in between calls to getRanq1.

Does that make sense?

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


Re: [Haskell-cafe] State Monad - using the updated state

2009-01-08 Thread Phil
I think I've got this now - thanks to you all for the superb advice!

The reason I cannot increment state inside main is because main is not a
State monad (it's an IO monad).  Thus in order to use my State Monad, I have
execute inside a State monad as that the state is encapsulated in there.

I'll have to have a think about how I'm going to structure the rest of my
code inside something like Ryan's randomComputation example - the basic
example works perfectly!  I'm writing a Monte Carlo simulator for financial
portfolios - it's something I've done in several languages so I often use it
to test drive a new language.  Most imperative implementations of this sort
thing are very state-heavy, so I thought it would fun to re-think it a bit
in Haskell.

My initial thoughts before delving into Monads was to take advantage of
Haskell's lazy evaluation and create an 'infinite' list of randoms using
something like the below:

ranq1List :: (Word64 - a ) - Word64 - [a]
ranq1List converter state = converter newState : ranq1List converter
newState
  where
newState = ranq1Increment state

This works fine - the converter is an extra parameter that carrys a
partially defined function used to numerically translate from
word64-whatever_type__we_want as stipulated in Numerical Recipes' C++
example.  It was at this point I felt it was getting a bit ugly and started
to look at Monads (plus I wanted to see what all 'fuss' was about with
Monads too!).

One more question on this - the other concern I had with the recursive list
approach was that although lazy evaluation prevents me generating numbers
before I 'ask' for them, I figured that if I was going to be asking for say
10 million over the course of one simulation, that although I request them
one by one, over hours or even days, at the end of the simulation I will
still have a list of 10 million word64s - each of which I could throw away
within minutes of asking for it.  This seemed like huge memory bloat, and
thus probably I was taking the wrong approach.

I'd be interested to know if you have any thoughts on the various solutions?
Ryan's randomComputation strikes me as the most practical and there's an old
adage that if a language provides a facility (i.e. The State Monad here),
you shouldn't be rewriting similar functionality yourself unless there is a
very very good reason to go it alone.  Thus I figure that Haskell's State
Monad used as described is always going to beat anything I come up with to
do the same thing - unless I spend an awful lot of time tailoring a specific
solution.

If you think there is a nicer non-Monadic, pure solution to this type of
problem, I'd be interested to hear them.

Thanks again for all your help,

Phil.



On 08/01/2009 13:27, Kurt Hutchinson kelansli...@gmail.com wrote:

 Ryan gave some great advice about restructuring your program to do
 what you want, but I wanted to give a small explanation of why that's
 necessary.
 
 2009/1/7 Phil pbeadl...@mail2web.com:
  I want to be able to do:
 
 Get_a_random_number
 
  a whole load of other stuff 
 
 Get the next number as defined by the updated state in the first call
 
 some more stuff
 
 Get another number, and so on.
 
 The issue you're having is that you're trying to do the other stuff
 in your 'main', but main isn't inside the State monad. The only State
 computation you're calling from main is getRanq1, but you really need
 another State computation that does other stuff and calls getRanq1
 itself. That's what Ryan's first suggestion implements. You need all
 your other stuff to be done inside the State monad so that it has
 read/update access to the current random state. So all your main does
 is run a State computation. That computation calls getRanq1 itself and
 then other stuff in between calls to getRanq1.
 
 Does that make sense?
 
 Kurt

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


Re: [Haskell-cafe] State Monad - using the updated state

2009-01-08 Thread Luke Palmer
On Thu, Jan 8, 2009 at 12:56 PM, Phil pbeadl...@mail2web.com wrote:

 One more question on this - the other concern I had with the recursive list
 approach was that although lazy evaluation prevents me generating numbers
 before I 'ask' for them, I figured that if I was going to be asking for say
 10 million over the course of one simulation, that although I request them
 one by one, over hours or even days, at the end of the simulation I will
 still have a list of 10 million word64s - each of which I could throw away
 within minutes of asking for it.  This seemed like huge memory bloat, and
 thus probably I was taking the wrong approach.


if you don't hold on to the whole list, i.e. you use the head of the list
and then pass the tail around, the garbage collector will collect the unused
prefix.

In Haskell lists are used like loops.  If a list is used in a sufficiently
forgetful fashion, it will use constant space.

Luke




 I'd be interested to know if you have any thoughts on the various
 solutions?
 Ryan's randomComputation strikes me as the most practical and there's an
 old
 adage that if a language provides a facility (i.e. The State Monad here),
 you shouldn't be rewriting similar functionality yourself unless there is a
 very very good reason to go it alone.  Thus I figure that Haskell's State
 Monad used as described is always going to beat anything I come up with to
 do the same thing - unless I spend an awful lot of time tailoring a
 specific
 solution.

 If you think there is a nicer non-Monadic, pure solution to this type of
 problem, I'd be interested to hear them.

 Thanks again for all your help,

 Phil.



 On 08/01/2009 13:27, Kurt Hutchinson kelansli...@gmail.com wrote:

  Ryan gave some great advice about restructuring your program to do
  what you want, but I wanted to give a small explanation of why that's
  necessary.
 
  2009/1/7 Phil pbeadl...@mail2web.com:
   I want to be able to do:
 
  Get_a_random_number
 
   a whole load of other stuff 
 
  Get the next number as defined by the updated state in the first call
 
  some more stuff
 
  Get another number, and so on.
 
  The issue you're having is that you're trying to do the other stuff
  in your 'main', but main isn't inside the State monad. The only State
  computation you're calling from main is getRanq1, but you really need
  another State computation that does other stuff and calls getRanq1
  itself. That's what Ryan's first suggestion implements. You need all
  your other stuff to be done inside the State monad so that it has
  read/update access to the current random state. So all your main does
  is run a State computation. That computation calls getRanq1 itself and
  then other stuff in between calls to getRanq1.
 
  Does that make sense?
 
  Kurt

 ___
 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


[Haskell-cafe] State Monad - using the updated state

2009-01-07 Thread Phil
Hi,

I¹m a newbie looking to get my head around using the State Monad for random
number generation.  I¹ve written non-monad code that achieves this no
problem.  When attempting to use the state monad I can get what I know to be
the correct initial value and state, but can¹t figure out for the life of me
how to then increment it without binding more calls there and then.  Doing
several contiguous calls is not what I want to do here ­ and the examples
I¹ve read all show this (using something like liftM2 (,) myRandom myRandom).
I want to be able to do:

Get_a_random_number

 a whole load of other stuff 

Get the next number as defined by the updated state in the first call

some more stuff

Get another number, and so on.

I get the first number fine, but am lost at how to get the second, third,
forth etc without binding there and then.  I just want each number one at a
time where and when I want it, rather than saying give 1,2,10 or even Œn¹
numbers now.  I¹m sure it¹s blindly obvious!

Note: I¹m not using Haskell¹s built in Random functionality (nor is that an
option), I¹ll spare the details of the method I¹m using (NRC¹s ranq1) as I
know it works for the non-Monad case, and it¹s irrelevent to the question.
So the code is:

ranq1 :: Word64 - ( Double, Word64 )
ranq1 state = ( output, newState )
  where
newState = ranq1Increment state
output = convert_to_double newState

ranq1Init :: Word64 - Word64
ranq1Init = convert_to_word64 . ranq1Increment . xor_v_init

-- I¹ll leave the detail of how ranq1Increment works out for brevity.  I
know this bit works fine.  Same goes for the init function it¹s just
providing an initial state.

-- The Monad State Attempt
getRanq1 :: State Word64 Double
getRanq1 = do
  state - get
  let ( randDouble, newState ) = ranq1 state
  put newState
  return randDouble


_ And then in my main _

-- 124353542542 is just an arbitrary seed
main :: IO()
main = do
   let x = evalState getRanq1 (ranq1Init 124353542542)
   print (x)


As I said this works fine; x gives me the correct first value for this
sequence, but how do I then get the second and third without writing the
giveMeTenRandoms style function?  I guess what I want is a next() type
function, imperatively speaking.


Many thanks for any help,


Phil.


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


[Haskell-cafe] State Monad - using the updated state in an adhoc manner

2009-01-07 Thread Phil
Hi,

I¹m a newbie looking to get my head around using the State Monad for random
number generation.  I¹ve written non-monad code that achieves this no
problem.  When attempting to use the state monad I can get what I know to be
the correct initial value and state, but can¹t figure out for the life of me
how to then increment it without binding more calls there and then.  Doing
several contiguous calls is not what I want to do here ­ and the examples
I¹ve read all show this (using something like liftM2 (,) myRandom myRandom).
I want to be able to do:

Get_a_random_number

 a whole load of other stuff 

Get the next number as defined by the updated state in the first call

some more stuff

Get another number, and so on.

I get the first number fine, but am lost at how to get the second, third,
forth etc without binding there and then.  I just want each number one at a
time where and when I want it, rather than saying give 1,2,10 or even Œn¹
numbers now.  I¹m sure it¹s blindly obvious!

Note: I¹m not using Haskell¹s built in Random functionality (nor is that an
option), I¹ll spare the details of the method I¹m using (NRC¹s ranq1) as I
know it works for the non-Monad case, and it¹s irrelevent to the question.
So the code is:

ranq1 :: Word64 - ( Double, Word64 )
ranq1 state = ( output, newState )
  where
newState = ranq1Increment state
output = convert_to_double newState

ranq1Init :: Word64 - Word64
ranq1Init = convert_to_word64 . ranq1Increment . xor_v_init

-- I¹ll leave the detail of how ranq1Increment works out for brevity.  I
know this bit works fine.  Same goes for the init function it¹s just
providing an initial state.

-- The Monad State Attempt
getRanq1 :: State Word64 Double
getRanq1 = do
  state - get
  let ( randDouble, newState ) = ranq1 state
  put newState
  return randDouble


_ And then in my main _

-- 124353542542 is just an arbitrary seed
main :: IO()
main = do
   let x = evalState getRanq1 (ranq1Init 124353542542)
   print (x)


As I said this works fine; x gives me the correct first value for this
sequence, but how do I then get the second and third without writing the
giveMeTenRandoms style function?  I guess what I want is a next() type
function, imperatively speaking.


Many thanks for any help,


Phil.


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


Re: [Haskell-cafe] State Monad - using the updated state

2009-01-07 Thread Ryan Ingram
Hi Phil.  First a quick style comment, then I'll get to the meat of
your question.

getRanq1 is correct; although quite verbose.  A simpler definition is this:
getRanq1 = State ranq1

This uses the State constructor from Control.Monad.State:
State :: (s - (a,s)) - State s a

What it sounds like you want is this:

main = do
x - getARandomNumber
... do some other stuff
y - getAnotherRandomNumber
.. etc.

using State.  There are two ways to go about this; the first is, if
the entire computation is pure, that is, the do some other stuff
doesn't do IO, you can embed the whole computation in State:

seed = 124353542542
main = do
result - evalState randomComputation (ranq1Init seed)
... some IO using result ...

randomComputation = do
x - getRanq1
let y = some pure computation using x
z - getRanq1
w - something that uses x, y, and z that also uses the random source
... etc.
return (some result)

The other option, if you want to do IO in between, is to use a
transformer version of State:

type MyMonad a = StateT Word64 IO a

main = withStateT (ranq1Init seed) $ do
x - getRanq1_t
liftIO $ print x
...
y - getRanq1_t
...

getRanq1_t :: MyMonad Double
getRanq1_t = liftStateT getRanq1

liftStateT :: State s a - MyMonad a
liftStateT m = StateT $ \s - return (runState m s)

withStateT :: Word64 - MyMonad a - IO a
withStateT s m = evalStateT m s  -- can also just use withStateT =
flip evalStateT

This uses these functions from Control.Monad.State:

liftIO :: MonadIO m = IO a - m a
   This takes any IO action and puts it into any monad that supports
IO.  In this case, StateT s IO a fits.

runState :: StateT s a - s - (a,s)
   This evaluates a pure stateful computation and gives you the result.

StateT :: (s - m (a,s)) - StateT s m a
   This builds a StateT directly.  You could get away without it like this:

liftStateT m = do
s - get
let (a, s') = runState m s
put s'
return a

(note the similarity to your getRanq1 function!)

evalStateT :: StateT s m a - s - m a
This is just evalState for the transformer version of State.  In
our case it has the type (MyMonad a - Word64 - IO a)

This said, as a beginner I recommend trying to make more of your code
pure so you can avoid IO; you do need side effects for some things,
but while learning it makes sense to try as hard as you can to avoid
it.  You can make a lot of interesting programs with just interact
and pure functions.

If you're just doing text operations, try to make your program look like this:

main = interact pureMain

pureMain :: String - String
pureMain s = ...

You'll find it will teach you a lot about laziness  the power of
purity!  A key insight is that State *is* pure, even though code using
it looks somewhat imperative.

  -- ryan

P.S. If you can't quite get out of the imperative mindset you can
visit imperative island via the ST boat.

2009/1/7 Phil pbeadl...@mail2web.com:
 Hi,

 I'm a newbie looking to get my head around using the State Monad for random
 number generation.  I've written non-monad code that achieves this no
 problem.  When attempting to use the state monad I can get what I know to be
 the correct initial value and state, but can't figure out for the life of me
 how to then increment it without binding more calls there and then.  Doing
 several contiguous calls is not what I want to do here – and the examples
 I've read all show this (using something like liftM2 (,) myRandom myRandom).
  I want to be able to do:

 Get_a_random_number

  a whole load of other stuff 

 Get the next number as defined by the updated state in the first call

 some more stuff

 Get another number, and so on.

 I get the first number fine, but am lost at how to get the second, third,
 forth etc without binding there and then.  I just want each number one at a
 time where and when I want it, rather than saying give 1,2,10 or even 'n'
 numbers now.  I'm sure it's blindly obvious!

 Note: I'm not using Haskell's built in Random functionality (nor is that an
 option), I'll spare the details of the method I'm using (NRC's ranq1) as I
 know it works for the non-Monad case, and it's irrelevent to the question.
  So the code is:

 ranq1 :: Word64 - ( Double, Word64 )
 ranq1 state = ( output, newState )
   where
 newState = ranq1Increment state
 output = convert_to_double newState

 ranq1Init :: Word64 - Word64
 ranq1Init = convert_to_word64 . ranq1Increment . xor_v_init

 -- I'll leave the detail of how ranq1Increment works out for brevity.  I
 know this bit works fine.  Same goes for the init function it's just
 providing an initial state.

 -- The Monad State Attempt
 getRanq1 :: State Word64 Double
 getRanq1 = do
   state - get
   let ( randDouble, newState ) = ranq1 state
   put newState
   return randDouble


 _ And then in my main _

 -- 124353542542 is just an arbitrary seed
 main :: IO()
 main = do
let x = evalState getRanq1 (ranq1Init 124353542542)
 

Re: [Haskell-cafe] State Monad - using the updated state in an adhoc manner

2009-01-07 Thread Brandon S. Allbery KF8NH

On 2009 Jan 7, at 20:58, Phil wrote:

-- 124353542542 is just an arbitrary seed
main :: IO()
main = do
   let x = evalState getRanq1 (ranq1Init 124353542542)
   print (x)


You're throwing away the state you want to keep by using evalState  
there.  But you're also missing the point of using State; done right  
the evalState *is* what you want.


What you want to do is run all of your operations within State,  
exiting it only when you're done:


 main = do
 print (evalState doRanqs (ranq1init 124353542542))

 doRanqs = do
 r - getRanq1
 -- do something involving it
 another - getRanq1
 -- do more stuff

Alternately you may use a tail recursive function or a fold, etc.,  
depending on what exactly you're trying to accomplish.


You do *not* want to execState or runState every individual time you  
want a random number; if you do that you'll have to carry the random  
state around yourself (in effect you'd be rewriting the State monad by  
hand, poorly).  Stay in State and let it do the carrying for you.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH


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