[Haskell-beginners] How to avoid repeating code
Daniel Fischer
daniel.is.fischer at googlemail.com
Thu May 26 13:47:40 CEST 2011
On Thursday 26 May 2011 02:23:06, Federico Mastellone wrote:
> Hi,
>
> I created a Data.MultiMap module based on Data.Map and Data.Set like
> this:
>
> data MultiMap k v = MultiMap (Map k (Set v))
>
> and a Data.IntMultiMap module based on Data.IntMap and data.IntSet like
> this:
>
> data IntMultiMap = IntMultiMap (IntMap IntSet)
Both of these would better be newtypes instead of data, I think.
Using data incurs some run-time overhead (the newtype doesn't exist at run-
time, only during compile-time [type checking phase], so it's a strictly
controlled type alias in practice, making it easier [or possible at all] to
apply optimisations available for the underlying type) due to the extra
indirections via the constructor and introduces the new value
(MultiMap _|_), which complicates strictness analysis and optimisations in
general.
>
> For example the functions to add a value I wrote are:
>
> For MultiMap:
> addValue :: k -> v -> MultiMap k v -> MultiMap k v
> addValue k v (MultiMap m) = MultiMap $ Map.insertWith (\new old ->
> Set.insert v old) k (Set.singleton v) m
>
> For IntMultiMap:
> addValue :: Int -> Int -> IntMultiMap -> IntMultiMap
> addValue k v (IntMultiMap m) = IntMultiMap $ IntMap.insertWith (\new old
> -> IntSet.insert v old) k (IntSet.singleton v) m
>
> Both modules look almost the same, with the same
> documentation, same behavior, same function names but with different
> type signatures.
Well, we have the same situation with Map/IntMap and Set/IntSet, so
>
> Is there a way to make this simpler?
Not a really good one (at least, none I know).
>
> The same thing happens to the modules that are using MultiMap and
> IntMultiMap, I have to write two versions of each.
You can reduce the code duplication at the use sites with a type class,
{-# LANGUAGE TypeFamilies #-}
class MultiMapClass m where
type Key m
type Value m
empty :: m
singleton :: Key m -> Value m -> m
addValue :: Key m -> Value m -> m -> m
...
instance (Ord k, Ord v) => MultiMapClass (MultiMap k v) where
type Key (MultiMap k v) = k
type Value (MultiMap k v) = v
empty = MultiMap Map.empty
...
instance MultiMapClass IntMultiMap where
type Key IntMultiMap = Int
type Value IntMultiMap = Int
empty = IntMultiMap IntMap.empty
...
>
> Thanks!
More information about the Beginners
mailing list