[Haskell-cafe] Avoiding name collisions by using value spaces instead of modules

Cale Gibbard cgibbard at gmail.com
Sun Jan 8 19:51:05 EST 2006


> Unifying these two under a single operation is certainly trickier, and
> it's a little more questionable that it should be done at all, given
> that their types are so different -- below is the closest I could come
> to it off-hand.
>
> ---
> {-# OPTIONS_GHC -fglasgow-exts #-} -- for fundeps/multiparameter classes
> import qualified Data.Map as Map
> import Data.Map (Map)
> import qualified Data.Set as Set
> import Data.Set (Set)
>
> class Insert t c a | c a -> t where
>     insert :: t -> c a -> c a
>
> instance (Ord a) => Insert a Set a where
>     insert x s = Set.insert x s
>
> instance (Ord k) => Insert (k,a) (Map k) a where
>     insert (k,v) m = Map.insert k v m
>
> exampleSet = insert 5 $ insert 6 $ Set.empty
> exampleMap = insert (1,2) $ insert (2,7) $ Map.empty
>
> ----
>
> Perhaps someone else will have some ideas as to suitable typeclass
> magic to allow for the curried form rather than using tuples.
>
>  - Cale
>

Oh, this is a little less general, but simpler to use:

{-# OPTIONS_GHC -fglasgow-exts #-}
import qualified Data.Map as Map
import Data.Map (Map)
import qualified Data.Set as Set
import Data.Set (Set)

class Insert t c | c -> t where
    insert :: t -> c -> c

instance (Ord a) => Insert a (Set a) where
    insert x s = Set.insert x s

instance (Ord k) => Insert (k,a) (Map k a) where
    insert (k,v) m = Map.insert k v m

exampleSet = insert 5 $ insert 6 $ Set.empty
exampleMap = insert (1,2) $ insert (2,7) $ Map.empty


More information about the Haskell-Cafe mailing list