{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE OverloadedStrings #-} -- | Main entry point. module Main where import Control.Concurrent import Control.Monad.Trans import Data.Text (Text) import qualified Data.Text as T import UI.NCurses -- | Main entry point. main :: IO () main = runCurses $ do w <- defaultWindow showScene w 0 -- | Render nyan cat flying through space. showScene :: Window -> Int -> Curses () showScene w sceneIndex = do updateWindow w $ do moveCursor 0 0 drawText $ frames !! sceneIndex render io $ threadDelay $ 1000 * 200 showScene w $ if sceneIndex == length frames - 1 then 0 else sceneIndex + 1 -- | Madness. io :: MonadIO m => IO a -> m a io = liftIO frames :: [Text] frames = T.splitOn ("\n\n") ";;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;________________________;;;;;;;;;;;;;;;;;;;;;;\n================/ \\;;;;;;;;;;;;;;;;;;;;;\n================| '@'''''''@'''''@_'''' |;;;;;;;;;;;;;;;;;;;;\n================| ''''''''''''''''| \\'@'' |;/ |;;;;;;;;;;;;;;;;\n================| ''''''''''''''''| \\_____/ |';;;;;;;;;;;;;;;\n==========_=====| ''''@''''@'''''| ;;;;;;;;;;;;;;;;\n=========| \\____| ''''''''''''''| _| _| \\;;;;;;;;;;;;;;\n==========\\_____| ''@''''''''''@| ## # ##|;;;;;;;;;;;;;\n================| '''''''@'''''''\\ |___,__| /;;;;;;;;;;;;;;\n================| ''@'''''''''''`\\___________;;;;;;;;;;;;;;;;;\n================ \\_________________________/; \\;;;;;;;;;;;;;;;;\n=================\\_\\;\\_\\;;;;;;;;;;;;;;;\\_\\;;;\\_\\;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;________________________;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;/ \\;;;;;;;;;;;;;;;;;;;;;\n================| ''''''''''''''''| \\'@'' |;/ |;;;;;;;;;;;;;;;;\n================| ''''''''''''''''| \\_____/ |';;;;;;;;;;;;;;;\n================| ''''@''''@'''''| ;;;;;;;;;;;;;;;;\n=========_______| ''''''''''''''| _| _| \\;;;;;;;;;;;;;;\n=========\\______| ''@''''''''''@| ## # ##|;;;;;;;;;;;;;\n================| '''''''@'''''''\\ |___,__| /;;;;;;;;;;;;;;\n================| ''@'''''''''''`\\___________;;;;;;;;;;;;;;;;;\n================| '''''''''''''''' /;;;;;;;;;;;;;;;;;\n===============| \\_________________________/ |;;;;;;;;;;;;;;;;;\n===============|_|;;|_/;;;;;;;;;;;;;;|_|;;|_|;;;;;;;;;;;;;;;;;;\n===============;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;________________________;;;;;;;;;;;;;;;;;;;;;;\n================/ \\;;;;;;;;;;;;;;;;;;;;;\n================| '@'''''''@'''''@_'''' |;;;;;;;;;;;;;;;;;;;;\n================| ''''''''''''''''| \\'@'' |;/ |;;;;;;;;;;;;;;;;\n================| ''''''''''''''''| \\_____/ |';;;;;;;;;;;;;;;\n================| ''''@''''@'''''| ;;;;;;;;;;;;;;;;\n=============___| ''''''''''''''| _| _| \\;;;;;;;;;;;;;;\n=========/```___| ''@''''''''''@| ## # ##|;;;;;;;;;;;;;\n=========|/``===| '''''''@'''''''\\ |___,__| /;;;;;;;;;;;;;;\n================| ''@'''''''''''`\\___________;;;;;;;;;;;;;;;;;\n==============/ \\________________________//;;;;;;;;;;;;;;;;;;;\n=============/_/;/_/;;;;;;;;;;;;;;/_/;;;/_/;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;\n;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;"