Skip to content

Instantly share code, notes, and snippets.

@skatenerd
Created December 12, 2023 14:38
Show Gist options
  • Save skatenerd/f88aed1e416dcab263f2620aba4564fe to your computer and use it in GitHub Desktop.
Save skatenerd/f88aed1e416dcab263f2620aba4564fe to your computer and use it in GitHub Desktop.
AOC 2023 Day 11 - all about transposition
{-# LANGUAGE OverloadedStrings #-}
module DayEleven where
import qualified Data.Text as T
import qualified Data.List as L
import qualified Text.Read as TR
import Debug.Trace (traceShowId, traceShow)
import qualified Data.Maybe as M
import qualified Data.Set as S
import Safe (atDef, atMay, minimumMay, headMay)
-- SETUP
data Tile = Empty | Galaxy deriving (Eq, Show, Ord)
type Universe = [[Tile]]
parseTile '#' = Galaxy
parseTile _ = Empty
parseUniverse = map ((map parseTile) . T.unpack)
buildIdxGrid universe = (map (\idx -> (map (\ri -> (idx, ri)) row)) colIdxs)
where colIdxs = 0 `enumFromTo` (height - 1)
row = 0 `enumFromTo` (width - 1)
height = length universe
width = length $ head universe
galaxyIndices universe = filter hasGalaxy allIndices
where allIndices = concat $ buildIdxGrid universe
hasGalaxy (r,c) = ((universe !! r) !! c) == Galaxy
manhattan (a,b) (c,d) = (abs (a-c)) + (abs (b-d))
universeTestCase :: [T.Text]
universeTestCase = ["...#......",
".......#..",
"#.........",
"..........",
"......#...",
".#........",
".........#",
"..........",
".......#..",
"#...#....."]
-- Part 1
expandRow row
| all (== Empty) row = [row, row]
| otherwise = [row]
expandUniverseVertically universe = concatMap expandRow universe
fullyExpand = expandUniverseVertically . L.transpose . expandUniverseVertically . L.transpose
partOne universe = do
first <- gi
second <- gi
if (first >= second) then [] else [manhattan first second]
where gi = galaxyIndices universe
-- Part 2
rowCost expansionFactor row
| all (== Empty) row = expansionFactor
| otherwise = 1
inclusiveRange a b = (min a b) `enumFromTo` (max a b)
verticalTravelCost expansionFactor universe startRow endRow = sum $ map (rowCost expansionFactor) rows
where rows = map (universe !!) (inclusiveRange startRow endRow)
horizontalTravelCost expansionFactor universe startCol endCol = verticalTravelCost expansionFactor (L.transpose universe) startCol endCol
partTwoDistance expansionFactor universe start@(sr,sc) end@(er,ec) = (verticalTravelCost expansionFactor universe sr er) + (horizontalTravelCost expansionFactor universe sc ec) - 2
partTwo expansionFactor universe = do
first <- gi
second <- gi
if (first >= second) then [] else [dist first second]
where gi = galaxyIndices universe
dist = partTwoDistance expansionFactor universe
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment