module Z.IO.Time
(
SystemTime(..), getSystemTime'
, parseSystemTime, parseSystemTimeGMT
, formatSystemTime, formatSystemTimeGMT
, TimeFormat, simpleDateFormat, iso8061DateFormat, webDateFormat, mailDateFormat
) where
import Data.Time.Clock.System
import Data.Word
import Data.Int
import Foreign.C.Types
import Z.Foreign
import Z.Data.CBytes
import Z.IO.UV.FFI_Env
import Z.IO.Exception
import System.IO.Unsafe (unsafePerformIO)
getSystemTime' :: HasCallStack => IO SystemTime
getSystemTime' :: IO SystemTime
getSystemTime' = do
(TimeVal64 Int64
s Int32
us) <- IO TimeVal64
HasCallStack => IO TimeVal64
getTimeOfDay
SystemTime -> IO SystemTime
forall (m :: * -> *) a. Monad m => a -> m a
return (Int64 -> Word32 -> SystemTime
MkSystemTime Int64
s (Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
us Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
* Word32
1000))
type TimeFormat = CBytes
simpleDateFormat :: TimeFormat
simpleDateFormat :: TimeFormat
simpleDateFormat = TimeFormat
"%Y-%m-%d %H:%M:%S"
iso8061DateFormat :: TimeFormat
iso8061DateFormat :: TimeFormat
iso8061DateFormat = TimeFormat
"%Y-%m-%dT%H:%M:%S%z"
webDateFormat :: TimeFormat
webDateFormat :: TimeFormat
webDateFormat = TimeFormat
"%a, %d %b %Y %H:%M:%S GMT"
mailDateFormat :: TimeFormat
mailDateFormat :: TimeFormat
mailDateFormat = TimeFormat
"%a, %d %b %Y %H:%M:%S %z"
formatSystemTime :: TimeFormat -> SystemTime -> IO CBytes
formatSystemTime :: TimeFormat -> SystemTime -> IO TimeFormat
formatSystemTime TimeFormat
fmt SystemTime
t = (BA# Word8 -> Int64 -> MBA# Word8 -> CInt -> IO CSize)
-> TimeFormat -> SystemTime -> IO TimeFormat
formatSystemTimeHelper BA# Word8 -> Int64 -> MBA# Word8 -> CInt -> IO CSize
c_format_unix_time TimeFormat
fmt SystemTime
t
{-# INLINE formatSystemTime #-}
formatSystemTimeGMT :: TimeFormat -> SystemTime -> CBytes
formatSystemTimeGMT :: TimeFormat -> SystemTime -> TimeFormat
formatSystemTimeGMT TimeFormat
fmt SystemTime
t =
IO TimeFormat -> TimeFormat
forall a. IO a -> a
unsafePerformIO (IO TimeFormat -> TimeFormat) -> IO TimeFormat -> TimeFormat
forall a b. (a -> b) -> a -> b
$ (BA# Word8 -> Int64 -> MBA# Word8 -> CInt -> IO CSize)
-> TimeFormat -> SystemTime -> IO TimeFormat
formatSystemTimeHelper BA# Word8 -> Int64 -> MBA# Word8 -> CInt -> IO CSize
c_format_unix_time_gmt TimeFormat
fmt SystemTime
t
{-# INLINE formatSystemTimeGMT #-}
parseSystemTime :: TimeFormat -> CBytes -> IO SystemTime
parseSystemTime :: TimeFormat -> TimeFormat -> IO SystemTime
parseSystemTime TimeFormat
fmt TimeFormat
str =
TimeFormat -> (BA# Word8 -> IO SystemTime) -> IO SystemTime
forall a. TimeFormat -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe TimeFormat
fmt ((BA# Word8 -> IO SystemTime) -> IO SystemTime)
-> (BA# Word8 -> IO SystemTime) -> IO SystemTime
forall a b. (a -> b) -> a -> b
$ \BA# Word8
cfmt ->
TimeFormat -> (BA# Word8 -> IO SystemTime) -> IO SystemTime
forall a. TimeFormat -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe TimeFormat
str ((BA# Word8 -> IO SystemTime) -> IO SystemTime)
-> (BA# Word8 -> IO SystemTime) -> IO SystemTime
forall a b. (a -> b) -> a -> b
$ \BA# Word8
cstr -> do
Int64
sec <- BA# Word8 -> BA# Word8 -> IO Int64
c_parse_unix_time BA# Word8
cfmt BA# Word8
cstr
SystemTime -> IO SystemTime
forall (m :: * -> *) a. Monad m => a -> m a
return (SystemTime -> IO SystemTime) -> SystemTime -> IO SystemTime
forall a b. (a -> b) -> a -> b
$ Int64 -> Word32 -> SystemTime
MkSystemTime Int64
sec Word32
0
parseSystemTimeGMT :: TimeFormat -> CBytes -> SystemTime
parseSystemTimeGMT :: TimeFormat -> TimeFormat -> SystemTime
parseSystemTimeGMT TimeFormat
fmt TimeFormat
str = IO SystemTime -> SystemTime
forall a. IO a -> a
unsafePerformIO (IO SystemTime -> SystemTime) -> IO SystemTime -> SystemTime
forall a b. (a -> b) -> a -> b
$
TimeFormat -> (BA# Word8 -> IO SystemTime) -> IO SystemTime
forall a. TimeFormat -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe TimeFormat
fmt ((BA# Word8 -> IO SystemTime) -> IO SystemTime)
-> (BA# Word8 -> IO SystemTime) -> IO SystemTime
forall a b. (a -> b) -> a -> b
$ \BA# Word8
cfmt ->
TimeFormat -> (BA# Word8 -> IO SystemTime) -> IO SystemTime
forall a. TimeFormat -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe TimeFormat
str ((BA# Word8 -> IO SystemTime) -> IO SystemTime)
-> (BA# Word8 -> IO SystemTime) -> IO SystemTime
forall a b. (a -> b) -> a -> b
$ \BA# Word8
cstr -> do
Int64
sec <- BA# Word8 -> BA# Word8 -> IO Int64
c_parse_unix_time_gmt BA# Word8
cfmt BA# Word8
cstr
SystemTime -> IO SystemTime
forall (m :: * -> *) a. Monad m => a -> m a
return (SystemTime -> IO SystemTime) -> SystemTime -> IO SystemTime
forall a b. (a -> b) -> a -> b
$ Int64 -> Word32 -> SystemTime
MkSystemTime Int64
sec Word32
0
foreign import ccall unsafe "c_parse_unix_time"
c_parse_unix_time :: BA# Word8 -> BA# Word8 -> IO Int64
foreign import ccall unsafe "c_parse_unix_time_gmt"
c_parse_unix_time_gmt :: BA# Word8 -> BA# Word8 -> IO Int64
foreign import ccall unsafe "c_format_unix_time"
c_format_unix_time :: BA# Word8 -> Int64 -> MBA# Word8 -> CInt -> IO CSize
foreign import ccall unsafe "c_format_unix_time_gmt"
c_format_unix_time_gmt :: BA# Word8 -> Int64 -> MBA# Word8 -> CInt -> IO CSize
formatSystemTimeHelper
:: (BA# Word8 -> Int64 -> MBA# Word8 -> CInt -> IO CSize)
-> TimeFormat
-> SystemTime
-> IO CBytes
formatSystemTimeHelper :: (BA# Word8 -> Int64 -> MBA# Word8 -> CInt -> IO CSize)
-> TimeFormat -> SystemTime -> IO TimeFormat
formatSystemTimeHelper BA# Word8 -> Int64 -> MBA# Word8 -> CInt -> IO CSize
formatFun TimeFormat
fmt SystemTime
t = Int -> IO TimeFormat
go Int
80
where
MkSystemTime Int64
sec Word32
_ = SystemTime
t
go :: Int -> IO TimeFormat
go !Int
siz = do
(TimeFormat
bs, CSize
r)<- Int -> (MBA# Word8 -> IO CSize) -> IO (TimeFormat, CSize)
forall a.
HasCallStack =>
Int -> (MBA# Word8 -> IO a) -> IO (TimeFormat, a)
allocCBytesUnsafe Int
siz ((MBA# Word8 -> IO CSize) -> IO (TimeFormat, CSize))
-> (MBA# Word8 -> IO CSize) -> IO (TimeFormat, CSize)
forall a b. (a -> b) -> a -> b
$ \ MBA# Word8
pbuf ->
TimeFormat -> (BA# Word8 -> IO CSize) -> IO CSize
forall a. TimeFormat -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe TimeFormat
fmt ((BA# Word8 -> IO CSize) -> IO CSize)
-> (BA# Word8 -> IO CSize) -> IO CSize
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
pfmt ->
BA# Word8 -> Int64 -> MBA# Word8 -> CInt -> IO CSize
formatFun BA# Word8
pfmt Int64
sec MBA# Word8
pbuf (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
siz)
if CSize
r CSize -> CSize -> Bool
forall a. Ord a => a -> a -> Bool
<= CSize
0 then Int -> IO TimeFormat
go (Int
sizInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
2) else TimeFormat -> IO TimeFormat
forall (m :: * -> *) a. Monad m => a -> m a
return TimeFormat
bs