<html><head></head><body style="word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space; "><div>I ran into this same issue in my own experimentation: if a type variable x has a kind with only one constructor K, GHC does not supply the equality x ~ K y for some fresh type variable y. Perhaps it should. I too had to use similar workarounds to what you have come up with.</div><div><br></div><div>One potential problem is the existence of the Any type, which inhabits every kind. Say x gets unified with Any. Then, we would have Any ~ K y, which is an inconsistent coercion (equating two types with distinct ground head types). However, because the RHS is a promoted datatype, we know that this coercion can never be applied to a term. Because equality is homogeneous (i.e. ~ can relate only two types of the same kind), I'm not convinced the existence of Any ~ K y is so bad. (Even with heterogeneous equality, it might work out, given that there is more than one type constructor that results in *...)</div><div><br></div><div>Regarding the m -&gt; k fundep: my experiments suggest that this dependency is implied when you have (m :: k), but I guess not when you have k appear in the kind of m in a more complicated way. Currently, there are no kind-level functions, so it appears that m -&gt; k could be implied whenever k appears anywhere in the kind of m. If (when!) there are kind-level functions, we'll have to be more careful.</div><div><br></div><div>Richard</div><br><div><div>On Aug 31, 2012, at 9:06 AM, Edward Kmett wrote:</div><br class="Apple-interchange-newline"><blockquote type="cite"><div><font face="arial, helvetica, sans-serif">This works, though it'll be all sorts of fun to try to scale up.&nbsp;</font></div><div><font face="arial, helvetica, sans-serif"><br></font></div><div><br></div><div><font face="courier new, monospace">{-# LANGUAGE FunctionalDependencies, GADTs, KindSignatures, MultiParamTypeClasses, PolyKinds, RankNTypes, TypeOperators, DefaultSignatures, DataKinds, FlexibleInstances, UndecidableInstances, TypeFamilies #-}</font></div>
<div><font face="courier new, monospace">module Indexed.Test where</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">class IMonad (m :: (k -&gt; *) -&gt; k -&gt; *) | m -&gt; k</font></div>
<div><font face="courier new, monospace">&nbsp; where ireturn :: a x -&gt; m a x</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">type family Fst (a :: (p,q)) :: p</font></div>
<div><font face="courier new, monospace">type instance Fst '(p,q) = p</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">type family Snd (a :: (p,q)) :: q</font></div>
<div><font face="courier new, monospace">type instance Snd '(p,q) = q</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">infixr 5 :-</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">&nbsp; Nil :: Thrist a '(i,i)</font></div><div><font face="courier new, monospace">&nbsp; (:-) :: (Snd ij ~ Fst jk, Fst ij ~ Fst ik, Snd jk ~ Snd ik) =&gt; a ij -&gt; Thrist a jk -&gt; Thrist a ik</font></div>
<div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">instance IMonad Thrist where&nbsp;</font></div><div><font face="courier new, monospace">&nbsp; ireturn a = a :- Nil</font></div><div>
<div><font face="arial, helvetica, sans-serif"><br></font></div><div><font face="arial, helvetica, sans-serif">I know Agda has to jump through some hoops to make the refinement work on pairs when they do eta expansion. I wonder if this could be made less painful.</font></div>
</div><div><font face="arial, helvetica, sans-serif"><br></font></div><br><div class="gmail_quote">On Fri, Aug 31, 2012 at 8:55 AM, Edward Kmett <span dir="ltr">&lt;<a href="mailto:ekmett@gmail.com" target="_blank">ekmett@gmail.com</a>&gt;</span> wrote:<br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Hrmm. This seems to work manually for getting product categories to work. Perhaps I can do the same thing for thrists.<div>
<br></div><div><div><font face="courier new, monospace">{-# LANGUAGE PolyKinds, DataKinds, TypeOperators, GADTs, TypeFamilies #-}</font></div><div class="im">
<div><font face="courier new, monospace">module Product where</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">import Prelude hiding (id,(.))</font></div><div>

<font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">class Category k where</font></div><div><font face="courier new, monospace">&nbsp; id :: k a a</font></div><div><font face="courier new, monospace">&nbsp; (.) :: k b c -&gt; k a b -&gt; k a c</font></div>

<div><font face="courier new, monospace"><br></font></div></div><div><font face="courier new, monospace">type family Fst (a :: (p,q)) :: p</font></div><div><font face="courier new, monospace">type instance Fst '(p,q) = p</font></div>

<div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">type family Snd (a :: (p,q)) :: q</font></div><div><font face="courier new, monospace">type instance Snd '(p,q) = q</font></div>
<div class="im">
<div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">data (*) :: (x -&gt; x -&gt; *) -&gt; (y -&gt; y -&gt; *) -&gt; (x,y) -&gt; (x,y) -&gt; * where</font></div></div><div><font face="courier new, monospace">&nbsp; (:*) :: x (Fst a) (Fst b) -&gt; y (Snd a) (Snd b) -&gt; (x * y) a b</font></div>
<div class="im">
<div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">instance (Category x, Category y) =&gt; Category (x * y) where</font></div><div><font face="courier new, monospace">&nbsp; id = id :* id</font></div>

<div><font face="courier new, monospace">&nbsp; (xf :* &nbsp;yf) . (xg :* yg) = (xf . xg) :* (yf . yg)</font></div><div><br></div><div><br></div><br></div><div><div class="h5"><div class="gmail_quote">On Fri, Aug 31, 2012 at 8:44 AM, Edward Kmett <span dir="ltr">&lt;<a href="mailto:ekmett@gmail.com" target="_blank">ekmett@gmail.com</a>&gt;</span> wrote:<br>

<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">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. =(&nbsp;<div>

<br></div><div><div>For instance, there doesn't even seem to be a way to make the following code compile, either.</div>
<div><br></div><div><br></div><div><div><font face="courier new, monospace">{-# LANGUAGE PolyKinds, DataKinds, TypeOperators, GADTs #-}</font></div><div><font face="courier new, monospace">module Product where</font></div>


<div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">import Prelude hiding (id,(.))</font></div><div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">class Category k where</font></div>


<div><font face="courier new, monospace">&nbsp; id :: k a a</font></div><div><font face="courier new, monospace">&nbsp; (.) :: k b c -&gt; k a b -&gt; k a c</font></div><div><font face="courier new, monospace"><br></font></div><div>


<font face="courier new, monospace">data (*) :: (x -&gt; x -&gt; *) -&gt; (y -&gt; y -&gt; *) -&gt; (x,y) -&gt; (x,y) -&gt; * where</font></div><div><font face="courier new, monospace">&nbsp; (:*) :: x a b -&gt; y c d -&gt; (x * y) '(a,c) '(b,d)</font></div>


<div><font face="courier new, monospace"><br></font></div><div><font face="courier new, monospace">instance (Category x, Category y) =&gt; Category (x * y) where</font></div><div><font face="courier new, monospace">&nbsp; id = id :* id</font></div>


<div><font face="courier new, monospace">&nbsp; (xf :* &nbsp;yf) . (xg :* yg) = (xf . xg) :* (yf . yg)</font></div><div><br></div><div><div>This all works perfectly fine in Conor's SHE, (as does the thrist example) so I'm wondering where the impedence mismatch comes in and how to gain knowledge of this injectivity to make it work.</div>


<div></div></div><div><br></div><div>Also, does it ever make sense for the kind of a kind variable mentioned in a type not to get a functional dependency on the type?&nbsp;</div><div><br></div><div>e.g. should</div><div><br></div>


<div>class Foo (m :: k -&gt; *)</div><div><br></div><div>always be</div><div><br></div><div>class Foo (m :: k -&gt; *) | m -&gt; k</div><div><br></div><div>?</div><div><br></div><div>Honest question. I can't come up with a scenario, but you might have one I don't know.</div>

<span><font color="#888888">
<div><br></div><div>-Edward</div></font></span><div><div><br><div class="gmail_quote">On Fri, Aug 31, 2012 at 5:55 AM, Simon Peyton-Jones <span dir="ltr">&lt;<a href="mailto:simonpj@microsoft.com" target="_blank">simonpj@microsoft.com</a>&gt;</span> wrote:<br>


<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><p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">With the code below, I get this error message with HEAD. And that looks right to me, no?<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">The current 7.6 branch gives the same message printed less prettily.<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>&nbsp;<u></u></span></p><p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">If I replace the defn of irt with<u></u><u></u></span></p><p class="MsoNormal" style="text-indent:36.0pt"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">irt :: a '(i,j) -&gt; Thrist a '(i,j)<u></u><u></u></span></p><p class="MsoNormal" style="text-indent:36.0pt"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">irt ax = ax :- Nil<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>&nbsp;<u></u></span></p><p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">then it typechecks.<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>&nbsp;<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>&nbsp;<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>&nbsp;<u></u></span></p><p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">Knett.hs:20:10:<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">&nbsp;&nbsp;&nbsp; Couldn't match type `x' with '(i0, k0)<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">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; `x' is a rigid type variable bound by<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">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; the type signature for irt :: a x -&gt; Thrist k a x at Knett.hs:19:8<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">&nbsp;&nbsp;&nbsp; Expected type: Thrist k a x<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">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; Actual type: Thrist k a '(i0, k0)<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">&nbsp;&nbsp;&nbsp; In the expression: ax :- Nil<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">&nbsp;&nbsp;&nbsp; In an equation for `irt': irt ax = ax :- Nil<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">simonpj@cam-05-unx:~/tmp$<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"><u></u>&nbsp;<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>&nbsp;<u></u></span></p><p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">{-# LANGUAGE FunctionalDependencies, GADTs, KindSignatures, MultiParamTypeClasses, PolyKinds,
<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">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;RankNTypes, TypeOperators, DefaultSignatures, DataKinds,
<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">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;FlexibleInstances, UndecidableInstances #-}<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>&nbsp;<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">module Knett where<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"><u></u>&nbsp;<u></u></span></p><p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">class IMonad (m :: (k -&gt; *) -&gt; k -&gt; *) | m -&gt; k 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">&nbsp;&nbsp;ireturn :: a x -&gt; m a x<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>&nbsp;<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">infixr 5 :-<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"><u></u>&nbsp;<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 Thrist :: ((i,i) -&gt; *) -&gt; (i,i) -&gt; * 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">&nbsp; Nil&nbsp; :: Thrist a '(i,i)<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">&nbsp; (:-) :: a '(i,j) -&gt; Thrist a '(j,k) -&gt; Thrist a '(i,k)<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>&nbsp;<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">-- instance IMonad Thrist 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">--&nbsp; ireturn a = a :- Nil<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>&nbsp;<u></u></span></p><p class="MsoNormal"><span style="font-size:11.0pt;font-family:&quot;Verdana&quot;,&quot;sans-serif&quot;;color:#1f497d">irt :: a x -&gt; Thrist a x<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">irt ax = ax :- Nil<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>&nbsp;<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>&nbsp;<u></u></span></p>
<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;"> <a href="mailto:glasgow-haskell-users-bounces@haskell.org" target="_blank">glasgow-haskell-users-bounces@haskell.org</a> [mailto:<a href="mailto:glasgow-haskell-users-bounces@haskell.org" target="_blank">glasgow-haskell-users-bounces@haskell.org</a>]
<b>On Behalf Of </b>Edward Kmett<br>
<b>Sent:</b> 31 August 2012 03:38<br>
<b>To:</b> <a href="mailto:glasgow-haskell-users@haskell.org" target="_blank">glasgow-haskell-users@haskell.org</a><br>
<b>Subject:</b> PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?<u></u><u></u></span></p>
</div>
</div><div><div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
<div><p class="MsoNormal">If I define the following<u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">{-# LANGUAGE FunctionalDependencies, GADTs, KindSignatures, MultiParamTypeClasses, PolyKinds, RankNTypes, TypeOperators, DefaultSignatures, DataKinds, FlexibleInstances, UndecidableInstances #-}</span><u></u><u></u></p>



</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">module Indexed.Test where</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">class IMonad (m :: (k -&gt; *) -&gt; k -&gt; *)&nbsp;where&nbsp;</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">&nbsp; ireturn :: a x -&gt; m a x</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">infixr 5 :-</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">data Thrist :: ((i,i) -&gt; *) -&gt; (i,i) -&gt; * where</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">&nbsp; Nil :: Thrist a '(i,i)</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">&nbsp; (:-) :: a '(i,j) -&gt; Thrist a '(j,k) -&gt; Thrist a '(i,k)</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">instance IMonad Thrist where</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">&nbsp; ireturn a = a :- Nil</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Arial&quot;,&quot;sans-serif&quot;">Then 'ireturn' complains (correctly) that it can't match the k with the kind (i,i). The reason it can't is because when you look at the resulting signature for the MPTC it generates it looks
 like</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div>
<div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">class IMonad k m where</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">&nbsp; ireturn :: a x -&gt; m a x</span><u></u><u></u></p>
</div>
</div>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Arial&quot;,&quot;sans-serif&quot;">However, there doesn't appear to be a way to say that the kind k should be determined by m.&nbsp;</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Arial&quot;,&quot;sans-serif&quot;">I tried doing:</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">class IMonad (m :: (k -&gt; *) -&gt; k -&gt; *) | m -&gt; k&nbsp;where&nbsp;</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">&nbsp; ireturn :: a x -&gt; m a x</span><u></u><u></u></p>
</div>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Arial&quot;,&quot;sans-serif&quot;">Surprisingly (to me) this compiles and generates the correct constraints for IMonad:</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">ghci&gt; :set -XPolyKinds -XKindSignatures -XFunctionalDependencies -XDataKinds -XGADTs</span><u></u><u></u></p>
</div>
<div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">ghci&gt; class IMonad (m :: (k -&gt; *) -&gt; k -&gt; *) | m -&gt; k where ireturn :: a x -&gt; m a x</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">ghci&gt; :info IMonad</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">class IMonad k m | m -&gt; k where</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">&nbsp; ireturn :: a x -&gt; m a x</span><u></u><u></u></p>
</div>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal">But when I add&nbsp;<u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">ghci&gt; :{</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">Prelude| data Thrist :: ((i,i) -&gt; *) -&gt; (i,i) -&gt; * where</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">Prelude| &nbsp; Nil :: Thrist a '(i,i)</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">Prelude| &nbsp; (:-) :: a '(i,j) -&gt; Thrist a '(j,k) -&gt; Thrist a '(i,k)</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">Prelude| :}</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div>
<div><p class="MsoNormal">and attempt to introduce the instance, I crash:<u></u><u></u></p>
</div>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">ghci&gt; instance IMonad Thrist where ireturn a = a :- Nil</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">ghc: panic! (the 'impossible' happened)</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">&nbsp; (GHC version 7.6.0.20120810 for x86_64-apple-darwin):</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><span><span style="font-family:&quot;Courier New&quot;">&nbsp;&nbsp;&nbsp;
</span></span><span style="font-family:&quot;Courier New&quot;">lookupVarEnv_NF: Nothing</span><u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal"><span style="font-family:&quot;Courier New&quot;">Please report this as a GHC bug: &nbsp;<a href="http://www.haskell.org/ghc/reportabug" target="_blank">http://www.haskell.org/ghc/reportabug</a></span><u></u><u></u></p>



</div>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal">Moreover, attempting to compile them in separate modules leads to a different issue.&nbsp;<u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal">Within the module, IMonad has a type that includes the kind k and the constraint on it from m. But from the other module, :info shows no such constraint, and the above code again fails to typecheck, but upon trying to recompile, when GHC
 goes to load the IMonad instance from the core file, it panicks again differently about references to a variable not present in the core.<u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal">Is there any way to make such a constraint that determines a kind from a type parameter in GHC 7.6 at this time?<u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal">I tried the Kind hack used in GHC.TypeLits, but it doesn't seem to be applicable to this situation.<u></u><u></u></p>
</div>
<div><p class="MsoNormal"><u></u>&nbsp;<u></u></p>
</div>
<div><p class="MsoNormal">-Edward<u></u><u></u></p>
</div>
</div></div></div>
</div>
</div>

</blockquote></div><br></div></div></div></div>
</blockquote></div><br></div></div></div>
</blockquote></div><br>
_______________________________________________<br>Glasgow-haskell-users mailing list<br><a href="mailto:Glasgow-haskell-users@haskell.org">Glasgow-haskell-users@haskell.org</a><br><a href="http://www.haskell.org/mailman/listinfo/glasgow-haskell-users">http://www.haskell.org/mailman/listinfo/glasgow-haskell-users</a><br></blockquote></div><br></body></html>