[Haskell-cafe] Optimization problem

Ross Paterson ross at soi.city.ac.uk
Fri Sep 15 22:03:02 EDT 2006


On Fri, Sep 15, 2006 at 05:13:29AM +0200, Bertram Felgenhauer wrote:
> Just to prove the point, here's the same code with balancing:

How embarrassing.  Still, your code is quite subtle.  As penance, here's
my explanation, separating the main idea from the knot-tying.

The ingredients are a map type with an insertion function

	data Key k a = ...
	instance Functor (Map k)

	insert :: Ord k => k -> a -> Map k a -> Map k a

with a partial inverse

	uninsert :: Ord k => k -> Map k () -> Map k a -> (a, Map k a)

satisfying

	uninsert k (fmap (const ()) m) (insert k v m) = (v, m)

for any map m not containing k.  We also need an update function

	update :: Ord k => k -> (a -> a) -> Map k x -> Map k a -> Map k a

where the two map arguments have the same shape.  Then splitSeq becomes:

	splitSeq :: Ord a => [(a,b)] -> [(a,[b])]
	splitSeq = fst . splitSeq' Leaf

	splitSeq' :: Ord a => Map a () -> [(a,b)] -> ([(a,[b])], Map a [b])
	splitSeq' bp [] = ([], map (const []) bp)
	splitSeq' bp ((a,b):xs)
	  | member a bp =
		let (l, m) = splitSeq' bp xs
		in  (l, update a (b:) bp m)
	  | otherwise =
		let bp' = insert a () bp
		    (l, m') = splitSeq' bp' xs
		    (bs, m) = uninsert a bp m'
		in ((a, b : bs) : l, m)

Applying a tupling transformation to insert+uninsert gives your version.

It's interesting that these composed transformations don't seem to cost
too much.



More information about the Haskell-Cafe mailing list