
#14288: ScopedTypeVariables with nexted foralls broken since 8.0.2 -------------------------------------+------------------------------------- Reporter: | Owner: (none) MikolajKonarski | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Type checker) | Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: GHC rejects (amd64) | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following example fails in 8.2.1 and 8.0.2. Works fine in 7.10.3. If that's intended (that only the first forall has extended scope), I didn't find any mention of that in GHC manual. The two commented out variants work fine in all. {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} main :: IO () main = do -- let f :: forall a ref. ref () -> () -- let f :: forall ref. forall a. ref () -> () let f :: forall a. forall ref. ref () -> () f x = let r :: ref () r = x in () return $ f (Just ()) }}} The error (the same in 8.2.1 and 8.0.2) is: {{{#!hs $ ghc --make forall.hs [1 of 1] Compiling Main ( forall.hs, forall.o ) forall.hs:8:21: error: • Couldn't match type ‘ref’ with ‘ref1’ ‘ref’ is a rigid type variable bound by the type signature for: f :: forall a (ref :: * -> *). ref () -> () at forall.hs:6:29 ‘ref1’ is a rigid type variable bound by the type signature for: r :: forall (ref1 :: * -> *). ref1 () at forall.hs:7:22 Expected type: ref1 () Actual type: ref () • In the expression: x In an equation for ‘r’: r = x In the expression: let r :: ref () r = x in () • Relevant bindings include r :: ref1 () (bound at forall.hs:8:17) x :: ref () (bound at forall.hs:7:9) f :: ref () -> () (bound at forall.hs:7:7) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14288 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler