class: center, middle, inverse, title-slide # Advent of Code 2021 ## Retrospective discussion ### David Selby, Heather Turner & James Tripp ### R-thritis & Warwick RUG ### 14 January 2022 --- class: center, middle, inverse
# Day 3: Binary Diagnostic <https://adventofcode.com/2021/day/3> --- ### Day 3: Binary Diagnostic - Part 1 .pull-left[ <dl> <dt>Γ</dt> <dd><em>most</em> common bits</dd> <dt>ε</dt> <dd><em>least</em> common bits</dd> </dl> .center[.BIG[.purple[⇓]] .green[Γ] = 10110 = 22 .green[ε] = 01001 = 9] ] .pull-right[ ``` 00100 11110 10110 10111 10101 01111 00111 11100 10000 11001 00010 01010 ``` ] --- ### Day 3: Binary Diagnostic - Part 1 Read in the bits as a numeric matrix: ```r input <- read.fwf('input.txt', widths = rep(1, 12)) ``` Get mean of each column and round it: ```r gamma <- round(colMeans(input) + 1) - 1 ``` Convert result from binary to decimal: ```r binary_to_int <- function(x) sum(x * 2 ^ rev(seq_along(x) - 1)) binary_to_int(gamma) * binary_to_int(!gamma) ``` --- ### Day 3: Binary Diagnostic - Part 2 Successively filter rows with most (least) common bit: ```r 00100 11110 1110 10110 0110 110 10 0 10111 0111 111 11 1 1 # Oxygen scrubber rating 10101 0101 101 01 01111 00111 11100 1100 10000 0000 000 11001 1001 00010 01010 ``` --- ### Day 3: Binary Diagnostic - Part 2 Loop over columns, filtering rows: ```r most_common <- function(x) round(colMeans(x) + 1) - 1 oxygen <- co2 <- input for (j in 1:ncol(input)) { if (nrow(oxygen) > 1) { common <- most_common(oxygen) oxygen <- oxygen[oxygen[, j] == common[j], ] } if (nrow(co2) > 1) { common <- most_common(co2) co2 <- co2[co2[, j] != common[j], ] } } binary_to_int(oxygen) * binary_to_int(co2) ``` --- class: center, middle, inverse # Day 9: Smoke Basin <https://adventofcode.com/2021/day/9> --- ### Day 9: Smoke Basin - Part 1 Add up the levels of the lowest points (+1): ``` 2199943210 21 43210 1 0 3987894921 3 878 4 21 9856789892 85678 8 2 5 8767896789 87678 678 9899965678 8 65678 5 ``` --- ### Day 9: Smoke Basin - Part 1 Read in the values as a numeric matrix (again): ```r heights <- read.matrix('input.txt') # custom function! ``` Vectorized way of comparing points with neighbours: ```r lowest <- function(h) { h < cbind(h, Inf)[, -1] & # right h < rbind(h, Inf)[-1, ] & # down h < cbind(Inf, h[, -ncol(h)]) & # left h < rbind(Inf, h[-nrow(h), ]) # up } ``` Add up the levels: ```r sum(heights[lowest_points(heights)] + 1) ``` --- ### Day 9: Smoke Basin - Part 2 Multiply the sizes of the three largest basins: ``` 2199943210 21 43210 3987894921 3 878 4 21 9856789892 85678 8 2 8767896789 87678 678 9899965678 8 65678 ``` --- ### Day 9: Smoke Basin - Part 2 ```r l <- lowest(h) h[] <- ifelse(h < 9, NA, Inf) h[l] <- 1:sum(l) while (anyNA(h)) { h <- h %c% cbind(h, NA)[, -1] %c% # right rbind(h, NA)[-1, ] %c% # down cbind(NA, h[, -ncol(h)]) %c% # left rbind(NA, h[-nrow(h), ]) # up } sizes <- table(h[is.finite(h)]) sort(sizes, decreasing = TRUE) |> head(3) |> prod() ``` ```r "%c%" <- function(x, y) { ifelse(is.infinite(x), x, ifelse(!is.na(x), x, ifelse(!is.infinite(y), y, x))) } ``` --- class: center, middle, inverse # Day 21: Dirac Dice <https://adventofcode.com/2021/day/21> --- ### Day 21: Dirac Dice - Part 1 Deterministic dice rolls: `1+2+3`, `4+5+6`, `7+8+9`, `...` Circular game track: `1, 2, ... 10, 1, ...` Players' scores increase by spaces they landed on. How many rolls till someone gets a score ≥1000? --- ### Day 21: Dirac Dice - Part 1 ```r deterministic_dice <- function(player1, player2) { score1 <- score2 <- nrolls <- 0 dice <- 1:3 repeat { player1 <- (player1 + sum(dice) - 1) %% 10 + 1 score1 <- score1 + player1 nrolls <- nrolls + 3 if (score1 >= 1000) break player2 <- (player2 + sum(dice + 3) - 1) %% 10 + 1 score2 <- score2 + player2 nrolls <- nrolls + 3 if (score2 >= 1000) break dice <- (dice + 6 - 1) %% 100 + 1 } prod(nrolls, min(score1, score2)) } ``` --- ### Day 21: Dirac Dice - Part 2 Three-sided die. On each roll, universe splits into three: one for each possible outcome. Game ends when a player's score reaches ≥21. Which player wins in more universes? How many? --- ### Day 21: Dirac Dice - Part 2 First notice that there are only seven possible sums of 3 rolls: ``` 3 4 5 6 7 8 9 # sum of the three dice 1 3 6 7 6 3 1 # number of combinations ``` Store in a list called `rolls`. --- ### Day 21: Dirac Dice - Part 2 ```r dirac_dice <- function(player1, player2) { count_wins <- memoise::memoise( function(player1, player2, score1, score2) { Reduce( \(wins, roll) { player1 <- (player1 + roll['sum'] - 1) %% 10 + 1 score1 <- score1 + player1 if (score1 >= 21) { return(wins + c(roll['n'], 0)) } else wins + roll['n'] * rev(count_wins(player2, player1, score2, score1)) }, rolls, init = c(w1 = 0, w2 = 0)) }) max(count_wins(player1, player2, 0, 0)) } ``` --- class: center, middle # Thanks! `david.selby@manchester.ac.uk` .small[For these slides: search `"rthritis" manchester`] <https://meetup.com/Warwick-useRs>