3
votes

I'd like a 'generic' map data structure that can be efficiently specialized by providing custom instances, much like in the GHC manual section on type families.

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

module MapKey where

import           Data.Map.Strict    (Map)
import qualified Data.Map.Strict    as Map

class MapKey k where
  data MMap k :: * -> *

instance {-# OVERLAPPING #-} MapKey () where
  newtype MMap () v = UnitMap (Maybe v)

instance {-# OVERLAPPABLE #-} Ord k => MapKey k where
  newtype MMap k v = OrdMap (Map k v)

Sadly, this doesn't work. GHC (8.2.1) complains:

    Conflicting family instance declarations:
      MMap () = UnitMap (Maybe v)
      MMap = OrdMap (Map k v)
   |
14 |   newtype MMap () v = UnitMap (Maybe v)
   |

Is there some language extension which allows this? Otherwise is there another way to make it easy for users to define a 'default' instance for Ord?

1
Data families must not be overlapping. Type safety no longer holds otherwise... Interesting idea though.Alec
Why so? Are there situations in which overlaps with associated types are unsafe where overlapping methods alone are still safe? I.o.w. when are overlapping type families 'more unsafe' than overlapping type classes?Sebastian Graf
Overlapping associated type families are fine, just not data families. Polymorphism breaks down with overlapping data families. Here's a sketch.Alec
(Continuing discussion in that gist)Sebastian Graf

1 Answers

2
votes

One solution that relinquishes overlapping instances is to use a default associated injective type family (quite a mouthful). I also attached some methods with default implementations for the default MMap synonym:

{-# LANGUAGE DefaultSignatures      #-}
{-# LANGUAGE TypeFamilies           #-}
{-# LANGUAGE TypeFamilyDependencies #-}

module MapKey where

import           Data.Map.Strict    (Map)
import qualified Data.Map.Strict    as Map

class MapKey k where
  type MMap k v = r | r -> k v
  type MMap k v = Map k v
  empty :: MMap k v
  default empty :: (MMap k v ~ Map k v) => MMap k v
  empty = Map.empty
  insert :: k -> v -> MMap k v -> MMap k v
  default insert :: (MMap k v ~ Map k v, Ord k) => k -> v -> MMap k v -> MMap k v
  insert = Map.insert
  lookupLE :: k -> MMap k v -> [(k, v)]
  default lookupLE :: (MMap k v ~ Map k v, Ord k) => k -> MMap k v -> [(k, v)]
  lookupLE k m =
    case Map.lookupLE k m of
      Nothing -> []
      Just e -> [e]

instance MapKey () where
  type MMap () v = Maybe v
  empty = Nothing
  insert _ v _ = Just v
  lookupLE _ m =
    case m of
      Nothing  -> []
      (Just v) -> [((), v)]

This means that client code still has to define boilerplate orphan instances like

instance MapKey Int

I'd rather see a solution that uses overlapping instances instead.