1
0
Fork 0

Compare commits

..

2 Commits

Author SHA1 Message Date
Bill Ewanick d54b9f9812 Be smarter! 2024-12-21 13:06:55 -05:00
Bill Ewanick b818aa089e Advent of Code 2024 Day 1 and 2 2024-12-21 13:06:43 -05:00
4 changed files with 1069 additions and 8 deletions

View File

@ -1,13 +1,14 @@
-- https://adventofcode.com/2024/day/1 -- https://adventofcode.com/2024/day/1
import Data.List import Data.List (elemIndices, sort)
import GHC.IO import GHC.IO (unsafePerformIO)
input :: FilePath input :: FilePath
input = "src/advent_of_code/2024/1.input" input = "src/advent_of_code/2024/1.input"
entries :: ([Int], [Int]) -- entries :: ([Int], [Int])
entries = unzip $ map parse' $ unsafePerformIO $ lines <$> readFile input -- entries = unzip $ map parse' $ unsafePerformIO $ lines <$> readFile input
entries = unsafePerformIO $ lines <$> readFile input
main :: IO () main :: IO ()
main = do main = do
@ -20,12 +21,10 @@ main = do
parse' :: String -> (Int, Int) parse' :: String -> (Int, Int)
parse' str = (read l, read r) parse' str = (read l, read r)
where where
l = take' str [l, r] = words str
r = reverse $ take' $ reverse str
take' = takeWhile (/= ' ')
solveP1 :: ([Int], [Int]) -> Int solveP1 :: ([Int], [Int]) -> Int
solveP1 (as, bs) = sum $ zipWith (\i j -> abs (i - j)) as' bs' solveP1 (as, bs) = sum $ map abs $ zipWith subtract as' bs'
where where
as' = sort as as' = sort as
bs' = sort bs bs' = sort bs

View File

@ -0,0 +1,56 @@
-- https://adventofcode.com/2024/day/2
{-# LANGUAGE OverloadedStrings #-}
import Data.List hiding (lines)
import Data.Text (Text, lines, pack, splitOn, unpack)
import Data.Text.IO (readFile)
import GHC.IO (unsafePerformIO)
import Prelude hiding (lines, readFile)
entries :: [[Int]]
entries = parse . unsafePerformIO $ lines <$> readFile "src/advent_of_code/2024/2.input"
entries' :: [[Int]]
entries' = parse . unsafePerformIO $ lines <$> readFile "src/advent_of_code/2024/2f.input"
parse :: [Text] -> [[Int]]
parse = map (map (read . unpack) . splitOn " ")
main :: IO ()
main = do
entries <- parse . lines <$> readFile "src/advent_of_code/2024/2.input"
print "Advent of Code 2024 - Day 2"
print $ "Part 1: " <> show (solveP1 entries)
print $ "Part 2: " <> show (solveP2 entries)
solveP1 :: [[Int]] -> Int
solveP1 = length . filter (== True) . map safeReport
safeReport :: [Int] -> Bool
safeReport report = isSorted && adjacentLevelCheck
where
isSorted = sortedReportASC == report || sortedReportDESC == report
sortedReportASC = sort report
sortedReportDESC = reverse sortedReportASC
adjacentLevelCheck =
all (((== True) . (\n-> n>=1 && n<=3)) . abs)
(zipWith subtract report (tail report))
solveP2 :: [[Int]] -> Int
solveP2 = length . filter (== True) . map safeReport'
safeReport' :: [Int] -> Bool
safeReport' report =
or $ zipWith (&&) (map adjacentLevelCheck reports) (map isSorted reports)
where
isSorted report = report `elem` [sort report, reverse (sort report)]
adjacentLevelCheck report =
all (((== True) . (\n-> n>=1 && n<=3)) . abs)
(zipWith subtract report (tail report))
reports = map tail $ permutations report

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,6 @@
7 6 4 2 1
1 2 7 8 9
9 7 6 2 1
1 3 2 4 5
8 6 4 4 1
1 3 6 7 9