Superclass Cycle via Associated Type

Edward Kmett ekmett at gmail.com
Thu Jul 21 20:36:41 CEST 2011


*Simon Peyton-Jones* simonpj at microsoft.com
<glasgow-haskell-users%40haskell.org?Subject=Re%3A%20Superclass%20Cycle%20via%20Associated%20Type&In-Reply-To=%3C59543203684B2244980D7E4057D5FBC125661A72%40DB3EX14MBXC308.europe.corp.microsoft.com%3E>
------------------------------

You point is that the (C Int) dictionary has (C String) as a superclass, and
> (C String) has (C Int) as a superclass. So the two instances are mutually
> recursive, but that's ok.
> That is not unreasonable. But it is dangerous. Consider
> class C [a] => C a
> Then any dictionary for (C a) would contain a dictionary for (C [a]) which
> would contain a dictionary for C [[a]], and so on. Haskell is lazy so we
> might even be able to build this infinite dictionary, but it *is* infinite.
> It's a bit like the "recursive instance" stuff introduced in "Scrap your
> boilerplate with class".
> After 5 mins thought I can't see a reason why this could not be made to
> work. But it'd take work to do. If you have a compelling application maybe
> you can open a feature request ticket, describing it, and referring this
> thread?
> Has anyone else come across this?
>

Yes. This is actually an active problem for me in my 'algebra' package.

We can define additive, additive abelian and multiplicative semigroups:

class Additive m where (+) :: m -> m -> m
class Additive m => Abelian m
class Multiplicative m where (*) :: m -> m -> m

then we can define semirings (in the semirings are semigroups with
distributive laws sense):

class (Additive m, Abelian m, Multiplicative m) => Semiring m

then to define monoids, we enforce the fact that every additive monoid is a
module over the naturals.

class (Semiring r, Additive m) => LeftModule r m where
  (.*) :: r -> m -> m
class LeftModule Natural m => Monoidal m where

This makes it an obligation of anyone that provides a Monoidal instance to
ensure that they also supply the LeftModule, side-stepping what would be a
hugely overlapping instance, and ensuring we can rely on it.

But we weren't able to exploit the fact that any Additive semigroup forms a
module over N+, due to the cycle.

Moreover, we also weren't able to encode that every semiring is a module
over itself.

If we could have superclass cycles, we could restate this all as

class LeftModule Whole m => Additive m where (+) :: m -> m -> m
class Additive m => Abelian m
class (Semiring r, Additive m) => LeftModule r m where (.*) :: r -> m -> m
class Multiplicative m where (*) :: m -> m -> m
class LeftModule Natural m => Monoidal m where zero :: m
class (Abelian m, Multiplicative m, LeftModule m m) => Semiring m
class (LeftModule Integer m, Monoidal m) => Group m where recip :: m -> m
class Multiplicative m => Unital m where one :: m
class (Monoidal r, Unital r, Semiring r) => Rig r where
  fromNatural :: Natural -> r
  fromNatural n = n .* one
class (Rig r, Group r) => Ring r where
  fromInteger :: Integer -> r
  fromInteger n = n .* one
...

There are a number of typeclass cycles in there, but I can safely
instantiate the whole mess without any overlapping instances and I already
have to ball all of these classes up in the same 'Internals' module to avoid
orphans instances anyways.

Using the usual dodge of a newtype to provide Self module over any given
semiring is particularly unsatisfying because the Natural and Integer
multiplication become horrific, and I wind up having to multiply the code
below this point in the hierarchy to deal with the 'self algebra' cases. =/

I've also run into the problem about once or twice a year when encoding
other concepts that are usually more categorical in nature.

I would love to be able to do this.

-Edward Kmett
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20110721/27207424/attachment.htm>


More information about the Glasgow-haskell-users mailing list