combinatorial search with running bound

I have a combinatorial search problem that requires a running lower bound to be tracked in order to prune the search. I have enough Haskell experience to know how to do a combinatorial search, for example with list compresions or the list monad, but I don't know how to keep a running lower bound. The problem is: I have two groups of boxes, and need to figure out how closely the centers of the groups can be brought left-right. For example, 55 11111 55 11111 44 22 44 22 + <- how close? -> + 33333 6666 33333 6666 33333 The left group consists of boxes 1, 2, and 3, which have both a size and a position (the position is relative to the center of the group, represented with the +). The right group has boxes 4, 5, and 6. The problem is to determine how closely the groups can be brought together without any boxes intersection. The basic algorithm is to consider each pair of boxes and ask if they have any "vertical overlap"---if so, figure out how closely they can be brought together without intersecting, otherwise ignore them. Then take the maximum of those numbers. -- (Here assume lrSeparation returns minBound for boxes that don't have -- vertical intersection.) boxesSep :: [Box] -> [Box] -> Int boxesSep lefts rights = maximum [ lrSeparation l r | l <- lefts, r <- rights ] However, this algorithm can be improved by pruning. - Define the 'left extent' of a box by how far its left edge sticks out to the left of the group center. Similarly the 'right extent'. - Sort the list of left boxes in the order of decreasing right extent. Sort the list of right boxes in order of decreasing left extent. - Consider pairs of boxes as a kind of outer loop on the left boxes, and inner loop on the right boxes. - Track the current maximum required separation, which is a lower bound on the final answer. - If at any point in the inner loop, the right extent has gotten so small that there's no way you could find a new maximum, skip the rest of the inner loop (skip the remainder of the right boxes). Here's my attempt to write this using a state monad. There's probably a more idiomatic way to do it. -- 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) boxesSep2' :: [BoxBounds] -> [BoxBounds] -> State SearchState Int -- Termination of algorithm: boxesSep2' [] _ = gets ssMaximum -- Initiate a new inner loop: boxesSep2' (l:ls) [] = do rights <- gets ssRights boxesSep' ls rights -- 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 So if there is a better way to do this, I'm all ears.

I made some mistakes in editing this code before posting it. I wrote BoxBounds in a couple places when I meant Box. Also made calls to boxesSep' when I meant boxesSep2'. Hopefully should all be obvious from context. Michael Mossey wrote:
I have a combinatorial search problem that requires a running lower bound to be tracked in order to prune the search. I have enough Haskell experience to know how to do a combinatorial search, for example with list compresions or the list monad, but I don't know how to keep a running lower bound.

On Sat, 26 Sep 2009, Michael Mossey wrote:
I have a combinatorial search problem that requires a running lower bound to be tracked in order to prune the search. I have enough Haskell experience to know how to do a combinatorial search, for example with list compresions or the list monad, but I don't know how to keep a running lower bound.
Sometimes the omega monad can help by searching the space in a diagonal manner: http://hackage.haskell.org/package/control-monad-omega

Michael Mossey
The problem is to determine how closely the groups can be brought together without any boxes intersection.
The basic algorithm is to consider each pair of boxes and ask if they have any "vertical overlap"---if so, figure out how closely they can be brought together without intersecting, otherwise ignore them. Then take the maximum of those numbers.
Wouldn't you mean minimum instead of maximum then? I suspect that your code would be clearer without using a state monad. -- 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

Hi Chung-chieh, 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. -Mike Chung-chieh Shan wrote:
Michael Mossey
wrote in article <3942.75.50.175.130.1253997756.squirrel@mail.alumni.caltech.edu> in gmane.comp.lang.haskell.cafe: The problem is to determine how closely the groups can be brought together without any boxes intersection.
The basic algorithm is to consider each pair of boxes and ask if they have any "vertical overlap"---if so, figure out how closely they can be brought together without intersecting, otherwise ignore them. Then take the maximum of those numbers.
Wouldn't you mean minimum instead of maximum then?
I suspect that your code would be clearer without using a state monad.

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
participants (3)
-
Chung-chieh Shan
-
Henning Thielemann
-
Michael Mossey