[Haskell-cafe] Should "do 1" compile

Simon Peyton-Jones simonpj at microsoft.com
Thu May 24 03:38:15 EDT 2007


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 at haskell.org [mailto:haskell-cafe-bounces at 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 at haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list