2016 Qualification Round

Counting Sheep

How do we get "INSOMNIA"? Obviously when the input is zero. But are there any nonzero numbers that lead to this output?

After trying a few examples, it seems it would be extraordinarily difficult to forever miss a digit. We could probably prove it, but we can save time with an educated gamble: if a counterexample existed, it would be tricky to find, and surely too tricky for a qualification round problem! Thus we proceed directly to a straightforward solution that brazenly assumes only zero leads to "INSOMNIA".

import qualified Data.Set as S
import Data.List
import Jam

main = jam $ do
  [n] <- getints
  pure $ if n == 0 then "INSOMNIA" else f n n S.empty

f acc n set = let
  set' = foldl' (flip S.insert) set (show acc)
  in if S.size set' == 10 then show acc else f (acc + n) n set'

Revenge of the Pancakes

Consider the plate holding the stack to be an unflippable pancake that has the happy side up, and let n be the number of pancakes whose sign differs from the pancake directly below.

All pancakes are happy side up if and only if n is zero. Since each move reduces n by at most one, the answer is at least n.

If n is nonzero, and we flip the group ending with the topmost pancake whose sign differs to that of the pancake directly below, then we reduce n by one. Thus the answer is at most n.

Therefore the answer must be n:

import Jam

main = jam $ do
  s <- gets
  pure $ show $ length $ filter id $ zipWith (/=) s $ tail s ++ "+"

Coin Jam

There are smarter ways to solve this problem, but it’s far quicker to take advantage of a library such as Haskell for Maths, and randomly search for solutions.

After checking that the numbers for each base is composite, we employ trial division up to some smallish constant (216). If we fail to find a factor, we simply retry with another random number.

Although it’s unlikely for larger inputs, to be on the safe side we use Set to avoid duplicates.

import qualified Data.Set as S
import System.Random
import Math.NumberTheory.Primes.Factorisation
import Math.NumberTheory.Primes.Testing
import Jam

main = do
  bits <- randomRs (0, 1) <$> getStdGen
  jam $ do
    [n, x] <- getints
    pure $ f bits n x S.empty

f bits n x set
  | S.size set == x = unlines $ unwords . map show <$> S.toList set
  | any isPrime ns || any ((== 1) . length) divs = f' set
  | otherwise = f' $ S.insert (last ns : map fst (head <$> divs)) set
  where
    ds = 1 : mid ++ [1]
    ns = conv 0 ds <$> [2..10]
    divs = trialDivisionTo (2^16) <$> ns
    f' = f bits' n x
    (mid, bits') = splitAt (n - 2) bits

conv acc [] _ = acc
conv acc (d:ds) base = conv (acc * base + d) ds base

To maximize purity, we generate an infinite list of random bits with randomRs, which becomes the input to a pure function.

Despite the nice library, I managed to screw up all the same. I failed to read the API documentation carefully enough, and thought that if no factor was found, it would return an empty list. In reality, the library returns the unfactored part in the list.

Fractiles

When S = K, we have a trivial solution: have the graduate students clean K tiles evenly spaced apart. Then G appeared in the original if and only if at least one of cleaned tiles is G.

import Jam

main = jam $ do
  [k, c, _] <- getintegers
  pure $ unwords $ show . (1 +) . ((k^(c-1)) *) <$> [0..k-1]

The solution was so easy that I rushed to write and submit it. My haste led to a series of blunders. First, I forgot to print the output in the desired format. Instead, my program was printing Haskell lists using the show function! After another rejection, I thought I had accidentally switched K and C around. After yet another rejection, I realized I had thought k^(c-1) but had written down something simpler. Then one more rejection reminded me to undo the erroneous variable switch.

There was a graver problem: if I write a solution for the large input, how will I be able to test it with the code I already wrote? In hindsight, I realized I should have gone straight for a clever solution and used the small input as a test.

Because of this tactical error, I resolved to write a program that would check my output. One of the tasks of this auxiliary program would be to determine whether a tile was G or L given the original sequence.

Solving this subproblem turns out to be a good way to solve the large input. I’ll leave the details as an exercis and make do with an outline. Suppose we have an original sequence of K = 10 tiles and C = 4, so the artwork has 10000 tiles. How do we determine the 123rd tile?

We soon find it is an L tile if and only if the first 4 tiles of the original sequence are all L tiles, otherwise it is a G tile. We generalize and see that a single L tile in the artwork implies up to C different tiles in the original sequence are L tiles, and gain maximal information by picking different digits in base K and selecting the corresponding tiles.

main = jam $ do
  [k, c, s] <- getints
  pure $ f [] k c s [0..k-1]

f acc _ _ _ [] = unwords $ show <$> acc
f acc _ _ 0 _  = "IMPOSSIBLE"
f acc k c s xs = let
  (as, xs') = splitAt c xs
  in f (1 + conv 0 k (take c $ as ++ repeat 0) : acc) k c (s - 1) xs'

conv acc _ [] = acc
conv acc base (d:ds) = conv (base * acc + d) base ds

As it happened, I eventually gave up on the verification program, as it was taking too much time and its complexity made me doubt its accuracy, Luckily, my solution for the large input turned out to be correct.


Ben Lynn blynn@cs.stanford.edu 💡