Cody’s Jams

In a list of prices, the smallest price must be a sale price, which we record. We compute the corresponding original price by multiplying by 4/3. After removing both these numbers, we recurse until the list is empty.

import Data.List
import Jam

main = jam $ do
  gets
  ps <- getints
  pure $ unwords $ show <$> f ps

f []     = []
f (x:xs) = x:f (delete (x * 4 `div` 3) xs)

Dance Around The Clock

We can easily simulate the steps as described:

import Jam
import Data.List
import Data.List.Split

main = jam $ do
  [d, k, n] <- getints
  let
    r = f n [1..d]
    Just i = elemIndex k r
  pure $ unwords $ show . (r!!) . (`mod` d) . (i+) <$> [1, -1]

f 0 xs = xs
f n xs = g (n - 1) $ concatMap reverse $ chunksOf 2 xs

g 0 xs = xs
g n xs = f (n - 1) $ concat [[last xs], concatMap reverse $
  init $ chunksOf 2 $ tail xs, [head xs]]

Naturally, we’ll need something better for the large dataset.

Consider the dancer numbered 1. Each turn, this dancer moves one position clockwise.

The same holds for any odd-numbered dancer. We also see that each turn, each even-numbered dancer moves counterclockwise by one position.

Let’s implicitly work modulo d, the number of dancers. Then the dancer numbered k ends up at position i = k + n for odd k and i = k - n otherwise.

Next we start from i - 1 and i + 1 and rewind n steps to find the dancers that end up in the positions on either side of dancer k at the end. If the parity of the position and n agree, then to go backwards is to go clockwise, otherwise it is to go counterclockwise.

import Jam

main = jam $ do
  [d, k, n] <- getints
  let
    i   | odd k        = k + n
        | otherwise    = k - n
    f j | even (j + n) = j + n
        | otherwise    = j - n
    mo a = case mod a d of
      0 -> d
      n -> n
  pure $ unwords $ show . mo . f . (i +) <$> [1, -1]

We postpone reducing by the modulus as late as possible. We wrap mod in our own function because instead of 0 we want to print d.

Polynesiaglot

Let f n be the number of words of length n. Then,

f 0 = 1  -- Unique empty word.
f 1 = v  -- One-letter word must be a vowel.
-- An `n`-letter word ends with a vowel, and is preceded by either an
-- `n-1`-letter word, or an `n-2`-letter word followed by a consonant.
f n = v * (f (n - 1) + c * f (n - 2))

We memoize (aka top-down dynamic programming) to make this fast enough for larger inputs, and reduce by the given modulus:

import Data.MemoTrie
import Jam

m = (`mod` (10^9 + 7))

main = jam $ do
  [c, v, l] <- getints
  let
    mf 0 = 1
    mf 1 = v
    mf n = m $ v * (f (n - 1) + c * f (n - 2))
    f = memo mf
  pure $ show $ f l

Password Security

The first dataset only has one password per case, If the password is only one-letter long, then there is no solution. Otherwise, if it contains two distinct letters, simply ensure our output has those two letters in the other order. Otherwise the password contains a repeated letter, in which case any permutation including the plain alphabet will do.

import Jam
import Data.List

main = jam $ do
  gets
  w <- gets
  pure $ if length w == 1 then "IMPOSSIBLE" else case nub w of
    (_:b:_) -> b:delete b ['A'..'Z']
    _       -> ['A'..'Z']

The second dataset has at most 50 passwords per case, which implies we need only be wary of single letters and bigrams preventing us from finding a solution: there are 25*24 different trigrams starting with a given letter, which is far greater than 50.

For the next section, assume there are no single-letter passwords.

If the passwords are all the two-letter strings containing X except for XX, of which there are exactly 50, then no solution is possible. Even if we place X on one end of a permutation, another letter will lie adjacent to it and form a password with X.

If the passwords are all the two-letter strings starting with X or Y except for XX and YY, of which there are exactly 50, then no solution is possible, because to avoid passwords starting with letter X, we must place X at then end of the permutation, but the same applies to the letter Y, and there can only be one last letter.

A similar argument applies when the passwords are the two-letter strings ending with X or Y.

Naturally, X and Y are examples, and these arguments generalize to all letters of the alphabet.

If none of the above cases hold, then we can always find a solution. We could probably do so deterministically, but it’s easiest to try random permutations until we succeed.

Unfortunately, randomness is tricky to introduce to our Jam monad. Luckily, for this problem, we can get away wtih the same sequence of pseudo-random permutations for every test case, which leads to the following code:

import Jam
import Data.List
import qualified Data.Set as S
import System.Random
import System.Random.Shuffle

main = randoms <$> getStdGen >>= \seeds -> jam $ do
  gets
  ws <- words <$> gets
  let
    al = ['A'..'Z']
    nodup = filter (\[x, y] -> x /= y)
    bad1 = [nodup $ map (:[x]) al ++ map (:[y]) al | x <- al, y <- al, x /= y]
    bad2 = map reverse <$> bad1
    bad3 = [nodup $ map (:[x]) al ++ map ((x:) . pure) al | x <- al]
    bads = S.fromList $ S.fromList <$> concat [bad1, bad2, bad3]
    good = not . (`any` ws) . flip isInfixOf

  pure $ if S.fromList ws `S.member` bads || any ((== 1) . length) ws
    then "IMPOSSIBLE"
    else head $ filter good $ shuffle' al 26 . mkStdGen <$> seeds

I made two mistakes when I attempted this problem. First I neglected to handle passwords like "QQ": I had skimmed the description too quickly; reading "Pi ≠ Pj for all i ≠ j. (All passwords are different.)" left me with the erroneous impression that all letters in each password were distinct.

Then for the second dataset, I overlooked some of the cases for which a solution is impossible.

A better strategy may be to unconditionally try 5000 random permutations for each case, and claim a solution is impossible if we fail to find one, which makes for elementary code:

import Jam
import Data.List
import Data.Maybe
import System.Random
import System.Random.Shuffle

main = take 5000 . randoms <$> getStdGen >>= \seeds -> jam $ do
  gets
  ws <- words <$> gets
  pure $ maybe "IMPOSSIBLE" id $ find (not . (`any` ws) . flip isInfixOf) $
    shuffle' ['A'..'Z'] 26 . mkStdGen <$> seeds

If a solution exists, random search will likely find it quickly, and if we’re extremely unlucky it only costs us a few minutes on the scoreboard because, unusually for a Google Code Jam problem, we can try again as many times as we like even on the harder dataset.


Ben Lynn blynn@cs.stanford.edu 💡