{-# LANGUAGE ScopedTypeVariables, LambdaCase #-} {- Copyright 2014 Ken Takusagawa This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} module Main where { import Data.List; import System.Environment; main :: IO(); main = -- getArgs >>= mapM_ putStrLn . flines . read . head; getArgs >>= \case { [height] -> do { putStrLn "P1"; putStrLn $ (show $ (read height) * 2 + 1) ++ " " ++ height; mapM_ putStrLn $ map (return . pbmchar) $ concat $ flines $ read height; }}; type B = [Bool]; next_list :: [Bool] -> [Bool]; next_list l = let { n :: [Bool]; n = next_list $ tail l; } in case l of { _:False:False:_ -> False:n; _:True:True:_ -> False:n; True:False:True:_ -> False:n; False:False:True:_ -> True:n; _:True:False:True:_ -> False:n; _:True:False:False:_ -> True:n; [] -> []; [_] -> []; [_,_] -> []; [_,_,_] -> []; }; eval :: [Bool] -> [Bool]; eval n = let { z :: B; z = next_list$ [False,False] ++ n ++ [False,False]; } in case last z of { False -> init z; True -> error $ "weird " ++ show n; }; bchar :: Bool -> Char; bchar b = if b then 'M' else ' '; fmt :: Int -> Int -> String -> String; fmt offset i s = let { pad :: String; pad = replicate (offset-i) ' '; } in pad ++ intersperse ' ' s ++ pad; flines :: Int -> [String]; flines offset = take offset $ zipWith (fmt offset) [0..] $ map (map bchar) $ iterate eval [True]; pbmchar :: Char -> Char; pbmchar b = if b == ' ' then '0' else '1'; }