It is both perfectly reasonable and unfortunately useless. :(<div><br></div><div>The problem is that the &quot;more polymorphic&quot; type isn&#39;t any more polymorphic, since (ideally) the product kind <font face="courier new, monospace">(a,b)</font> is only inhabited by things of the form <font face="courier new, monospace">&#39;(x,y)</font><font face="arial, helvetica, sans-serif">.</font></div>
<div><br></div><div>The product kind has a single constructor. But there is no way to express this at present that is safe.</div><div><br></div><div>As it stands, I can fake this to an extent in one direction, by writing</div>
<div><font face="courier new, monospace"><br></font></div><div><div><font face="courier new, monospace">{-# LANGUAGE FunctionalDependencies, GADTs, KindSignatures, MultiParamTypeClasses, PolyKinds, TypeFamilies,</font></div>
<div><font face="courier new, monospace">             RankNTypes, TypeOperators, DefaultSignatures, DataKinds,</font></div><div><font face="courier new, monospace">             FlexibleInstances, UndecidableInstances #-}</font></div>
<div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">module Kmett where</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">type family Fst (p :: (a,b)) :: a</font></div>
<div><font face="courier new, monospace">type instance Fst &#39;(a,b) = a</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">type family Snd (p :: (a,b)) :: b</font></div>
<div><font face="courier new, monospace">type instance Snd &#39;(a,b) = b</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">data Thrist :: ((i,i) -&gt; *) -&gt; (i,i) -&gt; * where</font></div>
<div><font face="courier new, monospace">  Nil  :: Thrist a &#39;(i,i)</font></div><div><font face="courier new, monospace">  (:-) :: (Fst ij ~ i, Snd ij ~ j, Fst ik ~ i, Snd ik ~ k) =&gt;</font></div><div><font face="courier new, monospace">          a ij -&gt; Thrist a &#39;(j,k) -&gt; Thrist a ik</font></div>
<div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">irt :: a x -&gt; Thrist a x</font></div><div><font face="courier new, monospace">irt ax = ax :- Nil</font></div><div><br></div>
<div class="gmail_quote">and this compiles, but it just pushes the problem down the road, because with that I can show that given ij :: (x,y), I can build up a tuple &#39;(Fst ij, Snd ij) :: (x,y)</div><div class="gmail_quote">
<br></div><div class="gmail_quote">But it doesn&#39;t give me that &#39;(Fst ij, Snd ij) ~ ij, which you need later when you go to define an indexed bind, and type families are insufficient to the task. Right now to get this property I&#39;m forced to fake it with unsafeCoerce.</div>
<div class="gmail_quote"><br></div><div class="gmail_quote">-Edward</div><div class="gmail_quote"><br></div><div class="gmail_quote">On Fri, Aug 31, 2012 at 1:00 PM, Simon Peyton-Jones <span dir="ltr">&lt;<a href="mailto:simonpj@microsoft.com" target="_blank">simonpj@microsoft.com</a>&gt;</span> wrote:</div>
<div class="gmail_quote"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">





<div lang="EN-GB" link="blue" vlink="purple">
<div><div class="im">
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">Same question.  Do you expect the code below to type-check?  I have stripped it down to essentials.  Currently it’s rejected with
<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">    Couldn&#39;t match type `a&#39; with &#39;(,) k k1 b0 d0<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">And that seems reasonable, doesn’t it?  After all, in the defn of bidStar, (:*) returns a value of type
<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">     Star x y ‘(a,c) ‘(b,d)<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">which is manifestly incompatible with the claimed, more polymorphic type.  And this is precisely the same error as comes from your class/instance example below,
 and for precisely the same reason.  <u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">I must be confused.<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">Simon<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">                                                                                                                                       
<u></u><u></u></span></p>
</div><p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">{-# LANGUAGE PolyKinds, DataKinds, TypeOperators, GADTs #-}<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">module Product where<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">data Star :: (x -&gt; x -&gt; *) -&gt; (y -&gt; y -&gt; *) -&gt; (x,y) -&gt; (x,y) -&gt; * where<u></u><u></u></span></p>
<div class="im">
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">  (:*) :: x a b -&gt; y c d -&gt; Star x y &#39;(a,c) &#39;(b,d)<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">bidStar :: Star T T a a<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">bidStar = bidT :* bidT<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">data T a b = MkT<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">bidT :: T a a<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">bidT = MkT<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d"><u></u> <u></u></span></p>
</div><div style="border:none;border-left:solid blue 1.5pt;padding:0cm 0cm 0cm 4.0pt">
<div>
<div style="border:none;border-top:solid #b5c4df 1.0pt;padding:3.0pt 0cm 0cm 0cm">
<p class="MsoNormal"><b><span lang="EN-US" style="font-size:10.0pt;font-family:&quot;Tahoma&quot;,&quot;sans-serif&quot;">From:</span></b><span lang="EN-US" style="font-size:10.0pt;font-family:&quot;Tahoma&quot;,&quot;sans-serif&quot;"> Edward Kmett [mailto:<a href="mailto:ekmett@gmail.com" target="_blank">ekmett@gmail.com</a>]
<br></span></p><div class="im">
<b>Sent:</b> 31 August 2012 13:45<br>
<b>To:</b> Simon Peyton-Jones<br>
<b>Cc:</b> <a href="mailto:glasgow-haskell-users@haskell.org" target="_blank">glasgow-haskell-users@haskell.org</a><br>
</div><b>Subject:</b> Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?<u></u><u></u><p></p>
</div>
</div><div class="im">
<p class="MsoNormal"><u></u> <u></u></p>
<p class="MsoNormal">Hrmm. This seems to render product kinds rather useless, as there is no way to refine the code to reflect the knowledge that they are inhabited by a single constructor. =( <u></u><u></u></p>
<div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
<div>
<div>
<p class="MsoNormal">For instance, there doesn&#39;t even seem to be a way to make the following code compile, either.<u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
<div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
<div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">{-# LANGUAGE PolyKinds, DataKinds, TypeOperators, GADTs #-}</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">module Product where</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">import Prelude hiding (id,(.))</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">class Category k where</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">  id :: k a a</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">  (.) :: k b c -&gt; k a b -&gt; k a c</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">data (*) :: (x -&gt; x -&gt; *) -&gt; (y -&gt; y -&gt; *) -&gt; (x,y) -&gt; (x,y) -&gt; * where</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">  (:*) :: x a b -&gt; y c d -&gt; (x * y) &#39;(a,c) &#39;(b,d)</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">instance (Category x, Category y) =&gt; Category (x * y) where</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">  id = id :* id</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">  (xf :*  yf) . (xg :* yg) = (xf . xg) :* (yf . yg)</span><u></u><u></u></p>
</div>
<div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
<div>
<div>
<p class="MsoNormal">This all works perfectly fine in Conor&#39;s SHE, (as does the thrist example) so I&#39;m wondering where the impedence mismatch comes in and how to gain knowledge of this injectivity to make it work.<u></u><u></u></p>

</div>
</div>
</div>
</div>
</div></div>
</div>
</div>

</blockquote></div><br></div>