16

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 floors with an elevator that can only go up 2 floors at a time and down 3 floors at a time. Using dynamic programming write a function that will compute the number of steps it takes the elevator to get from floor i to floor j.

This is obviously easy using a stateful approach, you create an array n elements long and fill it up with the values. You could even use a technically non-stateful approach that involves accumulating a result as recursively passing it around. My question is how to do this in a non-stateful manner by using lazy evaluation and tying the knot.


I think I've devised the correct mathematical formula:

f(i,j) = 0 when i is equal to j and f(i,j) = 1 + min of f(i+2,j) and f(i-3,j)

where i+2 and i-3 are within the allowed values.

Unfortunately I can't get it to terminate. If I put the i+2 case first and then choose an even floor I can get it to evaluate the even floors below the target level but that's it. I suspect that it shoots straight to the highest even floor for everything else, drops 3 levels, then repeats, forever oscillating between the top few floors.

So it's probably exploring the infinite space (or finite but with loops) in a depth first manner. I can't think of how to explore the space in a breadth first fashion without using a whole lot of data structures in between that effectively mimic a stateful approach.


Although this simple problem is disappointingly difficult I suspect that having seen a solution in 1 dimension I might be able to make it work for a 2 dimensional variation of the problem.


EDIT: A lot of the answers tried to solve the problem in a different way. The problem itself isn't interesting to me, the question is about the method used. Chaosmatter's approach of creating a minimal function which can compare potentially infinite numbers is possibly a step in the right direction. Unfortunately if I try to create a list representing a building with 100 floors the result takes too long to compute, since the solutions to sub problems are not reused.

I made an attempt to use a self-referencing data structure but it doesn't terminate, there is some kind of infinite loop going on. I'll post my code so you can understand what it is I'm going for. I'll change the accepted answer if someone can actually solve the problem using dynamic programming on a self-referential data structure using laziness to avoid computing things more than once.

levels = go [0..10]
  where
    go [] = []
    go (x:xs) = minimum
      [ if i == 7
          then 0
          else 1 + levels !! i
        | i <- filter (\n -> n >= 0 && n <= 10) [x+2,x-3] ]
      : go xs

You can see how 1 + levels !! i tries to reference the previously calculated result and how filter (\n -> n >= 0 && n <= 10) [x+2,x-3] tries to limit the values of i to valid ones. As I said, this doesn't actually work, it simply demonstrates the method by which I want to see this problem solved. Other ways of solving it are not interesting to me.

Lestat
  • 9,894
  • 5
  • 36
  • 68
Dave
  • 981
  • 7
  • 22
  • Getting to an odd floor is easy, just go up twice and down once, then you're at floor 1 (0-indexed), at which point you can go up to any odd you'd like. In general, if `j` is even, the number of steps needed is `j / 2`. If `j` is odd, the number of steps needed is `3 + (j - 1 / 2)`, since it's 3 initial steps to get to floor 1. – bheklilr Nov 23 '13 at 06:32
  • The actual answer to the function is less important than using dynamic programming with lazy evaluation to find it. The numbers by which the lift can move could be different depending on the levels, at which point there wouldn't necessarily be a simple formula for calculating the answer. – Dave Nov 23 '13 at 06:48
  • 2
    Your function doesn't handle the boundary conditions at 0 and n. – augustss Nov 23 '13 at 08:15
  • When I say "where i+2 and i-3 are within the allowed values." I meant that if those values are invalid, i.e. i+2 > n or i-3 < 0, then ignore that value. So you could say that f(i,j) = infinity when i < 0 or i > n. – Dave Nov 23 '13 at 09:02
  • 2
    see if https://en.wikipedia.org/wiki/Corecursion#Discussion helps. – Will Ness Nov 23 '13 at 11:35
  • 1
    I understand the intention of the question, but I can't help thinking that the Right Solution is to just dispatch to a computation that solves the problem immediately for each of the five possible cases for `i-j`: moving up by an amount equal to 0 or 1 mod 2 or moving down by an amount equal to 0, 1, or 2 mod 3. – Daniel Wagner Nov 23 '13 at 16:50
  • 1
    Regarding your edit: Before tabling a solution, you need to have a solution. If your code doesn't terminate because it recurses forever, a tabled version of it won't either. chaosmasttter's is a good solution to start with. I encourage you to understand it. Then you should study how you can table data in Haskell. I recommend http://bo1024.wordpress.com/2011/06/30/simple-memoization-in-haskell/ . Then you can put those together and get your own solution that you will understand. – Cirdec Nov 24 '13 at 07:00
  • @Cirdec, I've been introduced to this functional pearl, https://www.cs.ox.ac.uk/people/ralf.hinze/publications/HW03.pdf, which describes "sharing". I'll read your link and see if I can use sharing to construct the levels of the building as a nexus, as defined in the pearl. I don't know if this is really that different from using a table but I'd like to try. I've just spent half a Sunday (on and off) on this though so I'll probably take a break. I feel like I'm closer (maybe even there once I understand it) to what I was looking for thanks to you and everyone else here! – Dave Nov 24 '13 at 11:55
  • @Cirdec [An overview of Miranda](http://www.cs.kent.ac.uk/people/staff/dat/miranda/overview.pdf) by David Turner, Dec. **1986.**, page 7, shows how *"naive definition of “fib” can be improved from exponential to linear complexity by changing the recursion to use a lookup table"* :) (i.e. "going through a list" technique). – Will Ness Dec 07 '13 at 14:12

4 Answers4

9

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.

felix-eku
  • 2,133
  • 14
  • 19
  • +1 this is the way to go here. For efficiency the solutions to sub-problems should be memoized. – is7s Nov 23 '13 at 12:49
  • 2
    If you use `data Natural = Zero | Next Natural` you can even just derive `Ord` and get an almost identical implementation of `minimal` (namely, `min` itself!) for free. I'm not sure I understand this well enough to know whether the "almost identical" bit is identical enough to still work or not, though. – Daniel Wagner Nov 23 '13 at 16:45
  • This function works to compute the number of levels and it wouldn't be too hard to extend it to work with the boundaries as well. Unfortunately it doesn't reuse previously calculated results from the sub problems and trying to use this to produce a result for a building with 100 floors took longer than I cared to wait (I got to floor 57 when floor 7 was the target). This was why I wanted to use lazy evaluation to tie the knot on a self referential data structure but none of the answers here have done that. I'll update this question with the answer if I can find it but otherwise this is it. – Dave Nov 24 '13 at 01:42
  • The Dynamic Programming section of my answer adds "lazy evaluation to tie the knot on a self referential data structure" to this answer. It handles the 100 floor problem going from floor 100 to 7, `shortestPath'' (step 100) (1,100) 100 7` almost instantly (31 steps). Going from the thousandth floor of 1000 story building to floor 7 is also almost instant (331 step). Ten thousand floors (3331 steps) takes a few seconds. The algorithm described in the 'Breadth-first search redux" section is even faster. On my machine, `lengthShortestPath (step 100000) 100000 7` is almost instant. – Cirdec Nov 24 '13 at 03:16
  • Sorry, it was a long answer so I must have missed it. Give me a bit, I'll see if I can understand it. – Dave Nov 24 '13 at 03:18
  • It starts at "Next, to explore dynamic programming, we'll need to introduce some dynamic programming" – Cirdec Nov 24 '13 at 03:22
9

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).

Cirdec
  • 23,492
  • 2
  • 45
  • 94
  • I appreciate the huge amount of effort that must have gone into this answer but I'm not convinced it answers the problem in the desired fashion any more than Chaosmatter does. It's true that your algorithm is more efficient in that it can quickly solve for greater values of n but it doesn't tie the knot on a self referential data structure. So it uses a different style of algorithm. I apologize that I'm so fixated on that since there are arguably better ways to solve the problem but this is purely for educational purposes. There isn't a "real" application waiting for a solution. – Dave Nov 24 '13 at 05:03
  • @Dave `shortestPath'' steps bounds i j = go i` is defined in terms of `go`. `go` is defined in terms of the built `lookupTable` (it just looks up the answer in the table). `lookupTable` is defined in terms of `go2`, and `go2` is defined in terms of `go`. Recursion. When `go2` needs an answer it gets it from the table. If the thunk in the table hasn't been evaluated yet, it is lazily evaluated, which will in turn look at other pieces of the table. – Cirdec Nov 24 '13 at 06:19
  • @Cirdec let me rephrase that. :) in your *"We can modify it to attack the general problem for graphs containing only finite paths and finite cycles. If we are looking for a shortest path, it will still work as long as there exists a finite path"*, what is the second *it* referring to? I think my code should find the shortest path first if a finite path exists, that's my understanding of breadth-first search. :) Is that what you mean by the 2nd "it", (i.e. my algorithm), or do you mean the modified one? :) – Will Ness Nov 24 '13 at 06:29
  • @Will. No, I'm claiming that, in the presence of cycles, your exact answer doesn't reliably return `Nothing` when a path doesn't exist. Consider the `problematic` function defined above. If we replace `n` with `steps`, and `step n` with steps in your original function, and evaluate `solution problematic 1 4` we exhaust the memory of the computer without returning a result. If we try another problem without a cycle, (delete the edge from `3` to `2`), `solution` correctly returns `Nothing`. Simply adding cycle detection to expanding the queue will make it work for finite graphs in general. – Cirdec Nov 24 '13 at 06:31
  • I understand that. The sentence I was asking you about is unclear to me. – Will Ness Nov 24 '13 at 06:33
  • @Will I was referring to the new algorithm, but it should be true for both. I've modified those two sentances to read *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.* – Cirdec Nov 24 '13 at 06:40
  • Okay @Cirdec, you're probably right. It's certainly defined in terms of itself. The answer doesn't look like what I was expecting but I don't know enough here to be able to say if and how your solution doesn't fit the bill. – Dave Nov 24 '13 at 07:44
  • @Cirdec I've amended my answer with a small modification for cycle detection. :) It visits each floor at most once now. – Will Ness Nov 24 '13 at 07:54
4

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.

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.

Community
  • 1
  • 1
Will Ness
  • 62,652
  • 8
  • 86
  • 167
  • 1
    An observation that's important to understanding how this code works for this problem: there doesn't exist a building that simultaneously contains a cycle and a pair of floors that there is no path between. For example, if we instead had `step n i = [i-4 | i-4 > 0] ++ [i+2 | i+2 <= n]` then `solution 5 1 2` will never terminate. If we detected cycles, and instead wrote `let r = filter (/= i) $ step n i1`, this solution would work more generally. – Cirdec Nov 23 '13 at 15:14
  • Filtering against the initial element isn't enough to make this work for graphs in general, but should be enough when the operations are always go up or down the same constant numbers of floors from where we were. – Cirdec Nov 23 '13 at 15:34
3

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)
is7s
  • 3,380
  • 1
  • 17
  • 39