2013 Qualification Round

For some of these, I found it difficult to solve the small input without also solving the large input.

I struggled with Treasure: looks like I need more practice on these sorts of problems.

Tic-Tac-Toe-Tomek

A conceptually straightforward problem. The tricky part is designing our program so it gets the finicky details right the first time.

We do this by enumerating the rows, columns, and diagonals in a manner that’s hard to screw up, then sorting the characters within each such line and comparing to string literals to see if either player won.

import Jam
import Data.Array
import Data.List

main = jam $ do
  bs <- getsn 4
  gets
  let
    as = listArray ((0, 0), (3, 3)) $ concat bs
    lines = [(i, i) | i <- [0..3]] : [(i, 3 - i) | i <- [0..3]]
      :  [[(i, j) | i <- [0..3]] | j <- [0..3]]
      ++ [[(j, i) | i <- [0..3]] | j <- [0..3]]
    w = foldr (\line c -> if c /= '.' then c else case sort $ map (as!) line of
      "TXXX" -> 'X'
      "XXXX" -> 'X'
      "OOOO" -> 'O'
      "OOOT" -> 'O'
      _      -> c) '.' lines
  return $ case w of
    'X' -> "X won"
    'O' -> "O won"
    _   -> if '.' `elem` elems as then "Game has not completed" else "Draw"

Lawnmower

If the lawn is a single row or column, then it is trivially possible to obtain any pattern.

For less trivial lawns, consider one of the squares of minimum height. Then if a square in the same row is higher and another square in the same column is higher, then the square is blocked: the given pattern is impossible because we can only adjust the lawnmower’s height when off the lawn.

Otherwise, suppose no square in its row is higher, which implies the whole row has the same, minimum height. Assuming it is possible to reach this pattern, we can rearrange the sequence of cuts so that this row was cut last. Thus we remove the entire row, and recursively consider the remainder of the lawn.

Handling columns is similar, and in our code we call transpose so we can reuse our row code. The inputs are small enough that we can get away with inefficiencies like this.

import Jam
import Data.List
import Data.Maybe

g b m as = case break (all (== m)) as of
  (_, [])      -> if b then g False m $ transpose as else Nothing
  (xs, _:ys) -> Just $ xs ++ ys

f as | length as == 1 || length (head as) == 1 = "YES"
     | otherwise = maybe "NO" f $ g True m as
     where m = foldl1' min (map (foldl1' min) as)

main = jam $ do
  [n, _] <- getints
  as <- getintsn n
  return $ f as

Fair and Square

Brute force works on the first two inputs:

import Jam

isPal n = let s = show n in s == reverse s
fs = [n | i <- [1..], isPal i, let n = i^2, isPal n]

main = jam $ do
  [a, b] <- getintegers
  return $ show $ length $ takeWhile (<= b) $ dropWhile (< a) fs

For the largest input, we’ll need some mathematics.

Conisder an even palindrome whose digits are d[0] …​ d[k] d[k] …​ d[0]. The odd case turns out to be similar. We apply the method taught in primary school to find its square, except we temporarily increase our number base so that the result of our following multiplications and additions fit in a single digit.

Then we find the first and last digits are both s[0] = d[0] * d[0], the second and second-last digit are both s[1] = 2 * d[0] * d[1], and in general, s[j] = sum [d!!i * d!!(j - i) | i ← [0..j]]. In other words, the square of our palindrome is also a palindrome when the output base is sufficiently large.

What happens if we now go back to base 10? Let j be the smallest index where

sum [d!!i * d!!(j - i) | i <- [0..j]] > 9

By definition s[0] to s[j-1] are all small enough to fit within a single digit. Thus the first (j+1) least-significant digits are still s[0] to s[j], since the tens digit (and above) of s[j] will leave these alone. However, with the most-significant digits, at least the tens digit of s[j] gets carried over and added to s[j-1], which breaks the palindrome property.

There might be one way out: perhaps the carries are just the right size so that adding them to the most-significant digits happens to shift them one digit to the left and we somehow produce a palindrome after all. But the jth digit is at most j * 9 * 9, which I think can easily be used to show this cannot happen.

Truth be told, I didn’t bother with a proof because firstly, it almost looks that way by inspection, and secondly, programming contest organizers would most likely avoid problems with horrendous complications involving carried digits, at least for the qualification round!

Anyway, by hook or by crook:

sum [d!!i * d!!(j - i) | i <- [0..j]] <= 9

We could use more mathematics to show that, for palindromes, this maxes out at the sum of the squares of the digits, so a necessary and sufficient condition is that the squares of the digits sum to at most 9. This leads to the following characterization of the square roots of fair-and-square numbers:

  • The single digits 1, 2, 3.

  • Palindromes consisting of two 2s, at most one 1, and any number of 0s.

  • Palindromes consisting of one 2, either two or four 1s, and any number of 0s.

  • Palindromes consisting of up to 9 ones and any number of 0s.

However, thanks to the relatively small input size of even the largest input, it’s easier to write a slower program that reuses some code from our brute force solution based on simpler observations:

  • After 3, the only digits that can appear are 0, 1, and 2.

  • The square root of a fair-and-square number produces the square root of another fair-and-square number when the middle one/two digits are removed when the number of digits is odd/even.

In our code, we recursively search for fair-and-square numbers (reusing our brute force code, even though it’s enough to check the squares of the digits sum to at at most 9) with the function g. It takes in the first half of the square root of a known fair-and-square number, then tries inserting one central digit, and inserting two central digits and recursing on success.

import Jam

isPal n = let s = show n in s == reverse s

main = jam $ do
  [a, b] <- getintegers
  return $ show $ length $ takeWhile (<= b) $ dropWhile (< a) fs

g (ns, xs) = let
  odds = [n | x <- xs, c <- "012",
    let n = read (x ++ [c] ++ reverse x), isPal $ n^2]
  evensnext = [(n, x ++ [c]) | x <- xs, c <- "012",
    let n = read (x ++ [c, c] ++ reverse x), isPal $ n^2]
  in (ns ++ odds ++ map fst evensnext, map snd evensnext)

fs = map (\x -> x*x) $ fst $ iterate g ([1,2,3,11,22], ["1","2"])!!25

Treasure

This problem seems tough. What do we do? Brute force on 200 chests is too slow. Even with 25 chests, it’s difficult to simply try every permutation.

There’s no obvious way to apply dynamic programming because there’s the set of keys we’re holding as well as the unopened chests, which interact in complex ways.

We could try viewing the chests as vertices of a complete graph on which we’re to find a spanning tree, but we’re foiled again by the constantly changing set of keys on hand.

When completely bewildered, one strategy is to find just one simple concrete fact we can state about the problem. Anything will do; we’re seeking a toehold to gain a chance of eventually scaling the mountain.

Let’s start from the obvious. We can open a chest C if we hold the right key. Next, as the example shows, even if we lack the right key at the moment, we can still open it if we can find a sequence of chests such that:

  • we have the key to the first chest,

  • each chest contains a key to open the next, and,

  • the final chest contains a key to open C.

This inspires us to define a position to be individually soluble if for every chest C, we can open C eventually by opening a particular sequence of chests. This is a necessary condition for a solution, but not a sufficient condition since we check each chest C independently of the the others; it could turn out that we may be able to open chest A or chest B, but not both.

We can check solubiility of an individual chest C recursively. Define C[0] to be the singleton set containing C. Then starting from i = 0:

  1. If we possess a key that can open anything in C[i], then C can be opened eventually.

  2. Otherwise, let C[i+1] be the set of all chests that contain a key that can open any member of C[i] and are not members of C[0], …​, C[i].

  3. If C[i+1] is empty then there is no way to open C. Otherwise increment i and go to step 1.

At this point we may optimistically hope that a greedy algorithm may work, namely, at each step, we open the lexicographically smallest chest such that the resulting position is still individually soluble; if there is no such chest then we claim there is no solution.

It turns out our optimism is well-founded. Here’s a brief explanation. Suppose the greedy algorithm can fail, that is, somewhere along the way, the greedy algorithm makes a fatal mistake: with the key t, it opened the chest X when we should have instead opened the chest Y.

In the correct solution, let T(Y) be the tree of chests we can only open because we opened Y: the root of T(Y) is Y; each child chest is a chest that was opened by a key found in the parent chest. Similarly, let T(X) be the tree of chests rooted at X. T(X) may be a subtree of T(Y).

Since the greedy algorithm picked X, after opening X there is some way of getting a key t without opening Y. It cannot be in T(X) or outside T(Y), otherwise we could have opened X first and still have been able to open T(Y) later.

Thus t must be in a chest in T(Y) \ T(X), and the greedy algorithm errs by using up a key on some chest X' in T(X), when the correct solution is to open a chest Y' in T(Y) whose subtree contains t. But this is a contradiction, for it means we could have opened X first, then opened all chests in T(X) \ T(X'), then T(Y') which gives us a copy of t, then T(Y) \ T(Y'), then finally T(X') because X' and Y' need the same key. In other words, we can still open all of T(X) and T(Y) even if we choose to open X first.

import Jam
import Data.List

soluble _ [] = True
soluble [] _ = False
soluble keys cs = let
  f t = let
    g want cs = if not $ null $ want `intersect` keys then True else let
      (as, bs) = partition (\(_, (_, ks)) -> not $ null $ want `intersect` ks) cs
      in if null as then False else g (nub $ map (fst . snd) as) bs
    in g [t] cs
  in all (f . fst . snd) cs

go acc _ [] = unwords $ map show $ reverse acc
go acc keys cs = case [(i, ks', cs') | c@(i, (t, ks)) <- cs, t `elem` keys, let ks' = ks ++ delete t keys, let cs' = delete c cs, soluble ks' cs'] of
    [] -> "IMPOSSIBLE"
    ((i, ks, cs):_) -> go (i:acc) ks cs

main = jam $ do
  [_, n] <- getints
  keys <- getints
  cs <- zip [1..] . map (\(t:_:ks) -> (t, ks)) <$> getintsn n
  return $ if not $ soluble keys cs then "IMPOSSIBLE" else go [] keys cs

There are more efficient data structures for representing sets of integers, but the inputs are small enough for Haskell lists.


Ben Lynn blynn@cs.stanford.edu 💡