
#15033: ScopedTypeVariable and RankNTypes don't scope throughout function body -------------------------------------+------------------------------------- Reporter: parsonsmatt | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm writing a DSL that uses `TypeApplications`, and I noticed the following weird behavior with `ScopedTypeVariables` and `AllowAmbiguousTypes`. You can define a function that takes the `TypeApplication` after a parameter: {{{#!hs lol :: String -> forall a. IO () lol str = putStrLn str main = lol "hello" @Int }}} This works! Unfortunately, it is impossible to *refer* to that `a` type variable in the body of the function. It is as though `ScopedTypeVariables` were not turned on. A reproduction (tested on 8.2.2 and 8.4.1): {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} import Data.Typeable import Data.Proxy no :: String -> forall x. Typeable x => IO () no _ = print (typeRep (Proxy :: Proxy x)) yes :: forall x. Typeable x => String -> IO () yes _ = print (typeRep (Proxy :: Proxy x)) }}} `no` fails to compile, saying that `x` type variable is not in scope. `yes` works just fine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15033 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler