weird behaviour of context resolution with FlexibleContexts and TypeFamilies

Ganesh Sittampalam ganesh at earth.li
Fri Feb 25 17:39:01 CET 2011


Hi Simon,

You talk about the timing of application of the instance declaration
   instancePatchInspect (PrimOf p)) => Conflict p

but the constraint is actually defined in the class declaration, and I 
don't have any instance declarations for Conflict p itself.
classPatchInspect (PrimOf p)) => Conflict p

Does that make a difference to your answer, or do you mean that the 
constraint in the class declaration automatically gives rise to the same 
behaviour?

Ganesh

On 25/02/2011 09:06, Simon Peyton-Jones wrote:
>
> You are doing something very delicate here, akin to overlapping 
> instances.
>
> You have an instance
>
> instancePatchInspect (PrimOf p)) => Conflict p
>
> and a function
>
> clever :: (Conflict (OnPrim p), ..) => ...
>
> So if a constraint (Conflict blah) arises in the RHS of clever, the 
> instance declaration will immediately apply; and then the type check 
> fails.  But if it just so happens to precisely match the provided 
> constraint (Conflict (OnPrim p)), you want to use the provided 
> constraint.  In effect the type signature and the instance overlap.
>
> Arguably, GHC should refrain from applying the instance if there is 
> any possibility of a "given" constraint matching.  Currently it's a 
> bit random; but it's a very weird situation.
>
> But first, is this really what you intend?
>
> Simon
>
> *From:*glasgow-haskell-users-bounces at haskell.org 
> [mailto:glasgow-haskell-users-bounces at haskell.org] *On Behalf Of 
> *Sittampalam, Ganesh
> *Sent:* 24 February 2011 07:41
> *To:* glasgow-haskell-users at haskell.org
> *Subject:* weird behaviour of context resolution with FlexibleContexts 
> and TypeFamilies
>
> 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
> ==============================================================================
>
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20110225/a289a631/attachment.htm>


More information about the Glasgow-haskell-users mailing list