[Haskell-beginners] Question about define my own typeclass

Mateusz Kowalczyk fuuzetsu at fuuzetsu.co.uk
Thu Mar 27 16:36:12 UTC 2014


On 27/03/14 15:49, ke dou wrote:
> Thanks for your reply.
> 
> Yes, I understand that if I specify the 'b' to 'Prelude.Bool', it should
> work, but what if I also want use the typeclass Conversion to convert other
> types other than MyBool, like MyInt, or MyString?
> 
> --Ke
> 
> On Thu, Mar 27, 2014 at 11:36 AM, Brandon Allbery <allbery.b at gmail.com>wrote:
> 
>> On Thu, Mar 27, 2014 at 11:28 AM, ke dou <kd6ck at virginia.edu> wrote:
>>
>>>     class Conversion a where
>>>         conversion :: a  -> b
>>>
>>
>> b is completely unspecified here, since it's not defined as part of the
>> typeclass. The literal meaning of this is that "the caller can request any
>> type it pleases, and you have no way of knowing what it is". So the only
>> possible result of `conversion` is bottom (e.g. `undefined`).
>>
>> This is key: it does NOT mean that `conversion` gets to specify the result
>> type! You can't do that, except by specifying the type in the type
>> signature.
>>
>> --
>> brandon s allbery kf8nh                               sine nomine
>> associates
>> allbery.b at gmail.com
>> ballbery at sinenomine.net
>> unix, openafs, kerberos, infrastructure, xmonad
>> http://sinenomine.net
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>>
> 
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
> 

This post is Literate Haskell.

You can specify which type you can coerce to by having the typeclass
also specify ‘b’.

To have more than one type parameter, you'll need the MultiParamTypeClasses
language extension. Ignore FunctionalDependencies for now.

> {-# LANGUAGE FunctionalDependencies #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE UnicodeSyntax #-}
> module C where

First we define our own Bool for demonstration purposes.

> data MyBool = MyTrue | MyFalse

We define the class that also specifies ‘b’ as follows.

> class SimpleCoercible a b where
>   coerceSimple ∷ a → b

We can now achieve what you want: we can state that ‘a’ cana be
coerced into ‘b’. Here we state that we can convert to Haskell's Bool.

> instance SimpleCoercible MyBool Bool where
>   coerceSimple MyTrue = True
>   coerceSimple MyFalse = False

This works fine:

*C> coerceSimple MyTrue :: Bool
True

Note that I had to say what output type I wanted here because I'm not
using it
in a context that GHC could use to infer it. Just because there's only a
single
instance does not matter as anyone could come around and add a new
instance. In
fact, let's define one more just to show that you can do it. Let's go
with the
old 0 is True and 1 is False.

> instance SimpleCoercible MyBool Integer where
>   coerceSimple MyTrue = 0
>   coerceSimple MyFalse = 1

As you can see below, it all works great:

*C> coerceSimple MyTrue :: Integer
0
*C> coerceSimple MyTrue :: Bool
True


Now for something a bit out of scope of the question:

Now what if we wanted to only have a single possible mapping? Say, we
only want
MyBool to be coercible to Bool and nothing else? We can use
FunctionalDependencies language extension. I recommend you look it up if
you're
interested, here's an example:


> class CoercibleOneWay a b | a → b where
>   coerceOneWay ∷ a → b
>
> instance CoercibleOneWay MyBool Bool where
>   coerceOneWay MyTrue = True
>   coerceOneWay MyFalse = False

You might wonder if there's an advantage to doing such a thing. Well,
yes, GHC
now always knows what the output type (b) should be just by looking by
the input
type (a):

*C> :t coerceOneWay MyTrue
coerceOneWay MyTrue :: Bool

Note that this is not the case with our previous definition! GHC doesn't
know
exactly which ‘b’ we want:

*C> :t coerceSimple MyTrue
coerceSimple MyTrue :: SimpleCoercible MyBool b => b


Can we do more than this? What if we wanted to be able to coerce the
types the
other way too? We could write an instance for
“CoercibleOneWay Bool MyBool | b → a” but that's unwieldy. We can
instead have
a single type class which can take us both ways:

> class Coercible a b | a → b, b → a where
>   coerceTo ∷ a → b
>   coerceFrom ∷ b → a
>
> instance Coercible MyBool Bool where
>   coerceTo MyTrue = True
>   coerceTo MyFalse = False
>
>   coerceFrom True = MyTrue
>   coerceFrom False = MyFalse

This now lets us convert between MyBool and Bool freely:

*C> :t coerceTo MyTrue
coerceTo MyTrue :: Bool
*C> :t coerceFrom True
coerceFrom True :: MyBool

With this you can model 1-to-1 mapping between your types and built-in
types.

Note that another approach would simply be to add an instance for
“CoercibleOneWay Bool MyBool”. A nice thing about this approach is that
you can
use the overloaded function name:

> instance CoercibleOneWay Bool MyBool where
>   coerceOneWay True = MyTrue
>   coerceOneWay False = MyFalse

*C> :t coerceOneWay True
coerceOneWay True :: MyBool
*C> :t coerceOneWay MyTrue
coerceOneWay MyTrue :: Bool

I think it's a matter of preference as to which way you go.


-- 
Mateusz K.


More information about the Beginners mailing list