One of the best features of Haskell are typeclasses. Still, it is not easily possible to have multiple implementation of the same typeclass for the same data type. For example, to define an additive and a multiplicative instance of Monoid on Int, one needs to use specific newtype wrappers such as Sum and Product.

On the other hand, in Idris it is possible to define multiple named implementations of the same typeclass for the same data type.

A question now naturally arises:

Some extensions later…

Almost immediately Sjoerd came to the rescue and proposed the following

Let’s briefly review what these mentioned things are.

A phantom type is a parametrised type whose parameters do not all appear on the right-hand side of its definition.

For example newtype Const a b = Const { getConst :: a } is a phantom type because the parameter b does not appear after the = sign.

Phantom types are useful because they allow to add at the type level information which is not present at the value level.

A type parameter is said to be ambiguous if it can not be correctly inferred by the type checker. This happens with phantom types because the compiler, having no way to infer the actual type of the phantom parameter, considers it ambiguous. The extension AllowAmbiguousTypes allows us to ask the compiler to be a little more patient and not error immediately when it detects an ambiguous type.

Still, since the compiler is not able to infer it, we need a way to manually specify the value of an ambiguous type. This is possible with the @ syntax using the TypeApplications extension.

Let’s see these techniques in action while we try to solve our initial question.

Named typeclasses

We will start from the

class Monoid a where
  (<>)   :: a -> a -> a
  mempty :: a

typeclass, which lives in the Haskell Prelude.

As Sjoerd suggested, we can start by adding a new type parameter to it, which will be used later to do some type-level magic.

{-# LANGUAGE AllowAmbiguousTypes    #-}
{-# LANGUAGE MultiParamTypeClasses  #-}

class Monoid b a where
  (<>)   :: a -> a -> a
  mempty :: a

Then we can define some instances on the Int type.

import Prelude hiding (Monoid, mempty, (<>))

data Sum
data Product

instance Monoid Sum Int where
  x <> y = x + y
  mempty = 0

instance Monoid Product Int where
  x <> y = x * y
  mempty = 1

We need to define the ancillary data types Sum and Product, whithout any constructor, which we use as tags to distinguish the two different implementations of Monoid on Int1.

Next we want to define a function which uses our Monoid class. One typical operation which is performed on Monoids is a fold which recursively combines the elements of a list into a single element.

fold :: Monoid b a => [a] -> a

To implement it we actually need to use TypeApplications but also the ScopedTypeVariables extension. This is due to the fact that generally type variables have no notion of scope; this means that anytime we would use (<>) or mempty, the compiler would introduce a new b type variable. This leads to errors as Could not deduce (NamedTypeclass.Monoid b0 a) from the context: NamedTypeclass.Monoid b a, leaving us to wonder where that b0 comes from. ScopedTypevariables allows us to use the forall keyword to define explicitly the scope of a type variable.

Our definition of fold then becomes

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications    #-}

fold :: forall b a . Monoid b a => [a] -> a
fold []       = mempty @b
fold (x : xs) = (<>) @b x (fold @b xs)

Notice also how we had to use the @ syntax of TypeApplications to explicitly state that we are using the same b everywhere.

At this point it becomes just a matter of using TypeApplications to define specific folds on both our instances of Monoid.

For example we could define

sum :: [Int] -> Int
sum = fold @Sum

product :: [Int] -> Int
product = fold @Product

This allows us to use two different instances of the Monoid class on the same Int data type, without having to resort to newtype wrappers.

Single instances

Suppose now that for a datatype we want to define a unique instance of Monoid, as we did in the good old days when the phantom parameter b was not there.

For example, suppose that for lists we always want to define the same instance of Monoid, where the operation is given by concatenation.

{-# LANGUAGE FlexibleInstances #-}

instance Monoid b [a] where
  x <> y = x ++ y
  mempty = []

Notice that we needed to enable the FlexibleInstances extension, which allows us to use [a] as a type parameter.

Our instance definition amounts to say that for any possible b the definition of our instance is the same. The compiler is then smart enough to use this information and actually not require us to write any TypeApplication when we use the fold function on the [a] data type.

concat :: [[a]] -> [a]
concat = fold

Conclusion

We just went through a possible way to implement named typeclasses in Haskell. It could be a useful technique for newly defined typeclasses which you control, while it still remains hard to make such an approach interact nicely with already defined typeclasses.

There are other approaches to this same problem, as mentioned by @Iceland_jack

If you want to take a look at complete code, take a look at this gist.


  1. Again from Sjoerd: if you want, you could use GHC.Types (Symbol) and write instance Monoid "sum" Int where ... and avoid defining the ancillary types.