Wow, Jeremy, your solution looks very nice. I&#39;ll try it and report back<div>Thanks a lot!!<br><br><div class="gmail_quote">2012/5/3 Jeremy Shaw <span dir="ltr">&lt;<a href="mailto:jeremy@n-heptane.com" target="_blank">jeremy@n-heptane.com</a>&gt;</span><br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">This response is written in literal Haskell.<br>
<br>
&gt; {-# LANGUAGE DataKinds, KindSignatures, GADTs #-}<br>
<br>
The key to getting the type checker involved is to put the information<br>
where the type-checker can see it -- namely, the type signature.<br>
<br>
So, let&#39;s change A so that the Safe/Unsafe information is in the type:<br>
<br>
&gt; data A safety = A Int<br>
<br>
This is what is called a &#39;phantom type&#39;, because the &#39;safety&#39; type<br>
variable only appears on the left hand side. We can keep &#39;B&#39; the same:<br>
<div class="im"><br>
&gt; data B        = B Int<br>
<br>
</div>Now, we need some way to represent &#39;Safe&#39; and &#39;Unsafe&#39;:<br>
<br>
&gt; data Safe<br>
&gt; data Unsafe<br>
<br>
Normally data declarations have 1 or more data constructors. Here we<br>
have data-types with 0 constructors. We don&#39;t need to actually create<br>
any &#39;Safe&#39; or &#39;Unsafe&#39; values, because we are only going to be using<br>
them as the phantom arguments. We need two separate types, because we<br>
want to be able to tell the difference at compile time. As you saw,<br>
having a single type with two different constructors does not give you<br>
enough power to constrain things at compile time.<br>
<br>
Now we can make two helper functions which mark a value as &#39;Safe&#39; or &#39;Unsafe&#39;:<br>
<br>
&gt; unsafe :: A safety -&gt; A Unsafe<br>
&gt; unsafe  (A x) = (A x)<br>
<br>
&gt; safe :: A safety -&gt; A Safe<br>
&gt; safe    (A x) = (A x)<br>
<br>
And now we can make &#39;createB&#39; only accept safe values:<br>
<br>
&gt; createB :: A Safe -&gt; B<br>
&gt; createB (A x) = B x<br>
<br>
We can apply createB to &#39;Safe&#39; values:<br>
<br>
&gt; b :: B<br>
&gt; b = createB (safe (A 1))<br>
<br>
but not &#39;Unsafe&#39; values:<br>
<br>
&gt; {-<br>
<br>
&gt; b2 :: B<br>
&gt; b2 = createB (unsafe (A 1))<br>
<br>
Results in:<br>
<br>
    Couldn&#39;t match expected type `Safe&#39; with actual type `Unsafe&#39;<br>
    Expected type: A Safe<br>
      Actual type: A Unsafe<br>
<br>
&gt; -}<br>
<br>
Alas, we can also apply &#39;createB&#39; to values that are untagged:<br>
<br>
&gt; b3 :: B<br>
&gt; b3 = createB (A 1)<br>
<br>
Sometimes that is a good thing -- but in this case, it is not likely<br>
to be. A work around is to not export the &#39;A&#39; constructor. Instead we<br>
could export:<br>
<br>
&gt; unsafeA :: Int -&gt; A Unsafe<br>
&gt; unsafeA  x = (A x)<br>
<br>
&gt; safeA :: Int -&gt; A Safe<br>
&gt; safeA    x = (A x)<br>
<br>
If that is the only way to create values of type &#39;A&#39;, then we won&#39;t<br>
have any untagged &#39;A&#39; values.<br>
<br>
With our current definition for &#39;A&#39; we can mark values as &#39;Safe&#39; or<br>
&#39;Unsafe&#39; and prevent functions from being applied at compile time.<br>
However, this provides no easy way to write a function that behaves<br>
one way for &#39;Safe&#39; values and a different way for &#39;Unsafe&#39; values. If<br>
we wanted to do that, we would need to create a type class.<br>
<br>
We might try to fix this by changing A to have two constructors again:<br>
<br>
] data A&#39; safety = SafeA&#39; Int | UnsafeA&#39; Int<br>
<br>
But, now we have a very difficult problem of ensuring that values<br>
which use SafeA&#39; always have the phantom type &#39;Safe&#39; and that UnsafeA&#39;<br>
values always have the phantom type &#39;Unsafe&#39;. That is rather tricky.<br>
<br>
The solution here is the GADTs type extension. We can instead write:<br>
<br>
&gt; data A&#39; safety where<br>
&gt;     UnsafeInt :: Int -&gt; A&#39; Unsafe<br>
&gt;     SafeInt   :: Int -&gt; A&#39; Safe<br>
<br>
This declaration is similar to the normal data declaration:<br>
<br>
] data A&#39; safety<br>
]     = UnsafeInt Int<br>
]     | SafeInt Int<br>
<br>
But in the GADT version, we can specify that when we use the<br>
&#39;UnsafeInt&#39; constructor the phantom type variable *must* be &#39;Unsafe&#39;<br>
and when using &#39;SafeInt&#39; the phantom parameter *must* be &#39;Safe&#39;.<br>
<br>
This solves both &#39;issues&#39; that we described. We can now match on safe<br>
vs unsafe construtors *and* we can be sure that values of type A&#39; are<br>
*always* marked as &#39;Safe&#39; or &#39;Unsafe&#39;. If we wanted to have an<br>
untagged version we could explicitly add a third constructor:<br>
<br>
&gt;     UnknownInt   :: Int -&gt; A&#39; safety<br>
<br>
<br>
We can now write &#39;createB&#39; as:<br>
<br>
&gt; createB&#39; :: A&#39; Safe -&gt; B<br>
&gt; createB&#39; (SafeInt i) = B i<br>
<br>
In this case createB&#39; is total. The compiler knows that createB&#39; could<br>
never be called with &#39;UnsafeInt&#39; value. In fact, if you added:<br>
<br>
] createB&#39; (UnsafeInt i) = B i<br>
<br>
you would get the error:<br>
<br>
    Couldn&#39;t match type `Safe&#39; with `Unsafe&#39;<br>
    Inaccessible code in<br>
      a pattern with constructor<br>
        UnsafeInt :: Int -&gt; A&#39; Unsafe,<br>
<br>
One issue with both A and A&#39; is that the phantom variable parameter<br>
can be any type at all. For example we could write:<br>
<br>
&gt; nonsense :: A&#39; Char<br>
&gt; nonsense = UnknownInt 1<br>
<br>
But, the only types we want to support are &#39;Safe&#39; and &#39;Unsafe&#39;. A&#39;<br>
Char is a legal -- but meaningless type.<br>
<br>
In GHC 7.4 we can use Datatype promotion to make the acceptable types<br>
for the phantom parameter more restrictive.<br>
<br>
First we declare a normal Haskell type with constructors for safe and unsafe:<br>
<br>
&gt; data Safety = IsSafe | IsUnsafe<br>
<br>
But, with the &#39;DataKind&#39; extension enabled, we can now use this type<br>
to provide a signature for the the phantom type. The data type<br>
&#39;Safety&#39; automatically becomes a kind type &#39;Safety&#39; and the data<br>
constructors &#39;IsSafe&#39; and &#39;IsUnsafe&#39; automatically become type<br>
constructors. Now we can write:<br>
<br>
&gt; data Alpha (safetype :: Safety) where<br>
&gt;     SafeThing    :: Int -&gt; Alpha IsSafe<br>
&gt;     UnsafeThing  :: Int -&gt; Alpha IsUnsafe<br>
&gt;     UnknownThing :: Int -&gt; Alpha safetype<br>
<br>
Now we can write:<br>
<br>
&gt; foo :: Alpha IsUnsafe<br>
&gt; foo  = UnknownThing 1<br>
<br>
But if we try;<br>
<br>
] foo&#39; :: Alpha Char<br>
] foo&#39;  = UnknownThing 1<br>
<br>
we get the error:<br>
<br>
    Kind mis-match<br>
    The first argument of `Alpha&#39; should have kind `Safety&#39;,<br>
    but `Char&#39; has kind `*&#39;<br>
    In the type signature for foo&#39;: foo&#39; :: Alpha Char<br>
<br>
hope this helps!<br>
<span class="HOEnZb"><font color="#888888">- jeremy<br>
</font></span><div class="HOEnZb"><div class="h5"><br>
<br>
<br>
<br>
On Thu, May 3, 2012 at 10:36 AM, Ismael Figueroa Palet<br>
&lt;<a href="mailto:ifigueroap@gmail.com">ifigueroap@gmail.com</a>&gt; wrote:<br>
&gt; Hi, I&#39;m writing a program like this:<br>
&gt;<br>
&gt; data B = B Int<br>
&gt; data A = Safe Int | Unsafe Int<br>
&gt;<br>
&gt; createB :: A -&gt; B<br>
&gt; createB (Safe i) = B i<br>
&gt; createB (Unsafe i) = error &quot;This is not allowed&quot;<br>
&gt;<br>
&gt; Unfortunately, the situation when createB is called with an Unsafe value is<br>
&gt; only checked at runtime.<br>
&gt; If I omit the second case, it is not an error to not be exhaustive :-(<br>
&gt;<br>
&gt; Is there a way to make it a compile time error??<br>
&gt;<br>
&gt; Thanks!<br>
&gt; --<br>
&gt; Ismael<br>
&gt;<br>
&gt;<br>
</div></div><div class="HOEnZb"><div class="h5">&gt; _______________________________________________<br>
&gt; Haskell-Cafe mailing list<br>
&gt; <a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
&gt; <a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
&gt;<br>
</div></div></blockquote></div><br><br clear="all"><div><br></div>-- <br>Ismael<br><br>
</div>