Data.Map, Data.IntMap documentation

apfelmus apfelmus at quantentunnel.de
Thu Aug 16 07:26:32 EDT 2007


Adrian Hey schrieb:
> apfelmus wrote:
>> An example:
>>
>>   lookup k (union m m') = lookup k m' `mplus` lookup k m
> 
> Shouldn't that be..
> 
>     lookup k (union m m') = lookup k m `mplus` lookup k m'
 >

Oh indeed, and I thought it would be right-biased :)

> IMO the entire Data.Map module should be deprecated in favour of this..
> 
> http://darcs.haskell.org/packages/collections-ghc6.6/Data/Map/AVL.hs
> 
> and ultimately this..
> 
> http://darcs.haskell.org/packages/collections-ghc6.6/Data.Trie.General/Data/Trie/General/Types.hs 

Sounds good. But I think that the GT class is not general enough. I'd 
wait for associated type synonyms since we can then write

   class Map map k where
     type Elem map k

     empty  :: map
     insert :: k -> Elem map k -> map -> map
     lookup :: k -> map -> Maybe (Elem map k)
     ...

The Ord-constraint is too limiting for tries. Also, the map type does 
not necessarily fix the key type, we can use one map with different key 
types. For instance, we have the trivial

   instance Map map () where
     type Elem map () = map

for every map type. And we can compose maps

   instance Map (Data.Map k1 (Data.Map k2 a)) k1 where
     type Elem .. .. = Data.Map k2 a

   instance Map (Data.Map k1 (Data.Map k2 a)) (k1,k2) where
     type Elem .. .. = a

> But if we must stick with Data.Map for some reason then what Andriy is
> doing is worth while, the documentation does need improving. I found
> hardest thing about writing the clone was figuring out precisely what
> many of the functions did. (In many cases either the documentation was
> ambiguous, or it was OK but the implementation was not consistent with
> the docs.)

Yes, the documentation is in dire need of sharpening and I advocate the 
Haskell way, i.e. equational laws for that.

Regards,
apfelmus



More information about the Libraries mailing list