Lazily Tying the Knot for 1 Dimensional Dynamic Programming

前端 未结 4 837
春和景丽
春和景丽 2021-01-01 17:59

Several years ago I took an algorithms course where we were giving the following problem (or one like it):

There is a building of n floor

相关标签:
4条回答
  • 2021-01-01 18:43

    Others have answered your direct question about dynamic programming. However, for this kind of problem I think the greedy approach works the best. It's implementation is very straightforward.

    f i j :: Int -> Int -> Int
    f i j = snd $ until (\(i,_) -> i == j) 
                        (\(i,x) -> (i + if i < j then 2 else (-3),x+1))
                        (i,0)
    
    0 讨论(0)
  • 2021-01-01 18:49

    The problem is that min needs to fully evaluate both calls to f, so if one of them loops infinitly min will never return. So you have to create a new type, encoding that the number returned by f is Zero or a Successor of Zero.

    data Natural = Next Natural 
                 | Zero
    
    toNum :: Num n => Natural -> n
    toNum Zero     = 0
    toNum (Next n) = 1 + (toNum n)
    
    minimal :: Natural -> Natural -> Natural
    minimal Zero _            = Zero
    minimal _ Zero            = Zero
    minimal (Next a) (Next b) = Next $ minimal a b
    
    f i j | i == j = Zero
          | otherwise = Next $ minimal (f l j) (f r j)
          where l = i + 2
                r = i - 3
    

    This code actually works.

    0 讨论(0)
  • 2021-01-01 18:56

    Since you're trying to solve this in two dimensions, and for other problems than the one described, let's explore some more general solutions. We are trying to solve the shortest path problem on directed graphs.

    Our representation of a graph is currently something like a -> [a], where the function returns the vertices reachable from the input. Any implementation will additionally require that we can compare to see if two vertices are the same, so we'll need Eq a.

    The following graph is problematic, and introduces almost all of the difficulty in solving the problem in general:

    problematic 1 = [2]
    problematic 2 = [3]
    problematic 3 = [2]
    problematic 4 = []
    

    When trying to reach 4 from 1, there are is a cycle involving 2 and 3 that must be detected to determine that there is no path from 1 to 4.

    Breadth-first search

    The algorithm Will presented has, if applied to the general problem for finite graphs, worst case performance that is unbounded in both time and space. We can modify his solution to attack the general problem for graphs containing only finite paths and finite cycles by adding cycle detection. Both his original solution and this modification will find finite paths even in infinite graphs, but neither is able to reliably determine that there is no path between two vertices in an infinite graph.

    acyclicPaths :: (Eq a) => (a->[a]) -> a -> a -> [[a]]
    acyclicPaths steps i j = map (tail . reverse) . filter ((== j).head) $ queue
      where
        queue = [[i]] ++ gen 1 queue
        gen d _ | d <= 0 = []
        gen d (visited:t) = let r = filter ((flip notElem) visited) . steps . head $ visited 
                            in map (:visited) r ++ gen (d+length r-1) t
    
    shortestPath :: (Eq a) => (a->[a]) -> a -> a -> Maybe [a]
    shortestPath succs i j = listToMaybe (acyclicPaths succs i j)
    

    Reusing the step function from Will's answer as the definition of your example problem, we could get the length of the shortest path from floor 4 to 5 of an 11 story building by fmap length $ shortestPath (step 11) 4 5. This returns Just 3.

    Let's consider a finite graph with v vertices and e edges. A graph with v vertices and e edges can be described by an input of size n ~ O(v+e). The worst case graph for this algorithm is to have one unreachable vertex, j, and the remaining vertexes and edges devoted to creating the largest number of acyclic paths starting at i. This is probably something like a clique containing all the vertices that aren't i or j, with edges from i to every other vertex that isn't j. The number of vertices in a clique with e edges is O(e^(1/2)), so this graph has e ~ O(n), v ~ O(n^(1/2)). This graph would have O((n^(1/2))!) paths to explore before determining that j is unreachable.

    The memory required by this function for this case is O((n^(1/2))!), since it only requires a constant increase in the queue for each path.

    The time required by this function for this case is O((n^(1/2))! * n^(1/2)). Each time it expands a path, it must check that the new node isn't already in the path, which takes O(v) ~ O(n^(1/2)) time. This could be improved to O(log (n^(1/2))) if we had Ord a and used a Set a or similar structure to store the visited vertices.

    For non-finite graphs, this function should only fail to terminate exactly when there doesn't exists a finite path from i to j but there does exist a non-finite path from i to j.

    Dynamic Programming

    A dynamic programming solution doesn't generalize in the same way; let's explore why.

    To start with, we'll adapt chaosmasttter's solution to have the same interface as our breadth-first search solution:

    instance Show Natural where
        show = show . toNum 
    
    infinity = Next infinity
    
    shortestPath' :: (Eq a) => (a->[a]) -> a -> a -> Natural
    shortestPath' steps i j = go i
        where
            go i | i == j = Zero
                 | otherwise = Next . foldr minimal infinity . map go . steps $ i
    

    This works nicely for the elevator problem, shortestPath' (step 11) 4 5 is 3. Unfortunately, for our problematic problem, shortestPath' problematic 1 4 overflows the stack. If we add a bit more code for Natural numbers:

    fromInt :: Int -> Natural
    fromInt x = (iterate Next Zero) !! x    
    
    instance Eq Natural where
        Zero == Zero         = True
        (Next a) == (Next b) = a == b
        _ == _ = False
    
    instance Ord Natural where
        compare Zero Zero         = EQ
        compare Zero _            = LT
        compare _ Zero            = GT
        compare (Next a) (Next b) = compare a b
    

    we can ask if the shortest path is shorter than some upper bound. In my opinion, this really shows off what's happening with lazy evaluation. problematic 1 4 < fromInt 100 is False and problematic 1 4 > fromInt 100 is True.

    Next, to explore dynamic programming, we'll need to introduce some dynamic programming. Since we will build a table of the solutions to all of the sub-problems, we will need to know the possible values that the vertices can take. This gives us a slightly different interface:

    shortestPath'' :: (Ix a) => (a->[a]) -> (a, a) -> a -> a -> Natural
    shortestPath'' steps bounds i j = go i
        where
            go i = lookupTable ! i
            lookupTable = buildTable bounds go2
            go2 i | i == j = Zero
                  | otherwise = Next . foldr minimal infinity . map go . steps $ i
    
    -- A utility function that makes memoizing things easier
    buildTable :: (Ix i) => (i, i) -> (i -> e) -> Array i e
    buildTable bounds f = array bounds . map (\x -> (x, f x)) $ range bounds
    

    We can use this like shortestPath'' (step 11) (1,11) 4 5 or shortestPath'' problematic (1,4) 1 4 < fromInt 100. This still can't detect cycles...

    Dynamic programming and cycle detection

    The cycle detection is problematic for dynamic programming, because the sub-problems aren't the same when they are approached from different paths. Consider a variant of our problematic problem.

    problematic' 1 = [2, 3]
    problematic' 2 = [3]
    problematic' 3 = [2]
    problematic' 4 = []
    

    If we are trying to get from 1 to 4, we have two options:

    • go to 2 and take the shortest path from 2 to 4
    • go to 3 and take the shortest path from 3 to 4

    If we choose to explore 2, we will be faced with the following option:

    • go to 3 and take the shortest path from 3 to 4

    We want to combine the two explorations of the shortest path from 3 to 4 into the same entry in the table. If we want to avoid cycles, this is really something slightly more subtle. The problems we faced were really:

    • go to 2 and take the shortest path from 2 to 4 that doesn't visit 1
    • go to 3 and take the shortest path from 3 to 4 that doesn't visit 1

    After choosing 2

    • go to 3 and take the shortest path from 3 to 4 that doesn't visit 1 or 2

    These two questions about how to get from 3 to 4 have two slightly different answers. They are two different sub-problems which can't fit in the same spot in a table. Answering the first question eventually requires determining that you can't get to 4 from 2. Answering the second question is straightforward.

    We could make a bunch of tables for each possible set of previously visited vertices, but that doesn't sound very efficient. I've almost convinced myself that we can't do reach-ability as a dynamic programming problem using only laziness.

    Breadth-first search redux

    While working on a dynamic programming solution with reach-ability or cycle detection, I realized that once we have seen a node in the options, no later path visiting that node can ever be optimal, whether or not we follow that node. If we reconsider problematic':

    If we are trying to get from 1 to 4, we have two options:

    • go to 2 and take the shortest path from 2 to 4 without visiting 1, 2, or 3
    • go to 3 and take the shortest path from 3 to 4 without visiting 1, 2, or 3

    This gives us an algorithm to find the length of the shortest path quite easily:

    -- Vertices first reachable in each generation
    generations :: (Ord a) => (a->[a]) -> a -> [Set.Set a]
    generations steps i = takeWhile (not . Set.null) $ Set.singleton i: go (Set.singleton i) (Set.singleton i)
        where go seen previouslyNovel = let reachable = Set.fromList (Set.toList previouslyNovel >>= steps)
                                            novel = reachable `Set.difference` seen
                                            nowSeen = reachable `Set.union` seen
                                        in novel:go nowSeen novel
    
    lengthShortestPath :: (Ord a) => (a->[a]) -> a -> a -> Maybe Int
    lengthShortestPath steps i j = findIndex (Set.member j) $ generations steps i
    

    As expected, lengthShortestPath (step 11) 4 5 is Just 3 and lengthShortestPath problematic 1 4 is Nothing.

    In the worst case, generations requires space that is O(v*log v), and time that is O(v*e*log v).

    0 讨论(0)
  • 2021-01-01 18:56

    standing on the floor i of n-story building, find minimal number of steps it takes to get to the floor j, where

    step n i = [i-3 | i-3 > 0] ++ [i+2 | i+2 <= n]
    

    thus we have a tree. we need to search it in breadth-first fashion until we get a node holding the value j. its depth is the number of steps. we build a queue, carrying the depth levels,

    solution n i j = case dropWhile ((/= j).snd) queue
                       of []        -> Nothing
                          ((k,_):_) -> Just k
      where
        queue = [(0,i)] ++ gen 1 queue
    

    The function gen d p takes its input p from d notches back from its production point along the output queue:

        gen d _ | d <= 0 = []
        gen d ((k,i1):t) = let r = step n i1 
                           in map (k+1 ,) r ++ gen (d+length r-1) t
    

    Uses TupleSections. There's no knot tying here, just corecursion, i.e. (optimistic) forward production and frugal exploration. Works fine without knot tying because we only look for the first solution. If we were searching for several of them, then we'd need to eliminate the cycles somehow.

    • see also: https://en.wikipedia.org/wiki/Corecursion#Discussion

    With the cycle detection:

    solutionCD1 n i j = case dropWhile ((/= j).snd) queue
                        of []        -> Nothing
                           ((k,_):_) -> Just k
      where
        step n i visited =    [i2 | let i2=i-3, not $ elem i2 visited, i2 > 0] 
                           ++ [i2 | let i2=i+2, not $ elem i2 visited, i2 <=n]
        queue = [(0,i)] ++ gen 1 queue [i]
        gen d _ _ | d <= 0 = []
        gen d ((k,i1):t) visited = let r = step n i1 visited
                                   in map (k+1 ,) r ++ 
                                      gen (d+length r-1) t (r++visited)
    

    e.g. solution CD1 100 100 7 runs instantly, producing Just 31. The visited list is pretty much a copy of the instantiated prefix of the queue itself. It could be maintained as a Map, to improve time complexity (as it is, sol 10000 10000 7 => Just 3331 takes 1.27 secs on Ideone).


    Some explanations seem to be in order.

    First, there's nothing 2D about your problem, because the target floor j is fixed.

    What you seem to want is memoization, as your latest edit indicates. Memoization is useful for recursive solutions; your function is indeed recursive - analyzing its argument into sub-cases, synthetizing its result from results of calling itself on sub-cases (here, i+2 and i-3) which are closer to the base case (here, i==j).

    Because arithmetics is strict, your formula is divergent in the presence of any infinite path in the tree of steps (going from floor to floor). The answer by chaosmasttter, by using lazy arithmetics instead, turns it automagically into a breadth-first search algorithm which is divergent only if there's no finite paths in the tree, exactly like my first solution above (save for the fact that it's not checking for out-of-bounds indices). But it is still recursive, so indeed memoization is called for.

    The usual way to approach it first, is to introduce sharing by "going through a list" (inefficient, because of sequential access; for efficient memoization solutions see hackage):

    f n i j = g i
      where
        gs = map g [0..n]              -- floors 1,...,n  (0 is unused)
        g i | i == j = Zero
            | r > n  = Next (gs !! l)  -- assuming there's enough floors in the building
            | l < 1  = Next (gs !! r)
            | otherwise = Next $ minimal (gs !! l) (gs !! r)
          where r = i + 2
                l = i - 3
    

    not tested.

    My solution is corecursive. It needs no memoization (just needs to be careful with the duplicates), because it is generative, like the dynamic programming is too. It proceeds away from its starting case, i.e. the starting floor. An external accessor chooses the appropriate generated result.

    It does tie a knot - it defines queue by using it - queue is on both sides of the equation. I consider it the simpler case of knot tying, because it is just about accessing the previously generated values, in disguise.

    The knot tying of the 2nd kind, the more complicated one, is usually about putting some yet-undefined value in some data structure and returning it to be defined by some later portion of the code (like e.g. a back-link pointer in doubly-linked circular list); this is indeed not what my1 code is doing. What it does do is generating a queue, adding at its end and "removing" from its front; in the end it's just a difference list technique of Prolog, the open-ended list with its end pointer maintained and updated, the top-down list building of tail recursion modulo cons - all the same things conceptually. First described (though not named) in 1974, AFAIK.


    1 based entirely on the code from Wikipedia.

    0 讨论(0)
提交回复
热议问题