module CLI ( containsEither, filterParams, printVersion, runPomodoros, runSession, showManual, showUsage ) where import Control.Concurrent (threadDelay) import Control.Monad (void) import Data.Char (isDigit) import Data.List (intersect) import Data.Version (showVersion) import System.Exit (ExitCode(ExitSuccess)) import System.Process (system) import Paths_Monadoro (getDataFileName, version) import CountdownLoop (countdown_loop) import Pomodoro (session) showUsage :: IO () showUsage = putStrLn usage usage :: String usage = "Usage: monadoro [-h|--help] [-m|--man] [-v|--version] [--session]" ++ " [INTERVAL [...]]" runPomodoros :: [String] -> IO () runPomodoros xs = do warnAboutErrorsIfAny invalidIntervals runTimer (getDelayIfNeeded xs) validIntervals where (validIntervals, invalidIntervals) = checkInput $ filterParams xs runSession :: [String] -> IO () runSession xs = session (getDelayIfNeeded xs) runTimer :: IO () -> [String] -> IO () runTimer delayer [] = void (countdown_loop delayer "25:00") runTimer delayer [t] = void (countdown_loop delayer t) runTimer delayer (t:ts) = runTimer delayer [t] >> runTimer delayer ts filterParams :: [String] -> [String] filterParams = remove "-n" . remove "--nodelay" remove :: String -> [String] -> [String] remove element = filter (/=element) showManual :: IO () showManual = do man_file <- getDataFileName "man/monadoro.1" ExitSuccess <- system $ "man " ++ man_file return () printVersion :: IO () printVersion = putStrLn . showVersion $ version warnAboutErrorsIfAny :: [String] -> IO () warnAboutErrorsIfAny [] = return () warnAboutErrorsIfAny errors = putStrLn $ "Unable to parse as interval: " ++ show errors {-| checkInput Returns valid entries (first list) and invalid entries (second list). >>> checkInput [] ([],[]) >>> checkInput ["x"] ([],["x"]) >>> checkInput ["00:00"] (["00:00"],[]) >>> checkInput ["00:00", "x"] (["00:00"],["x"]) >>> checkInput ["00:00", "x"] (["00:00"],["x"]) >>> checkInput ["00:00", "00:01", "x"] (["00:00","00:01"],["x"]) -} checkInput :: [String] -> ([String], [String]) checkInput [] = ([], []) checkInput [x] | isValidTimeInterval x = ([x], []) | otherwise = ([], [x]) checkInput (x:xs) = (validEntries, invalidEntries) where validEntries = fst (checkInput [x]) ++ fst (checkInput xs) invalidEntries = snd (checkInput [x]) ++ snd (checkInput xs) {-| isValidTimeInterval >>> isValidTimeInterval "x" False >>> isValidTimeInterval "00:00" True -} isValidTimeInterval :: String -> Bool isValidTimeInterval (m1:m2:':':s1:[s2]) | all isDigit [m1, m2, s1, s2] = True isValidTimeInterval _ = False containsEither :: (Eq a) => [a] -> [a] -> Bool containsEither a = not . null . intersect a getDelayIfNeeded :: [String] -> IO () getDelayIfNeeded xs | xs `containsEither` ["--nodelay", "-n"] = wait 0 | otherwise = wait 1 milisec_per_second :: Int milisec_per_second = 10 ^ (6 :: Int) wait :: Int -> IO() wait n = threadDelay (n * milisec_per_second)