Functor instance for Set?

Daniel Gorín dgorin at dc.uba.ar
Thu Mar 1 09:33:31 CET 2012


On Feb 29, 2012, at 8:21 PM, Twan van Laarhoven wrote:

> On 2012-02-29 19:54, Daniel Gorín wrote:
>> Hi
>> 
>> ...
>> 
>> 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.
> 
> A problem is that you lose complexity guarantees. Consider for example:
> 
>    let ints = [0..1000000]
>    let setA = Set.fromList ints
>    let setB = fmap id setA
>    let slow = all (`Set.member` setB) ints
> 
> Each call to Set.member in slow will take O(n) instead of the expected O(log n), which means that this code takes O(n^2) instead of O(n*log n). The problem is that you keep converting the same set from a list to a tree over and over again.

Right, good point, updating a set after an fmap is ok, but querying is not. What one would need, then, is querying the set to have also the side-effect of updating the internal representation, from [a] to BST. This seems doable using an IORef and unsafePerformIO (example below). It is ugly but still referentially transparent (I think). Would this work in practice?

Daniel

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

import Data.IORef
import System.IO.Unsafe ( unsafePerformIO )

newtype Set a = Set{unSet :: IORef (Either (Internal.Set a) [a])}

toInternal :: Ord a => Set a -> Internal.Set a
toInternal (Set ref) = unsafePerformIO $
    do e <- readIORef ref
       case e of
         Left  s -> return s
         Right l -> do let s = Internal.fromList l
                       writeIORef ref (Left s)
                       return s

mkSet :: Either (Internal.Set a) [a] -> Set a
mkSet e = unsafePerformIO $
    do ref <- newIORef e
       return (Set ref)

list :: [a] -> Set a
list = mkSet . Right

this :: Internal.Set a -> Set a
this = mkSet . Left

toAscList :: Ord a => Set a -> [a]
toAscList = Internal.toAscList . toInternal

toList :: Set a -> [a]
toList = unsafePerformIO . fmap (either (Internal.toList) id) . readIORef . unSet

-- 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 = mkSet . Right . 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

member :: Ord a => a -> Set a -> Bool
member a = Internal.member a . toInternal




More information about the Libraries mailing list