{-# LANGUAGE LambdaCase #-} module Main where import Data.Functor import Data.Matrix hiding (trace) import Data.List import Debug.Trace parse :: String -> Matrix Char parse = fromLists . lines getGroup :: (Int,Int) -> Matrix Char -> [(Int,Int)] -> [(Int,Int)] getGroup p@(i,j) s v | p `elem` v = v | otherwise = let e = getElem i j s in nub . (p:) $ filter((== Just e) . flip (uncurry safeGet) s) [(i,j+1),(i,j-1),(i+1,j),(i-1,j)] >>= \p' -> getGroup p' s (p:v) where groups :: Matrix Char -> [[(Int,Int)]] groups s = nub $ go [(i,j) | i <- [1 .. nrows s], j <- [1 .. ncols s]] [] where go :: [(Int,Int)] -> [[(Int,Int)]] -> [[(Int,Int)]] go [] v = v go (x:xs) v | any (x `elem`) v = go xs v | otherwise = go xs (getGroup x s []:v) perimeter :: [(Int,Int)] -> Int perimeter s = length $ s >>= \(i,j) -> [(i,j+1),(i,j-1),(i+1,j),(i-1,j)] \\ s solve1 :: Matrix Char -> Int solve1 s = let g = groups s; p = perimeter <$> g in sum $ zipWith (*) (length <$> g) p solve2 :: Matrix Char -> Int solve2 = undefined main :: IO () main = readFile "inputs/12.example" <&> parse >>= \i -> print (solve1 i) >> print (solve2 i)