#!/usr/bin/env stack
--stack --install-ghc runghc

module CountdownLoop       (countdown) where

import System.Environment  (getArgs)
import System.Console.ANSI (saveCursor,
                            restoreCursor)
import System.IO (hFlush,
                  stdout)
import Control.Concurrent  (threadDelay)
import ParseTime           (count_down_time)

milisec_per_second :: Int
milisec_per_second :: Int
milisec_per_second = Int
10 Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
6 :: Int)

{-| wait: Pauses for the given number of seconds.

>>> wait 0
-}

wait :: Int -> IO()
wait :: Int -> IO ()
wait Int
n = Int -> IO ()
threadDelay (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
milisec_per_second)

with_delay :: IO()
with_delay :: IO ()
with_delay = Int -> IO ()
wait Int
1

-- Mocks a delay for test purposes.
no_delay :: IO()
no_delay :: IO ()
no_delay = Int -> IO ()
wait Int
0

{-| countdown_loop: Runs a Pomodoro timer.

>>> result <- countdown_loop no_delay "00:00"
...
>>> result
"00:00"

>>> result' <- countdown_loop no_delay "00:59"
...
>>> result'
"00:00"

>>> result'' <- countdown_loop no_delay "01:59"
...
>>> result''
"00:00"

-}

countdown :: String -> IO (String)
countdown :: String -> IO String
countdown = IO () -> String -> IO String
countdown_loop IO ()
with_delay

countdown_loop :: IO() -> String -> IO (String)
countdown_loop :: IO () -> String -> IO String
countdown_loop IO ()
delayer String
"00:00" = String -> IO ()
putStrLn String
"00:00" IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
"00:00"
countdown_loop IO ()
delayer String
s = do
  IO ()
saveCursor
  String -> IO ()
putStr String
s
  Handle -> IO ()
hFlush Handle
stdout
  IO ()
delayer
  IO ()
restoreCursor
  (IO () -> String -> IO String
countdown_loop IO ()
delayer (String -> IO String) -> (String -> String) -> String -> IO String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
count_down_time) String
s

parse :: [String] -> IO ()
parse :: [String] -> IO ()
parse [String
s] = IO () -> String -> IO String
countdown_loop IO ()
with_delay String
s IO String -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
parse [String]
_   = IO () -> String -> IO String
countdown_loop IO ()
with_delay String
"00:00" IO String -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

main :: IO ()
main :: IO ()
main = IO [String]
getArgs IO [String] -> ([String] -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [String] -> IO ()
parse