module Data.Time.Exts.Unix (
UnixDate(..)
, UnixDateTime(..)
, UnixDateTimeNanos(..)
, createUnixDate
, createUnixDateTime
, createUnixDateTimeNanos
, getCurrentUnixDate
, getCurrentUnixDateTime
, getCurrentUnixDateTimeNanos
, parseUnixDate
, parseUnixDateTime
, parseUnixDateTimeNanos
) where
import Control.Arrow ((***), first)
import Control.DeepSeq (NFData)
import Data.Data (Data, Typeable)
import Data.Int (Int32, Int64)
import Data.Text (Text)
import Foreign.C.Time (C'timeval(..), getTimeOfDay)
import Foreign.C.Types (CLong(..))
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.Util
newtype UnixDate (cal :: Calendar) = UnixDate Int32
deriving (Data, Eq, Generic, NFData, Ord, Storable, Typeable)
newtype UnixDateTime (cal :: Calendar) = UnixDateTime Int64
deriving (Data, Eq, Generic, NFData, Ord, Storable, Typeable)
data UnixDateTimeNanos (cal :: Calendar) = UnixDateTimeNanos !Int64 !Int32
deriving (Data, Eq, Generic, Ord, Typeable)
instance Bounded (UnixDate 'Gregorian) where
minBound = UnixDate 0
maxBound = UnixDate 2932896
instance Bounded (UnixDateTime 'Gregorian) where
minBound = UnixDateTime 0
maxBound = UnixDateTime 253402300799
instance Bounded (UnixDateTimeNanos 'Gregorian) where
minBound = UnixDateTimeNanos 0 0
maxBound = UnixDateTimeNanos 253402300799 999999999
instance Enum (UnixDate 'Gregorian) where
succ = flip plus (Day 1)
pred = flip plus ( Day 1)
fromEnum (UnixDate base) = fromIntegral base
toEnum base =
if minBound <= date && date <= maxBound then date
else error "toEnum{UnixDate 'Gregorian}: out of bounds"
where date = UnixDate $ fromIntegral base
instance Enum (UnixDateTime 'Gregorian) where
succ = flip plus (Second 1)
pred = flip plus ( Second 1)
fromEnum (UnixDateTime base) = fromIntegral base
toEnum base =
if minBound <= time && time <= maxBound then time
else error "toEnum{UnixDateTime 'Gregorian}: out of bounds"
where time = UnixDateTime $ fromIntegral base
instance Human (UnixDate 'Gregorian) where
type Components (UnixDate 'Gregorian) = DateStruct 'Gregorian
pack DateStruct {..} =
createUnixDate _d_year _d_mon _d_mday
unpack (UnixDate base) =
rec 1970 (Day base) where
rec !year !day =
if day >= size
then rec (year + 1) (day size)
else DateStruct year mon mday wday
where
wday = toEnum (1 + mod (fromIntegral base + 4) 7)
leap = isLeapYear year
size = if leap then 366 else 365
(mon, mday) =
if leap
then if day >= 182
then if day >= 274
then if day >= 335
then (December, day 334)
else if day >= 305
then (November, day 304)
else (October, day 273)
else if day >= 244
then (September, day 243)
else if day >= 213
then (August, day 212)
else (July, day 181)
else if day >= 091
then if day >= 152
then (June, day 151)
else if day >= 121
then (May, day 120)
else (April, day 090)
else if day >= 060
then (March, day 059)
else if day >= 031
then (February, day 030)
else (January, day + 001)
else if day >= 181
then if day >= 273
then if day >= 334
then (December, day 333)
else if day >= 304
then (November, day 303)
else (October, day 272)
else if day >= 243
then (September, day 242)
else if day >= 212
then (August, day 211)
else (July, day 180)
else if day >= 090
then if day >= 151
then (June, day 150)
else if day >= 120
then (May, day 119)
else (April, day 089)
else if day >= 059
then (March, day 058)
else if day >= 031
then (February, day 030)
else (January, day + 001)
instance Human (UnixDateTime 'Gregorian) where
type Components (UnixDateTime 'Gregorian) = DateTimeStruct 'Gregorian
pack DateTimeStruct {..} =
createUnixDateTime _dt_year _dt_mon _dt_mday _dt_hour _dt_min sec
where sec = round _dt_sec
unpack (UnixDateTime base) =
DateTimeStruct _d_year _d_mon _d_mday _d_wday hour min sec where
DateStruct {..} = unpack (UnixDate day :: UnixDate 'Gregorian)
(day, hms) = fromIntegral *** fromIntegral $ divMod base 86400
(hour, ms) = fromIntegral <$> divMod hms 3600
(min, sec) = realToFrac <$> divMod ms 0060
instance Human (UnixDateTimeNanos 'Gregorian) where
type Components (UnixDateTimeNanos 'Gregorian) = DateTimeStruct 'Gregorian
pack DateTimeStruct {..} =
createUnixDateTimeNanos _dt_year _dt_mon _dt_mday _dt_hour _dt_min sec nsec
where (sec, nsec) = properFracNanos _dt_sec
unpack (UnixDateTimeNanos base nsec) =
over dt_sec (+ frac) $ unpack time
where time = UnixDateTime base :: UnixDateTime 'Gregorian
frac = realToFrac nsec / 1000000000
instance Math (UnixDate 'Gregorian) Day where
duration (UnixDate old) (UnixDate new) = fromIntegral (new old)
plus (UnixDate base) days =
if minBound <= date && date <= maxBound then date
else error "plus{UnixDate 'Gregorian, Day}: out of bounds"
where date = UnixDate (base + fromIntegral days)
instance Math (UnixDateTime 'Gregorian) Day where
duration (UnixDateTime old) (UnixDateTime new) = fromIntegral (div (new old) 86400)
plus (UnixDateTime base) days =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTime 'Gregorian, Day}: out of bounds"
where time = UnixDateTime (base + fromIntegral days * 86400)
instance Math (UnixDateTime 'Gregorian) Hour where
duration (UnixDateTime old) (UnixDateTime new) = fromIntegral (div (new old) 3600)
plus (UnixDateTime base) hours =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTime 'Gregorian, Hour}: out of bounds"
where time = UnixDateTime (base + fromIntegral hours * 3600)
instance Math (UnixDateTime 'Gregorian) Minute where
duration (UnixDateTime old) (UnixDateTime new) = fromIntegral (div (new old) 60)
plus (UnixDateTime base) minutes =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTime 'Gregorian, Minute}: out of bounds"
where time = UnixDateTime (base + fromIntegral minutes * 60)
instance Math (UnixDateTime 'Gregorian) Second where
duration (UnixDateTime old) (UnixDateTime new) = fromIntegral (new old)
plus (UnixDateTime base) seconds =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTime 'Gregorian, Second}: out of bounds"
where time = UnixDateTime (base + fromIntegral seconds)
instance Math (UnixDateTimeNanos 'Gregorian) Day where
duration (UnixDateTimeNanos old _) (UnixDateTimeNanos new _) = fromIntegral (div (new old) 86400)
plus (UnixDateTimeNanos base nsec) days =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTimeNanos 'Gregorian, Day}: out of bounds"
where time = UnixDateTimeNanos (base + fromIntegral days * 86400) nsec
instance Math (UnixDateTimeNanos 'Gregorian) Hour where
duration (UnixDateTimeNanos old _) (UnixDateTimeNanos new _) = fromIntegral (div (new old) 3600)
plus (UnixDateTimeNanos base nsec) hours =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTimeNanos 'Gregorian, Hour}: out of bounds"
where time = UnixDateTimeNanos (base + fromIntegral hours * 3600) nsec
instance Math (UnixDateTimeNanos 'Gregorian) Minute where
duration (UnixDateTimeNanos old _) (UnixDateTimeNanos new _) = fromIntegral (div (new old) 60)
plus (UnixDateTimeNanos base nsec) minutes =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTimeNanos 'Gregorian, Minute}: out of bounds"
where time = UnixDateTimeNanos (base + fromIntegral minutes * 60) nsec
instance Math (UnixDateTimeNanos 'Gregorian) Second where
duration (UnixDateTimeNanos old _) (UnixDateTimeNanos new _) = fromIntegral (new old)
plus (UnixDateTimeNanos base nsec) seconds =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTimeNanos 'Gregorian, Second}: out of bounds"
where time = UnixDateTimeNanos (base + fromIntegral seconds) nsec
instance Math (UnixDateTimeNanos 'Gregorian) Millis where
duration old new = fold new fold old
where fold (UnixDateTimeNanos base nsec) =
fromIntegral base * 1000 + fromIntegral (div nsec 1000000)
plus (UnixDateTimeNanos base nsec) millis =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTimeNanos 'Gregorian, Millis}: out of bounds"
where nsum = fromIntegral nsec + fromIntegral millis * 1000000
time = uncurry UnixDateTimeNanos ((***) (+ base) fromIntegral (divMod nsum 1000000000))
instance Math (UnixDateTimeNanos 'Gregorian) Micros where
duration old new = fold new fold old
where fold (UnixDateTimeNanos base nsec) =
fromIntegral base * 1000000 + fromIntegral (div nsec 1000)
plus (UnixDateTimeNanos base nsec) micros =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTimeNanos 'Gregorian, Micros}: out of bounds"
where nsum = fromIntegral nsec + fromIntegral micros * 1000
time = uncurry UnixDateTimeNanos ((***) (+ base) fromIntegral (divMod nsum 1000000000))
instance Math (UnixDateTimeNanos 'Gregorian) Nanos where
duration old new =
if toInteger (minBound :: Int64) <= res &&
toInteger (maxBound :: Int64) >= res then fromInteger res
else error "duration{UnixDateTimeNanos 'Gregorian, Nanos}: integer overflow"
where res = fold new fold old
fold (UnixDateTimeNanos base nsec) =
toInteger base * 1000000000 + toInteger nsec
plus (UnixDateTimeNanos base nsec) nanos =
if minBound <= time && time <= maxBound then time
else error "plus{UnixDateTimeNanos 'Gregorian, Nanos}: out of bounds"
where nsum = fromIntegral nsec + fromIntegral nanos
time = uncurry UnixDateTimeNanos ((***) (+ base) fromIntegral (divMod nsum 1000000000))
instance NFData (UnixDateTimeNanos cal)
instance Random (UnixDate 'Gregorian) where
random = first toEnum . randomR (fromEnum a, fromEnum b)
where a = minBound :: UnixDate 'Gregorian
b = maxBound :: UnixDate 'Gregorian
randomR (a, b) = first toEnum . randomR (fromEnum a, fromEnum b)
instance Random (UnixDateTime 'Gregorian) where
random = first toEnum . randomR (fromEnum a, fromEnum b)
where a = minBound :: UnixDateTime 'Gregorian
b = maxBound :: UnixDateTime 'Gregorian
randomR (a, b) = first toEnum . randomR (fromEnum a, fromEnum b)
instance Random (UnixDateTimeNanos 'Gregorian) where
random = first toNano . randomR (fromNano a, fromNano b)
where a = minBound :: UnixDateTimeNanos 'Gregorian
b = maxBound :: UnixDateTimeNanos 'Gregorian
randomR (a, b) = first toNano . randomR (fromNano a, fromNano b)
instance Show (UnixDate 'Gregorian) where
show (unpack -> DateStruct {..}) =
printf "%.3s %.3s %02d %4d" (show _d_wday) (show _d_mon) _d_mday _d_year
instance Show (UnixDateTime 'Gregorian) where
show (unpack -> DateTimeStruct {..}) =
printf "%02d:%02d:%02d %s %.3s %.3s %02d %4d" 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 (UnixDateTimeNanos 'Gregorian) where
show (unpack -> DateTimeStruct {..}) =
printf "%02d:%02d:%02d.%09d %s %.3s %.3s %02d %4d" 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 (UnixDateTimeNanos 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 $! UnixDateTimeNanos base nsec
pokeElemOff ptr n (UnixDateTimeNanos base nsec) = do
let off = 12 * n
poke (plusPtr ptr (off + 0)) base
poke (plusPtr ptr (off + 8)) nsec
createUnixDate
:: Year
-> Month 'Gregorian
-> Day
-> UnixDate 'Gregorian
createUnixDate year mon mday =
if (minBound :: UnixDate 'Gregorian) <= date && date <= (maxBound :: UnixDate 'Gregorian) then date
else error "createUnixDate: out of bounds"
where Day base = unsafeEpochToDate year mon mday
date = UnixDate base
createUnixDateTime
:: Year
-> Month 'Gregorian
-> Day
-> Hour
-> Minute
-> Second
-> UnixDateTime 'Gregorian
createUnixDateTime year mon mday hour min sec =
if (minBound :: UnixDateTime 'Gregorian) <= time && time <= (maxBound :: UnixDateTime 'Gregorian) then time
else error "createUnixDateTime: out of bounds"
where Second base = unsafeEpochToDateTime year mon mday hour min sec
time = UnixDateTime base
createUnixDateTimeNanos
:: Year
-> Month 'Gregorian
-> Day
-> Hour
-> Minute
-> Second
-> Nanos
-> UnixDateTimeNanos 'Gregorian
createUnixDateTimeNanos year mon mday hour min sec nanos =
if (minBound :: UnixDateTimeNanos 'Gregorian) <= time && time <= (maxBound :: UnixDateTimeNanos 'Gregorian) then time
else error "createUnixDateTimeNanos: out of bounds"
where Second base = unsafeEpochToDateTime year mon mday hour min sec
nsum = fromIntegral nanos
time = uncurry UnixDateTimeNanos ((***) (+ base) fromIntegral (divMod nsum 1000000000))
getCurrentUnixDate :: IO (UnixDate 'Gregorian)
getCurrentUnixDate =
getTimeOfDay >>= \ (C'timeval (CLong base) _) ->
return $! UnixDate (fromIntegral (div base 86400))
getCurrentUnixDateTime :: IO (UnixDateTime 'Gregorian)
getCurrentUnixDateTime =
getTimeOfDay >>= \ (C'timeval (CLong base) _) ->
return $! UnixDateTime base
getCurrentUnixDateTimeNanos :: IO (UnixDateTimeNanos 'Gregorian)
getCurrentUnixDateTimeNanos =
getTimeOfDay >>= \ (C'timeval (CLong base) (CLong usec)) ->
return $! UnixDateTimeNanos base (fromIntegral usec * 1000)
parseUnixDate
:: TimeLocale
-> Format
-> Text
-> Either String (UnixDate 'Gregorian)
parseUnixDate locale format input =
build <$> runParser locale Nothing defaultParserState format input
where build ParserState {..} =
createUnixDate _ps_year _ps_mon _ps_mday
parseUnixDateTime
:: TimeLocale
-> Format
-> Text
-> Either String (UnixDateTime 'Gregorian)
parseUnixDateTime locale format input =
build <$> runParser locale Nothing defaultParserState format input
where build ParserState {..} =
createUnixDateTime _ps_year _ps_mon _ps_mday hour _ps_min sec
where hour = _ps_ampm _ps_hour
sec = truncate _ps_sec
parseUnixDateTimeNanos
:: TimeLocale
-> Format
-> Text
-> Either String (UnixDateTimeNanos 'Gregorian)
parseUnixDateTimeNanos locale format input =
build <$> runParser locale Nothing defaultParserState format input
where build ParserState {..} =
createUnixDateTimeNanos _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 -> UnixDateTimeNanos 'Gregorian
toNano = uncurry UnixDateTimeNanos . (***) fromInteger fromInteger . flip divMod 1000000000
fromNano :: UnixDateTimeNanos 'Gregorian -> Integer
fromNano (UnixDateTimeNanos base nsec) = toInteger base * 1000000000 + toInteger nsec
isLeapYear :: Year -> Bool
isLeapYear year = mod year 400 == 0 || (mod year 100 /= 0 && mod year 4 == 0)
unsafeEpochToYear :: Year -> Day
unsafeEpochToYear Year {..} = Day (365 * (getYear 1970) + div (getYear 1969) 004 div (getYear 1901) 100 + div (getYear 1601) 400)
unsafeEpochToDate :: Year -> Month 'Gregorian -> Day -> Day
unsafeEpochToDate year mon mday =
unsafeEpochToYear year + yearToMonth leap mon + mday 1
where leap = isLeapYear year
unsafeEpochToDateTime :: Year -> Month 'Gregorian -> Day -> Hour -> Minute -> Second -> Second
unsafeEpochToDateTime year mon mday hour min sec =
fromIntegral day * 86400 + fromIntegral hour * 3600 + fromIntegral min * 60 + sec
where day = unsafeEpochToDate year mon mday
yearToMonth :: Bool -> Month 'Gregorian -> Day
yearToMonth leap =
if leap
then \ case
January -> 000
February -> 031
March -> 060
April -> 091
May -> 121
June -> 152
July -> 182
August -> 213
September -> 244
October -> 274
November -> 305
December -> 335
else \ case
January -> 000
February -> 031
March -> 059
April -> 090
May -> 120
June -> 151
July -> 181
August -> 212
September -> 243
October -> 273
November -> 304
December -> 334