{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
-- |
-- Module      : Data.Hourglass.Diff
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : experimental
-- Portability : unknown
--
-- time arithmetic methods
--
module Data.Hourglass.Diff
    ( Duration(..)
    , Period(..)
    , durationNormalize
    , durationFlatten
    , elapsedTimeAddSeconds
    , elapsedTimeAddSecondsP
    , dateAddPeriod
    ) where

import Data.Data
import Data.Monoid
import Data.Hourglass.Types
import Data.Hourglass.Calendar
import Control.DeepSeq

-- | An amount of conceptual calendar time in terms of years, months and days.
--
-- This allow calendar manipulation, representing things like days and months
-- irrespective on how long those are related to timezone and daylight changes.
--
-- See 'Duration' for the time-based equivalent to this class.
data Period = Period
    { Period -> Int
periodYears  :: !Int
    , Period -> Int
periodMonths :: !Int
    , Period -> Int
periodDays   :: !Int
    } deriving (Int -> Period -> ShowS
[Period] -> ShowS
Period -> String
(Int -> Period -> ShowS)
-> (Period -> String) -> ([Period] -> ShowS) -> Show Period
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Period] -> ShowS
$cshowList :: [Period] -> ShowS
show :: Period -> String
$cshow :: Period -> String
showsPrec :: Int -> Period -> ShowS
$cshowsPrec :: Int -> Period -> ShowS
Show,ReadPrec [Period]
ReadPrec Period
Int -> ReadS Period
ReadS [Period]
(Int -> ReadS Period)
-> ReadS [Period]
-> ReadPrec Period
-> ReadPrec [Period]
-> Read Period
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Period]
$creadListPrec :: ReadPrec [Period]
readPrec :: ReadPrec Period
$creadPrec :: ReadPrec Period
readList :: ReadS [Period]
$creadList :: ReadS [Period]
readsPrec :: Int -> ReadS Period
$creadsPrec :: Int -> ReadS Period
Read,Period -> Period -> Bool
(Period -> Period -> Bool)
-> (Period -> Period -> Bool) -> Eq Period
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Period -> Period -> Bool
$c/= :: Period -> Period -> Bool
== :: Period -> Period -> Bool
$c== :: Period -> Period -> Bool
Eq,Eq Period
Eq Period
-> (Period -> Period -> Ordering)
-> (Period -> Period -> Bool)
-> (Period -> Period -> Bool)
-> (Period -> Period -> Bool)
-> (Period -> Period -> Bool)
-> (Period -> Period -> Period)
-> (Period -> Period -> Period)
-> Ord Period
Period -> Period -> Bool
Period -> Period -> Ordering
Period -> Period -> Period
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Period -> Period -> Period
$cmin :: Period -> Period -> Period
max :: Period -> Period -> Period
$cmax :: Period -> Period -> Period
>= :: Period -> Period -> Bool
$c>= :: Period -> Period -> Bool
> :: Period -> Period -> Bool
$c> :: Period -> Period -> Bool
<= :: Period -> Period -> Bool
$c<= :: Period -> Period -> Bool
< :: Period -> Period -> Bool
$c< :: Period -> Period -> Bool
compare :: Period -> Period -> Ordering
$ccompare :: Period -> Period -> Ordering
$cp1Ord :: Eq Period
Ord,Typeable Period
DataType
Constr
Typeable Period
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Period -> c Period)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Period)
-> (Period -> Constr)
-> (Period -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Period))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Period))
-> ((forall b. Data b => b -> b) -> Period -> Period)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Period -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Period -> r)
-> (forall u. (forall d. Data d => d -> u) -> Period -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Period -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Period -> m Period)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Period -> m Period)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Period -> m Period)
-> Data Period
Period -> DataType
Period -> Constr
(forall b. Data b => b -> b) -> Period -> Period
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Period -> c Period
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Period
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Period -> u
forall u. (forall d. Data d => d -> u) -> Period -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Period -> m Period
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Period -> m Period
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Period
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Period -> c Period
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Period)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Period)
$cPeriod :: Constr
$tPeriod :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Period -> m Period
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Period -> m Period
gmapMp :: (forall d. Data d => d -> m d) -> Period -> m Period
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Period -> m Period
gmapM :: (forall d. Data d => d -> m d) -> Period -> m Period
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Period -> m Period
gmapQi :: Int -> (forall d. Data d => d -> u) -> Period -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Period -> u
gmapQ :: (forall d. Data d => d -> u) -> Period -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Period -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r
gmapT :: (forall b. Data b => b -> b) -> Period -> Period
$cgmapT :: (forall b. Data b => b -> b) -> Period -> Period
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Period)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Period)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Period)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Period)
dataTypeOf :: Period -> DataType
$cdataTypeOf :: Period -> DataType
toConstr :: Period -> Constr
$ctoConstr :: Period -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Period
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Period
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Period -> c Period
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Period -> c Period
$cp1Data :: Typeable Period
Data,Typeable)

instance NFData Period where
    rnf :: Period -> ()
rnf (Period Int
y Int
m Int
d) = Int
y Int -> () -> ()
`seq` Int
m Int -> () -> ()
`seq` Int
d Int -> () -> ()
`seq` ()
#if (MIN_VERSION_base(4,11,0))
instance Semigroup Period where
    <> :: Period -> Period -> Period
(<>) (Period Int
y1 Int
m1 Int
d1) (Period Int
y2 Int
m2 Int
d2) =
        Int -> Int -> Int -> Period
Period (Int
y1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y2) (Int
m1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
m2) (Int
d1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
d2)
#endif
instance Monoid Period where
    mempty :: Period
mempty = Int -> Int -> Int -> Period
Period Int
0 Int
0 Int
0
    mappend :: Period -> Period -> Period
mappend (Period Int
y1 Int
m1 Int
d1) (Period Int
y2 Int
m2 Int
d2) =
        Int -> Int -> Int -> Period
Period (Int
y1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y2) (Int
m1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
m2) (Int
d1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
d2)

-- | An amount of time in terms of constant value like hours (3600 seconds),
-- minutes (60 seconds), seconds and nanoseconds.
data Duration = Duration
    { Duration -> Hours
durationHours   :: !Hours       -- ^ number of hours
    , Duration -> Minutes
durationMinutes :: !Minutes     -- ^ number of minutes
    , Duration -> Seconds
durationSeconds :: !Seconds     -- ^ number of seconds
    , Duration -> NanoSeconds
durationNs      :: !NanoSeconds -- ^ number of nanoseconds
    } deriving (Int -> Duration -> ShowS
[Duration] -> ShowS
Duration -> String
(Int -> Duration -> ShowS)
-> (Duration -> String) -> ([Duration] -> ShowS) -> Show Duration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Duration] -> ShowS
$cshowList :: [Duration] -> ShowS
show :: Duration -> String
$cshow :: Duration -> String
showsPrec :: Int -> Duration -> ShowS
$cshowsPrec :: Int -> Duration -> ShowS
Show,ReadPrec [Duration]
ReadPrec Duration
Int -> ReadS Duration
ReadS [Duration]
(Int -> ReadS Duration)
-> ReadS [Duration]
-> ReadPrec Duration
-> ReadPrec [Duration]
-> Read Duration
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Duration]
$creadListPrec :: ReadPrec [Duration]
readPrec :: ReadPrec Duration
$creadPrec :: ReadPrec Duration
readList :: ReadS [Duration]
$creadList :: ReadS [Duration]
readsPrec :: Int -> ReadS Duration
$creadsPrec :: Int -> ReadS Duration
Read,Duration -> Duration -> Bool
(Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool) -> Eq Duration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Duration -> Duration -> Bool
$c/= :: Duration -> Duration -> Bool
== :: Duration -> Duration -> Bool
$c== :: Duration -> Duration -> Bool
Eq,Eq Duration
Eq Duration
-> (Duration -> Duration -> Ordering)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Duration)
-> (Duration -> Duration -> Duration)
-> Ord Duration
Duration -> Duration -> Bool
Duration -> Duration -> Ordering
Duration -> Duration -> Duration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Duration -> Duration -> Duration
$cmin :: Duration -> Duration -> Duration
max :: Duration -> Duration -> Duration
$cmax :: Duration -> Duration -> Duration
>= :: Duration -> Duration -> Bool
$c>= :: Duration -> Duration -> Bool
> :: Duration -> Duration -> Bool
$c> :: Duration -> Duration -> Bool
<= :: Duration -> Duration -> Bool
$c<= :: Duration -> Duration -> Bool
< :: Duration -> Duration -> Bool
$c< :: Duration -> Duration -> Bool
compare :: Duration -> Duration -> Ordering
$ccompare :: Duration -> Duration -> Ordering
$cp1Ord :: Eq Duration
Ord,Typeable Duration
DataType
Constr
Typeable Duration
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Duration -> c Duration)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Duration)
-> (Duration -> Constr)
-> (Duration -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Duration))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration))
-> ((forall b. Data b => b -> b) -> Duration -> Duration)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Duration -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Duration -> r)
-> (forall u. (forall d. Data d => d -> u) -> Duration -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Duration -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Duration -> m Duration)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Duration -> m Duration)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Duration -> m Duration)
-> Data Duration
Duration -> DataType
Duration -> Constr
(forall b. Data b => b -> b) -> Duration -> Duration
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Duration -> c Duration
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Duration
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Duration -> u
forall u. (forall d. Data d => d -> u) -> Duration -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Duration
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Duration -> c Duration
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Duration)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration)
$cDuration :: Constr
$tDuration :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Duration -> m Duration
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
gmapMp :: (forall d. Data d => d -> m d) -> Duration -> m Duration
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
gmapM :: (forall d. Data d => d -> m d) -> Duration -> m Duration
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Duration -> m Duration
gmapQi :: Int -> (forall d. Data d => d -> u) -> Duration -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Duration -> u
gmapQ :: (forall d. Data d => d -> u) -> Duration -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Duration -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Duration -> r
gmapT :: (forall b. Data b => b -> b) -> Duration -> Duration
$cgmapT :: (forall b. Data b => b -> b) -> Duration -> Duration
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Duration)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Duration)
dataTypeOf :: Duration -> DataType
$cdataTypeOf :: Duration -> DataType
toConstr :: Duration -> Constr
$ctoConstr :: Duration -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Duration
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Duration
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Duration -> c Duration
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Duration -> c Duration
$cp1Data :: Typeable Duration
Data,Typeable)

instance NFData Duration where
    rnf :: Duration -> ()
rnf (Duration Hours
h Minutes
m Seconds
s NanoSeconds
ns) = Hours
h Hours -> () -> ()
`seq` Minutes
m Minutes -> () -> ()
`seq` Seconds
s Seconds -> () -> ()
`seq` NanoSeconds
ns NanoSeconds -> () -> ()
`seq` ()
#if (MIN_VERSION_base(4,11,0))
instance Semigroup Duration where
    <> :: Duration -> Duration -> Duration
(<>) (Duration Hours
h1 Minutes
m1 Seconds
s1 NanoSeconds
ns1) (Duration Hours
h2 Minutes
m2 Seconds
s2 NanoSeconds
ns2) =
        Hours -> Minutes -> Seconds -> NanoSeconds -> Duration
Duration (Hours
h1Hours -> Hours -> Hours
forall a. Num a => a -> a -> a
+Hours
h2) (Minutes
m1Minutes -> Minutes -> Minutes
forall a. Num a => a -> a -> a
+Minutes
m2) (Seconds
s1Seconds -> Seconds -> Seconds
forall a. Num a => a -> a -> a
+Seconds
s2) (NanoSeconds
ns1NanoSeconds -> NanoSeconds -> NanoSeconds
forall a. Num a => a -> a -> a
+NanoSeconds
ns2)
#endif
instance Monoid Duration where
    mempty :: Duration
mempty = Hours -> Minutes -> Seconds -> NanoSeconds -> Duration
Duration Hours
0 Minutes
0 Seconds
0 NanoSeconds
0
    mappend :: Duration -> Duration -> Duration
mappend (Duration Hours
h1 Minutes
m1 Seconds
s1 NanoSeconds
ns1) (Duration Hours
h2 Minutes
m2 Seconds
s2 NanoSeconds
ns2) =
        Hours -> Minutes -> Seconds -> NanoSeconds -> Duration
Duration (Hours
h1Hours -> Hours -> Hours
forall a. Num a => a -> a -> a
+Hours
h2) (Minutes
m1Minutes -> Minutes -> Minutes
forall a. Num a => a -> a -> a
+Minutes
m2) (Seconds
s1Seconds -> Seconds -> Seconds
forall a. Num a => a -> a -> a
+Seconds
s2) (NanoSeconds
ns1NanoSeconds -> NanoSeconds -> NanoSeconds
forall a. Num a => a -> a -> a
+NanoSeconds
ns2)
instance TimeInterval Duration where
    fromSeconds :: Seconds -> (Duration, Seconds)
fromSeconds Seconds
s = (Duration -> Duration
durationNormalize (Hours -> Minutes -> Seconds -> NanoSeconds -> Duration
Duration Hours
0 Minutes
0 Seconds
s NanoSeconds
0), Seconds
0)
    toSeconds :: Duration -> Seconds
toSeconds Duration
d   = (Seconds, NanoSeconds) -> Seconds
forall a b. (a, b) -> a
fst ((Seconds, NanoSeconds) -> Seconds)
-> (Seconds, NanoSeconds) -> Seconds
forall a b. (a -> b) -> a -> b
$ Duration -> (Seconds, NanoSeconds)
durationFlatten Duration
d

-- | Flatten a duration to a number of seconds, nanoseconds
durationFlatten :: Duration -> (Seconds, NanoSeconds)
durationFlatten :: Duration -> (Seconds, NanoSeconds)
durationFlatten (Duration Hours
h Minutes
m Seconds
s (NanoSeconds Int64
ns)) =
    (Hours -> Seconds
forall i. TimeInterval i => i -> Seconds
toSeconds Hours
h Seconds -> Seconds -> Seconds
forall a. Num a => a -> a -> a
+ Minutes -> Seconds
forall i. TimeInterval i => i -> Seconds
toSeconds Minutes
m Seconds -> Seconds -> Seconds
forall a. Num a => a -> a -> a
+ Seconds
s Seconds -> Seconds -> Seconds
forall a. Num a => a -> a -> a
+ Int64 -> Seconds
Seconds Int64
sacc, Int64 -> NanoSeconds
NanoSeconds Int64
ns')
  where (Int64
sacc, Int64
ns') = Int64
ns Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
1000000000

-- | Normalize all fields to represent the same value
-- with the biggest units possible.
--
-- For example, 62 minutes is normalized as 1h 2minutes
durationNormalize :: Duration -> Duration
durationNormalize :: Duration -> Duration
durationNormalize (Duration (Hours Int64
h) (Minutes Int64
mi) (Seconds Int64
s) (NanoSeconds Int64
ns)) =
    Hours -> Minutes -> Seconds -> NanoSeconds -> Duration
Duration (Int64 -> Hours
Hours (Int64
hInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int64
hacc)) (Int64 -> Minutes
Minutes Int64
mi') (Int64 -> Seconds
Seconds Int64
s') (Int64 -> NanoSeconds
NanoSeconds Int64
ns')
  where (Int64
hacc, Int64
mi') = (Int64
miInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int64
miacc) Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
60
        (Int64
miacc, Int64
s') = (Int64
sInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int64
sacc) Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
60
        (Int64
sacc, Int64
ns') = Int64
ns Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int64
1000000000

-- | add a period of time to a date
dateAddPeriod :: Date -> Period -> Date
dateAddPeriod :: Date -> Period -> Date
dateAddPeriod (Date Int
yOrig Month
mOrig Int
dOrig) (Period Int
yDiff Int
mDiff Int
dDiff) =
    Int -> Int -> Int -> Date
loop (Int
yOrig Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
yDiff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
yDiffAcc) Int
mStartPos (Int
dOrigInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
dDiff)
  where
    (Int
yDiffAcc,Int
mStartPos) = (Month -> Int
forall a. Enum a => a -> Int
fromEnum Month
mOrig Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
mDiff) Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int
12
    loop :: Int -> Int -> Int -> Date
loop Int
y Int
m Int
d
        | Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 =
            let (Int
m', Int
y') = if Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
                then (Int
11, Int
y Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
                else (Int
m Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1, Int
y)
            in
            Int -> Int -> Int -> Date
loop Int
y' Int
m' (Int -> Month -> Int
daysInMonth Int
y' (Int -> Month
forall a. Enum a => Int -> a
toEnum Int
m') Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
d)
        | Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
dMonth = Int -> Month -> Int -> Date
Date Int
y (Int -> Month
forall a. Enum a => Int -> a
toEnum Int
m) Int
d
        | Bool
otherwise  =
            let newDiff :: Int
newDiff = Int
d Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
dMonth
             in if Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
11
                    then Int -> Int -> Int -> Date
loop (Int
yInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
0 Int
newDiff
                    else Int -> Int -> Int -> Date
loop Int
y (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
newDiff
      where dMonth :: Int
dMonth = Int -> Month -> Int
daysInMonth Int
y (Int -> Month
forall a. Enum a => Int -> a
toEnum Int
m)

-- | Add a number of seconds to an Elapsed type
elapsedTimeAddSeconds :: Elapsed -> Seconds -> Elapsed
elapsedTimeAddSeconds :: Elapsed -> Seconds -> Elapsed
elapsedTimeAddSeconds (Elapsed Seconds
s1) Seconds
s2 = Seconds -> Elapsed
Elapsed (Seconds
s1Seconds -> Seconds -> Seconds
forall a. Num a => a -> a -> a
+Seconds
s2)

-- | Add a number of seconds to an ElapsedP type
elapsedTimeAddSecondsP :: ElapsedP -> Seconds -> ElapsedP
elapsedTimeAddSecondsP :: ElapsedP -> Seconds -> ElapsedP
elapsedTimeAddSecondsP (ElapsedP (Elapsed Seconds
s1) NanoSeconds
ns1) Seconds
s2 =
    Elapsed -> NanoSeconds -> ElapsedP
ElapsedP (Seconds -> Elapsed
Elapsed (Seconds
s1Seconds -> Seconds -> Seconds
forall a. Num a => a -> a -> a
+Seconds
s2)) NanoSeconds
ns1

{- disabled for warning purpose. to be implemented

-- | Duration string to time diff
--
-- <http://en.wikipedia.org/wiki/ISO_8601#Durations>
--
-- * P is the duration designator (historically called "period") placed at the start of the duration representation.
--
-- * Y is the year designator that follows the value for the number of years.
--
-- * M is the month designator that follows the value for the number of months.
--
-- * W is the week designator that follows the value for the number of weeks.
--
-- * D is the day designator that follows the value for the number of days.
--
-- * T is the time designator that precedes the time components of the representation.
--
-- * H is the hour designator that follows the value for the number of hours.
--
-- * M is the minute designator that follows the value for the number of minutes.
--
-- * S is the second designator that follows the value for the number of seconds.
--
timeDiffFromDuration :: String -> TimeDiff
timeDiffFromDuration _ = undefined

timeDiffFromString :: String -> (

-- | Human description string to time diff
--
-- examples:
--
-- * "1 day"
--
-- * "2 months, 5 days and 1 second"
--
timeDiffFromDescription :: String -> TimeDiff
timeDiffFromDescription _ = undefined
-}