module Daemon1st where import List(sort) import System(system) import Control.Concurrent(threadDelay) import Entry1st main = do putStrLn "The HCron daemon" spec <- readFile specLocation calTime <- getCalendarTime (TOD currentSecondsSinceEpoch _) <- getClockTime let entries = (read spec)::[Entry Time] entries' = filter isNew $ map toSeconds (sort entries) isNew (Entry t _) = t > currentSecondsSinceEpoch toSeconds x = x { when = timeToSeconds calTime (when x) } putStrLn "Successfully read entries. Starting daemon." putStrLn $ unlines $ map show entries putStrLn "After pruning:" putStrLn $ unlines $ map show entries' daemon entries' daemon :: [Entry Integer] -> IO() daemon [] = return () daemon ((Entry time command'):xs) = do (TOD clockTime _) <- getClockTime delaySeconds $ max 0 (time - clockTime) system command' daemon xs getCalendarTime :: IO CalendarTime getCalendarTime = do clockTime <- getClockTime toCalendarTime clockTime timeToSeconds :: CalendarTime -> Time -> Integer timeToSeconds calTime t = let t' = calTime { ctYear = year t, ctMonth = month t, ctDay = day t , ctHour = hour t, ctMin = minute t, ctSec = 0, ctPicosec = 0 } (TOD time _) = (toClockTime t') in time delaySeconds :: Integer -> IO () delaySeconds seconds = delayMicro (seconds * 1) -- FIXME: multiple by 10^6 where delayMicro ms | ms <= 0 = return () | otherwise = do let d = min (toInteger (maxBound::Int)) ms print (d `div` 10^6) threadDelay (fromInteger d) delayMicro (ms - d)