Day 3
This commit is contained in:
34
src/Days/D03.hs
Normal file
34
src/Days/D03.hs
Normal file
@@ -0,0 +1,34 @@
|
||||
{-# LANGUAGE ImportQualifiedPost #-}
|
||||
|
||||
module Days.D03 where
|
||||
|
||||
import Data.Char (ord)
|
||||
import Data.List (intersect)
|
||||
import Data.List.Extra (chunksOf)
|
||||
import Lib (Day (StringDay), definitive)
|
||||
|
||||
type Intermediate = [String]
|
||||
|
||||
halves :: [a] -> ([a], [a])
|
||||
halves l = splitAt (length l `div` 2) l
|
||||
|
||||
priority :: Char -> Int
|
||||
priority c =
|
||||
let o = ord c
|
||||
in if o < ord 'a'
|
||||
then o - ord 'A' + 26 + 1
|
||||
else o - ord 'a' + 1
|
||||
|
||||
part1 :: [String] -> Int
|
||||
part1 = sum . map (priority . head . uncurry intersect . halves)
|
||||
|
||||
part2 :: [String] -> Int
|
||||
part2 = sum . map (priority . head . foldl1 intersect) . chunksOf 3
|
||||
|
||||
day :: Day
|
||||
day =
|
||||
StringDay
|
||||
( \s ->
|
||||
let l = lines s
|
||||
in Right (definitive $ part1 l, definitive $ part2 l)
|
||||
)
|
||||
@@ -4,13 +4,13 @@
|
||||
|
||||
module Lib where
|
||||
|
||||
import Util (both, dupe)
|
||||
import Util (both)
|
||||
|
||||
import Data.Function ((&))
|
||||
import Data.Text qualified as T
|
||||
import Data.Text.IO qualified as T
|
||||
import Data.Void (Void)
|
||||
import Text.Megaparsec qualified as M (Parsec, eof, errorBundlePretty, parse, sepEndBy1)
|
||||
import Text.Megaparsec qualified as M (Parsec, eof, errorBundlePretty, parse)
|
||||
|
||||
data Answer where
|
||||
Answer :: (Show a) => a -> Answer
|
||||
|
||||
@@ -1,7 +1,6 @@
|
||||
module Print where
|
||||
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Lib (DayResult, PuzzleError (..))
|
||||
import Lib (DayResult)
|
||||
import Text.Printf (printf)
|
||||
|
||||
printDR :: Int -> DayResult -> IO ()
|
||||
|
||||
@@ -5,6 +5,3 @@ dupe a = (a, a)
|
||||
|
||||
both :: (a -> b) -> (a, a) -> (b, b)
|
||||
both f ~(x, y) = (f x, f y)
|
||||
|
||||
mapSnd :: (b -> c) -> (a, b) -> (a, c)
|
||||
mapSnd f (a, b) = (a, f b)
|
||||
Reference in New Issue
Block a user