{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE LambdaCase #-} module Main where import Config import Parse import Display import Export.Queue import System.FSNotify import Control.Concurrent import Control.Monad import qualified System.FilePath as FP import qualified System.Directory as D import qualified System.Environment as A -- todo [release] [importante] vedi se gli scatti nella animazione c -- sono dovuti da animascii o da lib. 100% del cpu รจ troppo! -- Anzi, sta andando lento il terminale. main :: IO () main = -- imagemagick check fmap not isImageMagick >>= \bi -> if bi then putStrLn "\nThis program needs imagemagick version 6 or later \ \to work!\nPlease install it and try again.\n" else -- args & run A.getArgs >>= \as -> if null as then animascii else putStrLn help where animascii = getConfig >>= \c -> -- render service createQueue >>= \mvq -> createResultQueue >>= \mrq -> forkIO (startQueue c mvq mrq) >> -- notify service newEmptyMVar >>= \mvf -> forkIO (notify c mvf mvq) >>= \tid -> -- terminal playAnimation (cFPS c) (cIDir c) mvf mvq mrq isImageMagick :: IO Bool isImageMagick = D.findExecutable "convert" >>= \case Nothing -> return False _ -> return True help :: String help = unlines $ ["\nAnimascii - text based ASCII animator, version 0.1.0.0", "manual: http://ariis.it/static/articles/animascii/page.html"] notify :: Config -> MVar FilePath -> MVar [FilePath] -> IO () notify c mv mvq = withManager $ \mgr -> (wt mgr >> forever (threadDelay 10000000)) where idir = cIDir c akt e = putMVar mv (eventPath e) >> addRenderJob (eventPath e) mvq wt mgr = watchTree mgr idir ff akt -- filter function for Events, ignore removes and dotfiles ff :: Event -> Bool ff e | Removed {} <- e = False | otherwise = let ep = eventPath e fn = FP.takeFileName ep ex = FP.takeExtension ep in if (head fn /= '.' && ex == ".txt") then True else False