Functor instance for Set?

Daniel Gorín dgorin at dc.uba.ar
Wed Feb 29 19:54:01 CET 2012


Hi

I was always  under the impression that the fact that Data.Set.Set can not be made an instance of Functor was a sort of unavoidable limitation. But if we look at the definition of Data.Set.map:

map :: (Ord a, Ord b) => (a->b) -> Set a -> Set b
map f = fromList . List.map f . toList

we see that 1) "Ord a" is not really used and 2) "Ord b" is only needed for the final fromList. Since every interesting function in Data.Set requires an Ord dictionary anyway, one could implement fmap using only the "List.map f . toList" part and leave the "fromList" to the successive function calls.

It appears to me, then, that if "Set a" were implemented as the sum of a list of a and a BST, it could be made an instance of Functor, Applicative and even Monad without affecting asymptotic complexity (proof of concept below). Am I right here? Would the overhead be significant? The one downside I can think of is that one would have to sacrifice the Foldable instance.

Thanks,
Daniel

import qualified Data.Set as Internal
import Data.Monoid
import Control.Applicative

data Set a = This (Internal.Set a) | List [a]

toInternal :: Ord a => Set a -> Internal.Set a
toInternal (This s) = s
toInternal (List s) = Internal.fromList s

toAscList :: Ord a => Set a -> [a]
toAscList (This s)   = Internal.toAscList s
toAscList (List s) = Internal.toAscList $ Internal.fromAscList s

toList :: Set a -> [a]
toList (This s) = Internal.toList s
toList (List s) = s

-- Here we break the API by requiring (Ord a).
-- We could require (Eq a) instead, but this would force us to use
-- nub in certain cases, which is horribly inefficient.
instance Ord a => Eq (Set a) where
  l == r = toInternal l == toInternal r

instance Ord a => Ord (Set a) where
  compare l r = compare (toInternal l) (toInternal r)

instance Functor Set where
  fmap f = List . map f . toList

instance Applicative Set where
  pure = singleton
  f <*> x = List $ toList f <*> toList x

instance Monad Set where
  return  = pure
  s >>= f = List $ toList s >>= (toList . f)

empty :: Set a
empty = This Internal.empty

singleton :: a -> Set a
singleton = This . Internal.singleton

insert :: Ord a => a -> Set a -> Set a
insert a = This . Internal.insert a . toInternal

delete :: Ord a => a -> Set a -> Set a
delete a = This . Internal.delete a . toInternal

instance Ord a => Monoid (Set a) where
    mempty = This mempty
    mappend (This l) (This r) = This (mappend l r)
    mappend l r = This . Internal.fromAscList $ mergeAsc (toAscList l) (toAscList r)
      where mergeAsc :: Ord a => [a] -> [a] -> [a]
            mergeAsc [] ys = ys
            mergeAsc xs [] = xs
            mergeAsc ls@(x:xs) rs@(y:ys) = case compare x y of
                                             EQ -> x : mergeAsc xs ys
                                             LT -> x : mergeAsc xs rs
                                             GT -> y : mergeAsc rs ys




More information about the Libraries mailing list