
Hi, As discussed on #haskell, the following code: ---------------- module Foo where foo = do (1 :: Int) ---------------- Compiles fine on Yhc, but doesn't on Hugs and GHC. GHC: Couldn't match expected type `t t1' against inferred type `Int' In the expression: (1 :: Int) In the expression: do (1 :: Int) In the definition of `foo': foo = do (1 :: Int) Hugs: ERROR "test.hs":4 - Type error in final generator *** Term : 1 *** Type : Int *** Does not match : a b So the question is, who is right? Where do the bugs need filing? Does this issue need clarifying for Haskell' ? Thanks Neil

On 23/05/07, Neil Mitchell
As discussed on #haskell, the following code:
---------------- module Foo where foo = do (1 :: Int) ----------------
Compiles fine on Yhc, but doesn't on Hugs and GHC.
Why should it compile? Expressions in a do-block have to have the type m a for some monad m, don't they? -- -David House, dmhouse@gmail.com

On 23/05/07, David House
Why should it compile? Expressions in a do-block have to have the type m a for some monad m, don't they?
Further developments on #haskell:

Neil,
As discussed on #haskell, the following code:
---------------- module Foo where foo = do (1 :: Int) ----------------
Compiles fine on Yhc, but doesn't on Hugs and GHC.
So the question is, who is right? Where do the bugs need filing? Does this issue need clarifying for Haskell' ?
Well, the Report (Sec. 3.14) states that, for any expression e, do {e} should be translated to e. So foo = do (1 :: Int} should be translated to foo = (1 :: Int) which seems type correct to me. However, although the Report does not state it explicitly, I think it was the intention of the language designers to always associate a do- block with a particular monad. So, maybe this should be stated (in some form) in the Report for Haskell'. Cheers, Stefan

Hi
foo = do (1 :: Int)
While intuitively this should be disallowed, it seems a pity that desugaring couldn't be totally separated from typechecking. Hmm.
You can always desugar as: do x ==> return () >> x Although then you are relying on the Monad laws more than you possibly should. You could also have: monady :: Monad m => m a -> m a monady x = x do x ==> monady x Then you are relying on an additional function that doesn't currently exist. Thanks Neil

On Wed, 23 May 2007 19:54:27 +0100
"Neil Mitchell"
Hi
foo = do (1 :: Int)
While intuitively this should be disallowed, it seems a pity that desugaring couldn't be totally separated from typechecking. Hmm.
You can always desugar as:
do x ==> return () >> x
Although then you are relying on the Monad laws more than you possibly should. You could also have:
monady :: Monad m => m a -> m a monady x = x
do x ==> monady x
How about: do x ==> (x :: Monad m => m a) Or even: do x ==> (asTypeOf x (return ())) Cheers, Spencer Janssen

Spencer,
How about:
do x ==> (x :: Monad m => m a)
That one does not do it, because now you demand x to be polymorphic in all monad types m and all monad-element types a, which I guess restricts x to undefined and return undefined and combinations thereof, glued together by monadic binds.
do x ==> (asTypeOf x (return ()))
Again, no, for now you restrict the element type to () and, hence, you preclude, for instance, do return False Cheers, Stefan

While we're on the topic of coupling/cohesion of types and syntactic
sugar (and because sometimes problems are made easier by generalizing
them), I have a question.
What is the rationale for disallowing the following code?
main = print "Type 'True' on three lines or I will quit." >> foo
foo = [ () | line1 <- readLn, line1, line2 <- readLn, line2, line3 <-
readLn, line3]
Obviously this example is contrived, and you'd never want to use the
list comprehension syntax for the IO monad. But you might want to for,
say, the probability monad. Isn't that enough reason enough to
decouple the sugar from the typing? (Though I agree with Claus that
cryptic error messages are a bad thing.)
On 5/23/07, Stefan Holdermans
Spencer,
How about:
do x ==> (x :: Monad m => m a)
That one does not do it, because now you demand x to be polymorphic in all monad types m and all monad-element types a, which I guess restricts x to
undefined
and
return undefined
and combinations thereof, glued together by monadic binds.
do x ==> (asTypeOf x (return ()))
Again, no, for now you restrict the element type to () and, hence, you preclude, for instance,
do return False
Cheers,
Stefan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Joshua,
Obviously this example is contrived, and you'd never want to use the list comprehension syntax for the IO monad. But you might want to for, say, the probability monad. Isn't that enough reason enough to decouple the sugar from the typing? (Though I agree with Claus that cryptic error messages are a bad thing.)
If I remember correctly, prior to Haskell 98, list comprehensions came in this general form, i.e., as monad comprehensions. I am not sure why they were restricted to lists, but I guess it had to do unresolved top-level overloading arising in a lot of programs that used monad comprehensions---and, hence, a lot of type annotations in a lot of run-of-the-mill comprehensions over lists. Cheers, Stefan

if you want to go down that route: Prelude> let monadic m = m `asTypeOf` return undefined Prelude> :t monadic undefined monadic undefined :: (Monad m) => m a Prelude> :t monadic $ undefined >> return () monadic $ undefined >> return () :: (Monad m) => m () Prelude> :t monadic $ undefined >> [ () ] monadic $ undefined >> [ () ] :: [()] Prelude> :t monadic $ undefined >> [ undefined ] monadic $ undefined >> [ undefined ] :: [a] btw, ghc says: Prelude> :t do undefined do undefined :: t t1 while hugs says: Hugs> :t do undefined do {...} :: Monad a => a b claus

2007/5/23, Ian Lynagh
On Wed, May 23, 2007 at 06:27:32PM +0100, Neil Mitchell wrote:
foo = do (1 :: Int)
While intuitively this should be disallowed, it seems a pity that desugaring couldn't be totally separated from typechecking. Hmm.
You *could* desugar it to foo = (id :: Monad m => m a -> m a) (1 :: Int) - Benja

On Wed, 23 May 2007, Ian Lynagh wrote:
On Wed, May 23, 2007 at 06:27:32PM +0100, Neil Mitchell wrote:
foo = do (1 :: Int)
While intuitively this should be disallowed, it seems a pity that desugaring couldn't be totally separated from typechecking. Hmm.
Disallow it by beating people around the head if they do it without good cause? Besides, this way round probably opens up a nice trick or two for people gutting the prelude who want to use the syntax for something slightly more general. -- flippa@flippac.org 'In Ankh-Morpork even the shit have a street to itself... Truly this is a land of opportunity.' - Detritus, Men at Arms

foo = do (1 :: Int)
While intuitively this should be disallowed, it seems a pity that desugaring couldn't be totally separated from typechecking. Hmm.
or perhaps not. while a type-free desugaring, followed by type-checking, seems more modular, i'd rather see any type errors in terms of the sugared syntax. which kind of rules out total separation, doesn't it? 'do {e}' --> 'e' could be interpreted in a type-free sense, but 'do {e1;e2}' --> 'e1 >> e2' already exposes the type constraints. i prefer to think of it as a kind of eta-expansion: i don't know the type of 'e', but i do know something about the type of '\x->e x' and i would like to know something about the type of 'do {e}'. monad laws have the same issue, btw: 'return () >> e' --> 'e' only makes sense for monadic 'e' claus

The Haskell report describes many contructs by translation to a simpler language. This translation defines the dynamic semantics but does it define the static semantics (ie. type system)? GHC type-checks the *source* code of your Haskell program, before any desugaring or translation. Looking at source code it'd be silly to say that do e had any type (including Int), whereas do { ...; e } must have a monadic type. Try writing the typing rules for do-notation! So I think it's a bug in the Report. To fix it, you could try do e = e >>= return Which would still respect the dynamic semantics (albeit with a gratuitous extra >>=) but would now have the right static semantics Simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Neil | Mitchell | Sent: 23 May 2007 18:28 | To: Haskell Café | Subject: [Haskell-cafe] Should "do 1" compile | | Hi, | | As discussed on #haskell, the following code: | | ---------------- | module Foo where | foo = do (1 :: Int) | ---------------- | | Compiles fine on Yhc, but doesn't on Hugs and GHC. | | GHC: | Couldn't match expected type `t t1' against inferred type `Int' | In the expression: (1 :: Int) | In the expression: do (1 :: Int) | In the definition of `foo': foo = do (1 :: Int) | | Hugs: | ERROR "test.hs":4 - Type error in final generator | *** Term : 1 | *** Type : Int | *** Does not match : a b | | So the question is, who is right? Where do the bugs need filing? Does | this issue need clarifying for Haskell' ? | | Thanks | | Neil | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, May 24, 2007 at 08:38:15AM +0100, Simon Peyton-Jones wrote:
So I think it's a bug in the Report. To fix it, you could try
do e = e >>= return
Which would still respect the dynamic semantics (albeit with a gratuitous extra >>=) but would now have the right static semantics
Except that this monad law does not always hold. Perhaps do e = e `asTypeOf` return undefined
participants (11)
-
Benja Fallenstein
-
Claus Reinke
-
David House
-
Ian Lynagh
-
Joshua Ball
-
Neil Mitchell
-
Philippa Cowderoy
-
Ross Paterson
-
Simon Peyton-Jones
-
Spencer Janssen
-
Stefan Holdermans