Reorganize imports

This commit is contained in:
ctsk
2023-08-30 09:32:12 +02:00
parent 404d2180af
commit 359aee0f22
10 changed files with 153 additions and 115 deletions

28
src/Common.hs Normal file
View File

@@ -0,0 +1,28 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ImportQualifiedPost #-}
module Common where
import Data.Text qualified as T
data Answer where
Answer :: (Show a) => a -> Answer
instance Show Answer where
showsPrec p (Answer a) = showsPrec p a
data PuzzleError
= MalformedInput String
| Unsolvable
type Result = Maybe Answer
definitive :: (Show a) => a -> Result
definitive = Just . Answer
type DayResult = Either String (Result, Result)
data Day
= TextDay (T.Text -> DayResult)
| StringDay (String -> DayResult)
| ParsecDay (FilePath -> T.Text -> DayResult)

View File

@@ -1,9 +1,8 @@
module Days.D01 where
import Lib (Day, Parser, definitive, parsecDay)
import Parse (number, someLines)
import Common
import Data.List (sortBy)
import Parse
type Intermediate = [[Int]]

View File

@@ -3,10 +3,9 @@
module Days.D02 where
import Lib
import Parse
import Common
import Data.Functor ((<&>))
import Parse
import Text.Megaparsec (oneOf)
import Text.Megaparsec.Char (space)
@@ -18,23 +17,23 @@ type Intermediate = [(Play, Guide)]
parser :: Parser Intermediate
parser = someLines line
where
line :: Parser (Play, Guide)
line = (,) <$> elf <* space <*> guide
where
line :: Parser (Play, Guide)
line = (,) <$> elf <* space <*> guide
elf :: Parser Play
elf =
oneOf "ABC" <&> \case
'A' -> Rock
'B' -> Paper
'C' -> Scissors
elf :: Parser Play
elf =
oneOf "ABC" <&> \case
'A' -> Rock
'B' -> Paper
'C' -> Scissors
guide :: Parser Guide
guide =
oneOf "XYZ" <&> \case
'X' -> X
'Y' -> Y
'Z' -> Z
guide :: Parser Guide
guide =
oneOf "XYZ" <&> \case
'X' -> X
'Y' -> Y
'Z' -> Z
playScore :: Play -> Int
playScore = (1 +) . fromEnum
@@ -47,33 +46,33 @@ convert = toEnum . fromEnum
part1 :: Intermediate -> Int
part1 = sum . map f
where
f (elf, guide) = let us = convert guide in playScore us + winScore (outcome elf us)
where
f (elf, guide) = let us = convert guide in playScore us + winScore (outcome elf us)
outcome :: Play -> Play -> Outcome
outcome Rock Rock = Draw
outcome Rock Paper = Win
outcome Rock Scissors = Loss
outcome Paper Rock = Loss
outcome Paper Paper = Draw
outcome Paper Scissors = Win
outcome Scissors Rock = Win
outcome Scissors Paper = Loss
outcome Scissors Scissors = Draw
outcome :: Play -> Play -> Outcome
outcome Rock Rock = Draw
outcome Rock Paper = Win
outcome Rock Scissors = Loss
outcome Paper Rock = Loss
outcome Paper Paper = Draw
outcome Paper Scissors = Win
outcome Scissors Rock = Win
outcome Scissors Paper = Loss
outcome Scissors Scissors = Draw
part2 :: Intermediate -> Int
part2 = sum . map f
where
f (elf, guide) = let us = convert guide in winScore us + playScore (counter us elf)
where
f (elf, guide) = let us = convert guide in winScore us + playScore (counter us elf)
counter :: Outcome -> Play -> Play
counter Draw e = e
counter Win Rock = Paper
counter Win Paper = Scissors
counter Win Scissors = Rock
counter Loss Rock = Scissors
counter Loss Paper = Rock
counter Loss Scissors = Paper
counter :: Outcome -> Play -> Play
counter Draw e = e
counter Win Rock = Paper
counter Win Paper = Scissors
counter Win Scissors = Rock
counter Loss Rock = Scissors
counter Loss Paper = Rock
counter Loss Scissors = Paper
day :: Day
day = parsecDay parser (definitive . part1, definitive . part2)

View File

@@ -1,11 +1,10 @@
{-# LANGUAGE ImportQualifiedPost #-}
module Days.D03 where
import Common
import Data.Char (ord)
import Data.List (intersect)
import Data.List.Extra (chunksOf)
import Lib (Day (StringDay), definitive)
type Intermediate = [String]

View File

@@ -1,55 +1,29 @@
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ImportQualifiedPost #-}
module Lib where
module Lib (
run,
Day,
days,
printDR,
) where
import Util (both)
import Common (Day (..), DayResult)
import Print (printDR)
import Days.D01 qualified as D01
import Days.D02 qualified as D02
import Days.D03 qualified as D03
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)
data Answer where
Answer :: (Show a) => a -> Answer
instance Show Answer where
showsPrec p (Answer a) = showsPrec p a
data PuzzleError
= MalformedInput String
| Unsolvable
type Result = Maybe Answer
definitive :: (Show a) => a -> Result
definitive = Just . Answer
type DayResult = Either String (Result, Result)
data Day
= TextDay (T.Text -> DayResult)
| StringDay (String -> DayResult)
| ParsecDay (FilePath -> T.Text -> DayResult)
run :: Day -> FilePath -> IO DayResult
run (TextDay f) = fmap f . T.readFile
run (StringDay f) = fmap f . readFile
run (ParsecDay f) = \path -> f path <$> T.readFile path
type Parser = M.Parsec Void T.Text
parsecDay ::
Parser a ->
(a -> Result, a -> Result) ->
Day
parsecDay parser parts =
ParsecDay
( \path text ->
( case M.parse (parser <* M.eof) path text of
Left e -> Left $ M.errorBundlePretty e
Right parsedInput -> Right $ both (parsedInput &) parts
)
)
days :: [[Day]]
days =
[ [D01.day]
, [D02.day]
, [D03.day]
]

View File

@@ -2,14 +2,32 @@
module Parse where
import Lib (Parser)
import Common
import Data.Function ((&))
import Data.Text qualified as T
import Data.Void
import Text.Megaparsec qualified as M
import Text.Megaparsec.Char qualified as MC
import Text.Megaparsec.Char.Lexer qualified as MCL
import Util (both)
someLines :: Parser a -> Parser [a]
someLines p = p `M.sepEndBy1` MC.newline
number :: Parser Int
number = MCL.decimal
number = MCL.decimal
type Parser = M.Parsec Void T.Text
parsecDay ::
Parser a ->
(a -> Result, a -> Result) ->
Day
parsecDay parser parts =
ParsecDay
( \path text ->
( case M.parse (parser <* M.eof) path text of
Left e -> Left $ M.errorBundlePretty e
Right parsedInput -> Right $ both (parsedInput &) parts
)
)

View File

@@ -1,6 +1,6 @@
module Print where
import Lib (DayResult)
import Common
import Text.Printf (printf)
printDR :: Int -> DayResult -> IO ()