{-# LANGUAGE OverloadedStrings #-}
module EasyLogger.Date
    ( FormattedTime
    , TimeFormat
    , newTimeCache
    , simpleTimeFormat
    , simpleTimeFormat'
    ) where

import           Control.AutoUpdate       (defaultUpdateSettings, mkAutoUpdate,
                                           updateAction)
import           Data.ByteString
import           Data.UnixTime            (formatUnixTime, fromEpochTime)
import           System.PosixCompat.Time  (epochTime)
import           System.PosixCompat.Types (EpochTime)


-- | Type aliaes for date format and formatted date.
type FormattedTime = ByteString
type TimeFormat = ByteString


----------------------------------------------------------------

-- | Get date using UnixTime.
getTime :: IO EpochTime
getTime :: IO EpochTime
getTime = IO EpochTime
epochTime

-- | Format unix EpochTime date.
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

----------------------------------------------------------------

-- |  Make 'IO' action which get cached formatted local time.
-- Use this to avoid the cost of frequently time formatting by caching an
-- auto updating formatted time, this cache update every 1 second.
-- more detail in "Control.AutoUpdate"
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 :: IO TimeFormat
updateAction = IO EpochTime
getTime IO EpochTime -> (EpochTime -> IO TimeFormat) -> IO TimeFormat
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= TimeFormat -> EpochTime -> IO TimeFormat
formatDate TimeFormat
fmt}

-- | A simple time cache using format @"%d/%b/%Y:%T %z"@
simpleTimeFormat :: TimeFormat
simpleTimeFormat :: TimeFormat
simpleTimeFormat = TimeFormat
"%d/%b/%Y:%T %z"

-- | A simple time cache using format @"%d-%b-%Y %T"@
simpleTimeFormat' :: TimeFormat
simpleTimeFormat' :: TimeFormat
simpleTimeFormat' = TimeFormat
"%d-%b-%Y %T"