module Data.Time.Exts.UTC (
UTCDate(..)
, UTCDateTime(..)
, UTCDateTimeNanos(..)
, createUTCDate
, createUTCDateTime
, createUTCDateTimeNanos
, getCurrentUTCDate
, getCurrentUTCDateTime
, getCurrentUTCDateTimeNanos
, parseUTCDate
, parseUTCDateTime
, parseUTCDateTimeNanos
) where
import Control.Arrow ((***), first)
import Control.DeepSeq (NFData)
import Control.Monad (join)
import Data.Data (Data, Typeable)
import Data.Int (Int32, Int64)
import Data.Text (Text)
import Data.Time.Zones (utcTZ)
import Foreign.Ptr (plusPtr)
import Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Lens.Simple (over)
import System.Locale (TimeLocale)
import System.Random (Random(..))
import Text.Printf (printf)
import Data.Time.Exts.Base
import Data.Time.Exts.Format
import Data.Time.Exts.Lens
import Data.Time.Exts.Parser
import Data.Time.Exts.Unix
import Data.Time.Exts.Util
newtype UTCDate cal = UTCDate (UnixDate cal)
deriving (Data, Eq, Generic, NFData, Ord, Storable, Typeable)
newtype UTCDateTime (cal :: Calendar) = UTCDateTime Int64
deriving (Data, Eq, Generic, NFData, Ord, Storable, Typeable)
data UTCDateTimeNanos (cal :: Calendar) = UTCDateTimeNanos !Int64 !Int32
deriving (Data, Eq, Generic, Ord, Typeable)
deriving instance Bounded (UTCDate 'Gregorian)
instance Bounded (UTCDateTime 'Gregorian) where
minBound = UTCDateTime 0
maxBound = UTCDateTime 253402300827
instance Bounded (UTCDateTimeNanos 'Gregorian) where
minBound = UTCDateTimeNanos 0 0
maxBound = UTCDateTimeNanos 253402300827 999999999
deriving instance Enum (UTCDate 'Gregorian)
instance Enum (UTCDateTime 'Gregorian) where
succ = flip plus (Second 1)
pred = flip plus ( Second 1)
fromEnum (UTCDateTime base) = fromIntegral base
toEnum base =
if minBound <= time && time <= maxBound then time
else error "toEnum{UTCDateTime 'Gregorian}: out of bounds"
where time = UTCDateTime $ fromIntegral base
instance Human (UTCDate 'Gregorian) where
type Components (UTCDate 'Gregorian) = DateStruct 'Gregorian
pack DateStruct {..} =
createUTCDate _d_year _d_mon _d_mday
unpack (UTCDate date) = unpack date
instance Human (UTCDateTime 'Gregorian) where
type Components (UTCDateTime 'Gregorian) = DateTimeStruct 'Gregorian
pack DateTimeStruct {..} =
createUTCDateTime _dt_year _dt_mon _dt_mday _dt_hour _dt_min sec
where sec = round _dt_sec
unpack (UTCDateTime base) =
over dt_sec (+ leap) (unpack time)
where time = UnixDateTime unix :: UnixDateTime 'Gregorian
(,) unix leap = baseUTCToUnix base
instance Human (UTCDateTimeNanos 'Gregorian) where
type Components (UTCDateTimeNanos 'Gregorian) = DateTimeStruct 'Gregorian
pack DateTimeStruct {..} =
createUTCDateTimeNanos _dt_year _dt_mon _dt_mday _dt_hour _dt_min sec nsec
where (,) sec nsec = properFracNanos _dt_sec
unpack (UTCDateTimeNanos base nsec) =
over dt_sec (+ leap) (unpack time)
where time = UnixDateTimeNanos unix nsec :: UnixDateTimeNanos 'Gregorian
(,) unix leap = baseUTCToUnix base
instance Math (UTCDate 'Gregorian) Day where
duration (UTCDate old) (UTCDate new) = duration old new
plus (UTCDate date) days = UTCDate (plus date days)
instance Math (UTCDateTime 'Gregorian) Second where
duration (UTCDateTime old) (UTCDateTime new) = fromIntegral (new old)
plus (UTCDateTime base) seconds =
if minBound <= time && time <= maxBound then time
else error "plus{UTCDateTime 'Gregorian, Second}: out of bounds"
where time = UTCDateTime (base + fromIntegral seconds)
instance Math (UTCDateTimeNanos 'Gregorian) Second where
duration (UTCDateTimeNanos old _) (UTCDateTimeNanos new _) = fromIntegral (new old)
plus (UTCDateTimeNanos base nsec) seconds =
if minBound <= time && time <= maxBound then time
else error "plus{UTCDateTimeNanos 'Gregorian, Second}: out of bounds"
where time = UTCDateTimeNanos (base + fromIntegral seconds) nsec
instance Math (UTCDateTimeNanos 'Gregorian) Millis where
duration old new = fold new fold old
where fold (UTCDateTimeNanos base nsec) =
fromIntegral base * 1000 + fromIntegral (div nsec 1000000)
plus (UTCDateTimeNanos base nsec) millis =
if minBound <= time && time <= maxBound then time
else error "plus{UTCDateTimeNanos 'Gregorian, Millis}: out of bounds"
where nsum = fromIntegral nsec + fromIntegral millis * 1000000
time = uncurry UTCDateTimeNanos ((***) (+ base) fromIntegral (divMod nsum 1000000000))
instance Math (UTCDateTimeNanos 'Gregorian) Micros where
duration old new = fold new fold old
where fold (UTCDateTimeNanos base nsec) =
fromIntegral base * 1000000 + fromIntegral (div nsec 1000)
plus (UTCDateTimeNanos base nsec) micros =
if minBound <= time && time <= maxBound then time
else error "plus{UTCDateTimeNanos 'Gregorian, Micros}: out of bounds"
where nsum = fromIntegral nsec + fromIntegral micros * 1000
time = uncurry UTCDateTimeNanos ((***) (+ base) fromIntegral (divMod nsum 1000000000))
instance Math (UTCDateTimeNanos 'Gregorian) Nanos where
duration old new =
if toInteger (minBound :: Int64) <= res &&
toInteger (maxBound :: Int64) >= res then fromInteger res
else error "duration{UTCDateTimeNanos 'Gregorian, Nanos}: integer overflow"
where res = fold new fold old
fold (UTCDateTimeNanos base nsec) =
toInteger base * 1000000000 + toInteger nsec
plus (UTCDateTimeNanos base nsec) nanos =
if minBound <= time && time <= maxBound then time
else error "plus{UTCDateTimeNanos 'Gregorian, Nanos}: out of bounds"
where nsum = fromIntegral nsec + fromIntegral nanos
time = uncurry UTCDateTimeNanos ((***) (+ base) fromIntegral (divMod nsum 1000000000))
instance NFData (UTCDateTimeNanos cal)
deriving instance Random (UTCDate 'Gregorian)
instance Random (UTCDateTime 'Gregorian) where
random = first toEnum . randomR (fromEnum a, fromEnum b)
where a = minBound :: UTCDateTime 'Gregorian
b = maxBound :: UTCDateTime 'Gregorian
randomR (a, b) = first toEnum . randomR (fromEnum a, fromEnum b)
instance Random (UTCDateTimeNanos 'Gregorian) where
random = first toNano . randomR (fromNano a, fromNano b)
where a = minBound :: UTCDateTimeNanos 'Gregorian
b = maxBound :: UTCDateTimeNanos 'Gregorian
randomR (a, b) = first toNano . randomR (fromNano a, fromNano b)
instance Show (UTCDate 'Gregorian) where
show (unpack -> DateStruct {..}) =
printf "%.3s %.3s %02d %4d UTC" wday mon _d_mday _d_year
where wday = show _d_wday
mon = show _d_mon
instance Show (UTCDateTime 'Gregorian) where
show (unpack -> DateTimeStruct {..}) =
printf "%02d:%02d:%02d %s %.3s %.3s %02d %4d UTC" hour _dt_min sec ampm wday mon _dt_mday _dt_year
where wday = show _dt_wday
mon = show _dt_mon
sec = round _dt_sec :: Second
(,) ampm hour = getPeriod _dt_hour
instance Show (UTCDateTimeNanos 'Gregorian) where
show (unpack -> DateTimeStruct {..}) =
printf "%02d:%02d:%02d.%09d %s %.3s %.3s %02d %4d UTC" hour _dt_min sec nsec ampm wday mon _dt_mday _dt_year
where wday = show _dt_wday
mon = show _dt_mon
(,) sec nsec = properFracNanos _dt_sec
(,) ampm hour = getPeriod _dt_hour
instance Storable (UTCDateTimeNanos cal) where
sizeOf = const 12
alignment = sizeOf
peekElemOff ptr n = do
let off = 12 * n
base <- peek (plusPtr ptr (off + 0))
nsec <- peek (plusPtr ptr (off + 8))
return $! UTCDateTimeNanos base nsec
pokeElemOff ptr n (UTCDateTimeNanos base nsec) = do
let off = 12 * n
poke (plusPtr ptr (off + 0)) base
poke (plusPtr ptr (off + 8)) nsec
createUTCDate
:: Year
-> Month 'Gregorian
-> Day
-> UTCDate 'Gregorian
createUTCDate year mon mday =
UTCDate $ createUnixDate year mon mday
createUTCDateTime
:: Year
-> Month 'Gregorian
-> Day
-> Hour
-> Minute
-> Second
-> UTCDateTime 'Gregorian
createUTCDateTime year mon mday hour min sec =
if (minBound :: UTCDateTime 'Gregorian) <= time && time <= (maxBound :: UTCDateTime 'Gregorian) then time
else error "createUTCDateTime: out of bounds"
where UnixDateTime unix = createUnixDateTime year mon mday hour min 0
time = UTCDateTime base
base = baseUnixToUTC unix + fromIntegral sec
createUTCDateTimeNanos
:: Year
-> Month 'Gregorian
-> Day
-> Hour
-> Minute
-> Second
-> Nanos
-> UTCDateTimeNanos 'Gregorian
createUTCDateTimeNanos year mon mday hour min sec nanos =
if (minBound :: UTCDateTimeNanos 'Gregorian) <= time && time <= (maxBound :: UTCDateTimeNanos 'Gregorian) then time
else error "createUTCDateTimeNanos: out of bounds"
where UnixDateTime unix = createUnixDateTime year mon mday hour min 0
time = UTCDateTimeNanos base nsec
base = baseUnixToUTC unix + fromIntegral sec + extra
(,) extra nsec = (***) fromIntegral fromIntegral (divMod nanos 1000000000)
getCurrentUTCDate :: IO (UTCDate 'Gregorian)
getCurrentUTCDate = UTCDate <$> getCurrentUnixDate
getCurrentUTCDateTime :: IO (UTCDateTime 'Gregorian)
getCurrentUTCDateTime = do
UnixDateTime unix <- getCurrentUnixDateTime
return $! UTCDateTime $ baseUnixToUTC unix
getCurrentUTCDateTimeNanos :: IO (UTCDateTimeNanos 'Gregorian)
getCurrentUTCDateTimeNanos = do
UnixDateTimeNanos unix nsec <- getCurrentUnixDateTimeNanos
let date = UnixDate (fromIntegral (div base 86400))
base = baseUnixToUTC unix
time = UTCDateTimeNanos base nsec
leap = round (11574.074074074073 * realToFrac (mod unix 86400) :: Double) :: Nanos
return $! case nextLeap of
Just ((==) date -> True) -> time `plus` leap
_ -> time
parseUTCDate
:: TimeLocale
-> Format
-> Text
-> Either String (UTCDate 'Gregorian)
parseUTCDate locale format input =
join $ build <$> runParser locale tzdata defaultParserState format input
where tzdata = Just utcTZ
build ParserState {..} = _ps_zone 0 *> do
return $! createUTCDate _ps_year _ps_mon _ps_mday
parseUTCDateTime
:: TimeLocale
-> Format
-> Text
-> Either String (UTCDateTime 'Gregorian)
parseUTCDateTime locale format input =
join $ build <$> runParser locale tzdata defaultParserState format input
where tzdata = Just utcTZ
build ParserState {..} = _ps_zone 0 *> do
return $! createUTCDateTime _ps_year _ps_mon _ps_mday hour _ps_min sec
where hour = _ps_ampm _ps_hour
sec = truncate _ps_sec
parseUTCDateTimeNanos
:: TimeLocale
-> Format
-> Text
-> Either String (UTCDateTimeNanos 'Gregorian)
parseUTCDateTimeNanos locale format input =
join $ build <$> runParser locale tzdata defaultParserState format input
where tzdata = Just utcTZ
build ParserState {..} = _ps_zone 0 *> do
return $! createUTCDateTimeNanos _ps_year _ps_mon _ps_mday hour _ps_min sec nsec
where hour = _ps_ampm _ps_hour
(,) sec nsec = properFracNanos $ _ps_frac _ps_sec
toNano :: Integer -> UTCDateTimeNanos 'Gregorian
toNano = uncurry UTCDateTimeNanos . (***) fromInteger fromInteger . flip divMod 1000000000
fromNano :: UTCDateTimeNanos 'Gregorian -> Integer
fromNano (UTCDateTimeNanos base nsec) = toInteger base * 1000000000 + toInteger nsec
nextLeap :: Maybe (UnixDate 'Gregorian)
nextLeap = Just (UnixDate 17166)