regression in handling of type variables in constraints on instances which do not appear in the instance head
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)
Trac metadata
Trac field | Value |
---|---|
Version | 7.7 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |