Hello,<div><br></div><div>The context in your example serves an important purpose: it records the fact that the behavior of the function may differ depending on which type it is instantiated with.   This is quite different from ordinary polymorphic functions, such as `const` for example,  which work in exactly the same way, no matter how you instantiate them.   Note that it doesn&#39;t matter that we can solve the constraint for all types of kind `D`---the constraint is there because we can&#39;t solve it _uniformly_ for all types.</div>
<div><br></div><div>-Iavor</div><div>PS: As an aside, these two forms of polymorphism are sometimes called &quot;parametric&quot; (when functions work in the same way for all types), and &quot;ad-hoc&quot; (when the behavior depends on which type is being used).</div>
<div><br></div><div><br></div><div><br><br><div class="gmail_quote">On Sun, May 6, 2012 at 9:48 AM, Serguey Zefirov <span dir="ltr">&lt;<a href="mailto:sergueyz@gmail.com" target="_blank">sergueyz@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">I decided to take a look at DataKinds extension, which became<br>
available in GHC 7.4.<br>
<br>
My main concerns is that I cannot close type classes for promoted data<br>
types. Even if I fix type class argument to a promoted type, the use<br>
of encoding function still requires specification of context. I<br>
consider this an omission of potentially very useful feature.<br>
<br>
Example is below.<br>
-----------------------------------------------------------------------------------------<br>
{-# LANGUAGE TypeOperators, DataKinds, TemplateHaskell, TypeFamilies,<br>
UndecidableInstances #-}<br>
{-# LANGUAGE GADTs #-}<br>
<br>
-- a binary numbers.<br>
infixl 5 :*<br>
data D =<br>
                D0<br>
        |       D1<br>
        |       D :* D<br>
        deriving Show<br>
<br>
-- encoding for them.<br>
data EncD :: D -&gt; * where<br>
        EncD0 :: EncD D0<br>
        EncD1 :: EncD D1<br>
        EncDStar :: EncD (a :: D) -&gt; EncD (b :: D) -&gt; EncD (a :* b)<br>
<br>
-- decode of values.<br>
fromD :: D -&gt; Int<br>
fromD D0 = 0<br>
fromD D1 = 1<br>
fromD (d :* d0) = fromD d * 2 + fromD d0<br>
<br>
-- decode of encoded values.<br>
fromEncD :: EncD d -&gt; Int<br>
fromEncD EncD0 = 0<br>
fromEncD EncD1 = 1<br>
fromEncD (EncDStar a b) = fromEncD a * 2 + fromEncD b<br>
<br>
-- constructing encoded values from type.<br>
-- I&#39;ve closed possible kinds for class parameter (and GHC<br>
successfully compiles it).<br>
-- I fully expect an error if I will try to apply mkD to some type<br>
that is not D.<br>
-- (and, actually, GHC goes great lengths to prevent me from doing that)<br>
-- By extension of argument I expect GHC to stop requiring context<br>
with MkD a where<br>
-- I use mkD &quot;constant function&quot; and it is proven that a :: D.<br>
class MkD (a :: D) where<br>
        mkD :: EncD a<br>
instance MkD D0 where<br>
        mkD = EncD0<br>
instance MkD D1 where<br>
        mkD = EncD1<br>
-- But I cannot omit context here...<br>
instance (MkD a, MkD b) =&gt; MkD (a :* b) where<br>
        mkD = EncDStar mkD mkD<br>
<br>
data BV (size :: D) where<br>
        BV :: EncD size -&gt; Integer -&gt; BV size<br>
<br>
bvSize :: BV (size :: D) -&gt; Int<br>
bvSize (BV size _) = fromEncD size<br>
<br>
-- ...and here.<br>
-- This is bad, because this context will arise in other places, some of which<br>
-- are autogenerated and context for them is incomprehensible to human<br>
-- reader.<br>
-- (they are autogenerated precisely because of that - it is tedious<br>
and error prone<br>
-- to satisfy type checker.)<br>
fromIntgr :: Integer -&gt; BV (size :: D) -- doesn&#39;t work, but desired.<br>
-- fromIntgr :: MkD size =&gt; Integer -&gt; BV (size :: D) -- does work,<br>
but is not that useful.<br>
fromIntgr int = BV mkD int<br>
-----------------------------------------------------------------------------------------<br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</blockquote></div><br></div>