<div dir="ltr">Thanks a lot! That really helps me understand the typeclass and solve my problem.<div><br></div><div>Best,</div><div>Ke</div><div class="gmail_extra"><div><div dir="ltr"><div><br></div></div></div><br><div class="gmail_quote">
On Thu, Mar 27, 2014 at 12:36 PM, Mateusz Kowalczyk <span dir="ltr"><<a href="mailto:fuuzetsu@fuuzetsu.co.uk" target="_blank">fuuzetsu@fuuzetsu.co.uk</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
<div class="HOEnZb"><div class="h5">On 27/03/14 15:49, ke dou wrote:<br>
> Thanks for your reply.<br>
><br>
> Yes, I understand that if I specify the 'b' to 'Prelude.Bool', it should<br>
> work, but what if I also want use the typeclass Conversion to convert other<br>
> types other than MyBool, like MyInt, or MyString?<br>
><br>
> --Ke<br>
><br>
> On Thu, Mar 27, 2014 at 11:36 AM, Brandon Allbery <<a href="mailto:allbery.b@gmail.com">allbery.b@gmail.com</a>>wrote:<br>
><br>
>> On Thu, Mar 27, 2014 at 11:28 AM, ke dou <<a href="mailto:kd6ck@virginia.edu">kd6ck@virginia.edu</a>> wrote:<br>
>><br>
>>>     class Conversion a where<br>
>>>         conversion :: a  -> b<br>
>>><br>
>><br>
>> b is completely unspecified here, since it's not defined as part of the<br>
>> typeclass. The literal meaning of this is that "the caller can request any<br>
>> type it pleases, and you have no way of knowing what it is". So the only<br>
>> possible result of `conversion` is bottom (e.g. `undefined`).<br>
>><br>
>> This is key: it does NOT mean that `conversion` gets to specify the result<br>
>> type! You can't do that, except by specifying the type in the type<br>
>> signature.<br>
>><br>
>> --<br>
>> brandon s allbery kf8nh                               sine nomine<br>
>> associates<br>
>> <a href="mailto:allbery.b@gmail.com">allbery.b@gmail.com</a><br>
>> <a href="mailto:ballbery@sinenomine.net">ballbery@sinenomine.net</a><br>
>> unix, openafs, kerberos, infrastructure, xmonad<br>
>> <a href="http://sinenomine.net" target="_blank">http://sinenomine.net</a><br>
>><br>
>> _______________________________________________<br>
>> Beginners mailing list<br>
>> <a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
>> <a href="http://www.haskell.org/mailman/listinfo/beginners" target="_blank">http://www.haskell.org/mailman/listinfo/beginners</a><br>
>><br>
>><br>
><br>
><br>
><br>
> _______________________________________________<br>
> Beginners mailing list<br>
> <a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
> <a href="http://www.haskell.org/mailman/listinfo/beginners" target="_blank">http://www.haskell.org/mailman/listinfo/beginners</a><br>
><br>
<br>
</div></div>This post is Literate Haskell.<br>
<br>
You can specify which type you can coerce to by having the typeclass<br>
also specify ‘b’.<br>
<br>
To have more than one type parameter, you'll need the MultiParamTypeClasses<br>
language extension. Ignore FunctionalDependencies for now.<br>
<br>
> {-# LANGUAGE FunctionalDependencies #-}<br>
> {-# LANGUAGE MultiParamTypeClasses #-}<br>
> {-# LANGUAGE UnicodeSyntax #-}<br>
> module C where<br>
<br>
First we define our own Bool for demonstration purposes.<br>
<div class=""><br>
> data MyBool = MyTrue | MyFalse<br>
<br>
</div>We define the class that also specifies ‘b’ as follows.<br>
<br>
> class SimpleCoercible a b where<br>
>   coerceSimple ∷ a → b<br>
<br>
We can now achieve what you want: we can state that ‘a’ cana be<br>
coerced into ‘b’. Here we state that we can convert to Haskell's Bool.<br>
<br>
> instance SimpleCoercible MyBool Bool where<br>
>   coerceSimple MyTrue = True<br>
>   coerceSimple MyFalse = False<br>
<br>
This works fine:<br>
<br>
*C> coerceSimple MyTrue :: Bool<br>
True<br>
<br>
Note that I had to say what output type I wanted here because I'm not<br>
using it<br>
in a context that GHC could use to infer it. Just because there's only a<br>
single<br>
instance does not matter as anyone could come around and add a new<br>
instance. In<br>
fact, let's define one more just to show that you can do it. Let's go<br>
with the<br>
old 0 is True and 1 is False.<br>
<br>
> instance SimpleCoercible MyBool Integer where<br>
>   coerceSimple MyTrue = 0<br>
>   coerceSimple MyFalse = 1<br>
<br>
As you can see below, it all works great:<br>
<br>
*C> coerceSimple MyTrue :: Integer<br>
0<br>
*C> coerceSimple MyTrue :: Bool<br>
True<br>
<br>
<br>
Now for something a bit out of scope of the question:<br>
<br>
Now what if we wanted to only have a single possible mapping? Say, we<br>
only want<br>
MyBool to be coercible to Bool and nothing else? We can use<br>
FunctionalDependencies language extension. I recommend you look it up if<br>
you're<br>
interested, here's an example:<br>
<br>
<br>
> class CoercibleOneWay a b | a → b where<br>
>   coerceOneWay ∷ a → b<br>
><br>
> instance CoercibleOneWay MyBool Bool where<br>
>   coerceOneWay MyTrue = True<br>
>   coerceOneWay MyFalse = False<br>
<br>
You might wonder if there's an advantage to doing such a thing. Well,<br>
yes, GHC<br>
now always knows what the output type (b) should be just by looking by<br>
the input<br>
type (a):<br>
<br>
*C> :t coerceOneWay MyTrue<br>
coerceOneWay MyTrue :: Bool<br>
<br>
Note that this is not the case with our previous definition! GHC doesn't<br>
know<br>
exactly which ‘b’ we want:<br>
<br>
*C> :t coerceSimple MyTrue<br>
coerceSimple MyTrue :: SimpleCoercible MyBool b => b<br>
<br>
<br>
Can we do more than this? What if we wanted to be able to coerce the<br>
types the<br>
other way too? We could write an instance for<br>
“CoercibleOneWay Bool MyBool | b → a” but that's unwieldy. We can<br>
instead have<br>
a single type class which can take us both ways:<br>
<br>
> class Coercible a b | a → b, b → a where<br>
>   coerceTo ∷ a → b<br>
>   coerceFrom ∷ b → a<br>
><br>
> instance Coercible MyBool Bool where<br>
>   coerceTo MyTrue = True<br>
>   coerceTo MyFalse = False<br>
><br>
>   coerceFrom True = MyTrue<br>
>   coerceFrom False = MyFalse<br>
<br>
This now lets us convert between MyBool and Bool freely:<br>
<br>
*C> :t coerceTo MyTrue<br>
coerceTo MyTrue :: Bool<br>
*C> :t coerceFrom True<br>
coerceFrom True :: MyBool<br>
<br>
With this you can model 1-to-1 mapping between your types and built-in<br>
types.<br>
<br>
Note that another approach would simply be to add an instance for<br>
“CoercibleOneWay Bool MyBool”. A nice thing about this approach is that<br>
you can<br>
use the overloaded function name:<br>
<br>
> instance CoercibleOneWay Bool MyBool where<br>
>   coerceOneWay True = MyTrue<br>
>   coerceOneWay False = MyFalse<br>
<br>
*C> :t coerceOneWay True<br>
coerceOneWay True :: MyBool<br>
*C> :t coerceOneWay MyTrue<br>
coerceOneWay MyTrue :: Bool<br>
<br>
I think it's a matter of preference as to which way you go.<br>
<span class="HOEnZb"><font color="#888888"><br>
<br>
--<br>
Mateusz K.<br>
</font></span><div class="HOEnZb"><div class="h5">_______________________________________________<br>
Beginners mailing list<br>
<a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/beginners" target="_blank">http://www.haskell.org/mailman/listinfo/beginners</a><br>
</div></div></blockquote></div><br></div></div>