Skip to content
This repository has been archived by the owner on Nov 17, 2024. It is now read-only.

Latest commit

 

History

History
185 lines (152 loc) · 7.77 KB

File metadata and controls

185 lines (152 loc) · 7.77 KB

Day 18

all / 1 / 2 / 3 / 4 / 5 / 6 / 7 / 8 / 9 / 10 / 11 / 12 / 13 / 14 / 15 / 16 / 17 / 18 / 19 / 20 / 21 / 22 / 23 / 24 / 25

Available as an RSS Feed

Prompt / Code / Rendered

Let's parse with parser combinators!

The main way I have learned how to deal with these binary-operation parsers is to separate out the stages into a "bottom" level containing only the leaves (here, the int literals) and parentheses, and then build up layers of precedence one-by-one from highest to lowest. For the first part we only have two layers, then, since we only have one level of precedence.

{-# LANGUAGE OverloadedStrings #-}

import qualified Text.Megaparsec            as P
import qualified Text.Megaparsec.Char       as P
import qualified Text.Megaparsec.Char.Lexer as PP

type Parser = P.Parsec Void String

parseBottom1 :: Parser Int
parseBottom1 = P.choice
    [ PP.decimal
    , P.between "(" ")" parseTop1  -- use -XOverloadedStrings to get parsers that match strings
    ]

parseTop1 :: Parser Int
parseTop1 = do
    leftOfOp <- parseBottom1   -- parse the left hand side of a possible binary operator
    doNext acc
  where
    doNext acc = P.choice          -- once we parse a left hand side, pick from:
      [ do " * "                        -- either it's a *
           rightOfOp <- parseBottom1    --   ... so we parse the right hand side and multiply
           doNext (acc * rightOfOp)
      , do " + "                        -- or it's a +
           rightOfOp <- parseBottom1    --   ... so we parse the right hand side and add
           doNext (acc + rightOfOp)
      , pure acc                        -- otherwise that was it, no operator
      ]

Remember that leftOfOp could either come from a leaf literal number or from a parenthesized equation. In the end, we get an Int, representing whatever number was on the left hand side of our operator. Then we move into doNext, which continually accumulates new operations after that first leftOfOp parse.

If we see a *, we parse the right hand side, fold that into our accumulator and repeat until we hit a dead end and yield our accumulated value; same for +.

So there's this sort of "cycle" that parseTop defers to parseBottom for its underlying things "in between" the operators, but parseBottom loops back up to parseTop to handle what is in the parentheses.

part1 :: String -> Maybe Int
part1 = P.parseMaybe $
          sum <$> P.many parseTop1

The twist for part 2 is that now we have to have another layer of precedence, so we split things out:

parseBottom2 :: Parser Int
parseBottom2 = P.choice
    [ PP.decimal
    , P.between "(" ")" parseTop2
    ]

parseMiddle2 :: Parser Int
parseMiddle2 = do
    leftOfOp <- parseBottom2
    doNext leftOfOp
  where
    doNext acc = P.choice
      [ do " + "
           rightOfOp <- parseBottom2
           doNext (acc + rightOfOp)
      , pure acc
      ]

parseTop2 :: Parser Int
parseTop2 = do
    leftOfOp <- parseMiddle2
    doNext leftOfOp
  where
    doNext acc = P.choice
      [ do " * "
           rightOfOp <- parseMiddle2
           doNext (acc * rightOfOp)
      , pure acc
      ]

So the parser dependency again is kind of interesting: parseTop2 is built up of chained parseMiddle2s, which is built up of chained parseBottom2, which could loop back up with parseTop2 if detect parentheses.

part2 :: String -> Maybe Int
part2 = P.parseMaybe $
          sum <$> (parseTop2 `P.sepBy` P.newline)

Note that this chaining and looping behavior can be abstracted out --- that's essentially what I wrote in my cleaned up solution. But also the Control.Monad.Combinators.Expr module also abstracts over this pattern, letting you specify the "layers" you want, and it'll generate the right parser for you with the correct weaving of dependencies like I described here. But still, I think it's fun to see how these things end up looking like under the hood :)

Back to all reflections for 2020

Day 18 Benchmarks

>> Day 18a
benchmarking...
time                 2.824 ms   (2.691 ms .. 3.014 ms)
                     0.975 R²   (0.952 R² .. 0.998 R²)
mean                 2.748 ms   (2.703 ms .. 2.844 ms)
std dev              208.7 μs   (100.8 μs .. 383.4 μs)
variance introduced by outliers: 53% (severely inflated)

* parsing and formatting times excluded

>> Day 18b
benchmarking...
time                 2.270 ms   (2.143 ms .. 2.447 ms)
                     0.974 R²   (0.958 R² .. 0.996 R²)
mean                 2.231 ms   (2.180 ms .. 2.378 ms)
std dev              236.7 μs   (129.2 μs .. 403.0 μs)
variance introduced by outliers: 70% (severely inflated)

* parsing and formatting times excluded