module AOC.Challenge.Day19 (
day19a
, day19b
) where
import AOC.Common.Elfcode
import AOC.Solver ((:~>)(..))
import Control.Lens (set)
import Control.Monad (mfilter)
import Data.Finite (Finite)
import qualified Data.Vector.Unboxed.Sized as V
day19a :: (Finite 6, ECProg) :~> Int
day19a = MkSol
{ sParse = parseElfcode
, sShow = show
, sSolve = \(i, p) -> Just . V.head
. execECProg i p
$ V.replicate 0
}
day19b :: (Finite 6, ECProg) :~> Int
day19b = MkSol
{ sParse = parseElfcode
, sShow = show
, sSolve = \(i, p) -> Just . V.head
. execECProg i (optimizeEC [addIfIsFactor i] p)
. set (V.ix 0) 1
$ V.replicate 0
}
addIfIsFactor
:: Finite 6
-> Peephole [Instr]
addIfIsFactor i = do
a <- currPeepPos
let a' = fromIntegral a
I OSetI _ _ n <- peep (Just 1 ) Nothing Nothing
let n' = fromIntegral n
I OMulR m _ z <- peep Nothing (Just n') Nothing
let z' = fromIntegral z
I OEqRR _ t _ <- peep (Just z') Nothing (Just z )
I OAddR _ _ _ <- peep (Just z') (Just i') (Just i )
I OAddI _ _ _ <- peep (Just i') (Just 1 ) (Just i )
I OAddR _ o _ <- mfilter (\I{..} -> fromIntegral _iInB == _iOut)
$ peep (Just m ) Nothing Nothing
I OAddI _ _ _ <- peep (Just n') (Just 1 ) (Just n )
I OGtRR _ _ _ <- peep (Just n') (Just t ) (Just z )
I OAddR _ _ _ <- peep (Just i') (Just z') (Just i )
I OSetI _ _ _ <- peep (Just a') Nothing (Just i )
b <- currPeepPos
let t' = fromIntegral t
o' = fromIntegral o
pure . take (b - a) $
[ I OModR t' m z
, I OEqRI z' 0 z
, I OAddR z' i' i
, I OAddI i' 1 i
, I OAddR m o o'
] ++ repeat (I ONoOp 0 0 0)
where
i' = fromIntegral i