Day01: solve part 1
This commit is contained in:
parent
f7197a5623
commit
04636aacc5
6 changed files with 1042 additions and 11 deletions
0
README.org
Normal file
0
README.org
Normal file
|
|
@ -132,6 +132,7 @@ test-suite spec
|
|||
main-is: Spec.hs
|
||||
other-modules:
|
||||
AoCSpec.UtilSpec
|
||||
AoCSpec.Y2023Spec
|
||||
SpecHook
|
||||
Paths_aoc
|
||||
autogen-modules:
|
||||
|
|
|
|||
File diff suppressed because it is too large
Load diff
22
src/AoC.hs
22
src/AoC.hs
|
|
@ -1,7 +1,8 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module AoC (
|
||||
defaultMain,
|
||||
runAoC,
|
||||
module AoC.Day,
|
||||
module AoC.Year,
|
||||
) where
|
||||
|
||||
import AoC.Day
|
||||
|
|
@ -14,17 +15,18 @@ import System.IO.Error qualified as IOError
|
|||
|
||||
import AoC.Y2023 qualified as Y2023
|
||||
|
||||
runAoC :: (MonadIO m) => [String] -> m ()
|
||||
runAoC _args = do
|
||||
riddle <- loadRiddle Y2023 D01
|
||||
result <- Y2023.solve D01 riddle
|
||||
print result
|
||||
runAoC :: (MonadIO m) => Year -> Day -> m (Either Text Solution)
|
||||
runAoC y d = do
|
||||
riddle <- loadRiddle y d
|
||||
solve y d riddle
|
||||
|
||||
solve :: (MonadIO m) => Year -> Day -> Riddle -> m (Either Text Solution)
|
||||
solve Y2023 = Y2023.solve
|
||||
solve y = \_ _ -> pure $ Left $ show y <> ": not implementedi"
|
||||
|
||||
handleError :: IOError.IOError -> IO ()
|
||||
handleError e = do
|
||||
hPutStrLn stderr $ "I ran into an issue: " <> show e
|
||||
|
||||
defaultMain :: IO ()
|
||||
defaultMain = do
|
||||
args <- getArgs
|
||||
Exception.catch (runAoC args) handleError
|
||||
defaultMain = Exception.catch (runAoC Y2023 D01 >>= print) handleError
|
||||
|
|
|
|||
|
|
@ -1,6 +1,24 @@
|
|||
module AoC.Y2023.D01 (solve) where
|
||||
|
||||
import AoC.Riddle
|
||||
import Data.Char (digitToInt, isDigit)
|
||||
import Relude.Unsafe (fromJust)
|
||||
|
||||
digits :: String -> [Int]
|
||||
digits = fmap digitToInt . filter isDigit
|
||||
|
||||
digits' :: String -> NonEmpty Int
|
||||
digits' = fromJust . nonEmpty . digits
|
||||
|
||||
calibrationValue :: String -> Int
|
||||
calibrationValue s = firstDigit * 10 + lastDigit
|
||||
where
|
||||
ds = digits' s
|
||||
firstDigit = head ds
|
||||
lastDigit = last ds
|
||||
|
||||
solvePart1 :: Text -> Integer
|
||||
solvePart1 = fromIntegral . sum . fmap (calibrationValue . toString) . lines
|
||||
|
||||
solve :: (MonadIO m) => Text -> m (Either Text Solution)
|
||||
solve _ = pure $ Left "not yet implemented"
|
||||
solve input = pure $ Right [solvePart1 input]
|
||||
|
|
|
|||
10
test/spec/AoCSpec/Y2023Spec.hs
Normal file
10
test/spec/AoCSpec/Y2023Spec.hs
Normal file
|
|
@ -0,0 +1,10 @@
|
|||
module AoCSpec.Y2023Spec (spec) where
|
||||
|
||||
import AoC
|
||||
import Test.Hspec
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
describe "Day 1" do
|
||||
it "calculates correctly" do
|
||||
runAoC Y2023 D01 `shouldReturn` Right [54331]
|
||||
Loading…
Add table
Add a link
Reference in a new issue