[Haskell-cafe] select :: [(Float, a)] -> a -- Weighted stochastic selection - help?

I am already using the following function pickOne xs g = (xs !! r, g') where (r, g') = Random.randomR (0, length xs - 1) g but I need to weight the items in the list, e.g. [(0.1, 'a') , (0.9, 'b')] for stochastic selection in a purely functional way, i.e. no monads. Any ideas welcome. Tim.

Am Freitag, 5. September 2008 18:54 schrieb Tim Millea:
I am already using the following function
pickOne xs g = (xs !! r, g') where (r, g') = Random.randomR (0, length xs - 1) g
but I need to weight the items in the list, e.g. [(0.1, 'a') , (0.9, 'b')] for stochastic selection in a purely functional way, i.e. no monads. Any ideas welcome.
Tim.
You could pair each item with the cumulative probability of all items up to and including it, that would be [(0.1,'a'),(1.0,'b')] in the above example, then pickOne prs g = (snd p,g') where (r,g') = Random.randomR (0,1.0) (smll,lrge) = span ((< r) . fst) prs p = case lrge of (x:_) -> x [] -> last smll

[snip] ... in a purely functional way, i.e. no monads. [snip] Err, what? Monads aren't purely functional?

Some Monads (such as State and IO) allow side effects and are therefore not pure. HTH, Chris. On Fri, 5 Sep 2008, Andrew Wagner wrote:
[snip] ... in a purely functional way, i.e. no monads. [snip]
Err, what? Monads aren't purely functional? _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Am Freitag, 5. September 2008 21:06 schrieb C.M.Brown:
Some Monads (such as State and IO) allow side effects and are therefore not pure.
State allows side effects? How that?
HTH, Chris.
On Fri, 5 Sep 2008, Andrew Wagner wrote:
[snip] ... in a purely functional way, i.e. no monads. [snip]
Err, what? Monads aren't purely functional?

IO is a special case, I'll grant you that. But I thought all other
monads were considered pure. State is just a wrapped up function,
basically. Nothing impure about that.
On Fri, Sep 5, 2008 at 3:42 PM, Daniel Fischer
Am Freitag, 5. September 2008 21:06 schrieb C.M.Brown:
Some Monads (such as State and IO) allow side effects and are therefore not pure.
State allows side effects? How that?
HTH, Chris.
On Fri, 5 Sep 2008, Andrew Wagner wrote:
[snip] ... in a purely functional way, i.e. no monads. [snip]
Err, what? Monads aren't purely functional?

It's certainly possibly to define or use State in a way that it gives the impression of modifying a global state, it therefore having a side-effect. Chris. On Fri, 5 Sep 2008, Daniel Fischer wrote:
Am Freitag, 5. September 2008 21:06 schrieb C.M.Brown:
Some Monads (such as State and IO) allow side effects and are therefore not pure.
State allows side effects? How that?
HTH, Chris.
On Fri, 5 Sep 2008, Andrew Wagner wrote:
[snip] ... in a purely functional way, i.e. no monads. [snip]
Err, what? Monads aren't purely functional?

Am Freitag, 5. September 2008 21:51 schrieb C.M.Brown:
It's certainly possibly to define or use State in a way that it gives the impression of modifying a global state, it therefore having a side-effect.
Chris.
Can you give an example? I don't see how that can be done using Control.Monad.State(.Strict).State, unless invocations of put or modify are considered side effects. Thanks, Daniel

Can you give an example? I don't see how that can be done using Control.Monad.State(.Strict).State, unless invocations of put or modify are considered side effects.
Actually, yes, sorry; I do see your point. I guess it's just IO then. Chris.

Excerpts from C.M.Brown's message of Fri Sep 05 22:12:05 +0200 2008:
Can you give an example? I don't see how that can be done using Control.Monad.State(.Strict).State, unless invocations of put or modify are considered side effects.
Actually, yes, sorry; I do see your point. I guess it's just IO then.
Technically, even the IO monad is pure, that's just the runtime-system that consume your 'main' function that perform effects (and unsafeP...). That's an important point to grasp about the way we do effects in a pure language. Once we've understood that point one tend to be a little less precise and consider IO as effect-full. Best regards, -- Nicolas Pouillard aka Ertai

On Sat, 6 Sep 2008, Nicolas Pouillard wrote:
Excerpts from C.M.Brown's message of Fri Sep 05 22:12:05 +0200 2008:
Can you give an example? I don't see how that can be done using Control.Monad.State(.Strict).State, unless invocations of put or modify are considered side effects.
Actually, yes, sorry; I do see your point. I guess it's just IO then.
Technically, even the IO monad is pure, that's just the runtime-system that consume your 'main' function that perform effects (and unsafeP...).
But, sure the IO monad does have side-effects? I'm confused as to how it could be pure. Could you explain?
That's an important point to grasp about the way we do effects in a pure language.
Once we've understood that point one tend to be a little less precise and consider IO as effect-full.
I consider IO to be effect-full anyway - I can't see how it isn't! Thanks, Chris.

Excerpts from C.M.Brown's message of Sat Sep 06 12:04:10 +0200 2008:
On Sat, 6 Sep 2008, Nicolas Pouillard wrote:
Excerpts from C.M.Brown's message of Fri Sep 05 22:12:05 +0200 2008:
Can you give an example? I don't see how that can be done using Control.Monad.State(.Strict).State, unless invocations of put or modify are considered side effects.
Actually, yes, sorry; I do see your point. I guess it's just IO then.
Technically, even the IO monad is pure, that's just the runtime-system that consume your 'main' function that perform effects (and unsafeP...).
But, sure the IO monad does have side-effects? I'm confused as to how it could be pure. Could you explain?
That's an important point to grasp about the way we do effects in a pure language.
Once we've understood that point one tend to be a little less precise and consider IO as effect-full.
I consider IO to be effect-full anyway - I can't see how it isn't!
In fact one consider the IO monad to be effect-full because we don't have a runIO [1] function that is safe. So to be clear you go in the monad, but you can't go out of it. In other terms you can make 'IO t' values but you can't get values inside of it (without being yourself inside of it again). For instance the State monad have a runState [2] function that allows you to go out the of the monad, or in other terms to get the value inside. So the State monad really is pure. The ST monad is also pure and provides a pure running function runST [3]. What is interesting with the ST monad is that one don't choose the state type, moreover one cannot access it either (no get and put functions). Moreover by having this rank-2 type the runST function force the caller to give a 'ST s a' computation that does not mix the state parameter 's'. Internally one can see 'ST' to be defined by something like that: type ST s a = s -> (s, a) So not far of the State monad. The IO monad internally is defined as 'ST RealWorld a', what means that 'IO a' values are in fact RealWorld passing function. An example: What is the side-effect of reducing 'putStrLn "Hello"'? Easy answer, there is no side-effect in a pure language. More precise answer: "Hello" :: String putStrLn :: String -> IO () So: putStrLn "Hello" :: IO () If one imprecisely expand IO: putStrLn "Hello" :: RealWorld -> (RealWorld, ()) Thus an argument is still missing, so no effect Is this clearer? [1] hypothetical type: runIO :: IO a -> a [2] runState :: State s a -> s -> (a, s) [3] runST :: (forall s. ST s a) -> a -- Nicolas Pouillard aka Ertai

Hi Nicolas, I'm sorry, but I just don't get it. What are you trying to say? I think it would be clearer if we started to define what exactly a "side-effect" is (in any language) and work our definitions from there, because now I'm really confused. Thanks, Chris. On Sat, 6 Sep 2008, Nicolas Pouillard wrote:
Excerpts from C.M.Brown's message of Sat Sep 06 12:04:10 +0200 2008:
On Sat, 6 Sep 2008, Nicolas Pouillard wrote:
Excerpts from C.M.Brown's message of Fri Sep 05 22:12:05 +0200 2008:
Can you give an example? I don't see how that can be done using Control.Monad.State(.Strict).State, unless invocations of put or modify are considered side effects.
Actually, yes, sorry; I do see your point. I guess it's just IO then.
Technically, even the IO monad is pure, that's just the runtime-system that consume your 'main' function that perform effects (and unsafeP...).
But, sure the IO monad does have side-effects? I'm confused as to how it could be pure. Could you explain?
That's an important point to grasp about the way we do effects in a pure language.
Once we've understood that point one tend to be a little less precise and consider IO as effect-full.
I consider IO to be effect-full anyway - I can't see how it isn't!
In fact one consider the IO monad to be effect-full because we don't have a runIO [1] function that is safe. So to be clear you go in the monad, but you can't go out of it. In other terms you can make 'IO t' values but you can't get values inside of it (without being yourself inside of it again).
For instance the State monad have a runState [2] function that allows you to go out the of the monad, or in other terms to get the value inside. So the State monad really is pure.
The ST monad is also pure and provides a pure running function runST [3]. What is interesting with the ST monad is that one don't choose the state type, moreover one cannot access it either (no get and put functions). Moreover by having this rank-2 type the runST function force the caller to give a 'ST s a' computation that does not mix the state parameter 's'.
Internally one can see 'ST' to be defined by something like that: type ST s a = s -> (s, a) So not far of the State monad.
The IO monad internally is defined as 'ST RealWorld a', what means that 'IO a' values are in fact RealWorld passing function.
An example:
What is the side-effect of reducing 'putStrLn "Hello"'?
Easy answer, there is no side-effect in a pure language.
More precise answer: "Hello" :: String putStrLn :: String -> IO () So: putStrLn "Hello" :: IO () If one imprecisely expand IO: putStrLn "Hello" :: RealWorld -> (RealWorld, ()) Thus an argument is still missing, so no effect
Is this clearer?
[1] hypothetical type: runIO :: IO a -> a [2] runState :: State s a -> s -> (a, s) [3] runST :: (forall s. ST s a) -> a

Excerpts from C.M.Brown's message of Sat Sep 06 12:43:08 +0200 2008:
Hi Nicolas,
I'm sorry, but I just don't get it. What are you trying to say? I think it would be clearer if we started to define what exactly a "side-effect" is (in any language) and work our definitions from there, because now I'm really confused.
OK, let's restrict the word side-effect to printing on the screen as the only
side-effect possible.
Some recalls:
- Yes the 'IO' monad allow the user to define side-effecting functions
- No the user cannot produce a side-effect in a pure language
- The 'main' *function* is a side-effecting function
- The runtime system consume 'main' and trigger it's effects
Example:
putStrLn is a side-effecting function expecting *2* arguments,
the first one is the string to print, and the second one is the world state.
So if you could give to arguments to putStrLn you could make a side-effect,
however you don't have a value of type RealWorld.
Is this clear?
In <
On Sat, 6 Sep 2008, Nicolas Pouillard wrote:
Excerpts from C.M.Brown's message of Sat Sep 06 12:04:10 +0200 2008:
On Sat, 6 Sep 2008, Nicolas Pouillard wrote:
Excerpts from C.M.Brown's message of Fri Sep 05 22:12:05 +0200 2008:
Can you give an example? I don't see how that can be done using Control.Monad.State(.Strict).State, unless invocations of put or modify are considered side effects.
Actually, yes, sorry; I do see your point. I guess it's just IO then.
Technically, even the IO monad is pure, that's just the runtime-system that consume your 'main' function that perform effects (and unsafeP...).
But, sure the IO monad does have side-effects? I'm confused as to how it could be pure. Could you explain?
That's an important point to grasp about the way we do effects in a pure language.
Once we've understood that point one tend to be a little less precise and consider IO as effect-full.
I consider IO to be effect-full anyway - I can't see how it isn't!
In fact one consider the IO monad to be effect-full because we don't have a runIO [1] function that is safe. So to be clear you go in the monad, but you can't go out of it. In other terms you can make 'IO t' values but you can't get values inside of it (without being yourself inside of it again).
For instance the State monad have a runState [2] function that allows you to go out the of the monad, or in other terms to get the value inside. So the State monad really is pure.
The ST monad is also pure and provides a pure running function runST [3]. What is interesting with the ST monad is that one don't choose the state type, moreover one cannot access it either (no get and put functions). Moreover by having this rank-2 type the runST function force the caller to give a 'ST s a' computation that does not mix the state parameter 's'.
Internally one can see 'ST' to be defined by something like that: type ST s a = s -> (s, a) So not far of the State monad.
The IO monad internally is defined as 'ST RealWorld a', what means that 'IO a' values are in fact RealWorld passing function.
An example:
What is the side-effect of reducing 'putStrLn "Hello"'?
Easy answer, there is no side-effect in a pure language.
More precise answer: "Hello" :: String putStrLn :: String -> IO () So: putStrLn "Hello" :: IO () If one imprecisely expand IO: putStrLn "Hello" :: RealWorld -> (RealWorld, ()) Thus an argument is still missing, so no effect
Is this clearer?
[1] hypothetical type: runIO :: IO a -> a [2] runState :: State s a -> s -> (a, s) [3] runST :: (forall s. ST s a) -> a
-- Nicolas Pouillard aka Ertai

Nicolas,
OK, let's restrict the word side-effect to printing on the screen as the only side-effect possible.
Some recalls:
Example:
putStrLn is a side-effecting function expecting *2* arguments, the first one is the string to print, and the second one is the world state. So if you could give to arguments to putStrLn you could make a side-effect, however you don't have a value of type RealWorld.
Is this clear?
Yes! Thanks for giving such a clear and insightful explanation. I guess I forgot about the IO being an abstraction for something else. So can I clarify that it's the runtime system that triggers the side-effect, and not Haskell? I have one last question that is still confusing me: what if I have a function that reads something from a file, say, and does something depending on that input - would that be a side-effect? Consider something modifying a file outside of the Haskell world that changes a program's behaviour. Am I right in thinking that the side-effect happens at runtime - but in Haskell, the funtion is still pure. I feel, also, that as a reasonably experienced Haskell user, I am getting confused with what should be fundamental Haskell concepts. Perhaps these concepts should be made much clearer to beginners in the first instance. Thanks! Chris.

Excerpts from C.M.Brown's message of Sat Sep 06 16:43:23 +0200 2008:
Nicolas,
OK, let's restrict the word side-effect to printing on the screen as the only side-effect possible.
Some recalls:
Example:
putStrLn is a side-effecting function expecting *2* arguments, the first one is the string to print, and the second one is the world state. So if you could give to arguments to putStrLn you could make a side-effect, however you don't have a value of type RealWorld.
Is this clear?
Yes! Thanks for giving such a clear and insightful explanation. I guess I forgot about the IO being an abstraction for something else. So can I clarify that it's the runtime system that triggers the side-effect, and not Haskell?
Right.
I have one last question that is still confusing me: what if I have a function that reads something from a file, say, and does something depending on that input - would that be a side-effect?
Reading is treated like writing, but it's a little more complicated to understand because it rely on binding part of (>>=), the first one was sequencing (as in (>>)). Example with getLine getLine >>= \name -> putStrLn ("Hello " ++ name ++ "!") getLine have type IO String, so it's a function that waits for *1* argument. (>>=) in the case of IO is a function that expect *3* arguments: the first is computation that produce something, the second is a function that tell what to do with the result (a kind of continuation), and the third argument is again the RealWorld value.
Consider something modifying a file outside of the Haskell world that changes a program's behaviour. Am I right in thinking that the side-effect happens at runtime - but in Haskell, the funtion is still pure.
Yes
I feel, also, that as a reasonably experienced Haskell user, I am getting confused with what should be fundamental Haskell concepts. Perhaps these concepts should be made much clearer to beginners in the first instance.
This article [1] seems a good introduction. Maybe one could sum-up what you think is missing from this article and extend it a bit. For instance one could explain the point about the run-time system. [1]: http://www.haskell.org/haskellwiki/Introduction_to_IO -- Nicolas Pouillard aka Ertai

Nicolas,
Yes
I feel, also, that as a reasonably experienced Haskell user, I am getting confused with what should be fundamental Haskell concepts. Perhaps these concepts should be made much clearer to beginners in the first instance.
This article [1] seems a good introduction. Maybe one could sum-up what you think is missing from this article and extend it a bit.
For instance one could explain the point about the run-time system.
Although what you've told me may be true (and I thank you for your explanation), I'm still not at all convinced that it's useful to think of IO as being pure. It still produces an effect if I evaluate it, no matter how we sugar-coat these things. I like the idea of the type system flagging the function as being effect-full by the IO - and find that more useful than thinking about runtime systems. Thanks, Chris.

Excerpts from C.M.Brown's message of Sat Sep 06 17:33:58 +0200 2008:
Nicolas,
Yes
I feel, also, that as a reasonably experienced Haskell user, I am getting confused with what should be fundamental Haskell concepts. Perhaps these concepts should be made much clearer to beginners in the first instance.
This article [1] seems a good introduction. Maybe one could sum-up what you think is missing from this article and extend it a bit.
For instance one could explain the point about the run-time system.
Although what you've told me may be true (and I thank you for your explanation), I'm still not at all convinced that it's useful to think of IO as being pure. It still produces an effect if I evaluate it, no matter how we sugar-coat these things.
I like the idea of the type system flagging the function as being effect-full by the IO - and find that more useful than thinking about runtime systems.
Once we've understood that monads (even the IO) is not an exception in the *language*, but that's the runtime system that consume and evaluate IO values starting from main. Then one could think in a more pragmatic way: IO is effect-full, and non IO is pure, that the type system help us to separate effects from pure code... -- Nicolas Pouillard aka Ertai

C.M.Brown wrote:
Technically, even the IO monad is pure, that's just the runtime-system
that consume your 'main' function that perform effects (and unsafeP...).
But, sure the IO monad does have side-effects? I'm confused as to how it could be pure. Could you explain?
I'm sorry, but I just don't get it. What are you trying to say? I think it would be clearer if we started to define what exactly a "side-effect" is (in any language) and work our definitions from there, because now I'm really confused.
A function say f :: Int -> Int is said to be *pure* if its result depends only on the argument. In Haskell, all functions are pure and the IO monad doesn't change anything about that. This is what is meant by "IO is pure". While IO allows you to print stuff on the screen, it doesn't change the fundamental property of the language that all functions are free of side-effects. In other languages like C or even ML, there are functions like putStr :: String -> () getChar :: () -> Char whose results depend on more things than their parameter and who can perform side-effects. Regards, apfelmus

The IO monad is defined as:
newtype IO a = IO (RealWorld -> (RealWorld, a))
Notice that it encapsulates a pure function from RealWorld to RealWord plus
result. Semantically, the whole state of the world is passed into your main
function and a new world state is returned containing any changes you made.
However, the implementation just performs side effects on the world (I/O),
but the monad type ensures that these side effects are sequential and that
you can never gain access to the underlying RealWorld so it won't be
duplicated. These restrictions allow us to view this implementation as a
pure function.
Non-primitive monads like Control.Monad.State are actually implemented as
pure functions passing the state around.
Cheers,
Tony
On Sat, Sep 6, 2008 at 10:18 AM, apfelmus
C.M.Brown wrote:
Technically, even the IO monad is pure, that's just the runtime-system
that consume your 'main' function that perform effects (and unsafeP...).
But, sure the IO monad does have side-effects? I'm confused as to how it could be pure. Could you explain?
I'm sorry, but I just don't get it. What are you trying to say? I think it would be clearer if we started to define what exactly a "side-effect" is (in any language) and work our definitions from there, because now I'm really confused.
A function say f :: Int -> Int is said to be *pure* if its result depends only on the argument.
In Haskell, all functions are pure and the IO monad doesn't change anything about that. This is what is meant by "IO is pure". While IO allows you to print stuff on the screen, it doesn't change the fundamental property of the language that all functions are free of side-effects.
In other languages like C or even ML, there are functions like
putStr :: String -> () getChar :: () -> Char
whose results depend on more things than their parameter and who can perform side-effects.
Regards, apfelmus
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Tony Hannan wrote:
The IO monad is defined as:
newtype IO a = IO (RealWorld -> (RealWorld, a))
Notice that it encapsulates a pure function from RealWorld to RealWord plus result. Semantically, the whole state of the world is passed into your main function and a new world state is returned containing any changes you made. However, the implementation just performs side effects on the world (I/O), but the monad type ensures that these side effects are sequential and that you can never gain access to the underlying RealWorld so it won't be duplicated. These restrictions allow us to view this implementation as a pure function.
Note that while IO a ~ RealWorld -> (RealWorld, a) is an intuitive way to think about IO, it's not the definition of IO and it doesn't always work. For instance, it's inadequate for modeling concurrency. But also in a sequential world, there are problems: consider the two programs loop, loop' :: IO () loop = loop loop' = putStr "X" >> loop' Both would have the denotation _|_ while being very different: one does nothing at all while the other prints an infinite stream of Xs. For more on the semantics of IO, see also Simon Peyton Jones. Tackling the Awkward Squad. http://research.microsoft.com/~simonpj/papers/marktoberdorf/
Non-primitive monads like Control.Monad.State are actually implemented as pure functions passing the state around.
Yes, so the difference between IO and the other monads is of course that IO is a primitive and cannot be implemented with other Haskell constructs. Regards, apfelmus

On 2008 Sep 6, at 6:04, C.M.Brown wrote:
On Sat, 6 Sep 2008, Nicolas Pouillard wrote:
Excerpts from C.M.Brown's message of Fri Sep 05 22:12:05 +0200 2008:
Can you give an example? I don't see how that can be done using Control.Monad.State(.Strict).State, unless invocations of put or modify are considered side effects.
Actually, yes, sorry; I do see your point. I guess it's just IO then.
Technically, even the IO monad is pure, that's just the runtime- system that consume your 'main' function that perform effects (and unsafeP...).
But, sure the IO monad does have side-effects? I'm confused as to how it could be pure. Could you explain?
Technically (in GHC at least) the IO monad builds a pure chain of function applications and returns it from main, which then implicitly passes it to an otherwise inacccessible runIO. Laziness makes this indistinguishable in practice from making effectful calls. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On 2008 Sep 5, at 16:06, Daniel Fischer wrote:
Am Freitag, 5. September 2008 21:51 schrieb C.M.Brown:
It's certainly possibly to define or use State in a way that it gives the impression of modifying a global state, it therefore having a side-effect.
Chris.
Can you give an example? I don't see how that can be done using Control.Monad.State(.Strict).State, unless invocations of put or modify are considered side effects.
That' the only thing I can figure, but it's easy to show that it's not actually global state (trust me, I had to find ways to make it do global state for GUI callbacks. pain!) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (8)
-
Andrew Wagner
-
apfelmus
-
Brandon S. Allbery KF8NH
-
C.M.Brown
-
Daniel Fischer
-
Nicolas Pouillard
-
Tim Millea
-
Tony Hannan