Skip to content

Commit e1b0a82

Browse files
committed
Add solution for second part of day22
1 parent a63778f commit e1b0a82

File tree

3 files changed

+140
-39
lines changed

3 files changed

+140
-39
lines changed

AdventOfCode2021.cabal

+1-1
Original file line numberDiff line numberDiff line change
@@ -135,6 +135,6 @@ executable day21
135135

136136
executable day22
137137
main-is: Main.hs
138-
build-depends: base ^>=4.14.3.0, containers
138+
build-depends: base ^>=4.14.3.0, multiset
139139
hs-source-dirs: day22/src
140140
default-language: Haskell2010

day22/src/Main.hs

+79-34
Original file line numberDiff line numberDiff line change
@@ -1,49 +1,53 @@
11
{-# LANGUAGE TupleSections #-}
22

33
import Data.Char (isDigit)
4-
import Data.Set (Set)
5-
import qualified Data.Set as Set (difference, empty, filter, fromList, size, union)
4+
import Data.Maybe (fromJust, isJust)
5+
import Data.MultiSet (MultiSet)
6+
import qualified Data.MultiSet as Set (difference, empty, filter, fromList, insert, map, size, union)
67
import Text.ParserCombinators.ReadP (ReadP, char, many1, readP_to_S, satisfy, string, (+++))
78

89
main :: IO ()
910
main = do
10-
testRules <- readInput "day22/test_input"
11-
rules <- readInput "day22/input"
12-
print $ "Test input: " ++ show (firstProblem testRules) ++ " == 39"
13-
print $ "Problem input: " ++ show (firstProblem rules) ++ " == 644257"
11+
testSteps <- readInput "day22/test_input"
12+
steps <- readInput "day22/input"
13+
print $ "Test input: " ++ show (firstProblem testSteps) ++ " == 474140"
14+
print $ "Problem input: " ++ show (firstProblem steps) ++ " == 644257"
15+
print $ "Test input: " ++ show (secondProblem testSteps) ++ " == 2758514936282235"
16+
print $ "Problem input: " ++ show (secondProblem steps) ++ " == 1235484513229032"
1417
where
1518
readInput file = map parseInput . lines <$> readFile file
16-
parseInput = fst . last . readP_to_S parseRule
19+
parseInput = fst . last . readP_to_S parseStep
1720

18-
data Rule = On Area | Off Area deriving (Show)
21+
data Step = Step StepType Cuboid deriving (Show, Eq)
1922

20-
data Area = Area {x :: Limits, y :: Limits, z :: Limits} deriving (Show)
23+
data StepType = On | Off deriving (Show, Eq)
24+
25+
data Cuboid = Cuboid {x :: Limits, y :: Limits, z :: Limits}
26+
deriving (Show, Eq, Ord)
2127

2228
-- Must be (lowerLimit, upperLimit)
2329
type Limits = (Int, Int)
2430

25-
type Point = (Int, Int, Int)
26-
27-
parseRule :: ReadP Rule
28-
parseRule = parseOnRule +++ parseOffRule
31+
parseStep :: ReadP Step
32+
parseStep = parseOnStep +++ parseOffStep
2933

30-
parseOnRule :: ReadP Rule
31-
parseOnRule = do
34+
parseOnStep :: ReadP Step
35+
parseOnStep = do
3236
string "on "
33-
On <$> parseArea
37+
Step On <$> parseCuboid
3438

35-
parseOffRule :: ReadP Rule
36-
parseOffRule = do
39+
parseOffStep :: ReadP Step
40+
parseOffStep = do
3741
string "off "
38-
Off <$> parseArea
42+
Step Off <$> parseCuboid
3943

40-
parseArea :: ReadP Area
41-
parseArea = do
44+
parseCuboid :: ReadP Cuboid
45+
parseCuboid = do
4246
l1 <- parseLimits
4347
char ','
4448
l2 <- parseLimits
4549
char ','
46-
Area l1 l2 <$> parseLimits
50+
Cuboid l1 l2 <$> parseLimits
4751

4852
parseLimits :: ReadP Limits
4953
parseLimits = do
@@ -58,17 +62,58 @@ parseNumber = do
5862
number <- many1 $ satisfy (\a -> isDigit a || a == '-')
5963
return $ read number
6064

61-
firstProblem :: [Rule] -> Int
62-
firstProblem = Set.size . foldl foldIntoSet Set.empty
65+
firstProblem :: [Step] -> Int
66+
firstProblem = reboot . filterInitialization
6367
where
64-
foldIntoSet set (On area) = Set.union set $ setFromArea area
65-
foldIntoSet set (Off area) = Set.difference set $ setFromArea area
66-
67-
setFromArea :: Area -> Set Point
68-
setFromArea (Area (x1, x2) (y1, y2) (z1, z2))
69-
| isInsideInitializationArea =
70-
Set.fromList [(x, y, z) | x <- [x1 .. x2], y <- [y1 .. y2], z <- [z1 .. z2]]
71-
| otherwise = Set.empty
68+
filterInitialization = filter (isInside 50 50 . getCuboidFromStep)
69+
isInside min max (Cuboid (x1, x2) (y1, y2) (z1, z2)) =
70+
x1 >= -50 && x2 <= 50 && y1 >= -50 && y2 <= 50 && z1 >= -50 && z2 <= 50
71+
72+
secondProblem :: [Step] -> Int
73+
secondProblem = reboot
74+
75+
reboot :: [Step] -> Int
76+
reboot = count . foldl applyStep (Set.empty, Set.empty)
77+
where
78+
count (add, sub) = getCardinalitySum add - getCardinalitySum sub
79+
getCardinalitySum set = sum (Set.map getCardinality set)
80+
81+
type State = (MultiSet Cuboid, MultiSet Cuboid)
82+
83+
applyStep :: State -> Step -> State
84+
applyStep (add, sub) (Step t cuboid)
85+
| t == On =
86+
( Set.insert cuboid $ Set.union subIntersections add,
87+
Set.union addIntersections sub
88+
)
89+
| otherwise =
90+
( Set.union subIntersections add,
91+
Set.union addIntersections sub
92+
)
93+
where
94+
addIntersections = filterNothing $ Set.map (getIntersection cuboid) add
95+
subIntersections = filterNothing $ Set.map (getIntersection cuboid) sub
96+
filterNothing = Set.map fromJust . Set.filter isJust
97+
98+
getCuboidFromStep :: Step -> Cuboid
99+
getCuboidFromStep (Step _ area) = area
100+
101+
getCardinality :: Cuboid -> Int
102+
getCardinality (Cuboid (x1, x2) (y1, y2) (z1, z2)) =
103+
getDist x1 x2 * getDist y2 y1 * getDist z2 z1
104+
where
105+
getDist a b = abs (a - b) + 1
106+
107+
getIntersection :: Cuboid -> Cuboid -> Maybe Cuboid
108+
getIntersection (Cuboid x1 y1 z1) (Cuboid x2 y2 z2) = do
109+
x <- getIntersection1D x1 x2
110+
y <- getIntersection1D y1 y2
111+
Cuboid x y <$> getIntersection1D z1 z2
112+
113+
getIntersection1D :: Limits -> Limits -> Maybe Limits
114+
getIntersection1D (l1, u1) (l2, u2)
115+
| lower <= upper = Just (lower, upper)
116+
| otherwise = Nothing
72117
where
73-
isInsideInitializationArea =
74-
x1 >= -50 && x2 <= 50 && y1 >= -50 && y2 <= 50 && z1 >= -50 && z2 <= 50
118+
lower = max l1 l2
119+
upper = min u1 u2

day22/test_input

+60-4
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,60 @@
1-
on x=10..12,y=10..12,z=10..12
2-
on x=11..13,y=11..13,z=11..13
3-
off x=9..11,y=9..11,z=9..11
4-
on x=10..10,y=10..10,z=10..10
1+
on x=-5..47,y=-31..22,z=-19..33
2+
on x=-44..5,y=-27..21,z=-14..35
3+
on x=-49..-1,y=-11..42,z=-10..38
4+
on x=-20..34,y=-40..6,z=-44..1
5+
off x=26..39,y=40..50,z=-2..11
6+
on x=-41..5,y=-41..6,z=-36..8
7+
off x=-43..-33,y=-45..-28,z=7..25
8+
on x=-33..15,y=-32..19,z=-34..11
9+
off x=35..47,y=-46..-34,z=-11..5
10+
on x=-14..36,y=-6..44,z=-16..29
11+
on x=-57795..-6158,y=29564..72030,z=20435..90618
12+
on x=36731..105352,y=-21140..28532,z=16094..90401
13+
on x=30999..107136,y=-53464..15513,z=8553..71215
14+
on x=13528..83982,y=-99403..-27377,z=-24141..23996
15+
on x=-72682..-12347,y=18159..111354,z=7391..80950
16+
on x=-1060..80757,y=-65301..-20884,z=-103788..-16709
17+
on x=-83015..-9461,y=-72160..-8347,z=-81239..-26856
18+
on x=-52752..22273,y=-49450..9096,z=54442..119054
19+
on x=-29982..40483,y=-108474..-28371,z=-24328..38471
20+
on x=-4958..62750,y=40422..118853,z=-7672..65583
21+
on x=55694..108686,y=-43367..46958,z=-26781..48729
22+
on x=-98497..-18186,y=-63569..3412,z=1232..88485
23+
on x=-726..56291,y=-62629..13224,z=18033..85226
24+
on x=-110886..-34664,y=-81338..-8658,z=8914..63723
25+
on x=-55829..24974,y=-16897..54165,z=-121762..-28058
26+
on x=-65152..-11147,y=22489..91432,z=-58782..1780
27+
on x=-120100..-32970,y=-46592..27473,z=-11695..61039
28+
on x=-18631..37533,y=-124565..-50804,z=-35667..28308
29+
on x=-57817..18248,y=49321..117703,z=5745..55881
30+
on x=14781..98692,y=-1341..70827,z=15753..70151
31+
on x=-34419..55919,y=-19626..40991,z=39015..114138
32+
on x=-60785..11593,y=-56135..2999,z=-95368..-26915
33+
on x=-32178..58085,y=17647..101866,z=-91405..-8878
34+
on x=-53655..12091,y=50097..105568,z=-75335..-4862
35+
on x=-111166..-40997,y=-71714..2688,z=5609..50954
36+
on x=-16602..70118,y=-98693..-44401,z=5197..76897
37+
on x=16383..101554,y=4615..83635,z=-44907..18747
38+
off x=-95822..-15171,y=-19987..48940,z=10804..104439
39+
on x=-89813..-14614,y=16069..88491,z=-3297..45228
40+
on x=41075..99376,y=-20427..49978,z=-52012..13762
41+
on x=-21330..50085,y=-17944..62733,z=-112280..-30197
42+
on x=-16478..35915,y=36008..118594,z=-7885..47086
43+
off x=-98156..-27851,y=-49952..43171,z=-99005..-8456
44+
off x=2032..69770,y=-71013..4824,z=7471..94418
45+
on x=43670..120875,y=-42068..12382,z=-24787..38892
46+
off x=37514..111226,y=-45862..25743,z=-16714..54663
47+
off x=25699..97951,y=-30668..59918,z=-15349..69697
48+
off x=-44271..17935,y=-9516..60759,z=49131..112598
49+
on x=-61695..-5813,y=40978..94975,z=8655..80240
50+
off x=-101086..-9439,y=-7088..67543,z=33935..83858
51+
off x=18020..114017,y=-48931..32606,z=21474..89843
52+
off x=-77139..10506,y=-89994..-18797,z=-80..59318
53+
off x=8476..79288,y=-75520..11602,z=-96624..-24783
54+
on x=-47488..-1262,y=24338..100707,z=16292..72967
55+
off x=-84341..13987,y=2429..92914,z=-90671..-1318
56+
off x=-37810..49457,y=-71013..-7894,z=-105357..-13188
57+
off x=-27365..46395,y=31009..98017,z=15428..76570
58+
off x=-70369..-16548,y=22648..78696,z=-1892..86821
59+
on x=-53470..21291,y=-120233..-33476,z=-44150..38147
60+
off x=-93533..-4276,y=-16170..68771,z=-104985..-24507

0 commit comments

Comments
 (0)