 
            #16033: Rank-n typechecking regression between GHC 8.4 and 8.6 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: | Keywords: RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: Old description:
The following program typechecks on GHC 7.0.4 through 8.4.4:
{{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} module Bug where
f :: (forall a. a -> forall b. b -> c) -> () f (_ :: forall a. a -> forall b. b -> z) = () }}}
However, it does not typecheck on GHC 8.6.3:
{{{ $ /opt/ghc/8.6.3/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:7:4: error: • Couldn't match type ‘b0 -> c’ with ‘forall b. b -> z’ Expected type: a -> forall b. b -> z Actual type: a -> b0 -> c • When checking that the pattern signature: forall a. a -> forall b. b -> z fits the type of its context: forall a. a -> forall b. b -> c In the pattern: _ :: forall a. a -> forall b. b -> z In an equation for ‘f’: f (_ :: forall a. a -> forall b. b -> z) = () • Relevant bindings include f :: (forall a. a -> forall b. b -> c) -> () (bound at Bug.hs:7:1) | 7 | f (_ :: forall a. a -> forall b. b -> z) = () | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}}
New description: The following program typechecks on GHC 7.0.4 through 8.4.4: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} module Bug where f :: (forall a. a -> forall b. b -> c) -> () f (_ :: forall a. a -> forall b. b -> c) = () }}} However, it does not typecheck on GHC 8.6.3: {{{ $ /opt/ghc/8.6.3/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:7:4: error: • Couldn't match type ‘b0 -> c1’ with ‘forall b. b -> c’ Expected type: a -> forall b. b -> c Actual type: a -> b0 -> c1 • When checking that the pattern signature: forall a. a -> forall b. b -> c fits the type of its context: forall a. a -> forall b. b -> c1 In the pattern: _ :: forall a. a -> forall b. b -> c In an equation for ‘f’: f (_ :: forall a. a -> forall b. b -> c) = () • Relevant bindings include f :: (forall a. a -> forall b. b -> c1) -> () (bound at Bug.hs:7:1) | 7 | f (_ :: forall a. a -> forall b. b -> c) = () | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16033#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler