Files
AOC22/src/Days/Day08.hs
2022-12-12 18:08:06 +01:00

55 lines
1.4 KiB
Haskell

module Days.Day08 where
import AOCUtil
import Data.Char
import Data.List
import GHC.Utils.Misc
runA :: IO ()
runA = interactF "data/day08.txt" (solve)
runB :: IO ()
runB = interactF "data/day08.txt" (solveB)
solve :: String -> String
solve s = show . length . filter (isVisible for) $ [(x, y) | x <- [0 .. fwidth for - 1], y <- [0 .. fheight for - 1]]
where
for = map (map readChar) . lines $ s
solveB :: String -> String
solveB s = show . maximum . map (scenicScore for) $ [(x, y) | x <- [0 .. fwidth for - 1], y <- [0 .. fheight for - 1]]
where
for = map (map readChar) . lines $ s
type Forrest = [[Int]]
isVisible :: Forrest -> (Int, Int) -> Bool
isVisible f (x, y) = isLookt h left || isLookt h (tail right2) || isLookt h top || isLookt h (tail bot2)
where
row = f !! y
col = transpose f !! x
h = f !! y !! x
(left, right2) = splitAt x row
(top, bot2) = splitAt y col
scenicScore :: Forrest -> (Int, Int) -> Int
scenicScore f (x, y) = viewDist h (reverse left) * viewDist h (tail right2) * viewDist h (reverse top) * viewDist h (tail bot2)
where
row = f !! y
col = transpose f !! x
h = f !! y !! x
(left, right2) = splitAt x row
(top, bot2) = splitAt y col
viewDist :: Int -> [Int] -> Int
viewDist i ls = min (length ls) . (+ 1) . length . takeWhile (< i) $ ls
isLookt :: Int -> [Int] -> Bool
isLookt m = all (< m)
fwidth :: Forrest -> Int
fwidth = length . head
fheight :: Forrest -> Int
fheight = length