module Main where import Data.Char (isDigit) import Data.List (intersect) import Data.Version (showVersion) import Paths_Monadoro (version) import System.Environment (getArgs) import Control.Monad (void) import CountdownLoop (countdown) import Pomodoro (session) main :: IO () main = monadoro monadoro :: IO () monadoro = getArgs >>= parseArgs parseArgs :: [String] -> IO () parseArgs xs | xs `containsEither` ["--help", "-h"] = putStrLn usage | xs `containsEither` ["--version", "-v"] = putStrLn . showVersion $ version | xs `containsEither` ["--session", "-s"] = session | otherwise = do warnAboutErrorsIfAny invalidIntervals runTimer validIntervals where (validIntervals, invalidIntervals) = checkInput xs 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 usage :: String usage = "Usage: monadoro [-vh] [--session] [INTERVAL [...]]" runTimer :: [String] -> IO () runTimer [] = void (countdown "25:00") runTimer [t] = void (countdown t) runTimer (t:ts) = parseArgs [t] >> parseArgs ts