-- |
-- Module: System.Logger.Internal
-- Copyright:
--     Copyright (c) 2016-2020 Lars Kuhtz <lakuhtz@gmail.com>
--     Copyright (c) 2014-2015 PivotCloud, Inc.
-- License: Apache License, Version 2.0
-- Maintainer: Lars Kuhtz <lakuhtz@gmail.com>
-- Stability: experimental
--

{-# LANGUAGE CPP #-}
{-# LANGUAGE UnicodeSyntax #-}

module System.Logger.Internal
( sshow
, formatIso8601
, formatIso8601Milli
, formatIso8601Micro
, timeSpecToUtc
) where

import Data.Monoid.Unicode
import Data.String
import Data.Time.Clock
import Data.Time.Clock.POSIX
import Data.Time.Format

import Numeric.Natural

import Prelude.Unicode

import System.Clock

sshow
     (Show a, IsString b)
     a
     b
sshow :: a -> b
sshow = String -> b
forall a. IsString a => String -> a
fromString (String -> b) -> (a -> String) -> a -> b
forall β γ α. (β -> γ) -> (α -> β) -> α -> γ
 a -> String
forall a. Show a => a -> String
show
{-# INLINE sshow #-}

-- | Format 'TimeSpec' as ISO8601 date-time string with
-- microseconds precision.
--
-- @since 0.2
--
formatIso8601Micro
     IsString a
     TimeSpec
     a
formatIso8601Micro :: TimeSpec -> a
formatIso8601Micro = Natural -> TimeSpec -> a
forall a. IsString a => Natural -> TimeSpec -> a
formatIso8601 Natural
6

-- | Format 'TimeSpec' as ISO8601 date-time string with
-- milliseconds precision.
--
-- @since 0.2
--
formatIso8601Milli
     IsString a
     TimeSpec
     a
formatIso8601Milli :: TimeSpec -> a
formatIso8601Milli = Natural -> TimeSpec -> a
forall a. IsString a => Natural -> TimeSpec -> a
formatIso8601 Natural
3

-- | Format 'TimeSpec' as ISO8601 date-time string with
-- the given sub-second precision.
--
-- @since 0.2
--
formatIso8601
     IsString a
     Natural
        -- ^ precision, a value between 0 (seconds) and 6 (microseconds)
     TimeSpec
     a
formatIso8601 :: Natural -> TimeSpec -> a
formatIso8601 Natural
precision
    = String -> a
forall a. IsString a => String -> a
fromString
    (String -> a) -> (TimeSpec -> String) -> TimeSpec -> a
forall β γ α. (β -> γ) -> (α -> β) -> α -> γ
 (String -> String -> String
forall α. Monoid α => α -> α -> α
 String
"Z")
    (String -> String) -> (TimeSpec -> String) -> TimeSpec -> String
forall β γ α. (β -> γ) -> (α -> β) -> α -> γ
 Int -> String -> String
forall a. Int -> [a] -> [a]
take (Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Natural -> Int) -> Natural -> Int
forall a b. (a -> b) -> a -> b
$ Natural
20 Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
+ Natural
precision)
    (String -> String) -> (TimeSpec -> String) -> TimeSpec -> String
forall β γ α. (β -> γ) -> (α -> β) -> α -> γ
 (String -> String -> String
forall α. Monoid α => α -> α -> α
 Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
precision) Char
'0')
    (String -> String) -> (TimeSpec -> String) -> TimeSpec -> String
forall β γ α. (β -> γ) -> (α -> β) -> α -> γ
 TimeLocale -> String -> UTCTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale (String
"%Y-%m-%dT%H:%M:%S%Q")
    (UTCTime -> String) -> (TimeSpec -> UTCTime) -> TimeSpec -> String
forall β γ α. (β -> γ) -> (α -> β) -> α -> γ
 TimeSpec -> UTCTime
timeSpecToUtc

-- | Convert a 'TimeSpec' value into 'UTCTime'
--
-- @since 0.2
--
timeSpecToUtc
     TimeSpec
     UTCTime
timeSpecToUtc :: TimeSpec -> UTCTime
timeSpecToUtc (TimeSpec Int64
s Int64
ns) =
    POSIXTime -> UTCTime
posixSecondsToUTCTime (Int64 -> POSIXTime
forall a b. (Real a, Fractional b) => a -> b
realToFrac Int64
s POSIXTime -> POSIXTime -> POSIXTime
forall a. Num a => a -> a -> a
+ Int64 -> POSIXTime
forall a b. (Real a, Fractional b) => a -> b
realToFrac Int64
ns POSIXTime -> POSIXTime -> POSIXTime
forall a. Num a => a -> a -> a
* POSIXTime
1e-9)