Skip to content

Commit

Permalink
Maths, how do they work
Browse files Browse the repository at this point in the history
  • Loading branch information
ephemient committed Dec 10, 2023
1 parent a89cf7b commit cdd0b5f
Show file tree
Hide file tree
Showing 4 changed files with 159 additions and 270 deletions.
86 changes: 36 additions & 50 deletions hs/src/Day10.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,71 +2,57 @@
Module: Day10
Description: <https://adventofcode.com/2023/day/10 Day 10: Pipe Maze>
-}
{-# LANGUAGE ViewPatterns #-}
module Day10 (solve) where

import Control.Arrow (first, second)
import Control.Monad (ap, guard)
import Data.Ix (range)
import Data.List ((\\), sort)
import Data.Maybe (listToMaybe)
import Control.Monad (guard)
import Data.List (scanl')
import Data.Map (Map)
import qualified Data.Map as Map ((!?), fromList)
import Data.Maybe (isJust, listToMaybe)
import Data.Text (Text)
import qualified Data.Text as T (index, length, lines, unpack)
import qualified Data.Text as T (index, length, lines, split)
import Data.Vector (Vector)
import qualified Data.Vector as V ((!), foldl', fromList, imap, length)
import qualified Data.Vector as V ((!), fromList, length)

data Direction = U | L | D | R deriving Eq

inverse :: Direction -> Direction
inverse U = D
inverse L = R
inverse D = U
inverse R = L
data Direction = U | L | D | R deriving (Eq, Ord, Show)

move :: Direction -> (Int, Int) -> (Int, Int)
move U = first pred
move L = second pred
move D = first succ
move R = second succ

(!) :: Vector Text -> (Int, Int) -> [Direction]
maze ! (y, x)
| '|' <- char = [U, D]
| '-' <- char = [L, R]
| 'L' <- char = [U, R]
| 'J' <- char = [U, L]
| '7' <- char = [L, D]
| 'F' <- char = [D, R]
| otherwise = []
where
line = maze V.! y
char
| y < 0 || y >= V.length maze = '.'
| x < 0 || x >= T.length line = '.'
| otherwise = line `T.index` x
lut :: Map (Direction, Char) Direction
lut = Map.fromList
[ ((U, '|'), U), ((U, '7'), L), ((U, 'F'), R)
, ((L, '-'), L), ((L, 'F'), D), ((L, 'L'), U)
, ((D, '|'), D), ((D, 'L'), R), ((D, 'J'), L)
, ((R, '-'), R), ((R, 'J'), U), ((R, '7'), D)
]

solve :: Text -> Maybe (Int, Int)
solve input = listToMaybe $ do
let maze = V.fromList $ T.lines input
height = V.length maze
width = V.foldl' (flip $ max . T.length) 0 maze
follow k (inverse -> d) pos
| d `elem` ds = ds \\ [d] >>= follow k' `ap` flip move pos
| otherwise = [(k', d)]
where
ds = maze ! pos
k' = pos : k
start <- concat . flip V.imap maze $ \y line ->
[(y, x) | (x, 'S') <- zip [0..] $ T.unpack line]
d0 <- [U, L, D, R]
(path@(end:_), d1) <- follow [] d0 $ move d0 start
startY <- [0..V.length maze - 1]
let line = maze V.! startY
startX <- drop 1 . init . scanl' (flip $ (+) . succ . T.length) (-1) $
T.split (== 'S') line
startDir <- [U, L, D, R]
let start = (startY, startX)
f (pos, Just dir)
| 0 <= y && y < V.length maze, line <- maze V.! y
, 0 <= x && x < T.length line, char <- line `T.index` x
= (pos', lut Map.!? (dir, char))
| otherwise = (pos', Nothing)
where pos'@(y, x) = move dir pos
(path, (end, _) : _) = first (map fst) . span (isJust . snd) $
iterate f (start, Just startDir)
guard $ start == end
let count (k, up, down, path) pos
| pos':path' <- path, pos == pos'
= (k, up /= (U `elem` dirs), down /= (D `elem` dirs), path')
where dirs = if pos == start then [d0, d1] else maze ! pos
count k@(_, False, False, _) _ = k
count (!k, True, True, path) _ = (k + 1, True, True, path)
(area, False, False, []) = foldl count (0, False, False, sort path) $
range ((0, 0), (height - 1, width - 1))
pure (length path `div` 2, area)
let (part1, 0) = length path `divMod` 2
(halfArea, 0) = sum
[ x0 * y1 - x1 * y0
| ((y0, x0), (y1, x1)) <- zip path $ drop 1 path ++ path
] `divMod` 2
part2 = abs halfArea - part1 + 1
pure (part1, part2)
Original file line number Diff line number Diff line change
@@ -1,89 +1,67 @@
package com.github.ephemient.aoc2023

import kotlin.math.absoluteValue

class Day10(input: String) {
private val maze = input.lines()
private val height = maze.size
private val width = maze.maxOf { it.length }
private lateinit var start: IntPair
private lateinit var startDirs: List<Direction>
private lateinit var path: List<IntPair>

@Suppress("NestedBlockDepth")
fun part1(): Int {
for ((y, line) in maze.withIndex()) {
for ((x, char) in line.withIndex()) {
if (char != 'S') continue
val start = y to x
dir@for (startDir in Direction.entries) {
var pos = start.move(startDir)
var lastDir = -startDir
val path = mutableListOf(start)
while (pos != start) {
val dir = symbols[maze.getOrNull(pos.first)?.getOrNull(pos.second)]
?.takeIf { lastDir in it }
?.singleOrNull { it != lastDir }
?: continue@dir
path += pos
pos = pos.move(dir)
lastDir = -dir
val startPos = y to x
for (startDir in Direction.entries) {
var pos = startPos
val path = buildList {
var dir = startDir
while (true) {
add(pos)
pos = pos.move(dir)
dir = lut[dir to maze.getOrNull(pos.first)?.getOrNull(pos.second)] ?: break
}
}.toList()
if (pos == startPos) {
this.path = path
return path.size / 2
}
this.start = start
this.startDirs = listOf(startDir, lastDir)
this.path = path
return path.size / 2
}
}
}
@Suppress("UseCheckOrError")
throw IllegalStateException("No loop found")
}

@Suppress("NestedBlockDepth")
fun part2(): Int {
if (!::start.isInitialized) part1()
val path = path.sortedWith(compareBy(IntPair::first, IntPair::second))
var count = 0
var up = false
var down = false
var pathIndex = 0
for (y in 0 until height) {
for (x in 0 until width) {
if (pathIndex < path.size && path[pathIndex].let { it.first == y && it.second == x }) {
pathIndex++
val dirs = if (start.first == y && start.second == x) startDirs else symbols[maze[y][x]]!!
up = up != dirs.contains(Direction.U)
down = down != dirs.contains(Direction.D)
} else {
if (up && down) count++
check(up == down)
}
}
}
check(!up && !down && pathIndex == path.size)
return count
if (!::path.isInitialized) part1()
return 1 + (
path.asSequence().plus(path[0]).zipWithNext { (y0, x0), (y1, x1) ->
x0 * y1 - x1 * y0
}.sum().absoluteValue - path.size
) / 2
}

private enum class Direction {
U, L, D, R,
}

companion object {
private val symbols = mapOf(
'|' to listOf(Direction.U, Direction.D),
'-' to listOf(Direction.L, Direction.R),
'L' to listOf(Direction.U, Direction.R),
'J' to listOf(Direction.U, Direction.L),
'7' to listOf(Direction.L, Direction.D),
'F' to listOf(Direction.D, Direction.R),
private val lut = mapOf(
Direction.U to '|' to Direction.U,
Direction.U to '7' to Direction.L,
Direction.U to 'F' to Direction.R,
Direction.L to '-' to Direction.L,
Direction.L to 'F' to Direction.D,
Direction.L to 'L' to Direction.U,
Direction.D to '|' to Direction.D,
Direction.D to 'L' to Direction.R,
Direction.D to 'J' to Direction.L,
Direction.R to '-' to Direction.R,
Direction.R to 'J' to Direction.U,
Direction.R to '7' to Direction.D,
)

private operator fun Direction.unaryMinus(): Direction = when (this) {
Direction.U -> Direction.D
Direction.L -> Direction.R
Direction.D -> Direction.U
Direction.R -> Direction.L
}

private fun IntPair.move(dir: Direction) = when (dir) {
Direction.U -> first - 1 to second
Direction.L -> first to second - 1
Expand Down
Loading

0 comments on commit cdd0b5f

Please sign in to comment.