
I wish I had enough of your code to type-check my code and perhaps even
try running it!
Michael Mossey
-- This is state used in the state monad. data SearchState = SearchState { -- running maximum: ssMaximum :: Int -- remember the full list of right boxes -- so we can initiate a new outer loop , ssRights :: [Box] }
boxesSep2 :: [Box] -> [Box] -> Int boxesSep2 lefts rights = let ls = sortBy ((flip compare) `on` rightExtent) lefts rs = sortBy ((flip compare) `on` leftExtent) rights in fst $ runState (boxesSep2' ls rs) (SearchState minBound rs)
First, ssRights never changes, so it should not be kept inside the state monad. Also, ssMaximum is already stored in the state, so boxesSep2' need not return it. data SearchState = SearchState { ssMaximum :: Int } boxesSep2 :: [Box] -> [Box] -> Int boxesSep2 lefts rights = let ls = sortBy ((flip compare) `on` rightExtent) lefts rs = sortBy ((flip compare) `on` leftExtent) rights in ssMaximum (execState (boxesSep2' ls rs) (SearchState minBound))
boxesSep2' :: [Box] -> [Box] -> State SearchState Int
-- Termination of algorithm: boxesSep2' [] _ = gets ssMaximum
-- Initiate a new inner loop: boxesSep2' (l:ls) [] = do rights <- gets ssRights boxesSep' ls rights
Instead, boxesSep2' can simply iterate through the left boxes. boxesSep2' :: [Box] -> [Box] -> State SearchState () boxesSep2' ls rs = mapM_ (flip boxesSep2'' rs) ls
-- Common case: boxesSep2' lss@(l:ls) (r:rs) = do -- In this way of writing the code, we distinguish between the -- left/right separation which is the sum of the extents, and the -- question of whether there is vertical overlap. let v = isVerticalOverlap l r sep = lrSeparation l r ss <- get let max = ssMaximum ss if sep <= max then boxesSep' ls (ssRights ss) --Here we "prune" (initiate new inner loop) else do -- Update max is needed: when v (put ss { ssMaximum = sep }) boxesSep' lss rs
The inner loop through the right boxes doesn't need to maintain the full list of right boxes, because that list is already part of the closure (flip boxesSep2'' rs) above. boxesSep2'' :: Box -> [Box] -> State SearchState () boxesSep2'' l [] = return () boxesSep2'' l (r:rs) = do let v = isVerticalOverlap l r sep = lrSeparation l r max <- gets ssMaximum when (sep > max) (do when v (put (SearchState { ssMaximum = sep })) boxesSep2'' l rs) Personally, I think it's slightly clearer to drop the SearchState constructor and use foldl and explicit state-passing instead of mapM_ and the state monad. But that's less crucial than removing the full rights list from the state. (In the state, the full rights list is a defunctionalized delimited continuation.)
When you ask for a pair of boxes, "How closely can they be brought together without intersection?" that provides a lower bound on the question "How closely can the groups be brought together?" (I.e. for that pair of boxes, bring them any closer and they intersect, so it is a lower bound.) The maximum of all these lower bounds in the minimum needed separation.
I think I see. Cheers! -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig Computer Science is no more about computers than astronomy is about telescopes. -Edsger Dijkstra