#4284: Adding parentheses introduces type error
---------------------------------+------------------------------------------
Reporter: jpbernardy | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 6.12.3 | Keywords: higher-rank polymorphism
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: GHC rejects valid program
---------------------------------+------------------------------------------
{{{
{-# LANGUAGE RankNTypes #-}
module Test where
foo :: () -> forall b. b
foo = undefined
works = id foo
fails = (id) foo
-- works type checks, but fails fails with the following error
-- message:
--
-- Cannot match a monotype with `() -> forall b. b'
-- Probable cause: `foo' is applied to too few arguments
-- In the first argument of `(id)', namely `foo'
-- In the expression: (id) foo
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4284>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs