This commit is contained in:
Agatha Lovelace 2021-12-02 21:24:58 +02:00
parent 948afa564b
commit 87f0c0d9d1
2 changed files with 86 additions and 0 deletions

43
Day2.hs Normal file
View File

@ -0,0 +1,43 @@
{-# LANGUAGE OverloadedStrings #-}
module Day2 where
import System.IO (openFile, IOMode (ReadMode), hClose, hGetContents)
import Data.Text (splitOn, Text, unpack, pack)
data Submarine = Submarine {
horizontal :: Int
, depth :: Int
} deriving Show
type Movement = (String, Int)
-- "forward 5" -> ("forward", 5)
parseInstruction :: String -> Movement
parseInstruction instr = (kind, magnitude)
where
split = map unpack $ splitOn " " $ pack instr
kind = head split
magnitude = read $ split !! 1
move :: Submarine -> Movement -> Submarine
move sub ("forward", magnitude) = sub { horizontal = horizontal sub + magnitude }
move sub ("down", magnitude) = sub { depth = depth sub + magnitude }
move sub ("up", magnitude) = sub { depth = depth sub - magnitude }
(++) :: Submarine -> Submarine -> Submarine
x ++ y = Submarine { horizontal = horizontal x + horizontal y, depth = depth x + depth y }
main :: IO ()
main = do
input <- openFile "inputs/2.txt" ReadMode
contents <- hGetContents input
let submarine = Submarine { horizontal = 0, depth = 0 }
let instructions = parseInstruction <$> lines contents
let sub = foldl move submarine instructions
print $ horizontal sub * depth sub
hClose input

43
Day2_1.hs Normal file
View File

@ -0,0 +1,43 @@
{-# LANGUAGE OverloadedStrings #-}
module Day2_1 where
import System.IO (openFile, IOMode (ReadMode), hClose, hGetContents)
import Data.Text (splitOn, Text, unpack, pack)
import Data.List (mapAccumL)
import Prelude hiding ((++))
data Submarine = Submarine {
horizontal :: Int
, depth :: Int
, aim :: Int
} deriving Show
type Movement = (String, Int)
-- "forward 5" -> ("forward", 5)
parseInstruction :: String -> Movement
parseInstruction instr = (kind, magnitude)
where
split = map unpack $ splitOn " " $ pack instr
kind = head split
magnitude = read $ split !! 1
move :: Submarine -> Movement -> Submarine
move sub ("forward", magnitude) = sub { depth = depth sub + (aim sub * magnitude), horizontal = horizontal sub + magnitude }
move sub ("down", magnitude) = sub { aim = aim sub + magnitude }
move sub ("up", magnitude) = sub { aim = aim sub - magnitude }
main :: IO ()
main = do
input <- openFile "inputs/2.txt" ReadMode
contents <- hGetContents input
let submarine = Submarine { horizontal = 0, depth = 0, aim = 0 }
let instructions = parseInstruction <$> lines contents
let sub = foldl move submarine instructions
print $ horizontal sub * depth sub
hClose input