[Haskell-cafe] dear traversable

Claude Heiland-Allen claudiusmaximus at goto10.org
Sat Jul 31 07:53:14 EDT 2010


On 31/07/10 12:13, wren ng thornton wrote:
> Stephen Tetley wrote:
>> wren ng thornton wrote:
>>> Ben wrote:
>>>
>>>> unzipMap :: M.Map a (b, c) -> (M.Map a b, M.Map a c)
>>>> unzipMap m = (M.map fst m, M.map snd m)
>>>
>>> I don't think you can give a more efficient implementation using the
>>> public
>>> interface of Data.Map. You need to have a sort of mapping function that
>>> allows you to thread them together, either via continuations or via a
>>> primitive:
>>
>> Unless I'm missing something. This one has one traversal...
>>
>> unzipMap :: Ord a => M.Map a (b, c) -> (M.Map a b, M.Map a c)
>> unzipMap = M.foldrWithKey fn (M.empty,M.empty)
>> where
>> fn k a (m1,m2) = (M.insert k (fst a) m1, M.insert k (snd a) m2)
>
> Well, that's one traversal of the original map, but you have to traverse
> the new maps repeatedly with all those M.insert calls. And since
> Data.Map is a balanced tree, that could lead to a whole lot of work
> rebalancing things.
>
> However, because we are not altering the set of keys, we are guaranteed
> that the structure of both new maps will be identical to the structure
> of the old map. Therefore, with the right primitives, we can keep one
> finger in each of the three maps and traverse them all in parallel
> without re-traversing any part of the spine. (The Either and Or variants
> will have some retraversal as the smart constructors prune out the spine
> leading to deleted keys. But this is, arguably, necessary.)
>

Why not something like this (with the correctness proof as an exercise):

\begin{code}

import Data.Map (Map)
import qualified Data.Map as M

unzipMap :: Map a (b, c) -> (Map a b, Map a c)
unzipMap m =
   let (ab, ac) = unzip . map fiddle . M.toAscList $ m
   in  (M.fromDistinctAscList ab, M.fromDistinctAscList ac)
   where
     fiddle :: (x, (y, z)) -> ((x, y), (x, z))
     fiddle (x, (y, z)) = ((x, y), (x, z))

\end{code}


(and I now see after writing this that Henning Thielemann wrote much the 
same some hours ago, however there are some slight differences so I'm 
sending this anyway)


Claude
-- 
http://claudiusmaximus.goto10.org


More information about the Haskell-Cafe mailing list