Skip to content

Commit

Permalink
redo parsers
Browse files Browse the repository at this point in the history
  • Loading branch information
mstksg committed Nov 30, 2024
1 parent e97b739 commit 19ea025
Show file tree
Hide file tree
Showing 25 changed files with 288 additions and 225 deletions.
7 changes: 3 additions & 4 deletions 2018/AOC2018/Common/Elfcode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,6 @@ import Control.Monad
import Control.Monad.Primitive
import qualified Control.Monad.ST as STS
import qualified Control.Monad.ST.Lazy as STL
import Control.Monad.Writer
import Data.Bits
import Data.Char
import Data.Finite
Expand All @@ -54,7 +53,7 @@ data Instr = I
, _iInB :: Int
, _iOut :: Finite 6
}
deriving (Show, Eq, Ord)
deriving stock (Show, Eq, Ord)

data OpCode
= OAddR
Expand All @@ -79,7 +78,7 @@ data OpCode
| ONoOp
| OOutR
| OOutI
deriving (Show, Eq, Ord, Enum, Bounded)
deriving stock (Show, Eq, Ord, Enum, Bounded)

execOp :: (PrimMonad m, PrimState m ~ s) => Instr -> Mem s -> m (Maybe Int)
execOp I{..} = case _iOp of
Expand Down Expand Up @@ -243,7 +242,7 @@ elfcodeParser =
where
lineParser =
P.try (Just <$> instrParser)
<|> Nothing <$ (P.char '#' *> P.many (P.noneOf "\n"))
<|> Nothing <$ (P.char '#' *> P.many (P.anySingleBut '\n'))

instrParser :: Parser Instr
instrParser =
Expand Down
2 changes: 1 addition & 1 deletion 2018/AOC2018/Day08.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module AOC2018.Day08 (
day08b,
) where

import AOC.Common (TokStream, parseTokStream_)
import AOC.Common.Parser (TokStream, parseTokStream_)
import AOC.Solver ((:~>) (..))
import Control.Lens (ix, (^?))
import Control.Monad (replicateM)
Expand Down
6 changes: 3 additions & 3 deletions 2018/AOC2018/Day12.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module AOC2018.Day12 (
day12b,
) where

import AOC.Common ((!!!))
import AOC.Common (asString, (!!!))
import AOC.Solver ((:~>) (..))
import Data.Bifunctor (bimap)
import Data.Finite (Finite, finites)
Expand Down Expand Up @@ -91,7 +91,7 @@ makeState =
. M.filter (== '#')
. M.fromList
. zip [0 ..]
. filter (`elem` "#.")
. filter (`elem` asString "#.")

makeCtxs :: String -> Set Ctx
makeCtxs =
Expand All @@ -102,7 +102,7 @@ makeCtxs =
( bimap parseLine head
. splitAt 5
. map (== '#')
. filter (`elem` "#.")
. filter (`elem` asString "#.")
)
. lines
where
Expand Down
4 changes: 2 additions & 2 deletions 2018/AOC2018/Day19.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ addIfIsFactor ::
Peephole [Instr]
addIfIsFactor i = do
a <- currPeepPos
let a' = fromIntegral a
let a' = a
I OSetI _ _ n <- peep (Just 1) Nothing Nothing
let n' = fromIntegral n
I OMulR m _ z <- peep Nothing (Just n') Nothing
Expand All @@ -67,7 +67,7 @@ addIfIsFactor i = do
I OAddR _ _ _ <- peep (Just i') (Just z') (Just i)
I OSetI _ _ _ <- peep (Just a') Nothing (Just i)
b <- currPeepPos
let t' = fromIntegral t
let t' = t
o' = fromIntegral o
pure . take (b - a) $
[ I OModR t' m z -- store (t `mod` m) to z
Expand Down
2 changes: 1 addition & 1 deletion 2018/AOC2018/Day20.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module AOC2018.Day20 (
day20b,
) where

import AOC.Common (TokStream, parseTokStreamT_)
import AOC.Common.Parser (TokStream, parseTokStreamT_)
import AOC.Common.Point (Point, cardinalNeighbs)
import AOC.Solver ((:~>) (..))
import Control.Monad (guard)
Expand Down
13 changes: 6 additions & 7 deletions 2019/AOC2019/Common/Intcode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,33 +63,32 @@ import Data.Void
import GHC.Generics
import GHC.Natural
import Linear
import Numeric.Natural (Natural)
import Text.Read (readMaybe)

type VM = Pipe Int Int Void

type AsciiVM = Pipe Text Text Void

data Mode = Pos | Imm | Rel
deriving (Eq, Ord, Enum, Show, Generic)
deriving stock (Eq, Ord, Enum, Show, Generic)
instance NFData Mode

data Instr = Add | Mul | Get | Put | Jnz | Jez | Clt | Ceq | ChB | Hlt
deriving (Eq, Ord, Enum, Show, Generic)
deriving stock (Eq, Ord, Enum, Show, Generic)
instance NFData Instr

data VMErr
= VMEBadMode Int
| VMEBadInstr Int
| VMEBadPos Int
deriving (Eq, Ord, Show, Typeable, Generic)
deriving stock (Eq, Ord, Show, Typeable, Generic)
instance Exception VMErr
makeClassyPrisms ''VMErr

data IErr
= IENoInput
| IEVM VMErr
deriving (Eq, Ord, Show, Typeable, Generic)
deriving stock (Eq, Ord, Show, Typeable, Generic)
instance Exception IErr
makeClassyPrisms ''IErr

Expand Down Expand Up @@ -141,7 +140,7 @@ withInput ::
Int ->
(t Int -> m r) ->
m (r, Mode)
withInput mo f = withInputLazy mo ((f =<<) . sequenceA)
withInput mo f = withInputLazy mo (f <=< sequenceA)

intMode :: Int -> Maybe Mode
intMode = \case
Expand Down Expand Up @@ -173,7 +172,7 @@ data InstrRes
IRNop
| -- | halt
IRHalt
deriving (Eq, Ord, Show, Generic)
deriving stock (Eq, Ord, Show, Generic)

step ::
(AsVMErr e, MonadError e m, MonadMem m) =>
Expand Down
3 changes: 1 addition & 2 deletions 2019/AOC2019/Common/Subset.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,6 @@ module AOC2019.Common.Subset (
) where

import AOC.Common
import AOC.Util
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.Trans.Maybe
Expand Down Expand Up @@ -170,7 +169,7 @@ printGraph f = GV.printIt . GV.graphToDot params
params =
GV.nonClusteredParams
{ GV.fmtNode = \(_, xs) -> [GV.toLabel (f xs)]
, GV.fmtEdge = \(_, _, b) -> [GV.toLabel $ if b then "GT" else "LT"]
, GV.fmtEdge = \(_, _, b) -> [GV.toLabel $ asString if b then "GT" else "LT"]
}

dTreeGraph :: forall a. DTree a -> Gr (Set a) Bool
Expand Down
2 changes: 1 addition & 1 deletion 2019/AOC2019/Day23.hs
Original file line number Diff line number Diff line change
Expand Up @@ -106,7 +106,7 @@ day23b =
, sShow = show
, sSolve =
firstJust (\(x, y) -> x <$ guard (x == y))
. (zip `ap` tail)
. (zip `ap` drop 1)
. mapMaybe natted
. iterate stepNetwork
. initNetwork
Expand Down
3 changes: 2 additions & 1 deletion 2020/AOC2020/Day02.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,8 @@ module AOC2020.Day02 (
)
where

import AOC.Common (CharParser, countTrue, parseLines)
import AOC.Common (countTrue)
import AOC.Common.Parser (CharParser, parseLines)
import AOC.Solver ((:~>) (..))
import Control.DeepSeq (NFData)
import Control.Monad.Combinators (some)
Expand Down
10 changes: 7 additions & 3 deletions 2020/AOC2020/Day07.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ module AOC2020.Day07 (
)
where

import AOC.Common (CharParser, pWord, parseLines)
import AOC.Common.Parser (CharParser, pWord, parseLines)
import AOC.Solver ((:~>) (..))
import Control.Applicative (many)
import Data.Map (Map)
Expand Down Expand Up @@ -46,7 +46,11 @@ bagParser = do
pure (nm, bs)
where
bagName :: CharParser Bag
bagName = (,) <$> (T.pack <$> pWord) <*> (T.pack <$> pWord <* pWord)
bagName = do
x <- T.pack <$> pWord
y <- T.pack <$> pWord
pWord
pure (x, y)

flipGraph :: Ord v => Graph v e -> Graph v e
flipGraph mp =
Expand Down Expand Up @@ -78,7 +82,7 @@ allDescendants :: Ord v => Graph v e -> Map v (Set v)
allDescendants =
foldMapGraph
S.singleton -- the node is embedded as itself
(\_ -> id) -- ignore the edge
(const id) -- ignore the edge

usageCounts :: Ord v => Graph v Int -> Map v (Sum Int)
usageCounts =
Expand Down
3 changes: 2 additions & 1 deletion 2020/AOC2020/Day08.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,8 @@ module AOC2020.Day08 (
)
where

import AOC.Common (CharParser, pDecimal, parseLines, perturbationsBy)
import AOC.Common (perturbationsBy)
import AOC.Common.Parser (CharParser, pDecimal, parseLines)
import AOC.Solver ((:~>) (..))
import Control.DeepSeq (NFData)
import Control.Lens (Index, IxValue, Ixed (..), (^?), _1)
Expand Down
2 changes: 1 addition & 1 deletion 2020/AOC2020/Day13.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module AOC2020.Day13 (
)
where

import AOC.Common (CharParser, parseMaybeLenient)
import AOC.Common.Parser (CharParser, parseMaybeLenient)
import AOC.Solver ((:~>) (..))
import Control.Applicative ((<|>))
import Data.Foldable (minimumBy)
Expand Down
2 changes: 1 addition & 1 deletion 2020/AOC2020/Day14.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ module AOC2020.Day14 (
)
where

import AOC.Common (CharParser, parseLines)
import AOC.Common.Parser (CharParser, parseLines)
import AOC.Solver ((:~>) (..))
import Control.DeepSeq (NFData)
import Control.Lens.Indexed (ifoldl', ifoldlM)
Expand Down
3 changes: 2 additions & 1 deletion 2020/AOC2020/Day16.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ module AOC2020.Day16 (
)
where

import AOC.Common (CharParser, pickUnique, withAllSized)
import AOC.Common (pickUnique, withAllSized)
import AOC.Common.Parser (CharParser)
import AOC.Solver (dyno_, (:~>) (..))
import Control.DeepSeq (NFData)
import Data.Char (isAlpha, isSpace)
Expand Down
3 changes: 2 additions & 1 deletion 2020/AOC2020/Day19.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ module AOC2020.Day19 (
)
where

import AOC.Common (countTrue, pTok)
import AOC.Common (countTrue)
import AOC.Common.Parser (pTok)
import AOC.Solver ((:~>) (..))
import Control.Applicative (empty)
import Control.DeepSeq (NFData)
Expand Down
3 changes: 2 additions & 1 deletion 2020/AOC2020/Day21.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ module AOC2020.Day21 (
)
where

import AOC.Common (countTrue, parseLines, pickUnique)
import AOC.Common (countTrue, pickUnique)
import AOC.Common.Parser (parseLines)
import AOC.Solver ((:~>) (..))
import Data.Foldable (toList)
import Data.Functor ((<&>))
Expand Down
10 changes: 3 additions & 7 deletions 2021/AOC2021/Day16.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,12 +11,8 @@ module AOC2021.Day16 (
day16b,
) where

import AOC.Common (
TokStream (..),
digitToIntSafe,
parseBinary,
toBinaryFixed,
)
import AOC.Common (digitToIntSafe, parseBinary, toBinaryFixed)
import AOC.Common.Parser (TokStream (..))
import AOC.Solver ((:~>) (..))
import Control.Applicative (empty)
import Control.DeepSeq (NFData)
Expand Down Expand Up @@ -55,7 +51,7 @@ day16 alg =
{ sParse =
Just
. TokStream
. concatMap (maybe [] id . fmap (toBinaryFixed 4) . digitToIntSafe)
. concatMap (maybe [] (toBinaryFixed 4) . digitToIntSafe)
, sShow = show
, sSolve = fmap (cata alg . snd) . preview _Right . P.runParser parsePacket ""
}
Expand Down
2 changes: 1 addition & 1 deletion 2022/AOC2022/Day11.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ parseMonkey :: String -> Maybe MonkeyData
parseMonkey blob = do
[_, a, b, c, d, e] <- pure $ lines blob
mdItems <- traverse readMaybe $ words (clearOut (not . isDigit) a)
[_, x, y] <- pure $ words . tail $ dropWhile (/= '=') b
[_, x, y] <- pure $ words . drop 1 $ dropWhile (/= '=') b
let mdTrans = (if x == "*" then Mul else Add, readMaybe y)
mdCond <- readMaybe $ clearOut (not . isDigit) c
mdTrue <- readMaybe $ clearOut (not . isDigit) d
Expand Down
2 changes: 1 addition & 1 deletion 2022/AOC2022/Day16.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ import Text.Read (readMaybe)

parseLine :: String -> Maybe (String, (Int, Set String))
parseLine xs = do
(a, bs) <- uncons $ words $ clearOut (not . isUpper) (tail xs)
(a, bs) <- uncons $ words $ clearOut (not . isUpper) (drop 1 xs)
r <- readMaybe $ clearOut (not . isDigit) xs
pure (a, (r, S.fromList bs))

Expand Down
Loading

0 comments on commit 19ea025

Please sign in to comment.