#4981: inconsistent class requirements with TypeFamilies and FlexibleContexts
---------------------------------+------------------------------------------
Reporter: ganesh | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.0.1 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: GHC rejects valid program
---------------------------------+------------------------------------------
If I build the code below with -DVER=2, I get a complaint about
PatchInspect (PrimOf p) being missing from the context of
cleverNamedResolve.
This doesn't happen with -DVER=1 or -DVER=3
I presume that type class resolution is operating slightly differently in
the different cases, but it's quite confusing - in the original code
joinPatches did something useful and I was trying to inline the known
instance definition. I would have expected it to be consistent between all
three cases, either requiring the context or not.
{{{
{-# LANGUAGE CPP, TypeFamilies, FlexibleContexts #-}
module Class ( cleverNamedResolve ) where
data FL p = FL p
class PatchInspect p where
instance PatchInspect p => PatchInspect (FL p) where
type family PrimOf p
type instance PrimOf (FL p) = PrimOf p
data WithName prim = WithName prim
instance PatchInspect prim => PatchInspect (WithName prim) where
class (PatchInspect (PrimOf p)) => Conflict p where
resolveConflicts :: p -> PrimOf p
instance Conflict p => Conflict (FL p) where
resolveConflicts = undefined
type family OnPrim p
#if VER==1
class FromPrims p where
instance FromPrims (FL p) where
joinPatches :: FromPrims p => p -> p
#else
#if VER==2
joinPatches :: FL p -> FL p
#else
joinPatches :: p -> p
#endif
#endif
joinPatches = id
cleverNamedResolve :: (Conflict (OnPrim p)
,PrimOf (OnPrim p) ~ WithName (PrimOf p))
=> FL (OnPrim p) -> WithName (PrimOf p)
cleverNamedResolve = resolveConflicts . joinPatches
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4981>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs