Commit c3bfe3c7 by Stuart Kurtz

Day 9 (incomplete, a done, b incorrect)

parent b1be6772
...@@ -88,14 +88,17 @@ executable aoc-08b ...@@ -88,14 +88,17 @@ executable aoc-08b
executable aoc-09a executable aoc-09a
import : aoc-common import : aoc-common
main-is : AOC-09a.hs main-is : AOC-09a.hs
build-depends : array
executable aoc-09b executable aoc-09b
import : aoc-common import : aoc-common
main-is : AOC-09b.hs main-is : AOC-09b.hs
build-depends : array
executable aoc-10a executable aoc-10a
import : aoc-common import : aoc-common
main-is : AOC-10a.hs main-is : AOC-10a.hs
build-depends : array
executable aoc-10b executable aoc-10b
import : aoc-common import : aoc-common
......
module Main where module Main where
import Data.Array
makeHeightMap :: String -> Array (Int,Int) Int
makeHeightMap s = array ((1,1),(mx,my)) entries where
rows = lines s
entries = [((x,y),z) | (x,row) <- zip [1..] (lines s)
, (y,c) <- zip [1..] row
, let z = read [c]
]
mx = length (rows)
my = length (head rows)
heightAt :: Array (Int,Int) Int -> (Int,Int) -> Int
heightAt arr pos =
if inRange (bounds arr) pos
then arr ! pos
else 10
neighbors :: (Int,Int) -> [(Int,Int)]
neighbors (x,y) = [(x-1,y),(x+1,y),(x,y-1),(x,y+1)]
isLowPoint :: Array (Int,Int) Int -> (Int,Int) -> Bool
isLowPoint arr pos = (arr ! pos) < minimum (map (heightAt arr) (neighbors pos))
score :: Array (Int,Int) Int -> Int
score heightMap = sum . map (+1) . map (heightMap !) . filter (isLowPoint heightMap) . range . bounds $ heightMap
main :: IO () main :: IO ()
main = pure () main = do
heightMap <- makeHeightMap <$> readFile "data/heightMap.txt"
print $ score heightMap
module Main where module Main where
import Data.Array
import Data.List
makeHeightMap :: String -> Array (Int,Int) Int
makeHeightMap s = array ((1,1),(mx,my)) entries where
rows = lines s
entries = [((x,y),z) | (x,row) <- zip [1..] (lines s)
, (y,c) <- zip [1..] row
, let z = read [c]
]
mx = length (rows)
my = length (head rows)
heightAt :: Array (Int,Int) Int -> (Int,Int) -> Int
heightAt arr pos =
if valid arr pos
then arr ! pos
else 10
valid :: (Ix k) => Array k v -> k -> Bool
valid arr key = (`inRange` key) . bounds $ arr
neighbors :: Array (Int,Int) Int -> (Int,Int) -> [(Int,Int)]
neighbors arr (x,y) = filter (valid arr) [(x-1,y),(x+1,y),(x,y-1),(x,y+1)]
isLowPoint :: Array (Int,Int) Int -> (Int,Int) -> Bool
isLowPoint arr pos = (arr ! pos) < minimum (map (heightAt arr) (neighbors arr pos))
lowPoints :: Array (Int,Int) Int -> [(Int,Int)]
lowPoints arr = filter (isLowPoint arr) . range . bounds $ arr
-- This code is wrong for the interpretation of a basin given by
-- the problem.
basin :: Array (Int,Int) Int -> (Int,Int) -> [(Int,Int)]
basin arr pos = pos : iter pos (neighbors arr pos) where
iter :: (Int,Int) -> [(Int,Int)] -> [(Int,Int)]
iter _ [] = []
iter p (n:ns)
| n `flowsTo` p = n : iter p ns ++ iter n (neighbors arr n)
| otherwise = iter p ns
flowsTo n p =
let target = heightAt arr n
flowPoints = filter ((< target) . (arr !)) . neighbors arr $ n
in flowPoints == [p]
main :: IO () main :: IO ()
main = pure () main = do
heightMap <- makeHeightMap <$> readFile "test/heightMap.txt"
putStr . unlines . map (show . sort) $ basin heightMap <$> lowPoints heightMap
2199943210
3987894921
9856789892
8767896789
9899965678
\ No newline at end of file
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or sign in to comment