{-# LANGUAGE ParallelListComp #-} import Linear.V3 import Linear.V4 import Control.Monad import Data.List import Control.Lens import Data.Function main :: IO () main = do input <- lines <$> readFile "input" print input -- print $ toV3 input -- print $ updateNeighbours $ toV3 input let final = flip (!!) 6 $ iterate step $ toV3 input putStrLn $ visualize (-2) final putStrLn $ visualize (-1) final putStrLn $ visualize 0 final print $ length final visualize :: Int -> [V3 Int] -> String visualize z vs = unlines $ visualize' (filter ((==z) . (^._z)) vs) (replicate height (replicate width '.')) where x' = maximumBy (compare `on` (^._x)) vs y' = maximumBy (compare `on` (^._y)) vs x = minimumBy (compare `on` (^._x)) vs y = minimumBy (compare `on` (^._y)) vs width = (x'-x) ^._x +1 height = (y'-y) ^._y +1 visualize' [] arr = arr visualize' ((V3 x'' y'' _):vs_f) arr = visualize' vs_f (beg++newLine:end) where (beg,line:end) = splitAt (y''-(y^._y)) arr (beg',_:end') = splitAt (x''-(x^._x)) line newLine = beg' ++ '#' : end' toV3 :: [String] -> [V3 Int] toV3 input = [V3 x y 0 | (y,line)<-zip [0..] input, (x,c)<-zip [0..] line, c=='#'] step :: [V3 Int] -> [V3 Int] step state = (nub . concatMap fst . filter f . ap zip (map length) . group . sort . updateNeighbours) state where f (x,n) = n==3 || n==2 && head x `elem` state updateNeighbours :: [V3 Int] -> [V3 Int] updateNeighbours = concatMap f where f coord = [coord + V3 x y z | [x,y,z]<-replicateM 3 [(-1)..1] \\ [[0,0,0]]] mapI :: Num b => (a -> b -> c) -> [a] -> [c] mapI f l = mapI' f 0 l where mapI' _ _ [] = [] mapI' f n (x:xs) = f x n : mapI' f (n+1) xs