new qualified operators

Hi, seeing http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/syntax-extns.html#ne... Could you add: "Spaces are not allowed in new qualified operators!" For {-# LANGUAGE NewQualifiedOperators #-} f1 = (+) f2 = ( +) f3 = (+ ) f4 = Prelude.(+) f5 = Prelude.( +) f6 = Prelude.(+ ) f1 - f4 are ok, but f5 and f6 are rejected by ghc-6.12.3 with: Not in scope: data constructor `Prelude' So ghc seems to see a composition and: data T = T (Int -> Int) f = T.( +) goes through, whereas f = T.(+) reports: Not in scope: `T.+' Note the old qualifiation in the error message. Christian

On 15/07/2010 13:46, Christian Maeder wrote:
Hi,
seeing http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/syntax-extns.html#ne...
Could you add:
"Spaces are not allowed in new qualified operators!"
For
{-# LANGUAGE NewQualifiedOperators #-}
f1 = (+) f2 = ( +) f3 = (+ ) f4 = Prelude.(+) f5 = Prelude.( +) f6 = Prelude.(+ )
f1 - f4 are ok, but f5 and f6 are rejected by ghc-6.12.3 with:
Not in scope: data constructor `Prelude'
Yes, it's really a bug, but it was difficult to make this consistent while retaining support for the old syntax. I expect that we'll deprecate this extension anyway, since the Haskell 2010 committee rejected it as a proposal. Cheers, Simon
participants (2)
-
Christian Maeder
-
Simon Marlow