
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

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. Twan

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

On 29 February 2012 19:54, Daniel Gorín
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.
I guess the way forward is to start using ConstraintKinds and TypeFamilies: {-# LANGUAGE ConstraintKinds, TypeFamilies, FlexibleInstances #-} import Prelude hiding (Functor, fmap) import Data.Set (Set) import qualified Data.Set as Set (map) import GHC.Exts (Constraint) class Functor f where type FunctorConstraint f :: * -> Constraint type FunctorConstraint f = Empty fmap :: (FunctorConstraint f b) => (a -> b) -> f a -> f b class Empty a instance Empty a instance Functor Set where type FunctorConstraint Set = Ord fmap = Set.map -- Note that the unnecessary 'Ord a' constraint needs to be dropped from: -- Set.map :: (Ord a, Ord b) => (a -> b) -> Set a -> Set b Regards, Bas

On Thu, 2012-03-01 at 09:31 +0100, Bas van Dijk wrote:
On 29 February 2012 19:54, Daniel Gorín
wrote: 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.
I guess the way forward is to start using ConstraintKinds and TypeFamilies: [...]
This doesn't really solve the problem I was looking at (namely, making an ordered-tree-based implementation of a Set type an instance of the standard Functor class) but I find it very interesting nevertheless. I need to look at this ConstraintKinds extension in more detail.... Thanks, Daniel

On 01/03/12 09:31, Bas van Dijk wrote:
class Functor f where type FunctorConstraint f :: * -> Constraint type FunctorConstraint f = Empty
fmap :: (FunctorConstraint f b) => (a -> b) -> f a -> f b
class Empty a instance Empty a
Do you really need this Empty class? That seems inconvenient. I had hoped you would be able to write something like type FunctorConstraint f :: * -> Constraint type FunctorConstraint f a = () Twan

On Thu, Mar 1, 2012 at 1:20 PM, Twan van Laarhoven
On 01/03/12 09:31, Bas van Dijk wrote:
class Functor f where type FunctorConstraint f :: * -> Constraint type FunctorConstraint f = Empty
fmap :: (FunctorConstraint f b) => (a -> b) -> f a -> f b
class Empty a instance Empty a
Do you really need this Empty class?
Depends on what you want. You do need it if you want to be able to use 'FunctorConstraint f' itself as a type of kind * -> Constraint, for example to say type FunctorWithoutConstraint f = (Functor f, FunctorConstraint f ~ Empty).
That seems inconvenient. I had hoped you would be able to write something like
type FunctorConstraint f :: * -> Constraint type FunctorConstraint f a = ()
See this thread: http://www.mail-archive.com/glasgow-haskell-users@haskell.org/msg20792.html

On 1 March 2012 13:20, Twan van Laarhoven
On 01/03/12 09:31, Bas van Dijk wrote:
class Functor f where type FunctorConstraint f :: * -> Constraint type FunctorConstraint f = Empty
fmap :: (FunctorConstraint f b) => (a -> b) -> f a -> f b
class Empty a instance Empty a
Do you really need this Empty class? That seems inconvenient. I had hoped you would be able to write something like
type FunctorConstraint f :: * -> Constraint type FunctorConstraint f a = ()
Twan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
In GHC-7.4.1 that will give the following error: Number of parameters must match family declaration; expected 1 In the type synonym instance default declaration for `FunctorConstraint' However, I believe SPJ fixed this in HEAD. Bas
participants (4)
-
Bas van Dijk
-
Daniel Gorín
-
Gábor Lehel
-
Twan van Laarhoven