[Haskell-cafe] Kind-agnostic type classes

Florian Weimer fw at deneb.enyo.de
Fri Oct 3 12:46:44 EDT 2008


* Luke Palmer:

>> For instance, I've got
>>
>> class Assignable a where
>>    assign :: a -> a -> IO ()
>>
>> class Swappable a where
>>    swap :: a -> a -> IO ()
>>
>> class CopyConstructible a where
>>    copy :: a -> IO a
>>
>> class (Assignable a, CopyConstructible a) => ContainerType a
>>
>> class (Swappable c, Assignable c, CopyConstructible c) => Container c where
>>    size :: (Num i, ContainerType t) => c t -> IO i
>
> Which is illegal because the three above classes force c to be kind *,
> but you're using it here as kind * -> *.
>
> What you want is not this informal "kind-agnostic" classes so much as
> quantification in constraints, I presume.  This, if it were supported,
> would solve your problem.
>
> class (forall t. Swappable (c t), forall t. Assignable (c t), forall
> t. CopyConstructible (c t)) => Contanter c where ...

In the meantime, I figured out that in ML, it suffices to make the
Container type c non-polymorphic (although the syntactic overhead is
rather problematic).  Trying to the same in Haskell, I learnt something
about functional dependencies.  I actually ended up with:

class (Assignable c, CopyConstructible c, Swappable c, ContainerType t, Num s)
    => Container c s t | c -> s, c -> t where
    size :: c -> IO Int
    empty ::c -> IO Bool

    empty c = do
      sz <- size c
      return (sz == 0)

(In fact, I stumbled across "A Comparative Study of Language Support for
Generic Programming" by Garcia et al., which contains a very helpful
Haskell example with functional dependencies and multi-parameter type
classes.)


More information about the Haskell-Cafe mailing list