Day 18 - replaced Matrix with UArray with great performance improvements!

This commit is contained in:
Jonathan Chan 2018-12-18 14:41:32 -08:00
parent 16e6c33658
commit 4d6f80a4db
3 changed files with 39 additions and 28 deletions

View File

@ -26,10 +26,10 @@ Now located in this repository's wiki.
| 12 | ~ 1.5 | | 12 | ~ 1.5 |
| 13 | ~ 0.5 | | 13 | ~ 0.5 |
| 14 | 22.3 | | 14 | 22.3 |
| 15 | < 1 | | 15 | |
| 16 | ~ 15 | | 16 | ~ 1 |
| 17 | 120 | | 17 | ~ 15 |
| 18 | | | 18 | ~ 6 |
| 19 | | | 19 | |
| 20 | | | 20 | |
| 21 | | | 21 | |

View File

@ -26,6 +26,7 @@ dependencies:
- extra - extra
- matrix - matrix
- vector - vector
- array
library: library:
source-dirs: src source-dirs: src

View File

@ -1,47 +1,57 @@
module Day18 (main) where module Day18 (main) where
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import Data.Matrix (Matrix, fromLists, nrows, ncols, (!), safeGet, setElem) import Data.Foldable (foldl')
import Data.Ix (range, inRange)
import Data.Array.Unboxed
type Landscape = Matrix Char type Landscape = UArray Coordinate Char
type Coordinate = (Int, Int) -- row, col type Coordinate = (Int, Int) -- row, col
stepCoord :: Landscape -> Coordinate -> Landscape -> Landscape parse :: String -> Landscape
stepCoord oldscape (r, c) newscape = parse str =
let neighbours = catMaybes $ map (flip (uncurry safeGet) oldscape) [(r', c') | r' <- [r-1 .. r+1], c' <- [c-1 .. c+1], (r', c') /= (r, c)] let nestedList = lines str
newAcre = case oldscape ! (r, c) of maxIx = (length nestedList, length $ head nestedList)
in listArray ((1, 1), maxIx) $ concat nestedList
stepCoord :: Landscape -> Landscape -> Coordinate -> Landscape
stepCoord oldscape newscape coord@(r, c) =
let neighbours = catMaybes . map (safeGet oldscape) . filter (/= coord) $ range ((r - 1, c - 1), (r + 1, c + 1))
newAcre = case oldscape ! coord of
'.' -> if (length $ filter (== '|') neighbours) >= 3 then '|' else '.' '.' -> if (length $ filter (== '|') neighbours) >= 3 then '|' else '.'
'|' -> if (length $ filter (== '#') neighbours) >= 3 then '#' else '|' '|' -> if (length $ filter (== '#') neighbours) >= 3 then '#' else '|'
'#' -> if '|' `elem` neighbours && '#' `elem` neighbours then '#' else '.' '#' -> if '|' `elem` neighbours && '#' `elem` neighbours then '#' else '.'
in setElem newAcre (r, c) newscape in newscape // [(coord, newAcre)]
where
safeGet :: Landscape -> Coordinate -> Maybe Char
safeGet scape coord = if inRange (bounds scape) coord then Just $ scape ! coord else Nothing
stepScape :: Landscape -> Landscape stepScape :: Landscape -> Landscape
stepScape oldscape = foldr (stepCoord oldscape) oldscape [(r, c) | r <- [1 .. nrows oldscape], c <- [1 .. ncols oldscape]] stepScape oldscape = foldl' (stepCoord oldscape) oldscape $ indices oldscape
getResVal :: Landscape -> Int
getResVal scape =
let woodedCount = length . filter (== '|') . elems $ scape
lumberyardCount = length . filter (== '#') . elems $ scape
in woodedCount * lumberyardCount
part1 :: Landscape -> Int part1 :: Landscape -> Int
part1 scape = part1 scape = getResVal $ iterate stepScape scape !! 10
let newscape = iterate stepScape scape !! 10
woodedCount = sum $ fmap (fromEnum . (== '|')) newscape
lumberyardCount = sum $ fmap (fromEnum . (== '#')) newscape
in woodedCount * lumberyardCount
part2 :: Landscape -> Int part2 :: Landscape -> Int
part2 scape = part2 scape =
let resVals = map getResVal $ iterate stepScape scape let resVals = map getResVal $ iterate stepScape scape
(i, i') = (461, 489) -- cycleIndices (drop 1 resVals) (drop 2 resVals) 1 2 (i1, i2) = tortoiseHare (drop 1 resVals) (drop 2 resVals) 1 2
cyclePos = (1000000000 - i) `mod` (i' - i) + i pos = (1000000000 - i1) `mod` (i2 - i1) + i1
in getResVal $ iterate stepScape scape !! cyclePos -- resVals !! cyclePos in resVals !! pos
where where
getResVal scape = tortoiseHare (t:ts) (h:_:hs) ti hi =
let woodedCount = sum $ fmap (fromEnum . (== '|')) scape if t == h then (ti, nextOcc t ts (ti + 1)) else tortoiseHare ts hs (ti + 1) (hi + 2)
lumberyardCount = sum $ fmap (fromEnum . (== '#')) scape nextOcc v (r:rs) n =
in woodedCount * lumberyardCount if v == r then n else nextOcc v rs (n + 1)
-- theoretically this works but it was just faster to print out the first 500 values
cycleIndices (t:ts) (h:_:hs) ti hi =
if t == h then (ti, hi) else cycleIndices ts hs (ti + 1) (hi + 2)
main :: IO () main :: IO ()
main = do main = do
input <- fromLists . lines <$> readFile "input/18.txt" input <- parse <$> readFile "input/18.txt"
print $ part1 input print $ part1 input
print $ part2 input print $ part2 input