{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module System.Log.FastLogger.Date (
newTimeCache,
simpleTimeFormat,
simpleTimeFormat',
) where
import Control.AutoUpdate (defaultUpdateSettings, mkAutoUpdate, updateAction, updateThreadName)
import Data.UnixTime (formatUnixTime, fromEpochTime)
import System.Log.FastLogger.Types (FormattedTime, TimeFormat)
import System.PosixCompat.Time (epochTime)
import System.PosixCompat.Types (EpochTime)
getTime :: IO EpochTime
getTime :: IO EpochTime
getTime = IO EpochTime
epochTime
formatDate :: TimeFormat -> EpochTime -> IO FormattedTime
formatDate :: TimeFormat -> EpochTime -> IO TimeFormat
formatDate TimeFormat
fmt = TimeFormat -> UnixTime -> IO TimeFormat
formatUnixTime TimeFormat
fmt (UnixTime -> IO TimeFormat)
-> (EpochTime -> UnixTime) -> EpochTime -> IO TimeFormat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EpochTime -> UnixTime
fromEpochTime
newTimeCache :: TimeFormat -> IO (IO FormattedTime)
newTimeCache :: TimeFormat -> IO (IO TimeFormat)
newTimeCache TimeFormat
fmt =
UpdateSettings TimeFormat -> IO (IO TimeFormat)
forall a. UpdateSettings a -> IO (IO a)
mkAutoUpdate
UpdateSettings ()
defaultUpdateSettings
{ updateAction = getTime >>= formatDate fmt
, updateThreadName = "Date string cacher of FastLogger (AutoUpdate)"
}
simpleTimeFormat :: TimeFormat
simpleTimeFormat :: TimeFormat
simpleTimeFormat = TimeFormat
"%d/%b/%Y:%T %z"
simpleTimeFormat' :: TimeFormat
simpleTimeFormat' :: TimeFormat
simpleTimeFormat' = TimeFormat
"%d-%b-%Y %T"