[GHC] #16116: Explicit foralls in associated type family equations are oblivious to class-bound variables

GHC ghc-devs at haskell.org
Mon Dec 31 17:50:57 UTC 2018


#16116: Explicit foralls in associated type family equations are oblivious to
class-bound variables
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.7
           Keywords:                 |  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:
-------------------------------------+-------------------------------------
 This doesn't typecheck on GHC HEAD:

 {{{#!hs
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}
 module Bug where

 class C a where
   type T a b

 instance C (Maybe a) where
   type forall b. T (Maybe a) b = Either a b
 }}}
 {{{
 $ ~/Software/ghc/inplace/bin/ghc-stage2 Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 Bug.hs:9:3: error:
     The RHS of an associated type declaration mentions out-of-scope
 variable ‘a’
       All such variables must be bound on the LHS
   |
 9 |   type forall b. T (Maybe a) b = Either a b
   |   ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 }}}

 But it ought to. `a` isn't out of scope at all—it's bound by the class
 head `instance C (Maybe a)`.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16116>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list