Skip to content

Instantly share code, notes, and snippets.

@jsoo1
Created March 29, 2022 04:29
Show Gist options
  • Save jsoo1/16fd3d6dff303d534a7613a9e2cdee66 to your computer and use it in GitHub Desktop.
Save jsoo1/16fd3d6dff303d534a7613a9e2cdee66 to your computer and use it in GitHub Desktop.
aoc-2021-22
{-# LANGUAGE NamedFieldPuns #-}
module Aoc2021Prob22 where
import Data.Bifunctor (bimap)
import Data.Maybe (fromJust)
import Text.Read (readMaybe)
data SpecLine = SpecLine
{ state :: State
, cuboid :: Cuboid
}
deriving (Show)
addSpecLine :: SpecLine -> SpecLine -> (SpecLine, SpecLine)
addSpecLine SpecLine { state, cuboid } _ = _
intersectionRange :: Range -> Range -> Maybe Range
intersectionRange Range { start = s1, end = e1 } Range { start = s2, end = e2 } =
if (s2 <= e1 && e1 <= e2) || (s1 <= e2 && e2 <= e1)
then Just (Range { start = max s1 s2, end = min e1 e2 })
else Nothing
-- Expect this intersection to be empty
-- --------xxxx-------xxxx-----
-- (-1, 0) (9, 11)
-- Expect this to be (-1, 0)
-- --------xxxyyxx-----
-- (-3, 0) (-1, 2)
maxRange :: Range
maxRange = Range
{ start = -50
, end = 50
}
intersectionCuboid :: Cuboid -> Cuboid -> Maybe Cuboid
intersectionCuboid Cuboid {x = x1, y = y1, z = z1} Cuboid {x = x2, y = y2, z = z2} =
Cuboid
<$> intersectionRange x1 x2
<*> intersectionRange y1 y2
<*> intersectionRange z1 z2
data State
= On
| Off
deriving (Show)
data Cuboid = Cuboid
{ x :: Range
, y :: Range
, z :: Range
}
deriving (Show)
data Range = Range
{ start :: Int
, end :: Int
}
deriving (Show)
main :: IO ()
main = do
ls <- map makeSpecLine . lines <$> readFile "./aoc-2021-problem-22-input.txt"
print ls
makeSpecLine :: String -> SpecLine
makeSpecLine specLineStr =
SpecLine
{ state = getState state'
, cuboid = getCuboid cuboid'
}
where
(state', _:cuboid') = break (== ' ') specLineStr
getState :: String -> State
getState "on" = On
getState _ = Off
getCuboid :: String -> Cuboid
getCuboid cs =
makeCuboid $ lines $ map (\c -> if c == ',' then '\n' else c) cs
where
makeCuboid :: [String] -> Cuboid
makeCuboid [x, y, z] =
Cuboid
{ x = parseRange x
, y = parseRange y
, z = parseRange z
}
parseRange :: String -> Range
parseRange s = Range { start, end }
where
(start, end) =
bimap read read
$ fmap (drop 2)
$ break (== '.')
$ snd
$ fmap tail
$ break (== '=') s
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment