Skip to content

Instantly share code, notes, and snippets.

@k0001
Last active December 3, 2019 16:51
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 k0001/72eb63528e6ae7d69f3b415c6516c0fa to your computer and use it in GitHub Desktop.
Save k0001/72eb63528e6ae7d69f3b415c6516c0fa to your computer and use it in GitHub Desktop.
-- This enables the `\case` syntax, which is not standard Haskell.
{-# LANGUAGE LambdaCase #-}
-- | Solution for https://adventofcode.com/2019/day/2
module Aoc2_1 where
-- We like Natural numbers. Kind of.
import Numeric.Natural
-- We redefine `drop` below, so we hide its original implementation
import Prelude hiding (drop)
------------------------------
-- Wherever there is meaning, there is a type.
-- | Instruction Pointer
data IP = IP Natural
-- | A Program
data Intcode = Intcode [Natural]
deriving (Show)
------------------------------
-- This is a solution to the problem.
-- Look at all those Maybes be there, yet not. Puff.
-- | Run an program starting at the given position.
run :: Intcode -> IP -> Maybe Intcode
run (Intcode xs) (IP pos) = case drop pos xs of
(99 : _) -> Just (Intcode xs)
(1 : a : b : c : _) ->
get a xs >>= \a' ->
get b xs >>= \b' ->
set c (a' + b') xs >>= \xs' ->
run (Intcode xs') (IP (pos + 4))
(2 : a : b : c : _) ->
get a xs >>= \a' ->
get b xs >>= \b' ->
set c (a' * b') xs >>= \xs' ->
run (Intcode xs') (IP (pos + 4))
_ -> Nothing
--------------------------------
-- Miscelaneous functions for modifying lists.
-- These are rather slow because lists are not the optimal
-- data structure for this problem.
-- But we are learning, so who cares.
-- | `get n xs` returns the element in `xs` at position `n`.
-- Returns `Nothing` if `n` is out of bounds.
get :: Natural -> [a] -> Maybe a
get _ [] = Nothing
get 0 (a : _) = Just a
get n (_ : rest) = get (n - 1) rest
-- | `set n x xs` sets the element at position `n` in `xs` to `x`.
-- Returns `Nothing` if `n` is out of bounds.
set :: Natural -> a -> [a] -> Maybe [a]
set _ _ [] = Nothing
set 0 a (_ : rest) = Just (a : rest)
set n a (b : rest) = fmap (b :) (set (n - 1) a rest)
-- | `drop n xs` drops the first `n` elements of `xs`,
-- or maybe less if the list is shorter than `n`.
drop :: Natural -> [a] -> [a]
drop 0 xs = xs
drop n (_ : xs) = drop (n - 1) xs
------------------------------
-- | This is the input I was given.
input :: Intcode
input = Intcode [1, {- 0 -} 12, {- 0 -} 2, 3, 1, 1, 2, 3, 1, 3, 4, 3, 1, 5, 0, 3, 2, 1, 6, 19, 1, 5, 19, 23, 1, 23, 6, 27, 1, 5, 27, 31, 1, 31, 6, 35, 1, 9, 35, 39, 2, 10, 39, 43, 1, 43, 6, 47, 2, 6, 47, 51, 1, 5, 51, 55, 1, 55, 13, 59, 1, 59, 10, 63, 2, 10, 63, 67, 1, 9, 67, 71, 2, 6, 71, 75, 1, 5, 75, 79, 2, 79, 13, 83, 1, 83, 5, 87, 1, 87, 9, 91, 1, 5, 91, 95, 1, 5, 95, 99, 1, 99, 13, 103, 1, 10, 103, 107, 1, 107, 9, 111, 1, 6, 111, 115, 2, 115, 13, 119, 1, 10, 119, 123, 2, 123, 6, 127, 1, 5, 127, 131, 1, 5, 131, 135, 1, 135, 6, 139, 2, 139, 10, 143, 2, 143, 9, 147, 1, 147, 6, 151, 1, 151, 13, 155, 2, 155, 9, 159, 1, 6, 159, 163, 1, 5, 163, 167, 1, 5, 167, 171, 1, 10, 171, 175, 1, 13, 175, 179, 1, 179, 2, 183, 1, 9, 183, 0, 99, 2, 14, 0, 0]
-- | This is my answer, which as long as the given `input` was well-formed, should be `Just`.
answer :: Maybe Natural
answer = run input (IP 0) >>= \case
Intcode (n : _) -> Just n
Intcode _ -> Nothing
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment