2015 Round 1C

Brattleship

For the small case, that is, a single row, our best strategy is to try columns [w, 2w, …​]. Due to cheating, we will hit at the highest multiple of w less than or equal to c.

If this happens to be the last square, then there is only one way to place the ship so we are guaranteed to sink it after w - 1 more hits. Otherwise, due to cheating, we shall miss one more time, so we will take w more hits.

import Jam

main = jam $ do
  [_, c, w] <- getints
  let (q, rem) = divMod c w
  pure $ show $ q - fromEnum (0 == rem) + w

For the large input, there may be more than one row. We apply the same strategy for each row. Due to cheating, we shall miss on all but the last row.

import Jam
main = jam $ do
  [r, c, w] <- getints
  let (q, rem) = divMod c w
  pure $ show $ r * q + signum rem - 1 + w

Just for fun, we use signum instead of fromEnum.

Typewriter Monkey

The limits of the small input are small enough that we can generate every possible string of length s and count the number of times the target word appears in each:

import Jam
import Control.Monad
import Data.List

main = jam $ do
  s  <- last <$> getints
  ks <- gets
  ls <- gets
  let
    t = length . filter (isPrefixOf ls) . tails <$> replicateM s ks
    e = fromIntegral (sum t) / fromIntegral (length t)
  pure $ show $ fromIntegral (maximum t) - e

The replicateM function succinctly produces all possible strings.

For the large input, we exploit linearity of expectation. We simply find the probability of typing the target word in l characters, and multiply by the number of places it could appear.

It remains to determine the number of bananas to bring. If the probability of typing the target word is zero, then we bring no bananas. Otherwise, we find the longest strict prefix of the target word that is also a suffix of the target word, and use this to compute the maximum number of times the target word can appear in s characters.

import Jam
import Data.List
import Data.Maybe
import Data.Ratio

len = fromIntegral . length

main = jam $ do
  [k, l, s] <- getintegers
  ks <- (zip <$> map head <*> map len) . group . sort <$> gets
  ls <- gets
  let
    e = product $ fromMaybe 0 . (`lookup` ks) <$> ls
    p = len $ head $ dropWhile (not . (`isPrefixOf` ls)) $ tail $ tails ls
  pure $ show $ if e == 0 then 0 else
    fromRational $ div (s - p) (l - p) % 1 - ((s - l + 1) * e % k^l)

We avoid floating-point until the last minute to get an accurate answer as possible.

Less Money, More Problems

We solve this with a simple recursion.

Let n be the largest value we can make using the denominations processed so far, where we are limited to at most c copies of any one denomination. Initially n is 0.

Let ds be the be list of denominations yet to be processed. Initially, ds is the input list of coins.

If n >= v, we are done: we can sum to any value up to v, so there is no need for any more denominations.

If ds is empty or the smallest of the remaining denominations to be processed exceeds n + 1, then we must introduce a coin of value n + 1. While it may be possible to introduce a coin worth less than n + 1 to sum to n + 1 with existing denominations, this may lead to a suboptimal solution. Then with this new coin, we can sum to any value up to (n + 1)*c + n, and we still have ds to process.

Otherwise, if h is the smallest of the remaining denominations, we can sum up to h*c + n, and we recurse on the other denominations.

import Jam

main = jam $ do
  [c, d, v] <- getints
  let
    f n ds
      | n >= v               = 0
      | null ds || h > n + 1 = f ((n + 1)*c + n) ds + 1
      | otherwise            = f (h      *c + n) t
      where (h:t) = ds
  show . f 0 <$> getints

Ben Lynn blynn@cs.stanford.edu 💡