module Data.Geo.Jord.Duration
(
Duration
, toMilliseconds
, milliseconds
, hours
, minutes
, seconds
, hms
, toHours
, toMinutes
, toSeconds
, readDuration
, readDurationE
, readDurationF
) where
import Control.Monad.Fail
import Data.Geo.Jord.Parser
import Data.Geo.Jord.Quantity
import Prelude hiding (fail)
import Text.ParserCombinators.ReadP
import Text.Printf
import Text.Read hiding (pfail)
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 Quantity Duration where
add a b = Duration (toMilliseconds a + toMilliseconds b)
sub a b = Duration (toMilliseconds a - toMilliseconds b)
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
readDuration :: String -> Duration
readDuration s = read s :: Duration
readDurationE :: String -> Either String Duration
readDurationE s =
case readMaybe s of
Nothing -> Left ("couldn't read duration " ++ s)
Just l -> Right l
readDurationF :: (MonadFail m) => String -> m Duration
readDurationF s =
let p = readEither s
in case p of
Left e -> fail e
Right l -> return l
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 <- integer
ms <- option 0 (char '.' >> natural)
_ <- char 'S'
return (fromIntegral s + fromIntegral ms / 10.0)