2010 Round 1A

Make It Smooth

The problem is asking for some sort of the edit distance, which has a well-known dynamic programming solution. Thus we look for a recursion as we traverse the array of pixels.

We define f k x to be the cost of reaching pixel value x after processing k pixels. It’s understood that any future deletions, insertions, and modifications will only happen to pixels after the processed pixels.

Let v be the value of pixel k + 1, and let d, i, m be the cost of deletion, cost of insertion, and smoothness bound.

The cost of obtaining an empty array of pixels after processing k pixels is c * k.

We now consider the m == 0 case. If we start from the empty array, we reach y is by changing v. Otherwise, we can only reach y from x if x == y, and we can either change v or simply delete it:

f (k + 1) y | m == 0 = minimum
  [ abs (v - y) + c * k
  , abs (v - y) + f k y
  , d           + f k y
  ]

Otherwise we have:

f (k + 1) y | otherwise = minimum $
  c * k + costEmpty v y : [f k x + cost v y x | x <- [0..255]]

where cost v y x is the cost of starting from the two pixels [x, v] and performing a sequence of operations such that the first pixel is still x and the last pixel is y, and costEmpty v y is the analogous cost starting from [v].

The result of costEmpty v y is the cheapest of the following:

  • Delete v then insert y

  • Change v to y

  • Add as few pixels as possible after v to reach y

  • A combination of the previous two options: let r = abs (v - y) `mod m. Then change v to reduce the distance to y by r, then add pixels to reach y.

Why are these the only possibilities we need consider? Well, if we are to change v, unless we change it to y, then we must add pixels to reach y. This only makes sense if the cost of adding pixels is at least as cheap as simply changing v, which implies changing v by m is at least as expensive as inserting a pixel that differs from v by m. Thus we may as well change v by a number strictly less than m, and cover the rest with insertions.

In this case, we should change v so that its distance to y is an exact multiple of m, because if we pay extra to get a bit closer, we still have to add the same number of pixels to satisfy the smoothness condition.

Thus, defining mdiv to be the number of pixels needed to reach y from x:

mdiv x y = div (abs (y - x) + m - 1) m

cost v y (-1) = minimum
  [ d + i
  , abs (y - v)
  , mdiv y v * i
  , r + i * q
  ] where (q, r) = abs (y - v) `divMod` m

Lastly, when x >= 0, the answer is the cheapest of the following choices:

  • Delete 'v' then insert pixels to reach y

  • Change v to y and insert pixels in between x and y.

  • Insert pixels between x and v then add pixels after v to reach `y.`

  • Change v by less than m to reduce its distance to x to an exact multiple of m, then insert pixels.

  • Same as previous option except instead of x, consider the distance from v to y.

We introduce a helper function via x v y to compute the cost of insertions to transform [x, v] into a smooth list that starts from x, goes through v, and ends at y. This is a touch fiddly because x and v are already present.

via x v y = (max 0 (mdiv v x - 1) + mdiv y v) * i

cost v y x = minimum
  [ d + via x x y
  , via x v y
  , abs (v - y) + via x y y
  , rx + via x (v - signum (v - x) * rx) y
  , ry + via x (v - signum (v - y) * ry) y
  ] where
    rx = abs (v - x) `mod` x
    ry = abs (v - y) `mod` y

Rather than explicitly keep track of k and compute n different lists of costs, we fold so that we compute each cost list from the previous cost list.

import Data.Array
import Data.List
import Jam

main = jam $ do
  [d, i, m, n] <- getints
  as <- getints
  let
    minimum' = foldl1' min
    f (c, cs) v = (c + d, map g [0..255]) where
      g y | m == 0 = minimum'
            [ abs (v - y) + c
            , abs (v - y) + cs!!y
            , d           + cs!!y
            ]
          | otherwise = minimum' $
            c + costEmpty v y : zipWith (+) cs (cost v y <$> [0..255])

    mdiv x y = div (abs (y - x) + m - 1) m
    via x y z = (max 0 (mdiv x y - 1) + mdiv y z) * i

    costEmpty v tgt = minimum [d + i, delta, r + i * q, mdiv v tgt * i] where
      delta = abs $ tgt - v
      (q, r) = delta `divMod` m

    cost v y x = minimum
      [ d + via x x y
      , via x v y
      , abs (v - y) + via x y y
      , rx + via x (v - signum (v - x) * rx) y
      , ry + via x (v - signum (v - y) * ry) y
      ] where
        rx = abs (v - x) `mod` m
        ry = abs (v - y) `mod` m

  pure $ show $ minimum' $ uncurry (:) $ foldl' f (0, replicate 256 i) as

When I first tried this problem, I neglected to handle the m == 0 case which led to divisions by zero. Then in my haste to fix the problem, I checked for m == 0 in the function cost instead of f, and thought I could get away from assigning a cost of 256 when x /= y. While 256 is greater than the cost of any single operation, it is lower than the sum of the costs of multiple operations, and so may allow an impossible solution to win. I could have fixed this by increasing the cost to 25501, which is greater than any possible total cost, but it’s better to handle the special case earlier.

I had hoped instead of enumerating so many cases, I could simply use brute force to try all ways of changing v, but this makes the program too slow. Already, my program takes between 2 and 3 minutes on my laptop.

Number Game

Without loss of generality, assume A >= B, and write A = Bq + r where r < B.

If q = 1, then Arya is forced to choose k = 1. If r = 0 then Arya loses, otherwise we recursively see if Bran can force a win.

Otherwise Arya can choose k = q - 1, which forces Bran’s next move to be k = 1, leaving (B, r) for Arya afterwards, or she can choose k = q to leave (B, r) for Bran afterwards. She can choose the one that guarantees victory.

Thus we can solve the small input with the following brute force solution:

import Jam

f a b | a > b     = g b a
      | a < b     = g a b
      | otherwise = 0

g a b | q == 1    = 1 - g r a
      | otherwise = 1
  where (q, r) = divMod b a

main = jam $ do
  [a1, a2, b1, b2] <- getints
  pure $ show $ sum $ f <$> [a1..a2] <*> [b1..b2]

How about the large input? We know that if A >= 2B then the position is won (and otherwise we must check recursively). Can we avoid the recursion? Are there simpler criteria?

By experimenting in an interactive shell, e.g:

[f 1000 b | b <- [1000..1500]]
[f 1000 b | b <- [1500..2000]]

we see that above some cutoff, Arya wins, and below this cutoff, Arya loses.

On a hunch, we suspect this cutoff is related to the golden ratio, that is, Arya wins if and only if a > phi * b. After all, if q = 1 in every division during the recursion, we wind up with the Fibonacci sequence.

We can verify that this guess works for a few guesses, and in a contest, this might be enough: we write our solution assuming we have guessed right.

However, ideally we’d like to know why we have guessed right. Here’s a rough explanation: if we repeatedly apply the FIbonacci recurrence starting from any two positive numbers, then the ratio between the current two numbers alternately overshoots and undershoots the golden ratio, but gradually approaches it.

Thus if we go backwards, just as the Number Game does, if we start from two numbers whose ratio exceeds phi, then on Arya’s turn the ratio gets bigger and bigger, while on Bran’s turn the ratio is always below phi and gets smaller and smaller. Once the ratio reaches two or higher, Arya can win.

Hence for each a ← [a1..a2], we count the size of the intersection of [ceiling (a * phi)..] and [b1..b2], and add it to the size of the intersection of [floor (a / phi)..] and [b1..b2]:

import Jam

phi = (1 + sqrt 5)/2

main = jam $ do
  [a1, a2, b1, b2] <- getints
  let
    tally a =
      max 0 (1 + b2 - upper) - max 0 (b1 - upper) +
      max 0 (1 + lower - b1) - max 0 (lower - b2)
      where
        upper = ceiling (phi * fromIntegral a)
        lower = floor   (fromIntegral a / phi)
  pure $ show $ sum $ tally <$> [a1..a2]

Ben Lynn blynn@cs.stanford.edu 💡