AoC/2023/day15/day15.hs
Gattix be9d88184c day15: not working
to be discarded, but cool enough to keep around in git I guess
2023-12-17 11:31:11 +01:00

44 lines
1.2 KiB
Haskell

import Control.Arrow
import Data.Function
import Data.List
import Data.List.Split
import Data.Maybe
import Text.Read
type HASH = (String, Maybe Int)
main :: IO ()
main = interact $ show . genBuckets . parse . init
parse :: String -> [HASH]
parse = map (second (readMaybe . tail) . break (`elem` "=-")) . splitOn ","
day15a :: String -> Int
day15a = sum . map (foldl' hashAlg 0) . splitOn ","
hashAlg :: Int -> Char -> Int
hashAlg x y = (17 * (fromEnum y + x)) `mod` 256
removeHashes :: [String] -> [HASH] -> [HASH]
removeHashes _ [] = []
removeHashes rs ((label, Nothing):xs) = removeHashes (label : rs) xs
removeHashes rs ((label, Just x):xs)
| label `elem` rs = removeHashes (delete label rs) xs
| otherwise = (label, Just x) : removeHashes rs xs
genBuckets :: [HASH] -> Int
genBuckets input =
sum
[ sum $ zipWith (*) [1 ..] $ map ((* (succ x)) . fromJust . snd) (sorted x)
| x <- [0 .. 255]
]
where
filterBucket x f =
nubBy ((==) `on` fst) $
f $ removeHashes [] (reverse $ filter (f1 x) input)
sorted x =
sortOn
(\y -> fst y `elemIndex` (map fst (filterBucket x reverse)))
(filterBucket x id)
f1 n (x, _) = foldl hashAlg 0 x == n