#6069: Rank 2 Polymorphism Compile Error
--------------------------+-------------------------------------------------
Reporter: clinton | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.4.1 | Keywords:
Os: Windows | Architecture: x86_64 (amd64)
Failure: None/Unknown | Testcase:
Blockedby: | Blocking:
Related: |
--------------------------+-------------------------------------------------
Not sure if this is a bug, perhaps this should be a feature request.
Given the following code:
{{{
{-# LANGUAGE Rank2Types #-}
import Control.Monad.ST
import Data.STRef
fourty_two :: forall s. ST s Int
fourty_two = do
x <- newSTRef (42::Int)
readSTRef x
main = (print . runST) fourty_two -- (1)
main = (print . runST) $ fourty_two -- (2)
main = ((print . runST) $) fourty_two -- (3)
}}}
(1) and (3) compile successfully, but (2) does not. I'm not sure why this
is the case.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6069>
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