Shersh
Shersh

Reputation: 9169

How to implement default associated type family for OVERLAPPABLE instance, monomorphic container and newtype wrapper?

I had the following Haskell code:

type family Element t

class ToList t where
    toList :: t -> [Element t]

It was suggested to me earlier to make Element an associated type family: Foldable IntSet

I tried to implement this approach. But it doesn't work for my case. Here is the whole code:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}

import Prelude hiding (toList)
import qualified Data.Foldable as Foldable (toList)
import Data.Text (Text, unpack)

class ToList t where
    type Element t :: *
    toList :: t -> [Element t]

-- | This instance makes 'ToList' compatible and overlappable by 'Foldable'.
instance {-# OVERLAPPABLE #-} Foldable f => ToList (f a) where
    type Element (f a) = a
    toList = Foldable.toList

instance ToList Text where
    type Element Text = Char
    toList = unpack

newtype WrappedList l = WrappedList l

instance ToList l => ToList (WrappedList l) where
    type Element (WrappedList l) = Element l
    toList (WrappedList l) = toList l

When I compile this code with GHC-8.2.2 I see the following error:

Element.hs:14:10: error:
    Conflicting family instance declarations:
      Element (f a) = a -- Defined at Element.hs:14:10
      Element (WrappedList l) = Element l -- Defined at Element.hs:24:10
   |
14 |     type Element (f a) = a
   |          ^^^^^^^^^^^^^^^^^

How I can fix this error? I have no idea how make this compilable with associated type family...

Upvotes: 4

Views: 840

Answers (1)

user2407038
user2407038

Reputation: 14578

The essential problem is that you can't use to type class overlap to make type families which overlap. It simply doesn't make sense - a type family computes a type from an input type, and the resulting type may not depend on how the compiler picks a type class instance (or else it wouldn't be a function - since the output of a function may only depend on the input). This problem is quite common, but how you solve it depends entirely on your specific use case.

The simplest solution is to give your default implementation using DefaultSignatures. Note that associated type families can have defaults as well:

type family ElementDefault (t :: *) :: * where
  ElementDefault (f a) = a

class ToList t where
    type Element t :: *
    type Element t = ElementDefault t

    toList :: t -> [Element t]
    default toList :: (Foldable f, t ~ f a, Element t ~ a) => t -> [Element t]
    toList = Foldable.toList

This allows you to write instances for all Foldable types without giving the implementation:

instance ToList [a]
instance ToList (Maybe a)
-- etc...

If you want to avoid writing such instances (even the instance heads), you need to move the associated type into the class instance head. Since it is only classes which may overlap, not open type families, doing so allows the 'element' type to also be overlapping.

class ToList t e | t -> e where
  toList :: t -> [e]

instance {-# OVERLAPPABLE #-} (a ~ a', Foldable f) => ToList (f a) a' where
  toList = Foldable.toList

instance ToList Text Char where
  toList = unpack

instance ToList l a => ToList (WrappedList l) a where
  toList (WrappedList l) = toList l

The simplest way to provide multiple default definitions is to provide them outside of the class. If you have 15 class functions, this indeed can be tedious. In such a situation, I would implement the class with a record:

data ToList' t e = ToList'
  { toList' :: t -> [e] {- 14 more fields... -} }

class ToList t where
  type Element t 
  toList_impl :: ToList' t (Element t)

-- For consumers of ToList
toList :: ToList t => t -> [Element t]
toList = toList' toList_impl

instance ToList Text where
  type Element Text = Char
  toList_impl = ToList' unpack

toList_Foldable_default :: Foldable f => ToList' (f a) a
toList_Foldable_default = ToList' Foldable.toList

toList_Wrapped_list :: ToList l => ToList' l (Element l)
toList_Wrapped_list = ToList' toList

With this approach, you can dispense with the typeclass entirely; its only remaining use is to get instance uniqueness.

Upvotes: 9

Related Questions