[Haskell-beginners] How to avoid repeating code

Federico Mastellone fmaste at gmail.com
Fri May 27 19:23:54 CEST 2011


Now I have a new problem, it's getting really difficult to program
generically and to create highly parameterized libraries.

So far so good with type families, but when I want to return a generic Set
for the getValues function and provide a default implementation for
getValuesCount function I don't know how to do it, I don't even know if it
is possible.

newtype MultiMap k v = MultiMap (Map.Map k (Set.Set v))

newtype IntMultiMap = IntMultiMap (IntMap.IntMap IntSet.IntSet)

class MultiMapClass m where
 type Key m
 type Value m
 empty :: m
 addValue :: Key m -> Value m -> m -> m
 getValues :: Key m -> m -> Set (Value m)
 getValueCount :: Key m -> m -> Int
 getValueCount k m = Set.size $ getValues k 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
 addValue k v m = ..........
 getValues k (MultiMap map) = map Map.! k

instance MultiMapClass IntMultiMap where
 type Key IntMultiMap = Int
 type Value IntMultiMap = Int
 empty = IntMultiMap IntMap.empty
 addValue k v m = ..........
 getValues k (IntMultiMap map) = map IntMap.! k

On Thu, May 26, 2011 at 1:47 PM, Federico Mastellone <fmaste at gmail.com>wrote:

>
> On Thu, May 26, 2011 at 8:47 AM, Daniel Fischer <
> daniel.is.fischer at googlemail.com> wrote:
>
>> 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.
>>
>>
> Thanks for the tip, I use newtype where I can but I thought it would be
> simpler here to explain my problem using data. Anyway, now I know better why
> I should use newtype instead.
>
>
>> >
>> > 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
>>
>>
> Yes, both pairs, (Set, InSet), and (Map, IntMap), have the exact same
> problem as my MultiMap module.
>
> But I think that as your solution involves using non-standard extensions we
> could not solve this problem in GHC's libraries. Am I OK?
>
> >
>> > 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 #-}
>>
>
> Is this a mostly experimental extension or I can use it safely? Is it used
> around the GHC packages?
>
>
>>
>> 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
>>  ...
>>
>>
> I'm going to read about this extension, try it and comment about it here.
>
>
>> >
>> > Thanks!
>>
>
> Thank you very much for your complete response, really helpful!
>
>
> --
> Federico Mastellone
> Computer Science Engineer - ITBA
>
> ".. there are two ways of constructing a software design: One way is to
> make it so simple that there are obviously no deficiencies, and the other
> way is to make it so complicated that there are no obvious deficiencies. The
> first method is far more difficult."
>
> Tony Hoare, 1980 ACM Turing Award Lecture.
>
>
>
>


-- 
Federico Mastellone
Computer Science Engineer - ITBA

".. there are two ways of constructing a software design: One way is to make
it so simple that there are obviously no deficiencies, and the other way is
to make it so complicated that there are no obvious deficiencies. The first
method is far more difficult."

Tony Hoare, 1980 ACM Turing Award Lecture.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20110527/d929fcda/attachment.htm>


More information about the Beginners mailing list