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

View File

@@ -12,31 +12,45 @@ source-repository head
location: https://github.com/ctsk/aoc-2022 location: https://github.com/ctsk/aoc-2022
common warnings common warnings
ghc-options: -Wall -O2 -ddump-simpl -ddump-to-file ghc-options: -Wall
common defaults
default-language: Haskell2010
build-depends:
base ^>=4.18.0.0
, extra ^>=1.7.14
, containers
library library
default-language: Haskell2010 import: warnings, defaults
hs-source-dirs: src hs-source-dirs: src
ghc-options: -Wall -O2 -ddump-simpl -ddump-to-file
exposed-modules: exposed-modules:
Lib Lib
Print other-modules:
Common
Parse Parse
Print
Util Util
Days.D01 Days.D01
Days.D02 Days.D02
Days.D03 Days.D03
build-depends: build-depends:
base ^>=4.18.0.0 megaparsec ^>=9.4.0
, extra ^>=1.7.14
, megaparsec ^>=9.4.0
, text , text
executable Y2022 executable Y2022
import: warnings import: warnings, defaults
hs-source-dirs: app
main-is: Main.hs main-is: Main.hs
build-depends: build-depends:
Y2022 Y2022
, base ^>=4.18.0.0
hs-source-dirs: app benchmark Y2022-bench
default-language: Haskell2010 import: defaults
type: exitcode-stdio-1.0
hs-source-dirs: bench
main-is: Bench.hs
build-depends:
Y2022
, criterion ^>=1.6.3.0

View File

@@ -3,21 +3,19 @@
module Main where module Main where
import Lib import Lib
import Print
import qualified Days.D01 as D01
import qualified Days.D02 as D02
import qualified Days.D03 as D03
import System.Environment (getArgs) import System.Environment (getArgs)
solutions :: [(Int, Day, FilePath)] paths :: [FilePath]
solutions = paths =
[ (1, D01.day, "./data/01.in") [ "./data/01.in"
, (2, D02.day, "./data/02.in") , "./data/02.in"
, (3, D03.day, "./data/03.in") , "./data/03.in"
] ]
solutions :: [(Int, Day, FilePath)]
solutions = zip3 [1 ..] (map head days) paths
runAll :: [(Int, Day, FilePath)] -> IO () runAll :: [(Int, Day, FilePath)] -> IO ()
runAll = mapM_ (\(dayNum, day, path) -> run day path >>= printDR dayNum) runAll = mapM_ (\(dayNum, day, path) -> run day path >>= printDR dayNum)

9
bench/Bench.hs Normal file
View File

@@ -0,0 +1,9 @@
module Main where
import Criterion (bench, whnfIO)
import Criterion.Main (defaultMain)
main =
defaultMain
[ bench "whnfIO readFile" $ whnfIO (readFile "Y2022.cabal")
]

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 module Days.D01 where
import Lib (Day, Parser, definitive, parsecDay) import Common
import Parse (number, someLines)
import Data.List (sortBy) import Data.List (sortBy)
import Parse
type Intermediate = [[Int]] type Intermediate = [[Int]]

View File

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

View File

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

View File

@@ -1,55 +1,29 @@
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ImportQualifiedPost #-} {-# 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.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 :: Day -> FilePath -> IO DayResult
run (TextDay f) = fmap f . T.readFile run (TextDay f) = fmap f . T.readFile
run (StringDay f) = fmap f . readFile run (StringDay f) = fmap f . readFile
run (ParsecDay f) = \path -> f path <$> T.readFile path run (ParsecDay f) = \path -> f path <$> T.readFile path
type Parser = M.Parsec Void T.Text days :: [[Day]]
days =
parsecDay :: [ [D01.day]
Parser a -> , [D02.day]
(a -> Result, a -> Result) -> , [D03.day]
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

@@ -2,14 +2,32 @@
module Parse where 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 qualified as M
import Text.Megaparsec.Char qualified as MC import Text.Megaparsec.Char qualified as MC
import Text.Megaparsec.Char.Lexer qualified as MCL import Text.Megaparsec.Char.Lexer qualified as MCL
import Util (both)
someLines :: Parser a -> Parser [a] someLines :: Parser a -> Parser [a]
someLines p = p `M.sepEndBy1` MC.newline someLines p = p `M.sepEndBy1` MC.newline
number :: Parser Int 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 module Print where
import Lib (DayResult) import Common
import Text.Printf (printf) import Text.Printf (printf)
printDR :: Int -> DayResult -> IO () printDR :: Int -> DayResult -> IO ()