Skip to content

Commit

Permalink
prefer getInputArray
Browse files Browse the repository at this point in the history
  • Loading branch information
glguy committed Dec 29, 2023
1 parent 486f07f commit 3e45c5c
Show file tree
Hide file tree
Showing 5 changed files with 27 additions and 27 deletions.
4 changes: 2 additions & 2 deletions solutions/solutions.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -1003,7 +1003,7 @@ executable sln_2023_02
executable sln_2023_03
import: day
main-is: 2023/03.hs
build-depends: containers
build-depends: array, containers

executable sln_2023_04
import: day
Expand Down Expand Up @@ -1035,7 +1035,7 @@ executable sln_2023_09
executable sln_2023_10
import: day
main-is: 2023/10.hs
build-depends: containers
build-depends: array

executable sln_2023_11
import: day
Expand Down
9 changes: 5 additions & 4 deletions solutions/src/2022/23.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,16 +22,16 @@ Maintainer : [email protected]
20
-}
module Main where
module Main (main) where

import Data.Array.Unboxed (Ix(rangeSize), UArray, accumArray)
import Data.Array.Unboxed (UArray, assocs, rangeSize, UArray, accumArray)
import Data.List (foldl', tails)
import Data.Map qualified as Map
import Data.Maybe (fromMaybe)
import Data.Set (Set)
import Data.Set qualified as Set

import Advent (arrIx, getInputMap)
import Advent (arrIx, getInputArray)
import Advent.Coord (Coord, above, below, boundingBox, left, neighbors, right)

-- |
Expand All @@ -40,7 +40,8 @@ import Advent.Coord (Coord, above, below, boundingBox, left, neighbors, right)
-- 1023
main :: IO ()
main =
do elves <- Map.keysSet . Map.filter ('#'==) <$> getInputMap 2022 23
do input <- getInputArray 2022 23
let elves = Set.fromList [c | (c, '#') <- assocs input]
let states = sim elves

-- part 1
Expand Down
18 changes: 9 additions & 9 deletions solutions/src/2023/03.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,12 +27,12 @@ Maintainer : [email protected]
-}
module Main (main) where

import Data.Map (Map)
import Data.Map qualified as Map
import Data.Char (isDigit)

import Advent (getInputMap, ordNub)
import Advent (getInputArray, ordNub, arrIx)
import Advent.Coord (Coord, left, neighbors, right)
import Data.Array.Unboxed (UArray, assocs)
import Data.Char (isDigit)
import Data.Map qualified as Map
import Data.Maybe (fromMaybe)

-- | Parse the input schematic and print answers to both parts.
--
Expand All @@ -41,21 +41,21 @@ import Advent.Coord (Coord, left, neighbors, right)
-- 81463996
main :: IO ()
main =
do input <- getInputMap 2023 3
do input <- getInputArray 2023 3
let numbers = extractNumbers input
print (sum [partNo | (partNo, _:_) <- numbers])
print (sum [a * b | [a, b] <- gearNumbers numbers])

-- | Extract the numbers from the diagram and the parts adjacent to them.
extractNumbers :: Map Coord Char -> [(Int, [(Coord, Char)])]
extractNumbers :: UArray Coord Char -> [(Int, [(Coord, Char)])]
extractNumbers input =
[ (read digits, partsNear cs)
| (c, digit) <- Map.assocs input
| (c, digit) <- assocs input
, isDigit digit, not (isDigit (lkp (left c))) -- left-boundary of number
, let (cs, digits) = unzip (numbersAfter c)
]
where
lkp i = Map.findWithDefault '.' i input
lkp = fromMaybe '.' . arrIx input
numbersAfter start =
[ (c, digit)
| c <- iterate right start
Expand Down
4 changes: 2 additions & 2 deletions solutions/src/2023/07.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,12 +28,12 @@ module Main (main) where

import Advent (format, counts)
import Data.Foldable (toList)
import Data.List (sortOn, sortBy, elemIndex, nub)
import Data.List (sortOn, sortBy, elemIndex)
import Data.Maybe (fromJust)
import Data.Map (Map)
import Data.Map qualified as Map

-- |
-- | Parse the input hands and print the answers to both parts.
--
-- >>> :main
-- 248422077
Expand Down
19 changes: 9 additions & 10 deletions solutions/src/2023/10.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,11 +60,9 @@ L7JLJL-JLJLJL--JLJ.L
-}
module Main (main) where

import Advent (getInputMap)
import Advent (getInputArray, arrIx)
import Advent.Coord (invert, invert', south, north, west, Coord(C))
import Advent.Search (dfsOn)
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Array.Unboxed (UArray, (!), assocs)

-- | Parse the input and print out answers to both parts.
--
Expand All @@ -73,29 +71,30 @@ import Data.Map qualified as Map
-- 541
main :: IO ()
main =
do input <- getInputMap 2023 10
do input <- getInputArray 2023 10
let (start, dir0) = pickStart input
route = getLoop (map fst (iterate (step input) (start, dir0)))
perimeter = length route
print (perimeter `quot` 2)
print (abs (polyareaRect route) - perimeter `quot` 2 + 1)

pickStart :: Map Coord Char -> (Coord, Coord)
pickStart :: UArray Coord Char -> (Coord, Coord)
pickStart input = head
[ (k, dir)
| (k, 'S') <- Map.assocs input
| (k, 'S') <- assocs input
, (dir, ok) <- [(south, "L|J"), (north, "F|7"), (west,"7-J")]
, let next = Map.findWithDefault '.' (k + dir) input
, next <- arrIx input (k + dir)
, next `elem` ok
]

getLoop :: Eq a => [a] -> [a]
getLoop (x:xs) = x : takeWhile (x /=) xs
getLoop [] = error "getLoop: empty input"

step :: Map Coord Char -> (Coord, Coord) -> (Coord, Coord)
step :: UArray Coord Char -> (Coord, Coord) -> (Coord, Coord)
step inp (here, dir) =
let here' = here + dir in
(here', pipeEffect (inp Map.! here') dir)
(here', pipeEffect (inp ! here') dir)

pipeEffect :: Char -> Coord -> Coord
pipeEffect = \case
Expand Down

0 comments on commit 3e45c5c

Please sign in to comment.