{- | RevDecTime is a tiny utility which displays the current French Revolutionary Decimal Time (metric clock). In this representation, each day is divided into ten (decimal) hours, each hour into a hundred minutes and each minute into a hundred seconds. The author of this tiny tool thinks that this is more comfortable than duodecimal. -} -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- ---- | ---- Module : Main ---- Copyright : (C) Kamil Stachowski ---- License : GPL3+ ---- Maintainer : Kamil Stachowski ---- Stability : unstable ---- Portability : unportable ---- A French revolutionary decimal time (metric) clock. -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- module Main ( main ) where import System.Time -- main ================================================================================= main :: IO () main = do nowClock <- getClockTime >>= toCalendarTime print $ toRevDecTime nowClock -- data ================================================================================= -- | Holds decimal time. data RevDecTime = RevDecTime { decHour :: Int , decMin :: Int , decSec :: Int } -- -------------------------------------------------------------------------------------- instance Show RevDecTime where show (RevDecTime h m s) = show h ++ ":" ++ show m ++ ":" ++ show s -- conversion =========================================================================== -- | Extracts the time from CalendarTime and converts it to RevDecTime (= decimal time). toRevDecTime :: CalendarTime -> RevDecTime toRevDecTime (CalendarTime _ _ _ h m s p _ _ _ _ _) = RevDecTime (fst decH) (fst decM) decS where decH = rmTrunc totalDecMs 10000000 decM = rmTrunc (snd decH) 100000 decS = snd decM `div` 1000 totalMs = h*60*60*1000 + m*60*1000 + s*1000 + (fromInteger p) `div` 1000000000 totalDecMs = round $ fromIntegral totalMs / 0.864 -- -------------------------------------------------------------------------------------- rmTrunc :: (Integral a) => a -> a -> (a, a) rmTrunc x y = (truncd, truncdless) where truncd = x `div` y truncdless = x - y*truncd