[GHC] #10390: Constraint order must match with RankNTypes

GHC ghc-devs at haskell.org
Wed May 6 21:56:24 UTC 2015


#10390: Constraint order must match with RankNTypes
-------------------------------------+-------------------------------------
              Reporter:  crockeea    |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  low         |         Milestone:
             Component:  Compiler    |           Version:  7.8.4
              Keywords:              |  Operating System:  Unknown/Multiple
          Architecture:              |   Type of failure:  None/Unknown
  Unknown/Multiple                   |        Blocked By:
             Test Case:              |   Related Tickets:
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 In the following code, GHC will not compile unless the constraints on the
 higher-rank function have the same *order* as the method declaration in
 `ApPair`.

 {{{#!hs
 {-# LANGUAGE RankNTypes #-}

 class ApPair r where
   apPair ::
     (forall a . (ApPair a, Num a) => Maybe a)
     -> Maybe r

 instance (ApPair a, ApPair b)
  => ApPair (a,b) where
   apPair = apPair'

 apPair' :: (ApPair b, ApPair c)
   => (forall a . (ApPair a, Num a) => Maybe a) -> Maybe (b,c)
 apPair' f =
   let (Just a) = apPair f
       (Just b) = apPair f
   in Just $ (a, b)
 }}}

 That is, the following does *not* compile:

 {{{#!hs
 apPair' :: (ApPair b, ApPair c)
   => (forall a . (Num a, ApPair a) => Maybe a) -> Maybe (b,c)
 apPair' f =
   let (Just a) = apPair f
       (Just b) = apPair f
   in Just $ (a, b)
 }}}

 GHC probably shouldn't care about lexical matching when checking
 constraints.

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


More information about the ghc-tickets mailing list