
Can anyone explain the following behavior (GHCi 6.6): Prelude Control.Monad.ST> runST (return 42) 42 Prelude Control.Monad.ST> (runST . return) 42 <interactive>:1:9: Couldn't match expected type `forall s. ST s a' against inferred type `m a1' In the second argument of `(.)', namely `return' In the expression: (runST . return) 42 In the definition of `it': it = (runST . return) 42 Thanks, Yitz

Yitzchak Gale wrote:
Can anyone explain the following behavior (GHCi 6.6):
Prelude Control.Monad.ST> runST (return 42) 42 Prelude Control.Monad.ST> (runST . return) 42
<interactive>:1:9: Couldn't match expected type `forall s. ST s a' against inferred type `m a1' In the second argument of `(.)', namely `return' In the expression: (runST . return) 42 In the definition of `it': it = (runST . return) 42
Section 7.4.8 of GHC manual states that a type variable can't be instantiated with a forall type, though it doesn't give any explanation why. Hazarding a guess, I suggest it *might* be due to the fact that forall s. ST s a means forall s. (ST s a) whereas you'd need it to mean (forall s. ST s) a in order for it to unify with (m a). Just a guess - I'd be interested to know the real reason as well. Brian. -- http://www.metamilk.com

I wrote:
Prelude Control.Monad.ST> runST (return 42) 42 Prelude Control.Monad.ST> (runST . return) 42
<interactive>:1:9: Couldn't match expected type `forall s. ST s a' against inferred type `m a1'
Brian Hulley wrote:
Hazarding a guess, I suggest it *might* be due to the fact that
forall s. ST s a
means
forall s. (ST s a)
whereas you'd need it to mean
(forall s. ST s) a
in order for it to unify with (m a).
But then why does "return 42" type successfully as forall s. (ST s a)? It needs that same unification. -Yitz

On Jan 1, 2007, at 6:02 , Yitzchak Gale wrote:
Prelude Control.Monad.ST> (runST . return) 42
<interactive>:1:9: Couldn't match expected type `forall s. ST s a' against inferred type `m a1'
I think the problem is that technically runST is a data constructor (possibly not relevant) which takes a function as a parameter (definitely relevant). In the normal compositional model, (f . g) x = f (g x), you're conceptually invoking f on the result of g x (g is independent of f); here, you're lifting the function g x into the ST s a monad via f (g is dependent on f). -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
I think the problem is that technically runST is a data constructor (possibly not relevant)
No, at least not in GHC. It is a function.
which takes a function as a parameter (definitely relevant).
It takes the type (forall s. ST s a) as its only parameter. How is that more or less a function than anything else?
In the normal compositional model, (f . g) x = f (g x), you're conceptually invoking f on the result of g x (g is independent of f); here, you're lifting the function g x into the ST s a monad via f (g is dependent on f).
I don't think I am using any special lifting mechanism here. The "return" function does exploit the fact that ST s has a Monad instance, but I only used the "return" function for simplicity. The same thing happens if you construct a function that explicitly returns (forall s. ST s a) and use that instead of "return": Prelude Control.Monad.ST> :set -fglasgow-exts Prelude Control.Monad.ST> let {f :: a -> (forall s. ST s a); f x = return x} Prelude Control.Monad.ST> runST (f 42) 42 Prelude Control.Monad.ST> (runST . f) 42 <interactive>:1:9: Couldn't match expected type `forall s. ST s a' against inferred type `ST s a1' ... Here is another possible clue to what is happening. When I try to define that same function f using monomorphic syntax, it fails: Prelude Control.Monad.ST> let {f :: a -> (forall s. ST s a); f = return} <interactive>:1:39: Inferred type is less polymorphic than expected Quantified type variable `s' escapes Expected type: a -> forall s1. ST s1 a Inferred type: a -> ST s a In the expression: return In the definition of `f': f = return (Of course, the MR is not relevant here, because I am providing an explicit type signature.) _ _ ... ... _ _ -Yitz

The plot thickens... It seems that I can't even use STRefs. Something is really wrong here. Prelude Control.Monad.ST Data.STRef> runST $ do {r<-newSTRef 2; readSTRef r} <interactive>:1:8: Couldn't match expected type `forall s. ST s a' against inferred type `a1 b' In the second argument of `($)', namely `do r <- newSTRef 2 readSTRef r' In the expression: runST $ (do r <- newSTRef 2 readSTRef r) In the definition of `it': it = runST $ (do r <- newSTRef 2 readSTRef r)

On 01/01/07, Yitzchak Gale
It seems that I can't even use STRefs. Something is really wrong here.
Prelude Control.Monad.ST Data.STRef> runST $ do {r<-newSTRef 2; readSTRef r}
Again, this is due to section 7.4.8 [1] of the GHC user manual, which states that you can't instantiate a type variable with a type involving a forall. You're trying to unify the first parameter of ($) :: a -> b -> a with (forall s. ST s a -> a), which is illegal. Using parentheses works: runST (do r <- newSTRef 2; readSTRef r) However, I'm as much in the dark as you are as to _why_ this is illegal. [1]: http://haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#uni... -- -David House, dmhouse@gmail.com

Hi Yitzchak Gale wrote:
Can anyone explain the following behavior (GHCi 6.6):
I don't know if I can explain it entirely, or justify it properly, but I do have some idea what the issue is. Type inference with higher-ran types is weird. The primary reference is Practical type inference for arbitrary-rank types Simon Peyton Jones, Dimitrios Vytiniotis, Stephanie Weirich, and Mark Shields. To appear in the Journal of Functional Programming. http://research.microsoft.com/~simonpj/papers/higher-rank/index.htm 'The paper is long, but is strongly tutorial in style.' Back in the Hindley-Milner days, we knew exactly what polymorphism could happen where. All the free type variables were existential (hence specialisable); generalisation over free type variables happened at let. Unification was untroubled by issues of scope or skolem constants. The machine could always guess what your idea was because you weren't allowed to have interesting ideas. Now you can ask for polymorphism in funny places by writing non-H-M types explicitly. As in runST :: (forall s. ST s a) -> a When you apply runST, you create a non-let source of (compulsory) polymorphism. You get a new type variable a and a new type constant s, and the argument is checked against (ST s a). Let's look.
Prelude Control.Monad.ST> runST (return 42) 42
Can (return 42) have type ST s a, for all s and some a? Yes! Instantiate return's monad to (ST s) and a to the type of 42 (some Num thing? an Int default?). In made up System F, labelling specialisable unknowns with ? runST@?a (/\s. return@(ST s)@?a (42@?a)) such that Num ?a Now what's happening here?
Prelude Control.Monad.ST> (runST . return) 42
We're trying to type an application of (.) (.) :: (y -> z) -> (x -> y) -> (x -> z) We get two candidates for y, namely what runST wants (forall s. ST s a) and what return delivers (m b) and these must unify if the functions are to compose. Oops, they don't. The point, I guess, is that application in Haskell source code is no longer always translated exactly to application in System F. We don't just get (runST@?a) (return@?m@?b) such that (forall s. ST s ?a) = ?m ?b we get that extra /\s. inserted for us, thanks to the explicit request for it in the type of runST. The type of (.) makes no such request. Same goes for type of ($), so runST behaves differently from (runST $). It's a murky world. Happy New Year Conor

Conor and others are right; it's all to do with type inference. There is nothing wrong with the program you are writing, but it's hard to design a type inference algorithm that can figure out what you are doing. The culprit is that you want to instantiate a polymorphic function (here (.) or ($) in your examples) with a higer-rank polymorphic type (the type of runST, in this case). That requires impredicative polymorphism and while GHC now allows that, it only allows it when it's pretty obvious what is going on --- and sadly this case is not obvious enough. The system GHC uses is described in our paper http://research.microsoft.com/~simonpj/papers/boxy Simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of | Conor McBride | Sent: 01 January 2007 13:49 | To: haskell-cafe@haskell.org | Subject: Re: [Haskell-cafe] Composing functions with runST | | Hi | | Yitzchak Gale wrote: | > Can anyone explain the following behavior (GHCi 6.6): | | I don't know if I can explain it entirely, or justify it properly, but I | do have some idea what the issue is. Type inference with higher-ran | types is weird. The primary reference is | | Practical type inference for arbitrary-rank types | Simon Peyton Jones, Dimitrios Vytiniotis, Stephanie Weirich, and Mark | Shields. | To appear in the Journal of Functional Programming. | | http://research.microsoft.com/~simonpj/papers/higher-rank/index.htm | | 'The paper is long, but is strongly tutorial in style.' | | Back in the Hindley-Milner days, we knew exactly what polymorphism could | happen where. All the free type variables were existential (hence | specialisable); generalisation over free type variables happened at let. | Unification was untroubled by issues of scope or skolem constants. The | machine could always guess what your idea was because you weren't | allowed to have interesting ideas. | | Now you can ask for polymorphism in funny places by writing non-H-M | types explicitly. As in | | runST :: (forall s. ST s a) -> a | | When you apply runST, you create a non-let source of (compulsory) | polymorphism. You get a new type variable a and a new type constant s, | and the argument is checked against (ST s a). Let's look. | | > Prelude Control.Monad.ST> runST (return 42) | > 42 | | Can (return 42) have type ST s a, for all s and some a? Yes! Instantiate | return's monad to (ST s) and a to the type of 42 (some Num thing? an Int | default?). In made up System F, labelling specialisable unknowns with ? | | runST@?a (/\s. return@(ST s)@?a (42@?a)) such that Num ?a | | Now what's happening here? | | > Prelude Control.Monad.ST> (runST . return) 42 | | We're trying to type an application of (.) | | (.) :: (y -> z) -> (x -> y) -> (x -> z) | | We get two candidates for y, namely what runST wants (forall s. ST s a) | and what return delivers (m b) and these must unify if the functions are | to compose. Oops, they don't. | | The point, I guess, is that application in Haskell source code is no | longer always translated exactly to application in System F. We don't | just get | | (runST@?a) (return@?m@?b) such that (forall s. ST s ?a) = ?m ?b | | we get that extra /\s. inserted for us, thanks to the explicit request | for it in the type of runST. The type of (.) makes no such request. Same | goes for type of ($), so runST behaves differently from (runST $). | | It's a murky world. | | Happy New Year | | Conor | | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe

Simon Peyton-Jones wrote:
There is nothing wrong with the program you are writing, but it's hard to design a type inference algorithm that can figure out what you are doing.
Thank you for your response. What I was actually trying to do was this: It seems to me that a natural notion of a state transformer in the ST monad is the type: STRef s st -> ST s a That is in some sense intermediate between pure monadic state transformers on the one hand, and doing state completely within the ST or IO monad with STRefs or IORefs. The idea is that you could then write converter functions like this: stToState :: MonadState st m => (STRef s st -> ST s a) -> m a That would make it very convenient, for example, to use arrays inside a pure state monad. The type signatures above do ensure (as far as I can see) that the opacity of the ST state thread is not violated. But unfortunately, the protective shield in runST created by the higher-rank polymorphism is too thick. Any ideas? A better approach? Thanks, Yitz

On 1/1/07, Yitzchak Gale
stToState :: MonadState st m => (STRef s st -> ST s a) -> m a
That would make it very convenient, for example, to use arrays inside a pure state monad.
The type signatures above do ensure (as far as I can see) that the opacity of the ST state thread is not violated. But unfortunately, the protective shield in runST created by the higher-rank polymorphism is too thick.
Probably, stToState :: MonadState st m => (forall s. STRef s st -> ST s a) -> m a E.g. stToState :: MonadState st m => (forall s. STRef s st -> ST s a) -> m a stToState f = do s <- get let (x, s') = runST (do r <- newSTRef s x <- f r s' <- readSTRef r return (x, s')) put s' return x -- Best regerds, Tolik

Yitzchak Gale wrote:
It seems to me that a natural notion of a state transformer in the ST monad is the type:
STRef s st -> ST s a
Are there any useful functions of this type? I guess, your intention is that this "transformer" makes no other use of the ST monad than reading or writing a single variable. It seems, every such function better had a purely functional interface anyway, even if it makes use of runST internally.
stToState :: MonadState st m => (STRef s st -> ST s a) -> m a
The type signatures above do ensure (as far as I can see) that the opacity of the ST state thread is not violated.
I doubt that. The "transformer" you pass in could have captured references from a different state thread, which is exactly the problem the rank-2 type should prevent. I guess, the type signature you want is stToState :: MonadState st m => (forall s . STRef s st -> ST s a) -> m a which should actually work with runST and which would also be a bit pointless (see above). At least if I got rank-2 types correctly, which isn't guaranteed.
Any ideas? A better approach?
Uhm... use MonadState in the first place? The converse is comparatively easily accomplished: stateToST :: STRef s st -> State st a -> ST s a stateToST ref action = do (a, st') <- readSTRef ref >>= runState action writeSTRef ref st' return a -Udo -- "Human legalese is the schema language of our society." -- Tim Berners-Lee in http://w3.org/DesignIssues/Evolution

I wrote:
It seems to me that a natural notion of a state transformer in the ST monad is the type: STRef s st -> ST s a
Udo Stenzel wrote:
Are there any useful functions of this type?
Sure. Anything that can be written as a pure state transformer can be written this way, of course. In addition, you can use mutable arrays for speed. Here is a concrete example: Let's say you want to shuffle a large list randomly, within a larger application that lives inside some MTL monad stack. Among other things, your monad m satisfies (RandomGen g, MonadState g m), perhaps after a lift. Well, it turns out that using Data.Sequence or Data.IntMap to shuffle a list becomes prohibitive if you might have more than about 10^5 elements in your list. So in that case you will need to use a mutable array, and you now need ST. Combining ST and MTL can be messy, even in this simple case. You will probably write something with a type like RandomGen g => [a] -> g -> ST s ([a], g) apply runST (tiptoeing carefully around the paradoxes mentioned in this thread), and then build an MTL state thing out of it. Wouldn't it be nice if instead you could just write: shuffle :: (RandomGen g, MonadState g m) => [a] -> m [a] shuffle = stToState . shuffleST
I guess, your intention is that this "transformer" makes no other use of the ST monad than reading or writing a single variable.
Well, it can do whatever it wants inside, but it needs to expose any state that is shared externally. If that state is complex, you can use the same techniques that you would use for a State monad - either build the complexity into the state type using, say, records, or compose several transformers. In this case composition would be: STRef s st1 -> STRef s st2 -> ST s a
It seems, every such function better have a purely functional interface anyway,
Yes, that is the intended use.
even if it makes use of runST internally.
You would not need to, stToState would take care of runST.
stToState :: MonadState st m => (STRef s st -> ST s a) -> m a The type signatures above do ensure (as far as I can see) that the opacity of the ST state thread is not violated.
I doubt that. The "transformer" you pass in could have captured references from a different state thread, which is exactly the problem the rank-2 type should prevent.
Hmm, you're right.
I guess, the type signature you want is stToState :: MonadState st m => (forall s . STRef s st -> ST s a) -> m a
Or use some opaque type or monad and do something unsafe inside.
Any ideas? A better approach?
Uhm... use MonadState in the first place?
You mean use ST in the first place. Yes, but I want to avoid that.
The converse is comparatively easily accomplished...
Yes. Regards, Yitz

Yitzchak Gale wrote:
Here is a concrete example:
Let's say you want to shuffle a large list randomly, within a larger application that lives inside some MTL monad stack. Among other things, your monad m satisfies (RandomGen g, MonadState g m), perhaps after a lift.
Well, it turns out that using Data.Sequence or Data.IntMap to shuffle a list becomes prohibitive if you might have more than about 10^5 elements in your list. So in that case you will need to use a mutable array, and you now need ST.
Combining ST and MTL can be messy, even in this simple case. You will probably write something with a type like
RandomGen g => [a] -> g -> ST s ([a], g)
But why would you even want to do this? It's ugly and cumbersome. You'd plug a runST in there and get shuffle :: RandomGen g => [a] -> g -> ([a], g) or lift it into a state monad. Telling the world that you messed with imperative code inside is completely pointless, since the only thing you could possibly do with the result anyway is apply runST to it.
Wouldn't it be nice if instead you could just write:
shuffle :: (RandomGen g, MonadState g m) => [a] -> m [a] shuffle = stToState . shuffleST
It seems, what you really want is shuffleST :: RandomGen g => [a] -> StateT g ST [a] No need to stick the generator into a mutable variable. Maybe you even want a MonadST class, analogous to MonadIO.
Uhm... use MonadState in the first place?
You mean use ST in the first place.
No, I don't. -Udo

I wrote:
Combining ST and MTL can be messy, even in this simple case. You will probably write something with a type like RandomGen g => [a] -> g -> ST s ([a], g)
Udo Stenzel wrote:
But why would you even want to do this? It's ugly and cumbersome.
Yes indeed.
You'd plug a runST in there and get shuffle :: RandomGen g => [a] -> g -> ([a], g)
Yes. In fact, that is what I did in practice. As you say, the overall effect is ugly and cumbersome. And this is with only the simplest of stateful calculations. I shudder to think about what happens when things are more complex. That is why I am thinking that -
Wouldn't it be nice if instead you could just write:
shuffle :: (RandomGen g, MonadState g m) => [a] -> m [a] shuffle = stToState . shuffleST
and then just use that directly inside a calculation that is otherwise purely non-ST?
It seems, what you really want is shuffleST :: RandomGen g => [a] -> StateT g ST [a]
Actually, I tried that. It didn't help - it was just one more layer I had to peel away to get at the ST inside. There seems to be no way to avoid the fact that you think about state in two very different ways in these two monads. Every program is written in either one style or the other. Occasionally, you require an isolated use of the opposite style, and I am looking for ways of simplifying the resulting mess. "StateT st ST" and "MonadST" look like ways of combining the two, but in practice I find that they just seem to get in the way. I am starting to be convinced that the only way to write the function I want is by using unsafeRunST. Or type it as stToState :: MonadState st m => (st -> ST s (a, st)) -> m a and then write in the documentation that the user is require to write do r <- newSTRef x ... y <- readSTRef r return (z, y) by hand every time. Yuck. Am I missing something? -Yitz

Yitzchak Gale wrote:
Well, it turns out that using Data.Sequence or Data.IntMap to shuffle a list becomes prohibitive if you might have more than about 10^5 elements in your list. So in that case you will need to use a mutable array, and you now need ST. [..]
Wouldn't it be nice if instead you could just write:
shuffle :: (RandomGen g, MonadState g m) => [a] -> m [a] shuffle = stToState . shuffleST
and then just use that directly inside a calculation that is otherwise purely non-ST?
It seems, what you really want is shuffleST :: RandomGen g => [a] -> StateT g ST [a]
Actually, I tried that. It didn't help - it was just one more layer I had to peel away to get at the ST inside.
There seems to be no way to avoid the fact that you think about state in two very different ways in these two monads. Every program is written in either one style or the other. Occasionally, you require an isolated use of the opposite style, and I am looking for ways of simplifying the resulting mess. "StateT st ST" and "MonadST" look like ways of combining the two, but in practice I find that they just seem to get in the way.
I don't get what exactly you want. If you want to carry your state named "MyState" (f.i. type MyState = [Cards,Players]) around in a monad, you use "Control.Monad.State MyState". If (and only if) you have an algorithm (like depth-first search) that carries an array as state around (nodes already visited) and you know that this array is used in a single threaded fashion, it might be worth to update the array in place. For that, you use Control.Monad.ST and Data.Array.ST and you can be confident that the state carrying has been strictness analyzed and fine tuned to match the machine. In short, you get updates in place without selling your soul to IO, runST is your protection from evil and will keep you pure. ST does not really have more uses than this one (besides being the foundation for IO). For more info on ST, see http://research.microsoft.com/Users/simonpj/Papers/state-lasc.ps.gz Note that the you can now achieve the array thing as well with Data.Array.Diff. This is a purely functional interface to an array type that uses destructible updates internally and keeps a history to become persistent. However, I doubt that an array makes a difference over Data.IntMap for all but the most special cases.
I am starting to be convinced that the only way to write the function I want is by using unsafeRunST. Or type it as
stToState :: MonadState st m => (st -> ST s (a, st)) -> m a
and then write in the documentation that the user is require to write
do r <- newSTRef x ... y <- readSTRef r return (z, y)
by hand every time. Yuck.
If the programmer needs to adhere to a policy, the type system may well enforce it for him. No unsafeRunST. It's far better to struggle with the safety device than to discover the hard way that running without it will directly lead into the debugging hell. Regards, apfelmus

I wrote:
Am I missing something?
Yes! In reality, I do not need unsafeSTRef for this at all, using a type suggested earlier by Udo: stToState :: MonadState st m => (forall s. STRef s st -> ST s a) -> m a stToState f = do s <- get let (y, s') = runST (stm f s) put s' return y where stm f s = do r <- newSTRef s y <- f r s' <- readSTRef r return (y, s') This works! Thanks, Udo! -Yitz

Simon Peyton-Jones wrote:
Conor and others are right; it's all to do with type inference. There is nothing wrong with the program you are writing, but it's hard to design a type inference algorithm that can figure out what you are doing.
The culprit is that you want to instantiate a polymorphic function (here (.) or ($) in your examples) with a higer-rank polymorphic type (the type of runST, in this case). That requires impredicative polymorphism and while GHC now allows that, it only allows it when it's pretty obvious what is going on --- and sadly this case is not obvious enough.
From a friendliness-to-newbies point of view, these error messages are a
I don't know enough type theory to suggest a specific patch, but I hope a future version of GHC can do the right thing for (.) and ($) in this situation (and possibly for other functions that simply rearrange their arguments, like flip). tremendous wart. I've been on haskell-cafe for a little over three months and seen postings from three people who were tripped up by this (the first of them was myself). So I can't just tell someone who's just starting to learn Haskell that "f $ g y" is equivalent to "f (g y)"; I have to say "those two are *almost always* equivalent, but if you use $ and the compiler complains about not being able to match the expected and the inferred type and a type signature in the error message has the word 'forall', try rewriting that expression without the $ and see if it compiles". Eeeww.

On 03/01/07, Seth Gordon
So I can't just tell someone who's just starting to learn Haskell that "f $ g y" is equivalent to "f (g y)"; I have to say "those two are *almost always* equivalent, but if you use $ and the compiler complains about not being able to match the expected and the inferred type and a type signature in the error message has the word 'forall', try rewriting that expression without the $ and see if it compiles". Eeeww.
Why would someone just starting to learn Haskell be using ST? The canonical tutorial structure is to start with the pure stuff and only introduce the (more complicated!) impure stuff (ST, IORefs, etc.) in an 'advanced techniques' or similar section. -- -David House, dmhouse@gmail.com

David House wrote:
So I can't just tell someone who's just starting to learn Haskell that "f $ g y" is equivalent to "f (g y)"; I have to say "those two are *almost always* equivalent, but if you use $ and the compiler complains about not being able to match the expected and the inferred type and a type signature in the error message has the word 'forall', try rewriting that expression without the $ and see if it compiles". Eeeww.
Why would someone just starting to learn Haskell be using ST? The canonical tutorial structure is to start with the pure stuff and only introduce the (more complicated!) impure stuff (ST, IORefs, etc.) in an 'advanced techniques' or similar section.
I (and one other person on this list) ran into this issue when I was trying to use takusen to make Haskell talk to a RDBMS. You obviously need to learn advanced techniques to *implement* such a thing, but you shouldn't need advanced knowledge to *use a library* that happens to use higher-rank polymorphic types in its API. There are many routes to fluency in a language, and not everybody is suitable for the route of "here are the axioms underlying the language and the simplest code that applies them; after you thoroughly understand those, we'll show you how to make something practical". Some of us prefer the route of "here are some examples of how to get practical things done; after you're comfortable with them, we'll show you the theory that underlies them". Actually, I suspect that *most* of us prefer the second route. Set theory is closer to the theoretical foundations of mathematics than arithmetic, but when elementary schools tried teaching kids set theory, it didn't work out so well.

On 1/3/07, Seth Gordon
David House wrote:
So I can't just tell someone who's just starting to learn Haskell that "f $ g y" is equivalent to "f (g y)"; I have to say "those two are *almost always* equivalent, but if you use $ and the compiler complains about not being able to match the expected and the inferred type and a type signature in the error message has the word 'forall', try rewriting that expression without the $ and see if it compiles". Eeeww.
Why would someone just starting to learn Haskell be using ST? The canonical tutorial structure is to start with the pure stuff and only introduce the (more complicated!) impure stuff (ST, IORefs, etc.) in an 'advanced techniques' or similar section.
I (and one other person on this list) ran into this issue when I was trying to use takusen to make Haskell talk to a RDBMS. You obviously need to learn advanced techniques to *implement* such a thing, but you shouldn't need advanced knowledge to *use a library* that happens to use higher-rank polymorphic types in its API.
That other person was me, and I agree entirely. I have a little sample project, using databases and concurrency, which I wanted to rewrite in Haskell, as a learning exercise. I hit exactly this issue when simply trying out some sample code, and my reaction was very much one of irritation, frustration and confusion. One of the nice things about Haskell, coming to it from an imperative POV, is that monads can be thought of a little like first-class composable "statement blocks". When I understood that, I had a real "hey, that's neat!" reaction. One of the nasty things about Haskell (at my level of experience) is that your nice helpful intuitions about monads can break down into real confusion when you hit complex monads, monad transformers and the like - *and you hit them quite early in the APIs of some libraries*! It's not a big deal, but it's a bit offputting for a newcomer. Paul.

Paul Moore wrote:
...your nice helpful intuitions about monads can break down into real confusion when you hit complex monads, monad transformers and the like - *and you hit them quite early in the APIs of some libraries*!
I don't think that is a problem with the design of the libraries. It is a problem with the documentation. Almost all library documentation could be written so that any user could easily use the library in a simple, practical, straightforward way. I am not saying that it would be easy, but it could be done. Nowadays, that type of documentation is taken for granted for every popular programming language. -Yitz

On 1/3/07, David House
On 03/01/07, Seth Gordon
wrote: So I can't just tell someone who's just starting to learn Haskell that "f $ g y" is equivalent to "f (g y)"; I have to say "those two are *almost always* equivalent, but if you use $ and the compiler complains about not being able to match the expected and the inferred type and a type signature in the error message has the word 'forall', try rewriting that expression without the $ and see if it compiles". Eeeww.
Why would someone just starting to learn Haskell be using ST? The canonical tutorial structure is to start with the pure stuff and only introduce the (more complicated!) impure stuff (ST, IORefs, etc.) in an 'advanced techniques' or similar section.
(slightly OT) It's true that this is the typical way of learning Haskell, but I for one think it's a bad way of learning Haskell. Very few real world programs get by without the "impure" stuff, so if you give the newbie the impression that it isn't there (by postponing it) there's a chance he'll run into a situation where he needs it before it's been even mentioned (queue newbie going "bah, academic language" and switching to C++). I find that the Haskell introductions I like the most are the ones that accompany papers about STM and such. I.e. ones which have to teach the reader about the basics of Haskell IO, but doesn't have enough space to start with the pretty stuff. Mix that with some actual comutations to show off some pretty stuff and you'll have a newbie who is both excited about the cool looking features of the pure aspects of Haskell, but completely aware of the fact that you can do impure stuff as well. Oh yeah, I agree that the relationship between ($) and (.) is a bit ugly from the user's perspective. It may have very good reasons, but I'd prefer consistency towards the user (i.e. spot when someone is using ($) with higher ranked types and do rewriting) rather than consistency towards the compiler. -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Hi,
It's true that this is the typical way of learning Haskell, but I for one think it's a bad way of learning Haskell. Very few real world programs get by without the "impure" stuff, so if you give the newbie the impression that it isn't there (by postponing it) there's a chance he'll run into a situation where he needs it before it's been even mentioned (queue newbie going "bah, academic language" and switching to C++).
I agree. It also confuses matters when the newbie is suddenly given a library of IO code to use -- but told to ignore it -- they suddenly start wondering why it is so difficult to do anything "useful" in Haskell. A consequence of which seems that the student becomes afraid (and ignorant) of Haskell.
I find that the Haskell introductions I like the most are the ones that accompany papers about STM and such. I.e. ones which have to teach the reader about the basics of Haskell IO, but doesn't have enough space to start with the pretty stuff.
I agree with this also. I don't think it is a difficult feat teaching an absolute beginner how do some some basic stuff with the IO monad. This shows straight away that haskell can do some useful stuff other than adding numbers together in Hugs.
Mix that with some actual comutations to show off some pretty stuff and you'll have a newbie who is both excited about the cool looking features of the pure aspects of Haskell, but completely aware of the fact that you can do impure stuff as well.
Yes, I wish this approach was applied much more often. Semi-related to this: I taught an algorithms and data structures class last term. In one of the classes the students were given an equation to solve and they were frantically typing it into their calculators, replacing the variable parameters with numbers. I told them they could all finish the class in 5 minutes if they used Haskell. Type the equation as it is and use higher-order functions to work out the parameters. The look of horror on the student's faces when I mentioned the 'H' word was priceless. However, they were all prepared to spend 50 minutes writing a Java program which would have the same effect. Chris.

It's true that this is the typical way of learning Haskell, but I for one think it's a bad way of learning Haskell. Very few real world programs get by without the "impure" stuff, so if you give the newbie the impression that it isn't there (by postponing it) there's a chance he'll run into a situation where he needs it before it's been even mentioned (queue newbie going "bah, academic language" and switching to C++).
On the contrary, I think it's an excellent way of learning Haskell. I'm writing a lot of useful Haskell code with only one IO action (interact). I don't think I could reasonably construct an introductory problem that couldn't be solved with it, and I haven't yet found an application for which I've needed more. I think it's destructive to teach people "we have a wonderful new paradigm of programming that solves all sorts of problems, but all we're going to use it for is doing what we did with C++ anyway". That's just my 2¢ -- I like Haskell specifically because I don't have to do things in order and I don't have to do things in an imperative style, I would love for more people to be taught about this wonderful thing. Bob

Hi
On the contrary, I think it's an excellent way of learning Haskell. I'm writing a lot of useful Haskell code with only one IO action (interact). I don't think I could reasonably construct an introductory problem that couldn't be solved with it, and I haven't yet found an application for which I've needed more.
I think interact is a bit ugly. Most introductory problems are "take a small amount of data, do something". In that case using Hugs/GHCi with :main arguments to give in the arguments, getArgs to read them and putStrLn to show the results is a very beautiful and does about all that you need. Very few programs are actually interactive - if they are they should usually get a GUI. As for beginner issues with rank-2 types, I've been learning Haskell for years now, and have never felt the need for a rank-2 type. If the interface for some feature requires rank-2 types I'd call that an abstraction leak in most cases. It certainly means that you can't properly Hoogle for it, can't compile it with Yhc, can't do full type inference etc. Thanks Neil

On 1/3/07, Neil Mitchell
As for beginner issues with rank-2 types, I've been learning Haskell for years now, and have never felt the need for a rank-2 type. If the interface for some feature requires rank-2 types I'd call that an abstraction leak in most cases. It certainly means that you can't properly Hoogle for it, can't compile it with Yhc, can't do full type inference etc.
That may well be true. Something I forgot to mention in my previous posting was that I'm not 100% convinced that the issue I hit with Takusen isn't a problem with the library - I find it very hard to read or understand some parts of the library documentation, basically because the types seem so complex. My intuition says that reading a database is logically similar to reading a file, so types like doQuery :: (Statement stmt sess q, QueryIteratee (DBM mark sess) q i seed b, IQuery q sess b) => stmt -> i -> seed -> DBM mark sess seed look pretty baffling to me - and don't match my intuition that main = do withSession (connect "user" "password" "server") $ do -- simple query, returning reversed list of rows. r <- doQuery (sql "select a, b, c from x") query1Iteratee [] liftIO $ putStrLn $ show r otherActions session is "basically I/O". (Oh, by the way - that "$" on the withSession line is the one that caused the error which started this thread...) Paul.

Seth Gordon wrote:
From a friendliness-to-newbies point of view, these error messages are a tremendous wart... Eeeww.
Neil Mitchell wrote:
If the interface for some feature requires rank-2 types I'd call that an abstraction leak in most cases.
As the original poster of this thread, the one who was bitten this time, let me point out that the use of rank-2 polymorphism here is actually really nice. It provides a strong safety guarantee for the ST monad at *compile time*. But the protection is a bit heavy-handed, so there are some painful side effects that need to be addressed. One is the confusion caused by the strange semantics to those not familiar with the theory. That should be fixed by simple, prominant, task-oriented documentation. ("You must always provide runST with an argument. So, for example, you cannot write "runST $" or "runST .".) And yes, perhaps the error messages in GHC could be improved for newbies, but that was never intended to be the strong point of GHC. I think Hugs is fine here. The other is awkwardness in extending the capabilites of ST. For that, I would propose that the function "unsafeRunST" be added to the library. Of course, if there is some way to improve both of these situations by compilers relaxing the restrictions on rank-2 types somewhat, that would be great. But that is probably for the future. -Yitz

Hello Yitzchak, Thursday, January 4, 2007, 12:25:41 PM, you wrote:
The other is awkwardness in extending the capabilites of ST. For that, I would propose that the function "unsafeRunST" be added to the library.
this function exists, but named unsafeIOtoST. IO and ST is exactly the same things, the only difference that foreign imports may be marked as IO operations but both ST ones. as a result, ST is restricted to a few standard operations that guarantees to bo be mutually transparent for consumers of runST. when one goes to extend ST functionality, unsafeIOtoST is used. for 3xample, in Hugs it is used to convert peek/poke IO operations into STUArray implementation. except for compile-time type sugar, there is no difference between those two type constructors. unsafeIOtoST is like liftIO: unsafeIOtoST :: IO a -> ST s a -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat, I wrote:
One is the confusion caused by the strange semantics to those not familiar with the theory...
Like me, of course.
The other is awkwardness in extending the capabilites of ST. For that, I would propose that the function "unsafeRunST" be added to the library.
Bulat Ziganshin wrote:
this function exists, but named unsafeIOtoST.
That wasn't what I had in mind, because it forces the thread parameter to take the specific value RealWorld. But I am not sure anymore that it is needed. It turned out that my case was just another instance of the first kind of awkwardness. So I no longer have any evidence that the second kind of awkwardness exists. So I withdraw my proposal. Thanks, Yitz

Hello Yitzchak, Thursday, January 4, 2007, 4:25:06 PM, you wrote:
The other is awkwardness in extending the capabilites of ST. For that, I would propose that the function "unsafeRunST" be added to the library.
Bulat Ziganshin wrote:
this function exists, but named unsafeIOtoST.
That wasn't what I had in mind, because it forces the thread parameter to take the specific value RealWorld.
this parameter don't have any "physical" meaning at runtime. i still think that it is just what you mean. what other meaning may have unsafeRunST operation? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Neil Mitchell wrote:
As for beginner issues with rank-2 types, I've been learning Haskell for years now, and have never felt the need for a rank-2 type. If the interface for some feature requires rank-2 types I'd call that an abstraction leak in most cases. It certainly means that you can't properly Hoogle for it, can't compile it with Yhc, can't do full type inference etc.
I think that the term "abstraction leak" is too harsh. In some sense, you may as well call "strong typing" an "abstraction leak" because one can do the stuff as well in a dynamic typed language and adding strong typing means that you can't compile it with current compilers, you need to implement type checking/inference etc. Of course, this analogy has flaws as higher rank types go to the edge of computability whereas strong typing can be implemented. Concerning interfaces, higher rank types offer crucial static checking that cannot be achieved without them. The prominent example is ST. The next example is the parsing library "frisby". In both cases, it would be easy to wrack havoc in case the interface would not use higher rank types. The same analogy as above applies: one uses strong typing because one does not want to wreak havoc. I would not call this an "abstraction leak". Concerning implementation, higher rank types are even more widespread: almost everything involving continuations needs them: ReadP, Exceptions (as opposed to Either), deforestation etc. In fact, it is quite possible to throw away algebraic data types altogether and build everything you need with higher rank types. A prominent example is [a] ~= (forall b . (a -> b -> b) -> b -> b) ~= (forall b . (Maybe (a,b) -> b) -> b) The denotational semantics do not change, but the time and space behavior is much different. Perhaps the above remarks misinterpret your statement and you meant "abstraction leak" in the sense that, because higher rank types are available, the interface author used them without thinking whether the same effect can be achieved in ordinary Haskell. Alas, such problems are not tied to higher rank types: proper interface design is an art and does not come for free, not to mention interface documentation[1]. One could easily berserk: why does this library use String and doesn't abstract it with a type class? Why does that interface only provide IO, why isn't this available as a library of pure functions? What do these obviously crappy semantics mean? In this case, higher rank types are a symptom, not the problem. If one wants to cure the problem by disallowing the symptom, then I suggest to also erase the symptom IO. Thoroughly. Of course, the drawbacks of higher rank types you mentioned remain. In the case of "hoogleability", I'm confident that it is possible to implement them, it's only that someone has to think hard about it. Implementing higher rank types in YHC is even harder but not impossible. Sure, type inference is the most difficult thing, and one has to accept glitches and drawbacks to make it work. Compared to these difficulties, I think that the remark
So I can't just tell someone who's just starting to learn Haskell that "f $ g y" is equivalent to "f (g y)"; I have to say "those two are *almost always* equivalent, but if you use $ and the compiler complains about not being able to match the expected and the inferred type and a type signature in the error message has the word 'forall', try rewriting that expression without the $ and see if it compiles". Eeeww.
posted in this tread is too harsh. That's life, every language has its flaws and glitches: parts of the layout rule, pattern guards, I want a better records system, views, generic programming, etc. But, when code has to be finished, those glitches or annoying things are best countered with a shrug: they are not life-threatening. A programming language with nonexistent type system and ugly semantics is. And much to our joy, Haskell is far from this. In that sense, dear reader of this post, just rewrite that expression without $ and see if it compiles. The complier authors don't want to annoy you, it's just that the exact reasons why this cannot yet be put to work are damn hard. You are encouraged to learn about System F to get a grasp of what is going on, but spending this one $ will be much cheaper. Regards, apfelmus [1] Concerning library documentation, I think that literate Haskell sources have the drawback that they are either tied to TeX (\begin{code}..\end{code}) or that every line has to start with a '>'. I'd suggest to add a <code>..</code> or something else. The point is that while (La)TeX can be cranked up to a publishing system, it is not suited for many tasks such as media-dependent processing. TeX is a macro language, not a structured document type. And for the strongly typed Haskell programmer used to referential transparency, macros are a nightmare.

Hi,
On the contrary, I think it's an excellent way of learning Haskell. I'm writing a lot of useful Haskell code with only one IO action (interact). I don't think I could reasonably construct an introductory problem that couldn't be solved with it, and I haven't yet found an application for which I've needed more. I think it's destructive to teach people "we have a wonderful new paradigm of programming that solves all sorts of problems, but all we're going to use it for is doing what we did with C++ anyway".
Yes, but the point is most students have already been poisoned with C++ (or Java). They don't see the point in Haskell becuase they can't see the wood for the trees. The only way to get them interested in Haskell in the first place is to make it look vaguely like C++ (or Java) -- it's like coercing a Donkey with a carrot. Once they are interested - show them there is a lot more to Haskell than imperative-style behaviour, that way they may also see the elegence of purely functional programming.
That's just my 2¢ -- I like Haskell specifically because I don't have to do things in order and I don't have to do things in an imperative style, I would love for more people to be taught about this wonderful thing.
So would I. But in reality it just doesn't seem to work like that. Chris.
participants (16)
-
Anatoly Zaretsky
-
apfelmus@quantentunnel.de
-
Brandon S. Allbery KF8NH
-
Brian Hulley
-
Bulat Ziganshin
-
C.M.Brown
-
Conor McBride
-
David House
-
Neil Mitchell
-
Paul Moore
-
Sebastian Sylvan
-
Seth Gordon
-
Simon Peyton-Jones
-
Thomas Davie
-
Udo Stenzel
-
Yitzchak Gale