module Data.Geo.Jord.Duration
(
Duration
, toMilliseconds
, milliseconds
, hours
, minutes
, seconds
, hms
, toHours
, toMinutes
, toSeconds
, duration
, read
, add
, subtract
, zero
) where
import Prelude hiding (read, subtract)
import Text.ParserCombinators.ReadP (ReadP, char, option, readP_to_S)
import Text.Printf (printf)
import Text.Read (readMaybe)
import Data.Geo.Jord.Parser
newtype Duration =
Duration
{ toMilliseconds :: Int
}
deriving (Eq)
instance Read Duration where
readsPrec _ = readP_to_S duration
instance Show Duration where
show d@(Duration millis) =
show h ++ "H" ++ show m ++ "M" ++ show s ++ "." ++ printf "%03d" ms ++ "S"
where
h = truncate (toHours d) :: Int
m = truncate (fromIntegral (millis `mod` 3600000) / 60000.0 :: Double) :: Int
s = truncate (fromIntegral (millis `mod` 60000) / 1000.0 :: Double) :: Int
ms = mod (abs millis) 1000
instance Ord Duration where
(<=) (Duration d1) (Duration d2) = d1 <= d2
add :: Duration -> Duration -> Duration
add a b = Duration (toMilliseconds a + toMilliseconds b)
subtract :: Duration -> Duration -> Duration
subtract a b = Duration (toMilliseconds a - toMilliseconds b)
zero :: Duration
zero = Duration 0
hms :: Int -> Int -> Double -> Duration
hms h m s = milliseconds (fromIntegral h * 3600000 + fromIntegral m * 60000 + s * 1000)
hours :: Double -> Duration
hours h = milliseconds (h * 3600000)
minutes :: Double -> Duration
minutes m = milliseconds (m * 60000)
seconds :: Double -> Duration
seconds s = milliseconds (s * 1000)
milliseconds :: Double -> Duration
milliseconds ms = Duration (round ms)
toHours :: Duration -> Double
toHours (Duration ms) = fromIntegral ms / 3600000.0 :: Double
toMinutes :: Duration -> Double
toMinutes (Duration ms) = fromIntegral ms / 60000.0 :: Double
toSeconds :: Duration -> Double
toSeconds (Duration ms) = fromIntegral ms / 1000.0 :: Double
read :: String -> Maybe Duration
read s = readMaybe s :: (Maybe Duration)
duration :: ReadP Duration
duration = do
h <- option 0 hoursP
m <- option 0 minutesP
s <- option 0.0 secondsP
return (milliseconds (h * 3600000.0 + m * 60000.0 + s * 1000.0))
hoursP :: ReadP Double
hoursP = do
h <- integer
_ <- char 'H'
return (fromIntegral h :: Double)
minutesP :: ReadP Double
minutesP = do
m <- integer
_ <- char 'M'
return (fromIntegral m :: Double)
secondsP :: ReadP Double
secondsP = do
s <- number
_ <- char 'S'
return s