Move Parser definition to its own module

This commit is contained in:
Alexander Kobjolke 2023-12-03 00:52:48 +01:00
parent 4ef752a765
commit a891996352
5 changed files with 33 additions and 26 deletions

19
src/AoC/Parser.hs Normal file
View file

@ -0,0 +1,19 @@
module AoC.Parser (Parser, parseText, ws, linewise) where
import Text.Megaparsec (Parsec, parse, sepEndBy1)
import Text.Megaparsec.Char (eol, space1)
import Text.Megaparsec.Char.Lexer qualified as L
type Parser = Parsec Void Text
parseText :: Parser a -> Text -> Either Text a
parseText p t = case parse p "<inline>" t of
Right a -> pure a
Left e -> Left $ show e
-- skip whitespace
ws :: Parser ()
ws = L.space space1 empty empty
linewise :: Parser a -> Parser [a]
linewise p = p `sepEndBy1` eol

View file

@ -1,7 +1,7 @@
module AoC.Riddle (
Riddle (..),
Error (..),
Solution (..),
Riddle,
Error,
Solution,
loadRiddle,
) where

View file

@ -1,30 +1,16 @@
module AoC.Y2023.D02 where
module AoC.Y2023.D02 (solve) where
import AoC.Parser
import AoC.Riddle
import Data.Map (foldMapWithKey)
import Data.Map qualified as M
import Text.Megaparsec (Parsec, choice, parse, sepBy, sepEndBy1)
import Text.Megaparsec.Char (char, eol, space1, string)
import Text.Megaparsec (choice, sepBy)
import Text.Megaparsec.Char (char, space1, string)
import Text.Megaparsec.Char.Lexer qualified as L
type Parser = Parsec Void Text
data Cube = Red | Green | Blue
deriving stock (Eq, Ord, Enum, Show)
parseText :: Parser a -> Text -> Either Text a
parseText p t = case parse p "<inline>" t of
Right a -> pure a
Left e -> Left $ show e
-- skip whitespace
ws :: Parser ()
ws = L.space space1 empty empty
linewise :: Parser a -> Parser [a]
linewise p = p `sepEndBy1` eol
type Round = Map Cube Integer
pRound :: Parser Round
@ -62,7 +48,7 @@ isGameValid :: Game -> Bool
isGameValid (_, rounds) = all isRoundValid rounds
isRoundValid :: Round -> Bool
isRoundValid = getAll . foldMapWithKey (\c n -> All $ cubesPossible c n)
isRoundValid = getAll . M.foldMapWithKey (\c n -> All $ cubesPossible c n)
cubesPossible :: Cube -> Integer -> Bool
cubesPossible Red = (<= 12)