parent
94c032e9da
commit
552dc4501c
4 changed files with 65 additions and 3 deletions
@ -1,17 +1,36 @@ |
|||||||
module Main where |
module Main where |
||||||
|
|
||||||
import Day1 |
import Day1 |
||||||
|
import Day2 |
||||||
import System.IO |
import System.IO |
||||||
|
import Data.List.Split |
||||||
|
|
||||||
day1_fuel :: String -> [Fuel] |
day1_fuel :: String -> [Fuel] |
||||||
day1_fuel = fmap (calculateFuel . read) . lines |
day1_fuel = fmap (calculateFuel . read) . lines |
||||||
|
|
||||||
|
day2_instructions :: String -> [Integer] |
||||||
|
day2_instructions = fmap read . splitOn "," |
||||||
|
|
||||||
|
day2 :: (Integer, Integer) -> [Integer] -> Integer |
||||||
|
day2 t = head . execute t |
||||||
|
|
||||||
|
day2_look :: [Integer] -> Integer |
||||||
|
day2_look xs = head $ [ 100*noun + verb | |
||||||
|
noun <- [0..99], |
||||||
|
verb <- [0..99], |
||||||
|
day2 (noun, verb) xs == 19690720 ] |
||||||
|
|
||||||
main :: IO () |
main :: IO () |
||||||
main = do |
main = do |
||||||
r <- readFile "./app/input_day1" |
r_day1 <- readFile "./app/input_day1" |
||||||
putStr "[Day 1-1] Fuel needed: " |
putStr "[Day 1-1] Fuel needed: " |
||||||
let fs = day1_fuel r |
let fs = day1_fuel r_day1 |
||||||
print $ sum fs |
print $ sum fs |
||||||
putStr "[Day 1-2] Fuel needed: " |
putStr "[Day 1-2] Fuel needed: " |
||||||
print (sum fs + (sum . fmap calculateFuelOfFuel) fs) |
print (sum fs + (sum . fmap calculateFuelOfFuel) fs) |
||||||
|
r_day2 <- readFile "./app/input_day2" |
||||||
|
let instructions = day2_instructions r_day2 |
||||||
|
putStr "[Day 2-1] Result:" |
||||||
|
print $ day2 (12,2) instructions |
||||||
|
putStr "[Day 2-2] Result:" |
||||||
|
print $ day2_look instructions |
||||||
|
@ -0,0 +1 @@ |
|||||||
|
1,0,0,3,1,1,2,3,1,3,4,3,1,5,0,3,2,1,13,19,1,9,19,23,2,13,23,27,2,27,13,31,2,31,10,35,1,6,35,39,1,5,39,43,1,10,43,47,1,5,47,51,1,13,51,55,2,55,9,59,1,6,59,63,1,13,63,67,1,6,67,71,1,71,10,75,2,13,75,79,1,5,79,83,2,83,6,87,1,6,87,91,1,91,13,95,1,95,13,99,2,99,13,103,1,103,5,107,2,107,10,111,1,5,111,115,1,2,115,119,1,119,6,0,99,2,0,14,0 |
@ -0,0 +1,40 @@ |
|||||||
|
module Day2 |
||||||
|
( |
||||||
|
execute |
||||||
|
) where |
||||||
|
|
||||||
|
import Data.Sequence |
||||||
|
import Data.Foldable |
||||||
|
import Control.Applicative |
||||||
|
|
||||||
|
preRun :: (Integer, Integer) -> Seq Integer -> Seq Integer |
||||||
|
preRun (noun, verb) = update 1 noun . update 2 verb |
||||||
|
|
||||||
|
execute :: (Integer, Integer) -> [Integer] -> [Integer] |
||||||
|
execute t = toList . executeCommandAtIndex 0 . preRun t . fromList |
||||||
|
|
||||||
|
executeCommandAtIndex :: Int -> Seq Integer -> Seq Integer |
||||||
|
executeCommandAtIndex i xs = |
||||||
|
case (!?) xs i of |
||||||
|
Just 1 -> executeCommandAtIndex (i + 4) (executeAddCommand i xs) |
||||||
|
Just 2 -> executeCommandAtIndex (i + 4) (executeMulCommand i xs) |
||||||
|
Just 99 -> xs |
||||||
|
_ -> error "Unknown Command" |
||||||
|
|
||||||
|
executeAddCommand :: Int -> Seq Integer -> Seq Integer |
||||||
|
executeAddCommand = executeCommand (+) |
||||||
|
|
||||||
|
executeMulCommand :: Int -> Seq Integer -> Seq Integer |
||||||
|
executeMulCommand = executeCommand (*) |
||||||
|
|
||||||
|
executeCommand :: |
||||||
|
(Integer -> Integer -> Integer) -> Int -> Seq Integer -> Seq Integer |
||||||
|
executeCommand f i xs = update n v xs |
||||||
|
where t1 = (!?) xs (i+1) >>= (!?) xs . fromIntegral |
||||||
|
t2 = (!?) xs (i+2) >>= (!?) xs . fromIntegral |
||||||
|
n = case (!?) xs (i+3) of |
||||||
|
Just n' -> fromIntegral n' |
||||||
|
_ -> error "Can't find update index" |
||||||
|
v = case liftA2 f t1 t2 of |
||||||
|
Just v' -> v' |
||||||
|
_ -> error "blah" |
Loading…
Reference in new issue