Day 8, parts 1 & 2: Initial solutions.
This commit is contained in:
parent
3be1e8fae3
commit
d9bce28737
|
|
@ -0,0 +1,26 @@
|
|||
#! /usr/bin/env stack
|
||||
-- stack --resolver lts-12.20 --install-ghc script
|
||||
{-# LANGUAGE DeriveFunctor, DeriveFoldable #-}
|
||||
module Main where
|
||||
|
||||
import qualified Control.Monad.State as St
|
||||
import qualified Data.List as L
|
||||
import qualified Data.Monoid as Mo
|
||||
|
||||
data Node a = Node [Node a] a deriving (Show, Functor, Foldable)
|
||||
|
||||
main :: IO ()
|
||||
main = interact $ show . Mo.getSum . foldMap (foldMap Mo.Sum) . parseTree
|
||||
|
||||
parseTree :: String -> Node [Int]
|
||||
parseTree = St.evalState parseNode
|
||||
|
||||
parseNode :: St.State String (Node [Int])
|
||||
parseNode = do
|
||||
nChildren <- parseInt
|
||||
nMetadata <- parseInt
|
||||
Node <$> St.replicateM nChildren parseNode
|
||||
<*> St.replicateM nMetadata parseInt
|
||||
|
||||
parseInt :: St.State String Int
|
||||
parseInt = read <$> St.state (L.break (== ' ') . L.dropWhile (== ' '))
|
||||
|
|
@ -0,0 +1,32 @@
|
|||
#! /usr/bin/env stack
|
||||
-- stack --resolver lts-12.20 --install-ghc script
|
||||
module Main where
|
||||
|
||||
import qualified Control.Monad.State as St
|
||||
import qualified Data.List as L
|
||||
|
||||
data Node = Node [Node] [Int] deriving (Show)
|
||||
|
||||
main :: IO ()
|
||||
main = interact $ show . treeValue . parseTree
|
||||
|
||||
treeValue :: Node -> Int
|
||||
treeValue (Node cs ms)
|
||||
| null cs = sum ms
|
||||
| otherwise = sum [ vs !! (m - 1) | m <- ms, 1 <= m, m <= ncs ]
|
||||
where
|
||||
vs = map treeValue cs
|
||||
ncs = length cs
|
||||
|
||||
parseTree :: String -> Node
|
||||
parseTree = St.evalState parseNode
|
||||
|
||||
parseNode :: St.State String Node
|
||||
parseNode = do
|
||||
nChildren <- parseInt
|
||||
nMetadata <- parseInt
|
||||
Node <$> St.replicateM nChildren parseNode
|
||||
<*> St.replicateM nMetadata parseInt
|
||||
|
||||
parseInt :: St.State String Int
|
||||
parseInt = read <$> St.state (L.break (== ' ') . L.dropWhile (== ' '))
|
||||
File diff suppressed because one or more lines are too long
Loading…
Reference in New Issue