Skip to content

Instantly share code, notes, and snippets.

@plredmond
Last active December 19, 2020 02:55
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save plredmond/97f6636e1e70b6ec20fe8fb1692bf312 to your computer and use it in GitHub Desktop.
Save plredmond/97f6636e1e70b6ec20fe8fb1692bf312 to your computer and use it in GitHub Desktop.
solution for part 2 of https://adventofcode.com/2020/day/18; the commentted part of `main` expects two files (one with the inputs and one with the outputs for each of the day-18 test expressions)
#!/usr/bin/env nix-shell
#!nix-shell --pure -i runhaskell -p "haskellPackages.ghcWithPackages (p: [p.doctest p.parsec])"
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC "-Wall" #-}
import Test.DocTest (doctest)
import Text.Printf (printf)
import qualified Text.Parsec as P
import qualified Text.Parsec.Char as PC
-- import Debug.Trace
-- * AST and evaluator
data AST
= AST :+ AST
| AST :* AST
| Par AST
| Num Int
deriving Show
eval :: AST -> Int
eval (a :+ b) = eval a + eval b
eval (a :* b) = eval a * eval b
eval (Par a) = eval a
eval (Num a) = a
-- * Parser
{- precedence order: + * ()
factor := factor + term
| term
term := term * atom
| atom
atom := ( factor )
| NUMBER
-}
type Parser a = P.Parsec String () a
parse :: String -> Either P.ParseError AST
parse raw = P.parse factor "" raw
w :: Parser a -> Parser a -- ignore whitespace around a parser
w p = P.spaces >> p >>= \out -> P.spaces >> return out
-- |
-- >>> P.parseTest factor "1 * 2"
-- Num 1 :* Num 2
factor :: Parser AST
factor = P.chainl1 term (w $ PC.char '*' >> return (:*))
-- |
-- >>> P.parseTest term "1 + 2"
-- Num 1 :+ Num 2
term :: Parser AST
term = P.chainl1 atom (w $ PC.char '+' >> return (:+))
-- |
-- >>> P.parseTest atom "(123)"
-- Par (Num 123)
--
-- >>> P.parseTest atom "123"
-- Num 123
atom :: Parser AST
atom = P.try par P.<|> P.try num
-- |
-- >>> P.parseTest par "(123)"
-- Par (Num 123)
--
-- >>> P.parseTest par "( 123 )"
-- Par (Num 123)
par :: Parser AST
par = w (PC.char '(') >> Par <$> factor >>= \f -> w (PC.char ')') >> return f
-- |
-- >>> P.parseTest num "123"
-- Num 123
num :: Parser AST
num = w $ P.many1 PC.digit >>= return . Num . read
-- * Main functions
-- | Parse and then evaluate
interpret :: String -> Either P.ParseError Int
interpret = fmap eval . parse
-- | Parse and then evaluate and emit useful errors
tryExample :: (String, Int) -> IO ()
tryExample (raw, expect) = case parse raw of
Left err -> printf "Parse error: [%s] got %s\n" raw (show err)
Right ast -> let actual = eval ast in
if actual == expect
then return ()
else printf "Wrong answer: [%s] with AST [%s] got %d" raw (show ast) actual
main :: IO ()
main = do
-- doctests
doctest [__FILE__]
-- -- manual tests
-- mapM_ tryExample =<< zip
-- <$> ( lines <$> readFile "day-18")
-- <*> (fmap read . lines <$> readFile "day-18-output")
-- sum expressions on stdin
interact
$ show
. sum
. fmap (either (error . show) id)
. fmap interpret
. lines
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment