[Haskell-cafe] common class for Set (and Map, resp.) implementations with different constraints on the keys

David Feuer david.feuer at gmail.com
Fri Sep 7 15:51:01 UTC 2018


In my opinion, such a class should usually have more than one parameter. In
the case of Set, I think it makes more sense to use a value type than a
constraint type.

class e ~ Elem s => SetC e s where
  type Elem s :: Type
  type Elem (_ a) = a
  singleton :: e -> s
  elem :: e -> s -> Bool
  union :: s -> s -> s
  ...

instance Ord a => SetC a (S.Set a) where
  singleton = S.singleton
  ...
instance a ~ Int => SetC a IntSet where
  type Elem IntSet = Int
  ...

For maps, you can do something similar:

class k ~ Key m => MapC k m where
  type Key m :: Type
  type Key (_ k) = k
  lookup :: k -> m a -> Maybe a
  ...

instance Ord k => MapC k (M.Map k) where
  lookup = M.lookup
  ....

instance k ~ Int => MapC k IM.IntMap where
  type Key IntMap = Int
  lookup = IM.lookup

If you like, you can add some constraints, like Traversable m. If you want
to use MFoldable for sets, you can use its Element type family instead of
Elem.

On Fri, Sep 7, 2018, 11:25 AM Johannes Waldmann <
johannes.waldmann at htwk-leipzig.de> wrote:

> Dear Cafe,
>
>
> we have Data.Set, Data.IntSet, Data.HashSet,
> and they all have similar API, where the only difference
> is the constraint on the elements. (Same thing for maps.)
>
> Can we unify this as follows:
>
> {-# language ConstraintKinds, TypeFamilies #-}
> class SetC s where
>   type Con s :: * -> Constraint
>   singleton :: (Con s a) => a -> s a
>   foldMap :: (Con s a, Monoid m) => (a -> m) -> s a -> m
>   ...
>
> Then for Data.Set, we write
>
> instance SetC S.Set where  type Con S.Set = Ord ; ...
>
> It seems to work, and it allows me to write polymorphic code,
> and switch implementations from the top.
> Full source:
>
> https://gitlab.imn.htwk-leipzig.de/waldmann/pure-matchbox/tree/master/src/Data/Set
> Example use case (switch implementation):
>
> https://gitlab.imn.htwk-leipzig.de/waldmann/pure-matchbox/blob/master/src/Matchbox/Tiling/Working.hs#L48
>
>
>
> Still, there are some clumsy corners in this code, perhaps you can help:
>
>
> * for  instance SetC HashSet, there are two constraints. I want to write
>
> type Con HashSet = \ e -> (Hashable e, Eq, e)
>
> but this does not work (there is no "type lambda"?)
>
>
> * for maps, I want to write
>
> class (forall k . Foldable m k) => MapC m
>
> but this seems impossible now (This is would work
> with  -XQuantifiedConstraints ?)
>
>
> * in some other code using the same idea (the class exports the
> constraint), I had an instance where the constraint was empty.
>
> Again, I cannot write  type Con Foo = \ s -> ()
>
>
> - J.W.
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20180907/c99a1e80/attachment.html>


More information about the Haskell-Cafe mailing list