Re: Re[2]: [Haskell-cafe] Newbie: State monad example questions

2008-05-24 Thread Olivier Boudry
On Sat, May 24, 2008 at 3:39 AM, Bulat Ziganshin [EMAIL PROTECTED]
wrote:

 Hello Olivier,

 Saturday, May 24, 2008, 5:37:32 AM, you wrote:

 (|) = flip (.)

  I even started to use it in my code and then stopped. It may be a
  stupid concern but as many optimizations performed by GHC are made
  through rewrite rules and I was worried that those rules may not
  fire when using this new operator.

 afaik ghc, | would be rewritten to flip (.) which would be rewritten
 to application of first function to second one and so on. rewrite
 rules doesn't work only on your original code but on intermediate
 variations too

 That's really good news.

Thanks Bulat,

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-23 Thread Olivier Boudry
On Fri, May 23, 2008 at 2:20 PM, Thomas Hartman [EMAIL PROTECTED] wrote:

  The big benefit I got from using the State Monad was that I was able to
 reorder the functions  by just copy/pasting the function name from one
 place to another.

 I don't understand... why do you need state to do this? Couldn't you
 have a function pipeline using dots for composition like

   (
...
parseAttn .
parsePoBox .
...
) address ...

 and have the functions be equally switchable? (well, the first and
 last can't quite be copy pasted, but close enough.)

 Introducing state seems like a lot of trouble to me if the only one is
 easier reorderability of lines.


Agreed, in fact I started with a function pipeline and then switched to
using the State Monad. As the program was written months ago I don't
remember exactly why. Maybe I don't like to read backwards. ;-)

Funtions running in the state monad can call other functions with the same
`State s a` signature (and so on as deep as you want). You never have to
care about passing parameters and restarting a new pipeline. But of course
you can easily do without the State Monad. I don't think the State Monad
allows to do thing that you can't do with basic Haskell. It just makes code
more readable (in my opinion at least).

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-22 Thread Olivier Boudry
On Wed, May 21, 2008 at 6:19 PM, Dmitri O.Kondratiev [EMAIL PROTECTED]
wrote:


 -- Then we can use  this State object (returned by getAny) in a function
 generating random values such as:

 makeRnd :: StdGen - (Int, StdGen)
 makeRnd = runState (do
   y - getAny
   return y)


You can simplify this:

do y - m
return y

is equivalent to

`do m`

or `m`

According to Monad Laws.

So you could write the same code as:
makeRnd = runState getAny

In that case, the use of the State Monad is not really interesting as you
just replaced a call to `random g` with a call to `runState getAny g`. The
State Monad is interesting if you have more than one action in the first
argument of the `runState` function because the state passing will only work
in a single `State s a`.

Thomas Hartman asked for use cases so I will describe  programs I used the
State Monad for:

1) You can find a portion of the code here: http://hpaste.org/7809

The purpose of this program was extracting address parts (PO box, street,
city, country, postal code, ...) from addresses which are composed of a
name, 3 free text lines and a zip code. The state is a list of AddressPart
elements. If you look at the extractAddress function, it contains many other
function running in the State Monad. Each function can get and put the
state. The state will contain both unparsed and already parsed AddressPart
elements.

The big benefit I got from using the State Monad was that I was able to
reorder the functions by just copy/pasting the function name from one place
to another.

Each of the `State Address ()` function will get the state, try to find an
address part in the unparsed AddressPart elements and put a new State with
the recognized AddressPartS if any.

I think parsing is a common use case for the State Monad where you want to
store the unparsed data along with the parse result and don't want to care
about passing those elements from one function to another.

2) I also recently used the State Monad Transformer to build a single
Data.Map from a set of different files. The State is the Data.Map and the
action in the runStateT is a mapM_ over a list of file names.

processFile :: String - StateT (PartsMap B.ByteString) IO ()
-- get the Map
-- add the file info
-- put the Map

runStateT (mapM_ processFile fileNames) M.Empty
-- each processFile call will get access to the result of the previous call
and put the updated Map.

I don't know if it's a common use case for the State Monad, but I found it
useful. I could probably have used foldM to achieve the same goal and don't
worry about using the State Monad.

Best regards,

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-22 Thread Eric Stansifer
 So, are there any other simple motivating examples that show what
 state is really good for?

Here's an example from some code that I'm (trying to) write;  I am
writing a DSL for the Povray Scene Description Language.  This part of
my program creates a `String' which holds a piece of Povray SDL code.
I am using the state to keep track of an infinite list of unique
identifiers -- when I use an identifier I would like to avoid reusing
the same one later.

 type Identifier = String
 type Identifiers = [Identifier]
 all_identifiers :: Identifiers
 all_identifiers = map (\n - var ++ show n) [0, 1..]

 next_id :: State Identifiers Identifier
 next_id = do
   (a:as) - get
   put as
   return a

I define a function let_ so that if a user of my code writes something like:

 let_ value expr

For example, if a user said:

 let_ (vector (0, 0, 0))
   (\origin -
 let_ (vector (1, 2, 3))
   (\p -
   union [box origin p, sphere origin (float 1), cylinder origin p 
 (float 0.5)]))

it should be analogous to:

 union [box (vector (0, 0, 0)) (vector (1, 2, 3)), sphere (vector (0, 0, 0)) 
 (float 1), cylinder (vector (0, 0, 0)) (vector (1, 2, 3)) (float 0.5)]

(Cf. http://www.haskell.org/pipermail/haskell-cafe/2008-February/039639.html
for details on what I'm trying to do here, but it has nothing to do
with my example usage of a state monad.)

In my definition of let_, I extract a fresh, unused identifier which
is assigned to the value of value.

 type Code x = State Identifiers String
 let_ :: Code x - (Code x - Code y) - Code y
 let_ m_value m_expr = do
   id - next_id
   value - m_value
   expr - m_expr (return id)
   return (#declare  ++ id ++  =  ++ value ++ ;\n ++ expr)

Either of the expressions m_value or m_expr may require their own
unique identifiers, but the State monad takes care of threading my
`Identifiers' state so that the same identifier will not be used more
than once.

Later on, when I made a more sophisticated version of `Identifiers'
which kept of track of multiple different namespaces from which
identifiers could come, I only had to modify `next_id' without having
to worry about whether I would have to make changes in other parts of
the program (although I believe further changes would not have been
necessary even if I had not used State monads, the modularity of the
code is much more obvious when using the State monad instead of
explicitly writing out the state that is being passed around).

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-22 Thread David Menendez
2008/5/22 Olivier Boudry [EMAIL PROTECTED]:
 On Wed, May 21, 2008 at 6:19 PM, Dmitri O.Kondratiev [EMAIL PROTECTED]
 wrote:


 -- Then we can use  this State object (returned by getAny) in a function
 generating random values such as:

 makeRnd :: StdGen - (Int, StdGen)
 makeRnd = runState (do
   y - getAny
   return y)

 You can simplify this:

 do y - m
 return y

 is equivalent to

 `do m`

 or `m`

 According to Monad Laws.

 So you could write the same code as:
 makeRnd = runState getAny

 In that case, the use of the State Monad is not really interesting as you
 just replaced a call to `random g` with a call to `runState getAny g`. The
 State Monad is interesting if you have more than one action in the first
 argument of the `runState` function because the state passing will only work
 in a single `State s a`.

Incidentally, since random has type (Random a, RandomGen g) = g -
(a,g), getAny could have been defined simply as

getAny = State random

It may be helpful to prove that this definition is equivalent to the
one given in the original post.

Oh, and here's a super-simple example using the state monad:

randR :: (Random a) = (a,a) - State StdGen a
randR range = State (randomR range)

twoDice :: State StdGen Int
twoDice = do
d1 - randR (1,6)
d2 - randR (1,6)
return (d1 + d2)

nDice :: Int - State StdGen Int
nDice n | n  1 = return 0
nDice n = do
x - randR (1,6)
y - rollN (n - 1)
return (x + y)

Because State StdGen is a monad, you can rewrite nDice without
explicit recursion using foldM:

nDice n = foldM (\sum m - liftM (sum+) m) 0 $ take n $ repeat (randR (1,6))

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Thomas Hartman
I would be interested in seeing good motivating examples for use of
the state monad, other than that example from All About Monads.

Okay, it's good for randomness. What else?

Reading the source code for State, I think I saw an example about
using state to uniquely label elements of a tree with ascending
integers, such that equal leaves in the original tree are also equal
in the int-labeled tree. But this struck me as something that could be
more elegantly done with some kind of tree fold.

So, are there any other simple motivating examples that show what
state is really good for?

Thomas.

Am 19. Mai 2008 16:04 schrieb Dmitri O.Kondratiev [EMAIL PROTECTED]:
 I am trying to understand State monad example15 at:
 http://www.haskell.org/all_about_monads/html/statemonad.html

 Example 15 uses getAny that I don't understand at all how it works:

 getAny :: (Random a) = State StdGen a
 getAny = do g  - get
 (x,g') - return $ random g
 put g'
 return x


 Questions:
 1) random has type:
 random :: (Random a, RandomGen g) = g - (a, g)

 and for State monad:

 return a = State (\s - (a, s))

 then:
 return (random g) = State (\s - ((a,g), s))

 Is  it correct?

 2) What x and g' will match to in:
do ...
 (x,g') - return $ random g

 which, as I understand equals to:
do ...
 (x,g') - State (\s - ((a,g), s))

 What x and g' will match to in the last expression?

 3) In general, in do expression (pseudo):
 do { x - State (\s - (a, s)); ...}

 What x will refer to? Will x stand for a whole lambda function: \s - (a, s)
 ?

 4) How 'g - get' works in this function (getAny) ?
 5) Why we need 'put g'?

 Thanks!


 ___
 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] Newbie: State monad example questions

2008-05-21 Thread Yitzchak Gale
Thomas Hartman wrote:
 I would be interested in seeing good motivating examples for use of
 the state monad...
 Okay, it's good for randomness. What else?
 ...I saw an example about
 using state to uniquely label elements of a tree
 So, are there any other simple motivating examples that show what
 state is really good for?

I find that there are two basic ways that the State monad
is useful for me.

One is when functions have an extra parameter, or a
tuple return type, that is not really a natural part of the
meaning of the function but is only there for keeping state.
In those cases, a state monad makes the intention
more clear. The examples you mentioned - random
generators and tree labeling - are both of this type.

This first use is especially helpful when there are
several functions that all share the same state.

The other use is for backtracking. In the monad StateT s [],
the state is re-initialized to its original value for each
item of the list. Here is a fully spelled out example:

http://haskell.org/haskellwiki/Sudoku#Backtrack_monad_solver

The first solver on that page, by Cale Gibbard, is a
more elegant way to do the same thing without
spelling out so explicitly all the details of how the
monad is giving you the backtracking effect.
A few other solvers also use a backtracking monad.

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Dmitri O.Kondratiev
Thanks everybody for your help!
Oliver,  you provided an excellent write-up  on  State  monad without
going  into 'scary' :) details, great work indeed!
Alas,  in this case I need the details, and in particular the most scary
ones!

So let's start with fundamental and most intriguing  (to me) things:

getAny :: (Random a) = State StdGen a
getAny = do g - get -- magically get the current StdGen

First line above declares a data type:

State StdGen a

which is constructed with the function:

State {runState :: (StdGen - (a, StdGen))}

Q1: Where in the example (
http://www.haskell.org/all_about_monads/examples/example15.hs) data of this
type *actually gets constructed* ?

Looking at example15.hs code we see the following sequence:

1) makeRandomValue g -- where g is a StdGen instance, ok

2) makeRandomValue g ~ expands into ~

~  (runState (do { ...; b - getAny;...})) g


This last expression puzzles me. I can understand, for example, this:

State StdGen a :: aState
StdGen:: g1

(v, g2) = (runStae aState) g1 -- this returns a state function which is then
passed a generator g1, and as result returns pair (value, new generaor)

But '(runState (do ...)) g' implies that expression (do ...)  must be
somehow of type 'State StdGen a' ?
Yet, when we call 'makeRandomValue g' we just pass to this function
g::StgGen

So, my next question:
Q2: How (do {...;b - getAny;...}) becomes an *instance* of type 'State
StdGen a' ?


On Tue, May 20, 2008 at 7:01 PM, Olivier Boudry [EMAIL PROTECTED]
wrote:

 2008/5/19 Dmitri O.Kondratiev [EMAIL PROTECTED]:

 I am trying to understand State monad example15 at:
 http://www.haskell.org/all_about_monads/html/statemonad.html


 Hi Dmitri,

 I'm not sure you need to understand everything about Monad and do-notation
 to use the State Monad. So I will try to explain its use without talking
 about those scary topics. ;-)

 In Haskell you use the state monad when you want to hide state passing
 between function calls. As Haskell is pure you cannot change state. You can
 just create a new state and return it along with the value. In haskell you
 would do this by returning the value and new state in a tuple. State passing
 functions usually have the type `s - (a, s)` where a is the type of the
 return value and s is the type of the State.

 This is exactly what the `random` function does. It gets a state and
 returns a tuple made of a value and a new state (StdGen: is a new seed for
 the random generator) to be used on the next `random` function call .

 Without the state monad you have to explicitely pass the new seed between
 calls to `random` as using the same seed for all function calls would always
 give you the same not so random number.

 Explicit state passing would look like this.

 get3RandomInts :: StdGen - (Int, Int, Int)
 get3RandomInts g1 =
 let (r1, g2) = random g1
 (r2, g3) = random g2
 (r3, _)  = random g3
 in (r1, r2, r3)

 It's tedious, unreadable and error prone as it's easy to mess up the
 numbering (based on my experience).

 The State Monad allow you to hide the state passing. You don't have to give
 the state as an argument and your function won't return a changed state
 along with the data. Code running in the State Monad will look like this:

 getAny :: (Random a) = State StdGen a
 getAny = do g - get -- magically get the current StdGen
 let (x, g') = random g
 put g' -- magically save the new StdGen for later
 return x

 get3RandomIntsWithState :: State StdGen (Int, Int, Int)
 get3RandomIntsWithState = do
 r1 - getAny -- you don't care about stdgen passing
 r2 - getAny
 r3 - getAny
 return (r1, r2, r3)

 To use your get3RandomIntsWithState function you need to run it using one
 of runState (returns the (value, state)) or evalState (returns the value).

 main :: IO ()
 main = do
 g - getStdGen
 let t = evalState get3RandomsWithState g
 print t

 The interesting bits are in the getAny function. The State Monad provides
 you with 2 new function, get and set. If you look at this function as
 blackboxes; `get` will retrieve the current State and `put` will save a new
 State. You don't need to worry about how the State is passed from one getAny
 function call to another as long as they're run in the same `evalState`
 call.

 Now getAny can be simplified. If you look at the random function and at the
 State newtype declaration you will see that a State is a `s - (a, s)`
 function hidden in the State constructor.

 newtype State s a = State {runState :: s - (a, s)}

 random is also of the type `s - (a, s)` even if variables are labelled `g`
 and `a`

 random :: (RandomGen g, Random a) = g - (a, g)

 So wrapping the random function into the State constructor will just give
 you a getAny function for free.

 getAny :: (Random a) = State StdGen a
 getAny = State random

 I put a copy of the code in http://hpaste.org/7768

 In short to use the State monad, you just need to care about 

Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Olivier Boudry
On Wed, May 21, 2008 at 8:42 AM, Dmitri O.Kondratiev [EMAIL PROTECTED]
wrote:

 So let's start with fundamental and most intriguing  (to me) things:

 getAny :: (Random a) = State StdGen a
 getAny = do g - get -- magically get the current StdGen

 First line above declares a data type:

 State StdGen a

 which is constructed with the function:

 State {runState :: (StdGen - (a, StdGen))}

 Q1: Where in the example (
 http://www.haskell.org/all_about_monads/examples/example15.hs) data of
 this type *actually gets constructed* ?


In getAny and getOne. Their signature has type `State StdGen a`. The use of
the do notation to chain the actions and the use of get and put from the
State Monad make this function a `State StdGen a`.


 Looking at example15.hs code we see the following sequence:

 1) makeRandomValue g -- where g is a StdGen instance, ok

 2) makeRandomValue g ~ expands into ~

 ~  (runState (do { ...; b - getAny;...})) g


 This last expression puzzles me. I can understand, for example, this:

 State StdGen a :: aState
 StdGen:: g1

 (v, g2) = (runStae aState) g1 -- this returns a state function which is
 then passed a generator g1, and as result returns pair (value, new generaor)

 But '(runState (do ...)) g' implies that expression (do ...)  must be
 somehow of type 'State StdGen a' ?
 Yet, when we call 'makeRandomValue g' we just pass to this function
 g::StgGen

 So, my next question:
 Q2: How (do {...;b - getAny;...}) becomes an *instance* of type 'State
 StdGen a' ?


In 2) I suppose you're talking of `makeRandomValueST` as `makeRandomValue`
is the function that runs without the State Monad.

makeRandomValueST does not build a `State StdGen a` it uses `runState` to
run the (do block) which has type `State StdGen a`.

Using `runState` will run an action which has `State s a` type on an initial
state `s` and return a `(a, s)` tuple.

`makeRandomValueST` does just the same using its parameter `g :: StdGen` as
initial state and returning a tuple of type `(MyType, StdGen)`. Now what
makes the do-block used in `runState` an instance of type `State StdGen a`
is type inference. `runState` expects a `State s a` as first argument and
`s` as second argument. The function signature, the use of `=` and
`return` (desugared do-block) to combine actions and the use of actions
already having that type like `getAny` and `getOne` will make your do block
a `State StdGen a`.

I'm not sure we can talk of building an instance of `State s a`. It's a
parameterized variant of `State s a` which itself is an instance of the
Monad class. We're just assigning types to the `s` and `a` type variables in
`State s a`.

In short `runState` takes the value (s - (a, s)) out of the State monad. In
the case of the State Monad that value is a function and it is run on the
initial state. Its usually what runX functions do. They have type
`(Monad m) = m a - a`.

Actions in the State Monad have type `State (s - (a, s))`. The value stored
in the State constructor is a function. Combining two actions using the
`=` and `` functions (hidden or not in a do-block) just create a bigger
`s - (a, s)` function. The function is hidden in a `State` constructor
just to ensure you don't run it when you don't want to. When you whant to
run the big function you first have to take it out of the State
constructor using the accessor `runState` and then run it on the initial
state. The end result is of course a (a, s) tuple.

Clear as mud, isn't it? It tooks me lots of time to understand how the State
Monad works. I read many tutorial and still understood nothing about it. Its
only by looking at the source code, playing with it and trying to rewrite
the State Monad that I finally got an understanding of it. So I'm not sure
you'll get it before you go through the same kind of path.

The key to understand this Monad, at least based on my experience, is to
keep in mind that `=` just assembles small state passing functions into
bigger ones, but does not run the built function until you explicitly use
the `runState` function on it.

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Jules Bean

Dmitri O.Kondratiev wrote:

Thanks everybody for your help!
Oliver,  you provided an excellent write-up  on  State  monad without  
going  into 'scary' :) details, great work indeed!
Alas,  in this case I need the details, and in particular the most scary 
ones!


So let's start with fundamental and most intriguing  (to me) things:

getAny :: (Random a) = State StdGen a
getAny = do g - get -- magically get the current StdGen

First line above declares a data type:

State StdGen a

which is constructed with the function:

State {runState :: (StdGen - (a, StdGen))}

Q1: Where in the example 
(http://www.haskell.org/all_about_monads/examples/example15.hs) data of 
this type *actually gets constructed* ?


Actually get constructed?

It gets constructed by = and return, both of which construct state 
objects:


instance Monad (State s) where
return a = State $ \s - (a, s)
m = k  = State $ \s - let
(a, s') = runState m s
in runState (k a) s'


How do = and return get called? Well you can see explicit calls to 
return. The = is implicit in the way do-notation is desugared.


getAny = do g  - get
let (x,g') = random g
put g'
return x

rewrites to

getAny = get = \g - ( let (x,g') = random g in (put g'  return x) )

where I have added some not strictly necessary ()s and taken the liberty 
of changing the confusing a - return x idiom to let a = x.


So the *actually gets constructed* part is that use of = .

HTH,

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Dmitri O.Kondratiev
State is a data type. As any other data type it can be instantiated. State
instance is a structure of one record that contains (\s -(a,s)) lambda
function. This function can be parametrized by types of its arguments 's'
and 'a'. I don't see magic here :)

Ok, then from declaration:

getAny :: (Random a) = State StdGen a
getAny = do g - get

we can say that looking at type 'State StdGen a' compiler concludes that
later on in the 'do' block statements like:

g - get

will resolve into bind function (=) *as bind is defined for State monad*.
Fine, I assume compiler is capable of such reasoning.

Then
g - get
may be written as:

get = \g - ...

To understand how State monad work, I wrote MyState data type that emulates
State and (=) 'bind' function that emulates 'real' bind (=)
implementation for State monad:

(=) :: MyState StdGen Int - (Int - MyState StdGen Int) -  MyState
StdGen Int
(MyState ms) = fn =  MyState(\seed - let(v1, newSeed) = ms seed
   ms2 = fn v1
in (runState ms2) newSeed)

Inserting 'get' into = (or = in my code) will in fact result in thinking
about State instance that 'get' returns as denoted by 'ms' in this code of
mine.
From 'get' definition follows that function hiding behind 'ms' State
instance is:

\s - (s,s)

So when later we will feed generator 'g1' into this function will get:
(g1,g1)
And we also will get:
v1 = g1
newSeed = g1
ms2 = fn g1

and finally 'g' in expression 'g - get' will be equal to 'g1' that will be
later fed in through the function call:

'makeRandomValueST g1'

But how will 'g1' actually get delivered from 'makeRandomValueST g1' to
invocation of 'getAny' I don't yet understand!


On Wed, May 21, 2008 at 5:55 PM, Olivier Boudry [EMAIL PROTECTED]
wrote:

 On Wed, May 21, 2008 at 8:42 AM, Dmitri O.Kondratiev [EMAIL PROTECTED]
 wrote:

 So let's start with fundamental and most intriguing  (to me) things:

 getAny :: (Random a) = State StdGen a
 getAny = do g - get -- magically get the current StdGen

 First line above declares a data type:

 State StdGen a

 which is constructed with the function:

 State {runState :: (StdGen - (a, StdGen))}

 Q1: Where in the example (
 http://www.haskell.org/all_about_monads/examples/example15.hs) data of
 this type *actually gets constructed* ?


 In getAny and getOne. Their signature has type `State StdGen a`. The use of
 the do notation to chain the actions and the use of get and put from the
 State Monad make this function a `State StdGen a`.


 Looking at example15.hs code we see the following sequence:

 1) makeRandomValue g -- where g is a StdGen instance, ok

 2) makeRandomValue g ~ expands into ~

 ~  (runState (do { ...; b - getAny;...})) g


 This last expression puzzles me. I can understand, for example, this:

 State StdGen a :: aState
 StdGen:: g1

 (v, g2) = (runStae aState) g1 -- this returns a state function which is
 then passed a generator g1, and as result returns pair (value, new generaor)

 But '(runState (do ...)) g' implies that expression (do ...)  must be
 somehow of type 'State StdGen a' ?
 Yet, when we call 'makeRandomValue g' we just pass to this function
 g::StgGen

 So, my next question:
 Q2: How (do {...;b - getAny;...}) becomes an *instance* of type 'State
 StdGen a' ?


 In 2) I suppose you're talking of `makeRandomValueST` as `makeRandomValue`
 is the function that runs without the State Monad.

 makeRandomValueST does not build a `State StdGen a` it uses `runState` to
 run the (do block) which has type `State StdGen a`.

 Using `runState` will run an action which has `State s a` type on an
 initial state `s` and return a `(a, s)` tuple.

 `makeRandomValueST` does just the same using its parameter `g :: StdGen` as
 initial state and returning a tuple of type `(MyType, StdGen)`. Now what
 makes the do-block used in `runState` an instance of type `State StdGen a`
 is type inference. `runState` expects a `State s a` as first argument and
 `s` as second argument. The function signature, the use of `=` and
 `return` (desugared do-block) to combine actions and the use of actions
 already having that type like `getAny` and `getOne` will make your do block
 a `State StdGen a`.

 I'm not sure we can talk of building an instance of `State s a`. It's a
 parameterized variant of `State s a` which itself is an instance of the
 Monad class. We're just assigning types to the `s` and `a` type variables in
 `State s a`.

 In short `runState` takes the value (s - (a, s)) out of the State monad.
 In the case of the State Monad that value is a function and it is run on the
 initial state. Its usually what runX functions do. They have type
 `(Monad m) = m a - a`.

 Actions in the State Monad have type `State (s - (a, s))`. The value
 stored in the State constructor is a function. Combining two actions using
 the `=` and `` functions (hidden or not in a do-block) just create a
 bigger `s - (a, s)` function. The function is hidden in a 

Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Dmitri O.Kondratiev
Jules,

Stupid question, please bear with me:

x :: Int -- x declared, but not constructed
x = 1 -- x constructed

s1 :: State StdGen a -- s1 declared, yes, but why s1 is *also already
constructed* ?

On Wed, May 21, 2008 at 6:54 PM, Jules Bean [EMAIL PROTECTED] wrote:

 Dmitri O.Kondratiev wrote:

 Thanks everybody for your help!
 Oliver,  you provided an excellent write-up  on  State  monad without
  going  into 'scary' :) details, great work indeed!
 Alas,  in this case I need the details, and in particular the most scary
 ones!

 So let's start with fundamental and most intriguing  (to me) things:

 getAny :: (Random a) = State StdGen a
 getAny = do g - get -- magically get the current StdGen

 First line above declares a data type:

 State StdGen a

 which is constructed with the function:

 State {runState :: (StdGen - (a, StdGen))}

 Q1: Where in the example (
 http://www.haskell.org/all_about_monads/examples/example15.hs) data of
 this type *actually gets constructed* ?


 Actually get constructed?

 It gets constructed by = and return, both of which construct state
 objects:

 instance Monad (State s) where
return a = State $ \s - (a, s)
m = k  = State $ \s - let
(a, s') = runState m s
in runState (k a) s'


 How do = and return get called? Well you can see explicit calls to
 return. The = is implicit in the way do-notation is desugared.

 getAny = do g  - get
let (x,g') = random g
put g'
return x

 rewrites to

 getAny = get = \g - ( let (x,g') = random g in (put g'  return x) )

 where I have added some not strictly necessary ()s and taken the liberty of
 changing the confusing a - return x idiom to let a = x.

 So the *actually gets constructed* part is that use of = .

 HTH,

 Jules




-- 
Dmitri O. Kondratiev
[EMAIL PROTECTED]
http://www.geocities.com/dkondr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Jules Bean

Dmitri O.Kondratiev wrote:

Jules,

Stupid question, please bear with me:

x :: Int -- x declared, but not constructed
x = 1 -- x constructed

s1 :: State StdGen a -- s1 declared, yes, but why s1 is *also already 
constructed* ?


it's not.

it's constructed when you do

s1 = return 1

... or ...

s1 = get = put

.. or some other more complex interaction, perhaps using do notation.

It's the = or the return that construct the State, just as the '1' is 
enough to construct the Int.


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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-21 Thread Dmitri O.Kondratiev
-- Jules, Oliver, thanks! Things are getting clarified, I hope.
-- Let me summarize how I now understand getAny operation, please correct me
if I am wrong.

getAny :: (Random a) = State StdGen a
getAny = do g  - get
(x,g') - return $ random g
put g'
return x

{--
getAny operation may be abbreviated as:

do {
-- 1) x calculation, equivalent to (x,g2) = random g1
-- 2) return x ~ State $ \s - (x,s) -- puts x into State container

Thus getAny returns a State instantiated with a function which is a
composition of several binds = from the above 'do' block and which
calculates 'x'
--}

-- Then we can use  this State object (returned by getAny) in a function
generating random values such as:

makeRnd :: StdGen - (Int, StdGen)
makeRnd = runState (do
  y - getAny
  return y)

{--
where:

y - getAny
return y

passes a first value from the tuple generated by getAny State function  into
'y' and puts 'y' into a new State object.
After that 'runState' in makeRnd extracts from this new State a function
parametrized by 'y' value.
As a result we get curried 'makeRnd' which we can call with some generator
instance and get a random value.
--}

On Wed, May 21, 2008 at 10:31 PM, Olivier Boudry [EMAIL PROTECTED]
wrote:

 On Wed, May 21, 2008 at 11:10 AM, Dmitri O.Kondratiev [EMAIL PROTECTED]
 wrote:

 But how will 'g1' actually get delivered from 'makeRandomValueST g1' to
 invocation of 'getAny' I don't yet understand!


 It may be easier to understand the state passing if you remove the do
 notation and replace get, put and return with their definition in the
 instance declarations (Monad and MonadState).

 getAny :: (Random a) = State StdGen a
 getAny = do g  - get
 (x,g') - return $ random g
 put g'
 return x

 get = State $ \s - (s, s) -- copy the state as a return value and pass
 state
 put s = State $ \_ - ((), s) -- return unit, ignore the passed state and
 replace it with the state given as parameter.
 return a = State $ \s - (a, s) -- return given value and pass state.

 getAnyNoSugar :: (Random a) = State StdGen a
 getAnyNoSugar = (State $ \s - (s, s)) = \g -
 (State $ \s - (random g, s)) = \(x,g') -
 (State $ \_ - ((), g')) 
 (State $ \s - (x, s))

 The function is still useable this way and the state transformations should
 be a bit more visible. The first element of the tuple is the value that will
 be used to call the next function (of type Monad m = a - m b). The second
 element of the tuple is the state and the (=) operator will handle passing
 it between actions.

 Desugaring the (=) and () operators would give you something like this
 (I replaced `s` with `y` in the `put` and `return` desugaring and simplified
 it):

 State $ \s = let
   (g, s') = (\y - (y,y)) s
   ((x,g'), s'') = (\y - (random g, y)) s'
   (_, s''') = (\_ - ((), g')) s''
   in (x, s''')

 Which is explict state passing between function calls. Extract the State
 using `runState`, run it with an initial state and it should give you the
 expected result.

 Regards,

 Olivier.




-- 
Dmitri O. Kondratiev
[EMAIL PROTECTED]
http://www.geocities.com/dkondr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-20 Thread Olivier Boudry
2008/5/19 Dmitri O.Kondratiev [EMAIL PROTECTED]:

 I am trying to understand State monad example15 at:
 http://www.haskell.org/all_about_monads/html/statemonad.html


Hi Dmitri,

I'm not sure you need to understand everything about Monad and do-notation
to use the State Monad. So I will try to explain its use without talking
about those scary topics. ;-)

In Haskell you use the state monad when you want to hide state passing
between function calls. As Haskell is pure you cannot change state. You can
just create a new state and return it along with the value. In haskell you
would do this by returning the value and new state in a tuple. State passing
functions usually have the type `s - (a, s)` where a is the type of the
return value and s is the type of the State.

This is exactly what the `random` function does. It gets a state and returns
a tuple made of a value and a new state (StdGen: is a new seed for the
random generator) to be used on the next `random` function call .

Without the state monad you have to explicitely pass the new seed between
calls to `random` as using the same seed for all function calls would always
give you the same not so random number.

Explicit state passing would look like this.

get3RandomInts :: StdGen - (Int, Int, Int)
get3RandomInts g1 =
let (r1, g2) = random g1
(r2, g3) = random g2
(r3, _)  = random g3
in (r1, r2, r3)

It's tedious, unreadable and error prone as it's easy to mess up the
numbering (based on my experience).

The State Monad allow you to hide the state passing. You don't have to give
the state as an argument and your function won't return a changed state
along with the data. Code running in the State Monad will look like this:

getAny :: (Random a) = State StdGen a
getAny = do g - get -- magically get the current StdGen
let (x, g') = random g
put g' -- magically save the new StdGen for later
return x

get3RandomIntsWithState :: State StdGen (Int, Int, Int)
get3RandomIntsWithState = do
r1 - getAny -- you don't care about stdgen passing
r2 - getAny
r3 - getAny
return (r1, r2, r3)

To use your get3RandomIntsWithState function you need to run it using one of
runState (returns the (value, state)) or evalState (returns the value).

main :: IO ()
main = do
g - getStdGen
let t = evalState get3RandomsWithState g
print t

The interesting bits are in the getAny function. The State Monad provides
you with 2 new function, get and set. If you look at this function as
blackboxes; `get` will retrieve the current State and `put` will save a new
State. You don't need to worry about how the State is passed from one getAny
function call to another as long as they're run in the same `evalState`
call.

Now getAny can be simplified. If you look at the random function and at the
State newtype declaration you will see that a State is a `s - (a, s)`
function hidden in the State constructor.

newtype State s a = State {runState :: s - (a, s)}

random is also of the type `s - (a, s)` even if variables are labelled `g`
and `a`

random :: (RandomGen g, Random a) = g - (a, g)

So wrapping the random function into the State constructor will just give
you a getAny function for free.

getAny :: (Random a) = State StdGen a
getAny = State random

I put a copy of the code in http://hpaste.org/7768

In short to use the State monad, you just need to care about a couple of
details.

The type of your functions running in the State Monad must end in `State s
a` where `s` is the type of the state and `a` the type of the return value.

You have to run it using either runState, execState or evalState. runState
will return both the value and the state, execState will return the state
and evalState will return just the value.

You must use put and get to retrieve and store the State but don't need to
care about the details of how the state is passed. As long as your function
calls are all part of the same action.

I hope it helps. I'm also quite new at Haskell and the terminology used is
probably not very accurate.

Best regards,

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


Re: [Haskell-cafe] Newbie: State monad example questions

2008-05-19 Thread Andrew Wagner
Dmitri,
Excellent questions. There's one step you're missing. Most of your
questions revolve around 'foo - bar' constructs within a monad. I
would suggest that you review the de-sugaring rules at
http://en.wikibooks.org/wiki/Haskell/Syntactic_sugar#Do_and_proc_notation
and see if that helps you out some. The best process would be for you
to 1.) De-sugar this function completely and 2.) look at bind (denoted
as =), and substitute it in.

Hope this helps!

2008/5/19 Dmitri O.Kondratiev [EMAIL PROTECTED]:
 I am trying to understand State monad example15 at:
 http://www.haskell.org/all_about_monads/html/statemonad.html

 Example 15 uses getAny that I don't understand at all how it works:

 getAny :: (Random a) = State StdGen a
 getAny = do g  - get
 (x,g') - return $ random g
 put g'
 return x


 Questions:
 1) random has type:
 random :: (Random a, RandomGen g) = g - (a, g)

 and for State monad:

 return a = State (\s - (a, s))

 then:
 return (random g) = State (\s - ((a,g), s))

 Is  it correct?

 2) What x and g' will match to in:
do ...
 (x,g') - return $ random g

 which, as I understand equals to:
do ...
 (x,g') - State (\s - ((a,g), s))

 What x and g' will match to in the last expression?

 3) In general, in do expression (pseudo):
 do { x - State (\s - (a, s)); ...}

 What x will refer to? Will x stand for a whole lambda function: \s - (a, s)
 ?

 4) How 'g - get' works in this function (getAny) ?
 5) Why we need 'put g'?

 Thanks!


 ___
 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] Newbie: State monad example questions

2008-05-19 Thread Luke Palmer
Hi Dmitri.  I'm just going to ramble on about what I know and how I
think of things, and maybe you'll pick something up :-)

On 5/19/08, Dmitri O.Kondratiev [EMAIL PROTECTED] wrote:
 getAny :: (Random a) = State StdGen a
 getAny = do g  - get
 (x,g') - return $ random g
 put g'
 return x

 Questions:
 return (random g) = State (\s - ((a,g), s))

 Is  it correct?

Yes, where a is a random value and g is a new generator.

 2) What x and g' will match to in:
do ...
 (x,g') - return $ random g

 which, as I understand equals to:
do ...
 (x,g') - State (\s - ((a,g), s))

 What x and g' will match to in the last expression?

Well, I also suggest working through the desugared version of = as
the other poster suggested:

State (\s - ((a,g), s)) = (\(x,g') - ...)

The question is, what values do x and g' have in '...'.  Expand out
the definition and see.  State is kind of complicated, but you will
get an answer.

But I can provide some intuition aside from the formality.

x - action

Does the action and names the return value x.  Your action is
return $ random g, namely it's an action that doesn't have any
effects and just returns a value.  So:

   (x,g') - return $ random g

Is equivalent to:

   let (x,g') = random g

Nothing particular to State is happening here.

 3) In general, in do expression (pseudo):
 do { x - State (\s - (a, s)); ...}

 What x will refer to? Will x stand for a whole lambda function: \s - (a, s)
 ?

Here x will be equal to a, and the implicit state will be unchanged
after the binding.

 4) How 'g - get' works in this function (getAny) ?

The representation of a state action is State f, where f takes the
current state as an argument and returns the result of the computation
along with the new state.  get is defined as:

   get = State $ \s - (s,s)

So its function takes a state, and returns the current state as the
return value as well as the next state; that is to say, it does not
update the state and it also returns it.  So:

x - get
...

Gives the name x to the implicit state at the time get was called.

 5) Why we need 'put g'?

Otherwise this function would not modify the implicit state, and you'd
always get the same random number back when you called it.

Something to keep in mind:  If you have an action :: m a for some
monad m, then in:

x - action

x will name a value of type Foo.

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