[Haskell-cafe] Typeclass with an ‘or’ restriction.

Adam Gundry adam.gundry at strath.ac.uk
Fri May 10 17:10:07 CEST 2013


Hi Mateusz,

It's not directly possible to write a class with a choice of
superclasses; as you point out, it's not really clear what that would
mean. One workaround, though it might not be sensible in practice, is
the following.

> {-# LANGUAGE ConstraintKinds, GADTs #-}

First, reify the constraints we are interested in as types that pack up
the corresponding dictionary. Thanks to ConstraintKinds, it's possible
to do this once and for all.

> data Dict c where
>   Dict :: c => Dict c

Now we can describe types with either Num or Eq dictionaries (or both)
as a class.  The proxy argument makes it easy to specify the type, in
the absence of explicit type application.

> class NumOrEq a where
>   numOrEq :: proxy a -> Either (Dict (Num a)) (Dict (Eq a))

Something like your Foo class can then be defined like this:

> class NumOrEq a => Foo a where
>   bar :: a -> a -> Bool
>   bar x y = case numOrEq [x] of
>                 Left Dict   -> False
>                 Right Dict  -> x == y

When giving an instance for NumOrEq, you must choose which dictionary to
pack up if both are available.

> instance NumOrEq Int where
>   numOrEq _ = Left Dict

> instance NumOrEq Bool where
>   numOrEq _ = Right Dict

> instance Foo Int
> instance Foo Bool

And with all that, we have:

> bar 3 (3 :: Int) == False
> bar True True == True

Now I'm wondering why we would want that in the first place.

Hope this helps,

Adam


On 10/05/13 14:58, Mateusz Kowalczyk wrote:
| Greetings,
|
| We can currently do something like
|> class (Num a, Eq a) => Foo a where bar :: a -> a -> Bool bar =
|> (==)
|
| This means that our `a' has to be an instance of Num and Eq. Apologies
| for a bit of an artificial example.
|
| Is there a way however to do something along the lines of:
|> class Eq a => Foo a where bar :: a -> a -> Bool bar = (==)
|
|> class Num a => Foo a where bar :: a -> a -> Bool bar _ _ = False
| This would allow us to make an instance of Num be an instance of Foo
| or an instance of Eq to be an instance of Foo.
|
| The compiler currently complains about multiple declarations. Is there
| currently a way to achieve this?
|
| The main issue I can see with this is that given an instance of both,
| Num and Eq, it wouldn't be possible to pick the correct default
| implementation.
|
| Purely a theoretical question.


-- 
The University of Strathclyde is a charitable body, registered in
Scotland, with registration number SC015263.



More information about the Haskell-Cafe mailing list