weird behaviour of context resolution with FlexibleContexts and TypeFamilies

Sittampalam, Ganesh ganesh.sittampalam at credit-suisse.com
Thu Feb 24 08:40:51 CET 2011


Hi,

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.

Is it a bug, or just one of the risks one takes by using
FlexibleContexts?

I've tried this with GHC 6.12.3 and with 7.0.2RC2.

Cheers,

Ganesh

{-# 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



=============================================================================== 
Please access the attached hyperlink for an important electronic communications disclaimer: 
http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
=============================================================================== 

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20110224/48d45109/attachment-0001.htm>


More information about the Glasgow-haskell-users mailing list