Skip to content
This repository has been archived by the owner on Nov 17, 2024. It is now read-only.

Latest commit

 

History

History
167 lines (131 loc) · 6.65 KB

File metadata and controls

167 lines (131 loc) · 6.65 KB

Day 5

all / 1 / 2 / 3 / 4 / 5 / 6 / 7 / 8 / 9 / 10 / 11 / 12 / 13 / 14 / 15 / 16 / 17 / 18 / 19 / 20 / 21 / 22 / 23 / 24 / 25

Available as an RSS Feed

Prompt / Code / Rendered

So, compared to yesterday's, this was decently chill :)

The main insight here probably is that the puzzle is just describing that the seat ID's are straight up binary notation for numerals, with F/L representing what is traditionally 0, and B/R representing what is traditionally 1. So we can use any of our binary parsers from the standard libraries, or we can just directly pull it into binary.

seatId :: String -> Int
seatId = foldl' iGuessWe'reDoingThis 0
  where
    iGuessWe'reDoingThis n = \case
      'B' -> 2*n+1
      'R' -> 2*n+1
      _   -> 2*n

A nice one-pass way to find the missing seat ID is to realize that if we sum all the numbers from min to max, and sum all of our lists's seat id's, then the difference is the missing number. Luckily there's a nice closed-form solution for the sum of all numbers in a given range (the sum of numbers from a to b is b*(b+1)`div`2 - a*(a-1)`div`2), so we can do all of this in a single pass using the foldl library

{-# LANGUAGE ApplicativeDo #-}
import qualified Control.Foldl as F

findHole :: F.Fold Int (Maybe Int)
findHole = do
    mn <- F.minimum
    mx <- F.maximum
    sm <- F.sum
    pure $
      missingItem <$> mn <*> mx <*> pure sm
  where
    missingItem mn mx sm = totalSum - sm
      where
        totalSum = mx*(mx+1)`div`2 - mn*(mn-1)`div`2

A F.Fold Int (Maybe Int) folds a list of Ints into a Maybe Int. You can run it with F.fold :: F.Fold a b -> [a] -> b.

I really like the foldl library because it lets you build a complex single-pass fold by combining multiple simple single-pass folds (like F.minimum, F.maximum, F.sum) using an Applicative interface. We need to do a bit of wrangling with the Maybes because F.minimum and F.maximum each return Maybe Int.

And that's more or less it! We can actually represent the entire thing as a fold if we use F.premap, to pre-map a fold...

F.premap                 :: (c -> a) -> F.Fold a b -> F.Fold c b

-- "pre-apply" `setId` so we fold over a string instead
F.premap seatId findHole :: F.Fold String (Maybe Int)

And...that's enough to do it all in a single pass!

part1 :: [String] -> Maybe Int
part1 = F.fold $ F.premap seatId F.maximum

part2 :: [String] -> Maybe Int
part2 = F.fold $ F.premap seatId findHole

Bonus: I was tipped off that the 3rd from last digit of F/L are 1, while the same digit of B/R are 0:

ghci> (.&. 1) . (`shiftR` 2) . ord <$> "FLBR"
[1,1,0,0]

So we can actually use this for seatId to get a slight speed boost and help out the branch predictor maybe:

import Data.Bits

seatId :: String -> Int
seatId = foldl' iGuessWe'reDoingThis 0
  where
    iGuessWe'reDoingThis n c =
      2 * n + (complement (ord c) `shiftR` 2) .&. 1

Back to all reflections for 2020

Day 5 Benchmarks

>> Day 05a
benchmarking...
time                 17.30 μs   (17.28 μs .. 17.35 μs)
                     1.000 R²   (1.000 R² .. 1.000 R²)
mean                 17.32 μs   (17.30 μs .. 17.37 μs)
std dev              89.27 ns   (48.81 ns .. 150.8 ns)

* parsing and formatting times excluded

>> Day 05b
benchmarking...
time                 18.84 μs   (18.82 μs .. 18.85 μs)
                     1.000 R²   (1.000 R² .. 1.000 R²)
mean                 18.84 μs   (18.83 μs .. 18.86 μs)
std dev              56.33 ns   (44.68 ns .. 77.97 ns)

* parsing and formatting times excluded