[GHC] #8390: regression in handling of type variables in constraints on instances which do not appear in the instance head

GHC ghc-devs
Tue Oct 1 00:14:27 UTC 2013


#8390: regression in handling of type variables in constraints on instances which
do not appear in the instance head
----------------------------+----------------------------------------------
       Reporter:  aavogt    |             Owner:
           Type:  bug       |            Status:  new
       Priority:  normal    |         Milestone:
      Component:  Compiler  |           Version:  7.7
       Keywords:            |  Operating System:  Unknown/Multiple
   Architecture:            |   Type of failure:  GHC rejects valid program
  Unknown/Multiple          |         Test Case:
     Difficulty:  Unknown   |          Blocking:
     Blocked By:            |
Related Tickets:            |
----------------------------+----------------------------------------------
 ghc-7.7.20130720 (from here
 http://darcs.haskell.org/ghcBuilder/uploads/igloo-m/) rejects instances
 which
 work with ghc-7.6.2.

 {{{
 {-# LANGUAGE FlexibleInstances, ImplicitParams, MultiParamTypeClasses,
 ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}

 class Fun f a b where
     fun :: f -> a -> b

 instance (b ~ Int, a ~ Int) => Fun F a b
     where fun _ = (+1)

 data F = F

 data Compose a b = Compose a b

 -- ghc-7.6 version
 instance (Fun f b c, Fun g a b) => Fun (Compose f g) a c where
     fun (Compose f g) a = fun f (fun g a :: b)

 {- | ghc >= 7.7 accepts this second instance, which is an ugly workaround
 >>> fun (Compose F F) 2
 4

 unsatisfactory ghc-77 workaround:

 >>> let ?b = undefined in fun (Compose F F) 2
 4

 -}
 instance (Fun f b c, Fun g a b, ?b :: b) => Fun (Compose f g) a c where
     fun (Compose f g) a = fun f (fun g a `asTypeOf` ?b)
 }}}

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



More information about the ghc-tickets mailing list