<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 3.2//EN">
<HTML>
<HEAD>
<META HTTP-EQUIV="Content-Type" CONTENT="text/html; charset=us-ascii">
<META NAME="Generator" CONTENT="MS Exchange Server version 6.5.7655.10">
<TITLE>weird behaviour of context resolution with FlexibleContexts and TypeFamilies</TITLE>
</HEAD>
<BODY>
<!-- Converted from text/rtf format -->

<P><FONT SIZE=2 FACE="Courier New">Hi,</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">If I build the code below with -DVER=2, I get a complaint about PatchInspect (PrimOf p) being missing from the context of cleverNamedResolve.</FONT></P>

<P><FONT SIZE=2 FACE="Courier New">This doesn't happen with -DVER=1 or -DVER=3</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">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.</FONT></P>

<P><FONT SIZE=2 FACE="Courier New">Is it a bug, or just one of the risks one takes by using FlexibleContexts?</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">I've tried this with GHC 6.12.3 and with 7.0.2RC2.</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">Cheers,</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">Ganesh</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">{-# LANGUAGE CPP, TypeFamilies, FlexibleContexts #-}</FONT>

<BR><FONT SIZE=2 FACE="Courier New">module Class ( cleverNamedResolve ) where</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">data FL p = FL p</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">class PatchInspect p where</FONT>

<BR><FONT SIZE=2 FACE="Courier New">instance PatchInspect p =&gt; PatchInspect (FL p) where</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">type family PrimOf p</FONT>

<BR><FONT SIZE=2 FACE="Courier New">type instance PrimOf (FL p) = PrimOf p</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">data WithName prim = WithName prim</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">instance PatchInspect prim =&gt; PatchInspect (WithName prim) where</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">class (PatchInspect (PrimOf p)) =&gt; Conflict p where</FONT>

<BR><FONT SIZE=2 FACE="Courier New">&nbsp;&nbsp;&nbsp; resolveConflicts :: p -&gt; PrimOf p</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">instance Conflict p =&gt; Conflict (FL p) where</FONT>

<BR><FONT SIZE=2 FACE="Courier New">&nbsp;&nbsp;&nbsp; resolveConflicts = undefined</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">type family OnPrim p</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">#if VER==1</FONT>

<BR><FONT SIZE=2 FACE="Courier New">class FromPrims p where</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">instance FromPrims (FL p) where</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">joinPatches :: FromPrims p =&gt; p -&gt; p</FONT>

<BR><FONT SIZE=2 FACE="Courier New">#else</FONT>

<BR><FONT SIZE=2 FACE="Courier New">#if VER==2</FONT>

<BR><FONT SIZE=2 FACE="Courier New">joinPatches :: FL p -&gt; FL p</FONT>

<BR><FONT SIZE=2 FACE="Courier New">#else</FONT>

<BR><FONT SIZE=2 FACE="Courier New">joinPatches :: p -&gt; p</FONT>

<BR><FONT SIZE=2 FACE="Courier New">#endif</FONT>

<BR><FONT SIZE=2 FACE="Courier New">#endif</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">joinPatches = id</FONT>
</P>

<P><FONT SIZE=2 FACE="Courier New">cleverNamedResolve :: (Conflict (OnPrim p)</FONT>

<BR><FONT SIZE=2 FACE="Courier New">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; ,PrimOf (OnPrim p) ~ WithName (PrimOf p))</FONT>

<BR><FONT SIZE=2 FACE="Courier New">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; =&gt; FL (OnPrim p) -&gt; WithName (PrimOf p)</FONT>

<BR><FONT SIZE=2 FACE="Courier New">cleverNamedResolve = resolveConflicts . joinPatches</FONT>
</P>
<BR>

 <BR/><!DOCTYPE html PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN"><html><p class=MsoNormal><span lang=EN-US style='font-size:8.0pt;font-family:Courier'>==============================================================================<br>Please access the attached hyperlink for an important electronic communications disclaimer:<br><a href="http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html">http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html</a><br>==============================================================================<o:p></o:p></span></p></html> <br>
</body>
</HTML>