[GHC] #15033: ScopedTypeVariable and RankNTypes don't scope throughout function body

#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

#15033: ScopedTypeVariable and RankNTypes don't scope throughout function body -------------------------------------+------------------------------------- Reporter: parsonsmatt | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => invalid Comment: This is by design. If you want to make a type variable scope over the body of a function, it must be quantified by the outermost, syntactically visible `forall` of the type signature. Per the [http://git.haskell.org/ghc.git/blob/fea04defa64871caab6339ff3fc5511a272f37c7... users' guide]:
The type variable is quantified by the single, syntactically visible, outermost `forall` of the type signature. For example, GHC will reject all of the following examples:
{{{#!hs f1 :: forall a. forall b. a -> [b] -> [b] f1 _ (x:xs) = xs ++ [ x :: b ]
f2 :: forall a. a -> forall b. [b] -> [b] f2 _ (x:xs) = xs ++ [ x :: b ]
type Foo = forall b. [b] -> [b]
f3 :: Foo f3 (x:xs) = xs ++ [ x :: b ] }}}
In `f1` and `f2`, the type variable `b` is not quantified by the outermost `forall`, so it is not in scope over the bodies of the functions. Neither is `b` in scope over the body of `f3`, as the `forall` is tucked underneath the `Foo` type synonym.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15033#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC