{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Time.Types
(
NanoSeconds(..)
, Seconds(..)
, Minutes(..)
, Hours(..)
, TimeInterval(..)
, Month(..)
, WeekDay(..)
, TimezoneOffset(..)
, timezoneOffsetToSeconds
, timezone_UTC
, Elapsed(..)
, ElapsedP(..)
, Date(..)
, TimeOfDay(..)
, DateTime(..)
) where
import Data.Int
import Data.Data
import Data.Ratio
import Control.DeepSeq
import Data.Hourglass.Utils (pad2)
class TimeInterval i where
toSeconds :: i -> Seconds
fromSeconds :: Seconds -> (i, Seconds)
newtype NanoSeconds = NanoSeconds Int64
deriving (Read,Eq,Ord,Num,Data,Typeable,NFData)
instance Show NanoSeconds where
show (NanoSeconds v) = shows v "ns"
instance TimeInterval NanoSeconds where
toSeconds (NanoSeconds ns) = Seconds (ns `div` 1000000000)
fromSeconds (Seconds s) = (NanoSeconds (s * 1000000000), 0)
newtype Seconds = Seconds Int64
deriving (Read,Eq,Ord,Enum,Num,Real,Integral,Data,Typeable,NFData)
instance Show Seconds where
show (Seconds s) = shows s "s"
instance TimeInterval Seconds where
toSeconds = id
fromSeconds s = (s,0)
newtype Minutes = Minutes Int64
deriving (Read,Eq,Ord,Enum,Num,Real,Integral,Data,Typeable,NFData)
instance Show Minutes where
show (Minutes s) = shows s "m"
instance TimeInterval Minutes where
toSeconds (Minutes m) = Seconds (m * 60)
fromSeconds (Seconds s) = (Minutes m, Seconds s')
where (m, s') = s `divMod` 60
newtype Hours = Hours Int64
deriving (Read,Eq,Ord,Enum,Num,Real,Integral,Data,Typeable,NFData)
instance Show Hours where
show (Hours s) = shows s "h"
instance TimeInterval Hours where
toSeconds (Hours h) = Seconds (h * 3600)
fromSeconds (Seconds s) = (Hours h, Seconds s')
where (h, s') = s `divMod` 3600
newtype Elapsed = Elapsed Seconds
deriving (Read,Eq,Ord,Num,Data,Typeable,NFData)
instance Show Elapsed where
show (Elapsed s) = show s
data ElapsedP = ElapsedP {-# UNPACK #-} !Elapsed {-# UNPACK #-} !NanoSeconds
deriving (Read,Eq,Ord,Data,Typeable)
instance Show ElapsedP where
show (ElapsedP e ns) = shows e ('.' : show ns)
instance NFData ElapsedP where rnf e = e `seq` ()
instance Num ElapsedP where
(+) = addElapsedP
(-) = subElapsedP
(ElapsedP e1 ns1) * (ElapsedP e2 ns2) = ElapsedP (e1*e2) (ns1*ns2)
negate (ElapsedP e ns) = ElapsedP (negate e) ns
abs (ElapsedP e ns) = ElapsedP (abs e) ns
signum (ElapsedP e ns) = ElapsedP (signum e) ns
fromInteger i = ElapsedP (Elapsed (fromIntegral i)) 0
addElapsedP :: ElapsedP -> ElapsedP -> ElapsedP
addElapsedP (ElapsedP e1 (NanoSeconds ns1)) (ElapsedP e2 (NanoSeconds ns2)) =
let notNormalizedNS = ns1 + ns2
(retainedNS, ns) = notNormalizedNS `divMod` 1000000000
in ElapsedP (e1 + e2 + (Elapsed $ Seconds retainedNS)) (NanoSeconds ns)
subElapsedP :: ElapsedP -> ElapsedP -> ElapsedP
subElapsedP (ElapsedP e1 (NanoSeconds ns1)) (ElapsedP e2 (NanoSeconds ns2)) =
let notNormalizedNS = ns1 - ns2
notNormalizedS = e1 - e2
in if notNormalizedNS < 0
then ElapsedP (notNormalizedS - oneSecond) (NanoSeconds (1000000000 + notNormalizedNS))
else ElapsedP notNormalizedS (NanoSeconds notNormalizedNS)
where
oneSecond :: Elapsed
oneSecond = Elapsed $ Seconds 1
instance Real ElapsedP where
toRational (ElapsedP (Elapsed (Seconds s)) (NanoSeconds 0)) =
fromIntegral s
toRational (ElapsedP (Elapsed (Seconds s)) (NanoSeconds ns)) =
fromIntegral s + (fromIntegral ns % 1000000000)
data Month =
January
| February
| March
| April
| May
| June
| July
| August
| September
| October
| November
| December
deriving (Show,Read,Eq,Ord,Enum,Data,Typeable,Bounded)
data WeekDay =
Sunday
| Monday
| Tuesday
| Wednesday
| Thursday
| Friday
| Saturday
deriving (Show,Read,Eq,Ord,Enum,Data,Typeable,Bounded)
newtype TimezoneOffset = TimezoneOffset
{ timezoneOffsetToMinutes :: Int
} deriving (Eq,Ord,Data,Typeable,NFData)
timezoneOffsetToSeconds :: TimezoneOffset -> Seconds
timezoneOffsetToSeconds (TimezoneOffset ofs) = Seconds (fromIntegral ofs * 60)
instance Show TimezoneOffset where
show (TimezoneOffset tz) =
concat [if tz < 0 then "-" else "+", pad2 tzH, pad2 tzM]
where (tzH, tzM) = abs tz `divMod` 60
timezone_UTC :: TimezoneOffset
timezone_UTC = TimezoneOffset 0
data Date = Date
{ dateYear :: {-# UNPACK #-} !Int
, dateMonth :: !Month
, dateDay :: {-# UNPACK #-} !Int
} deriving (Show,Read,Eq,Ord,Data,Typeable)
instance NFData Date where
rnf (Date y m d) = y `seq` m `seq` d `seq` ()
data TimeOfDay = TimeOfDay
{ todHour :: {-# UNPACK #-} !Hours
, todMin :: {-# UNPACK #-} !Minutes
, todSec :: {-# UNPACK #-} !Seconds
, todNSec :: {-# UNPACK #-} !NanoSeconds
} deriving (Show,Read,Eq,Ord,Data,Typeable)
instance NFData TimeOfDay where
rnf (TimeOfDay h m s ns) = h `seq` m `seq` s `seq` ns `seq` ()
data DateTime = DateTime
{ dtDate :: Date
, dtTime :: TimeOfDay
} deriving (Show,Read,Eq,Ord,Data,Typeable)
instance NFData DateTime where
rnf (DateTime d t) = rnf d `seq` rnf t `seq` ()