-
Notifications
You must be signed in to change notification settings - Fork 1
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
refactor(2024.07-haskell): add data types and flesh out docs
- Loading branch information
Showing
3 changed files
with
120 additions
and
41 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,6 +1,6 @@ | ||
The MIT License (MIT) | ||
|
||
Copyright © 2016-2022 Eric Bailey <[email protected]> | ||
Copyright © 2016-2025 Eric Bailey <[email protected]> | ||
|
||
Permission is hereby granted, free of charge, to any person obtaining a copy | ||
of this software and associated documentation files (the “Software”), to deal | ||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1 +1 @@ | ||
2024.7.2.3 | ||
2024.7.2.4 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,6 +1,35 @@ | ||
{-# LANGUAGE MonadComprehensions #-} | ||
|
||
module AdventOfCode.Year2024.Day07 where | ||
-- | | ||
-- Module : AdventOfCode.Year2024.Day07 | ||
-- Description : Advent of Code 2024 Day 7: Bridge Repair | ||
-- Copyright : (c) Eric Bailey, 2025 | ||
-- License : MIT | ||
-- Maintainer : [email protected] | ||
-- Stability : experimental | ||
-- Portability : POSIX | ||
-- https://adventofcode.com/2024/day/7 | ||
module AdventOfCode.Year2024.Day07 | ||
( -- * Introduction | ||
-- $intro | ||
|
||
-- * Data types | ||
CalibrationEquation, | ||
Operator (..), | ||
|
||
-- * Solution | ||
main, | ||
partOne, | ||
partTwo, | ||
execInverseOperation, | ||
calibrate, | ||
isPossible, | ||
|
||
-- * Input and example | ||
getInput, | ||
getExample, | ||
) | ||
where | ||
|
||
import AdventOfCode.Input (parseInput, parseString) | ||
import AdventOfCode.TH (defaultMain, inputFilePath) | ||
|
@@ -11,19 +40,74 @@ import Data.List.NonEmpty (NonEmpty (..)) | |
import Data.Maybe (mapMaybe) | ||
import Text.Trifecta (Parser, char, decimal, newline, sepEndBy, sepEndByNonEmpty, string) | ||
|
||
-- $intro | ||
-- This module borrows | ||
-- [ideas](https://github.com/mstksg/advent-of-code/wiki/Reflections-2024#day-7) | ||
-- from [Justin Le](https://blog.jle.im). In particular, 'isPossible' is | ||
-- essentially the same as Justin's | ||
-- [@search@](https://github.com/mstksg/advent-of-code/blob/0128ceaf/2024/AOC2024/Day07.hs#L24-L27). | ||
-- The main idea is to process the operands from right to left, which enables | ||
-- quickly filtering out equations that are impossible. | ||
|
||
-- | A calibration equation consists of a test value and a nonempty list of | ||
-- operands. | ||
type CalibrationEquation = (Int, NonEmpty Int) | ||
|
||
-- | An invertible binary operator. | ||
data Operator | ||
= -- | Add | ||
(:+:) | ||
| -- | Multiply | ||
(:*:) | ||
| -- | Concatenate | ||
(:||:) | ||
deriving (Eq, Show, Enum, Bounded) | ||
|
||
-- | Given an operator and two operands, execute the inverse operation. | ||
-- | ||
-- >>> execInverseOperation (:+:) 40 (81 + 40) | ||
-- Just 81 | ||
-- | ||
-- >>> execInverseOperation (:*:) 19 (10 * 19) | ||
-- Just 10 | ||
-- | ||
-- >>> execInverseOperation (:||:) 345 12345 | ||
-- Just 12 | ||
execInverseOperation :: Operator -> Int -> Int -> Maybe Int | ||
execInverseOperation operator x y = | ||
case operator of | ||
(:+:) -> [y - x | y >= x] | ||
(:*:) -> [y `div` x | y `mod` x == 0] | ||
(:||:) -> | ||
let pow = numDigits x | ||
(d, m) = y `divMod` (10 ^ pow) | ||
in [d | m == x] | ||
|
||
-- | Solve the puzzle and print the results. | ||
main :: IO () | ||
main = $(defaultMain) | ||
|
||
partOne :: [(Int, NonEmpty Int)] -> Int | ||
partOne = calibrate [unAdd, unMultiply] | ||
-- | Calibrate the equations using addition and multiplication. | ||
-- | ||
-- @partOne = 'calibrate' ['(:+:)', '(:*:)']@ | ||
partOne :: [CalibrationEquation] -> Int | ||
partOne = calibrate [(:+:), (:*:)] | ||
|
||
partTwo :: [(Int, NonEmpty Int)] -> Int | ||
partTwo = calibrate [unAdd, unMultiply, unConcatenate] | ||
-- | Calibrate the equations using addition, multiplication, and concatenation. | ||
-- | ||
-- @partTwo = 'calibrate' ['(:+:)', '(:*:)', '(:||:)']@ | ||
partTwo :: [CalibrationEquation] -> Int | ||
partTwo = calibrate [(:+:), (:*:), (:||:)] | ||
|
||
-- | Given a list of operators and a list of calibration equations, compute the | ||
-- calibration result, i.e., the sum of the test values from just the equations | ||
-- that could possibly be true. | ||
calibrate :: [Int -> Int -> Maybe Int] -> [(Int, NonEmpty Int)] -> Int | ||
-- sum of the test values from just the equations that could possibly be true. | ||
-- | ||
-- >>> calibrate [(:+:), (:*:)] <$> getExample | ||
-- 3749 | ||
-- | ||
-- >>> calibrate [(:+:), (:*:), (:||:)] <$> getExample | ||
-- 11387 | ||
calibrate :: [Operator] -> [CalibrationEquation] -> Int | ||
calibrate operators = foldl' go 0 | ||
where | ||
go acc eq = | ||
|
@@ -38,54 +122,49 @@ calibrate operators = foldl' go 0 | |
-- Process the operands from right to left, using the inverses of the given | ||
-- operators, to short circuit on operations that make the equation impossible. | ||
-- | ||
-- >>> isPossible [unAdd, unMultiply] (190, 10 :| [19]) | ||
-- @190: 10 19@ has only one position that accepts an operator: between @10@ and | ||
-- @19@. Choosing @+@ would give @29@, but choosing @*@ would give the test | ||
-- value (@10 * 19 = 190@). | ||
-- | ||
-- >>> isPossible [(:+:), (:*:)] (190, 10 :| [19]) | ||
-- True | ||
isPossible :: [Int -> Int -> Maybe Int] -> (Int, NonEmpty Int) -> Bool | ||
isPossible operators (testValue, operand :| operands) = | ||
operand `elem` foldrM go testValue operands | ||
where | ||
go x y = mapMaybe (\f -> f x y) operators | ||
|
||
-- | The inverse of addition. | ||
-- | ||
-- >>> unAdd 40 121 | ||
-- Just 81 | ||
unAdd :: Int -> Int -> Maybe Int | ||
unAdd x y = [y - x | y >= x] | ||
|
||
-- | The inverse of multiplication. | ||
-- @3267: 81 40 27@ has two positions for operators. Of the four possible | ||
-- configurations of the operators, /two/ cause the right side to match the test | ||
-- value: @81 + 40 * 27@ and @81 * 40 + 27@ both equal @3267@ (when evaluated | ||
-- left-to-right)! | ||
-- | ||
-- >>> unMultiply 19 190 | ||
-- Just 10 | ||
unMultiply :: Int -> Int -> Maybe Int | ||
unMultiply x y = [y `div` x | y `mod` x == 0] | ||
|
||
-- | The inverse of concatenation. | ||
-- >>> isPossible [(:+:), (:*:)] (3267, 81 :| [40, 27]) | ||
-- True | ||
-- | ||
-- >>> unConcatenate 345 12345 | ||
-- Just 12 | ||
unConcatenate :: Int -> Int -> Maybe Int | ||
unConcatenate x y = [d | m == x] | ||
-- @292: 11 6 16 20@ can be solved in exactly one way: @11 + 6 * 16 + 20@. | ||
-- | ||
-- >>> isPossible [(:+:), (:*:)] (292, 11 :| [6, 16, 20]) | ||
-- True | ||
isPossible :: [Operator] -> CalibrationEquation -> Bool | ||
isPossible operators (testValue, operand :| operands) = | ||
operand `elem` foldrM go testValue operands | ||
where | ||
pow = numDigits x | ||
(d, m) = y `divMod` (10 ^ pow) | ||
go x y = mapMaybe (\operator -> execInverseOperation operator x y) operators | ||
|
||
getInput :: IO [(Int, NonEmpty Int)] | ||
-- | Parse the input into a list of calibration equations. | ||
getInput :: IO [CalibrationEquation] | ||
getInput = parseInput (calibrationEquation `sepEndBy` newline) $(inputFilePath) | ||
|
||
-- | Parse a calibration equation, i.e., a test value and a nonempty list of | ||
-- operands. | ||
calibrationEquation :: Parser (Int, NonEmpty Int) | ||
-- | Parse a calibration equation. | ||
calibrationEquation :: Parser CalibrationEquation | ||
calibrationEquation = | ||
(,) | ||
<$> (decimalInt <* string ": ") | ||
<*> decimalInt `sepEndByNonEmpty` char ' ' | ||
where | ||
decimalInt = fromInteger <$> decimal | ||
|
||
getExample :: IO [(Int, NonEmpty Int)] | ||
-- | Parse the example into a list of calibration equations. | ||
getExample :: IO [CalibrationEquation] | ||
getExample = parseString (calibrationEquation `sepEndBy` newline) example | ||
|
||
-- | The example. | ||
example :: String | ||
example = | ||
"190: 10 19\n\ | ||
|