{-# LANGUAGE CPP                   #-}
{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE DeriveFunctor         #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE GADTs                 #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies          #-}

{- |
Copyright:  (c) 2018-2022 Kowainik, 2023-2025 Co-Log
SPDX-License-Identifier: MPL-2.0

This module contains logging messages data types along with the formatting and
logging actions for them.
-}

module Colog.Message
       ( -- * Simple message type
         -- ** Type
         SimpleMsg (..)
         -- ** Logging
       , logText
         -- ** Formatting
       , fmtSimpleMessage
       , formatWith

         -- * Core messaging
         -- ** Types
       , Msg (..)
       , Message
         -- ** Logging
       , log
       , logDebug
       , logInfo
       , logWarning
       , logError
       , logException
         -- ** Formatting
       , fmtMessage
       , showSeverity
       , showSourceLoc
       , showTime
       , showTimeOffset
       , showThreadId

         -- * Externally extensible message type
         -- ** Field of the dependent map
       , FieldType
       , MessageField (..)
       , unMessageField
       , extractField
         -- ** Dependent map that allows to extend logging message
       , FieldMap
       , defaultFieldMap

         -- ** Extensible message
       , RichMessage
       , RichMsg (..)
       , fmtRichMessageDefault
       , fmtSimpleRichMessageDefault
       , fmtRichMessageCustomDefault
       , upgradeMessageAction
       ) where

import Prelude hiding (lookup, log)

import Control.Concurrent (ThreadId, myThreadId)
import Control.Exception (Exception, displayException)
import Control.Monad.IO.Class (MonadIO (..))
import Data.Dependent.Map (DMap, fromList, lookup)
import Data.Dependent.Sum (DSum ((:=>)))
import Data.Kind (Type)
import Data.Text (Text)
import GHC.Stack (CallStack, SrcLoc (..), callStack, getCallStack, withFrozenCallStack)
import GHC.TypeLits (Symbol)
import System.Console.ANSI (Color (..), ColorIntensity (Vivid), ConsoleLayer (Foreground), SGR (..),
                            setSGRCode)
import Type.Reflection (TypeRep, typeRep)

import Colog.Core (LogAction, Severity (..), cmap)
import Colog.Monad (WithLog, logMsg)

import qualified Data.Time as C
import qualified Data.Text as T

----------------------------------------------------------------------------
-- Plain message
----------------------------------------------------------------------------

{- | General logging message data type. Contains the following fields:

1. Polymorphic severity. This can be anything you want if you need more
flexibility.
2. Function 'CallStack'. It provides useful information about source code
locations where each particular function was called.
3. Custom text for logging.
-}
data Msg sev = Msg
    { forall sev. Msg sev -> sev
msgSeverity :: !sev
    , forall sev. Msg sev -> CallStack
msgStack    :: !CallStack
    , forall sev. Msg sev -> Text
msgText     ::  Text
    }

{- | Message data type without 'Severity'. Use 'logText' to log
messages of this type.

@since 0.4.0.0
-}
data SimpleMsg = SimpleMsg
    { SimpleMsg -> CallStack
simpleMsgStack :: !CallStack
    , SimpleMsg -> Text
simpleMsgText  :: !Text
    }

{- | 'Msg' parametrized by the 'Severity' type. Most formatting functions in
this module work with 'Severity' from @co-log-core@.
-}
type Message = Msg Severity

-- | Logs the message with given severity @sev@.
log :: WithLog env (Msg sev) m => sev -> Text -> m ()
log :: forall env sev (m :: * -> *).
WithLog env (Msg sev) m =>
sev -> Text -> m ()
log sev
msgSeverity Text
msgText =
    (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (Msg sev -> m ()
forall msg env (m :: * -> *). WithLog env msg m => msg -> m ()
logMsg Msg{ msgStack :: CallStack
msgStack = CallStack
HasCallStack => CallStack
callStack, sev
Text
msgSeverity :: sev
msgText :: Text
msgSeverity :: sev
msgText :: Text
.. })

-- | Logs the message with the 'Debug' severity.
logDebug :: WithLog env Message m => Text -> m ()
logDebug :: forall env (m :: * -> *). WithLog env Message m => Text -> m ()
logDebug = (HasCallStack => Text -> m ()) -> Text -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (Severity -> Text -> m ()
forall env sev (m :: * -> *).
WithLog env (Msg sev) m =>
sev -> Text -> m ()
log Severity
Debug)

-- | Logs the message with the 'Info' severity.
logInfo :: WithLog env Message m => Text -> m ()
logInfo :: forall env (m :: * -> *). WithLog env Message m => Text -> m ()
logInfo = (HasCallStack => Text -> m ()) -> Text -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (Severity -> Text -> m ()
forall env sev (m :: * -> *).
WithLog env (Msg sev) m =>
sev -> Text -> m ()
log Severity
Info)

-- | Logs the message with the 'Warning' severity.
logWarning :: WithLog env Message m => Text -> m ()
logWarning :: forall env (m :: * -> *). WithLog env Message m => Text -> m ()
logWarning = (HasCallStack => Text -> m ()) -> Text -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (Severity -> Text -> m ()
forall env sev (m :: * -> *).
WithLog env (Msg sev) m =>
sev -> Text -> m ()
log Severity
Warning)

-- | Logs the message with the 'Error' severity.
logError :: WithLog env Message m => Text -> m ()
logError :: forall env (m :: * -> *). WithLog env Message m => Text -> m ()
logError = (HasCallStack => Text -> m ()) -> Text -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (Severity -> Text -> m ()
forall env sev (m :: * -> *).
WithLog env (Msg sev) m =>
sev -> Text -> m ()
log Severity
Error)

-- | Logs 'Exception' message with the 'Error' severity.
logException :: forall e m env . (WithLog env Message m, Exception e) => e -> m ()
logException :: forall e (m :: * -> *) env.
(WithLog env Message m, Exception e) =>
e -> m ()
logException = (HasCallStack => e -> m ()) -> e -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (Text -> m ()
forall env (m :: * -> *). WithLog env Message m => Text -> m ()
logError (Text -> m ()) -> (e -> Text) -> e -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (e -> String) -> e -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> String
forall e. Exception e => e -> String
displayException)

{- | Logs 'SimpleMsg' without severity, only 'CallStack' and 'Text'
body message.

@since 0.4.0.0
-}
logText :: WithLog env SimpleMsg m => Text -> m ()
logText :: forall env (m :: * -> *). WithLog env SimpleMsg m => Text -> m ()
logText Text
msgText = (HasCallStack => m ()) -> m ()
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack (SimpleMsg -> m ()
forall msg env (m :: * -> *). WithLog env msg m => msg -> m ()
logMsg SimpleMsg{ simpleMsgStack :: CallStack
simpleMsgStack = CallStack
HasCallStack => CallStack
callStack, simpleMsgText :: Text
simpleMsgText = Text
msgText })

{- | Formats the 'Message' type according to the following format:

@
[Severity] [SourceLocation] \<Text message\>
@

__Examples:__

@
[Warning] [Main.app#39] Starting application...
[Debug]   [Main.example#34] app: First message...
@

See 'fmtRichMessageDefault' for a richer format.
-}
fmtMessage :: Message -> Text
fmtMessage :: Message -> Text
fmtMessage Msg{CallStack
Severity
Text
msgSeverity :: forall sev. Msg sev -> sev
msgStack :: forall sev. Msg sev -> CallStack
msgText :: forall sev. Msg sev -> Text
msgSeverity :: Severity
msgStack :: CallStack
msgText :: Text
..} =
    Severity -> Text
showSeverity Severity
msgSeverity
    Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> CallStack -> Text
showSourceLoc CallStack
msgStack
    Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
msgText

{- | Formats the 'SimpleMsg' type in according to the following format:

@
[SourceLocation] \<Text message\>
@

__Examples:__

@
[Main.app#39] Starting application...
[Main.example#34] app: First message...
@

See 'fmtSimpleRichMessageDefault' for richer format.

@since 0.4.0.0
-}
fmtSimpleMessage :: SimpleMsg -> Text
fmtSimpleMessage :: SimpleMsg -> Text
fmtSimpleMessage SimpleMsg{CallStack
Text
simpleMsgStack :: SimpleMsg -> CallStack
simpleMsgText :: SimpleMsg -> Text
simpleMsgStack :: CallStack
simpleMsgText :: Text
..} = CallStack -> Text
showSourceLoc CallStack
simpleMsgStack Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
simpleMsgText

{- | Alias for 'cmap' specialized for formatting purposes. If you have
an action that can output 'Text' (for example
'Colog.Actions.logTextStdout'), you can convert it to the action that
can print 'SimpleMsg' or 'Message':

@
logSimpleMsgStdout :: 'LogAction' 'IO' 'SimpleMsg'
logSimpleMsgStdout = 'formatWith' 'fmtSimpleMessage' 'Colog.Actions.logTextStdout'

logMessageStdout :: 'LogAction' 'IO' 'Message'
logMessageStdout = 'formatWith' 'fmtMessage' 'Colog.Actions.logTextStdout'
@

@since 0.4.0.0
-}
formatWith :: (msg -> Text) -> LogAction m Text -> LogAction m msg
formatWith :: forall msg (m :: * -> *).
(msg -> Text) -> LogAction m Text -> LogAction m msg
formatWith = (msg -> Text) -> LogAction m Text -> LogAction m msg
forall a b (m :: * -> *).
(a -> b) -> LogAction m b -> LogAction m a
cmap
{-# INLINE formatWith #-}

{- | Formats severity in different colours with alignment.
-}
showSeverity :: Severity -> Text
showSeverity :: Severity -> Text
showSeverity = \case
    Severity
Debug   -> Color -> Text -> Text
color Color
Green  Text
"[Debug]   "
    Severity
Info    -> Color -> Text -> Text
color Color
Blue   Text
"[Info]    "
    Severity
Warning -> Color -> Text -> Text
color Color
Yellow Text
"[Warning] "
    Severity
Error   -> Color -> Text -> Text
color Color
Red    Text
"[Error]   "
 where
    color :: Color -> Text -> Text
    color :: Color -> Text -> Text
color Color
c Text
txt =
        String -> Text
T.pack ([SGR] -> String
setSGRCode [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Vivid Color
c])
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
txt
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack ([SGR] -> String
setSGRCode [SGR
Reset])

square :: Text -> Text
square :: Text -> Text
square Text
t = Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"] "

{- | Shows source code locations in the following format:

@
[Main.example#35]
@
-}
showSourceLoc :: CallStack -> Text
showSourceLoc :: CallStack -> Text
showSourceLoc CallStack
cs = Text -> Text
square Text
showCallStack
  where
    showCallStack :: Text
    showCallStack :: Text
showCallStack = case CallStack -> [(String, SrcLoc)]
getCallStack CallStack
cs of
        []                             -> Text
"<unknown loc>"
        [(String
name, SrcLoc
loc)]                  -> String -> SrcLoc -> Text
showLoc String
name SrcLoc
loc
        (String
_, SrcLoc
loc) : (String
callerName, SrcLoc
_) : [(String, SrcLoc)]
_ -> String -> SrcLoc -> Text
showLoc String
callerName SrcLoc
loc

    showLoc :: String -> SrcLoc -> Text
    showLoc :: String -> SrcLoc -> Text
showLoc String
name SrcLoc{Int
String
srcLocPackage :: String
srcLocModule :: String
srcLocFile :: String
srcLocStartLine :: Int
srcLocStartCol :: Int
srcLocEndLine :: Int
srcLocEndCol :: Int
srcLocPackage :: SrcLoc -> String
srcLocModule :: SrcLoc -> String
srcLocFile :: SrcLoc -> String
srcLocStartLine :: SrcLoc -> Int
srcLocStartCol :: SrcLoc -> Int
srcLocEndLine :: SrcLoc -> Int
srcLocEndCol :: SrcLoc -> Int
..} =
        String -> Text
T.pack String
srcLocModule Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
srcLocStartLine)

----------------------------------------------------------------------------
-- Externally extensible message
----------------------------------------------------------------------------

{- | Open type family that maps some user defined tags (type names) to actual
types. The type family is open so you can add new instances.
-}
type family FieldType (fieldName :: Symbol) :: Type
type instance FieldType "threadId" = ThreadId
type instance FieldType "utcTime"  = C.UTCTime

{- | @newtype@ wrapper. Stores monadic ability to extract value of 'FieldType'.

__Implementation detail:__ this exotic writing of 'MessageField' is required in
order to use it nicer with type applications. So users can write

@
MessageField @"threadId" myThreadId
@

instead of

@
MessageField @_ @"threadId" myThreadId
@

Simpler version of this @newtype@:

@
newtype MessageField m fieldName = MessageField
    { unMesssageField :: m (FieldType fieldName)
    }
@
-}
newtype MessageField (m :: Type -> Type) (fieldName :: Symbol) where
    MessageField :: forall fieldName m . m (FieldType fieldName) -> MessageField m fieldName

-- | Extracts field from the 'MessageField' constructor.
unMessageField :: forall fieldName m . MessageField m fieldName -> m (FieldType fieldName)
unMessageField :: forall (fieldName :: Symbol) (m :: * -> *).
MessageField m fieldName -> m (FieldType fieldName)
unMessageField (MessageField m (FieldType fieldName)
f) = m (FieldType fieldName)
f
{-# INLINE unMessageField #-}

-- | Helper function to deal with 'MessageField' when looking it up in the 'FieldMap'.
extractField
    :: Applicative m
    => Maybe (MessageField m fieldName)
    -> m (Maybe (FieldType fieldName))
extractField :: forall (m :: * -> *) (fieldName :: Symbol).
Applicative m =>
Maybe (MessageField m fieldName) -> m (Maybe (FieldType fieldName))
extractField = (MessageField m fieldName -> m (FieldType fieldName))
-> Maybe (MessageField m fieldName)
-> m (Maybe (FieldType fieldName))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse MessageField m fieldName -> m (FieldType fieldName)
forall (fieldName :: Symbol) (m :: * -> *).
MessageField m fieldName -> m (FieldType fieldName)
unMessageField
{-# INLINE extractField #-}

-- same as:
-- extractField = \case
--    Nothing -> pure Nothing
--    Just (MessageField field) -> Just <$> field

{- | Depedent map from type level strings to the corresponding types. See
'FieldType' for mapping between names and types.
-}
type FieldMap m = DMap TypeRep (MessageField m)

{- | Default message map that contains actions to extract 'ThreadId' and
'C.UTCTime'. Basically, the following mapping:

@
"threadId" -> 'myThreadId'
"utcTime"  -> 'C.getCurrentTime'
@
-}
defaultFieldMap :: MonadIO m => FieldMap m
defaultFieldMap :: forall (m :: * -> *). MonadIO m => FieldMap m
defaultFieldMap = [DSum TypeRep (MessageField m)] -> DMap TypeRep (MessageField m)
forall {k1} (k2 :: k1 -> *) (f :: k1 -> *).
GCompare k2 =>
[DSum k2 f] -> DMap k2 f
fromList
    [ forall {k} (a :: k). Typeable a => TypeRep a
forall (a :: Symbol). Typeable a => TypeRep a
typeRep @"threadId" TypeRep "threadId"
-> MessageField m "threadId" -> DSum TypeRep (MessageField m)
forall {k} (tag :: k -> *) (f :: k -> *) (a :: k).
tag a -> f a -> DSum tag f
:=> m (FieldType "threadId") -> MessageField m "threadId"
forall (fieldName :: Symbol) (m :: * -> *).
m (FieldType fieldName) -> MessageField m fieldName
MessageField (IO ThreadId -> m ThreadId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ThreadId
myThreadId)
    , forall {k} (a :: k). Typeable a => TypeRep a
forall (a :: Symbol). Typeable a => TypeRep a
typeRep @"utcTime"  TypeRep "utcTime"
-> MessageField m "utcTime" -> DSum TypeRep (MessageField m)
forall {k} (tag :: k -> *) (f :: k -> *) (a :: k).
tag a -> f a -> DSum tag f
:=> m (FieldType "utcTime") -> MessageField m "utcTime"
forall (fieldName :: Symbol) (m :: * -> *).
m (FieldType fieldName) -> MessageField m fieldName
MessageField (IO UTCTime -> m UTCTime
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UTCTime
C.getCurrentTime)
    ]

{- | Contains additional data to 'Message' to display more verbose information.

@since 0.4.0.0
-}
data RichMsg (m :: Type -> Type) (msg :: Type) = RichMsg
    { forall (m :: * -> *) msg. RichMsg m msg -> msg
richMsgMsg :: !msg
    , forall (m :: * -> *) msg. RichMsg m msg -> FieldMap m
richMsgMap :: !(FieldMap m)
    } deriving stock ((forall a b. (a -> b) -> RichMsg m a -> RichMsg m b)
-> (forall a b. a -> RichMsg m b -> RichMsg m a)
-> Functor (RichMsg m)
forall a b. a -> RichMsg m b -> RichMsg m a
forall a b. (a -> b) -> RichMsg m a -> RichMsg m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
forall (m :: * -> *) a b. a -> RichMsg m b -> RichMsg m a
forall (m :: * -> *) a b. (a -> b) -> RichMsg m a -> RichMsg m b
$cfmap :: forall (m :: * -> *) a b. (a -> b) -> RichMsg m a -> RichMsg m b
fmap :: forall a b. (a -> b) -> RichMsg m a -> RichMsg m b
$c<$ :: forall (m :: * -> *) a b. a -> RichMsg m b -> RichMsg m a
<$ :: forall a b. a -> RichMsg m b -> RichMsg m a
Functor)

-- | Specialised version of 'RichMsg' that stores severity, callstack and text message.
type RichMessage m = RichMsg m Message

{- | Formats 'RichMessage' in the following way:

@
[Severity] [Time] [SourceLocation] [ThreadId] \<Text message\>
@

__Examples:__

@
[Debug]   [03 May 2019 05:23:19.058 +00:00] [Main.example#34] [ThreadId 11] app: First message...
[Info]    [03 May 2019 05:23:19.059 +00:00] [Main.example#35] [ThreadId 11] app: Second message...
@

See 'fmtMessage' if you don't need both time and thread ID.
-}
fmtRichMessageDefault :: MonadIO m => RichMessage m -> m Text
fmtRichMessageDefault :: forall (m :: * -> *). MonadIO m => RichMessage m -> m Text
fmtRichMessageDefault RichMessage m
msg = RichMessage m
-> (Maybe ThreadId -> Maybe UTCTime -> Message -> Text) -> m Text
forall (m :: * -> *) msg.
MonadIO m =>
RichMsg m msg
-> (Maybe ThreadId -> Maybe UTCTime -> msg -> Text) -> m Text
fmtRichMessageCustomDefault RichMessage m
msg Maybe ThreadId -> Maybe UTCTime -> Message -> Text
formatRichMessage
  where
    formatRichMessage :: Maybe ThreadId -> Maybe C.UTCTime -> Message -> Text
    formatRichMessage :: Maybe ThreadId -> Maybe UTCTime -> Message -> Text
formatRichMessage (Text -> (ThreadId -> Text) -> Maybe ThreadId -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" ThreadId -> Text
showThreadId -> Text
thread) (Text -> (UTCTime -> Text) -> Maybe UTCTime -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" UTCTime -> Text
showTime -> Text
time) Msg{CallStack
Severity
Text
msgSeverity :: forall sev. Msg sev -> sev
msgStack :: forall sev. Msg sev -> CallStack
msgText :: forall sev. Msg sev -> Text
msgSeverity :: Severity
msgStack :: CallStack
msgText :: Text
..} =
        Severity -> Text
showSeverity Severity
msgSeverity
     Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
time
     Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> CallStack -> Text
showSourceLoc CallStack
msgStack
     Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
thread
     Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
msgText

{- | Formats 'RichMessage' in the following way:

@
[Time] [SourceLocation] [ThreadId] \<Text message\>
@

__Examples:__

@
[03 May 2019 05:23:19.058 +00:00] [Main.example#34] [ThreadId 11] app: First message...
[03 May 2019 05:23:19.059 +00:00] [Main.example#35] [ThreadId 11] app: Second message...
@

Practically, it formats a message as 'fmtRichMessageDefault' without the severity information.

@since 0.4.0.0
-}
fmtSimpleRichMessageDefault :: MonadIO m => RichMsg m SimpleMsg -> m Text
fmtSimpleRichMessageDefault :: forall (m :: * -> *). MonadIO m => RichMsg m SimpleMsg -> m Text
fmtSimpleRichMessageDefault RichMsg m SimpleMsg
msg = RichMsg m SimpleMsg
-> (Maybe ThreadId -> Maybe UTCTime -> SimpleMsg -> Text) -> m Text
forall (m :: * -> *) msg.
MonadIO m =>
RichMsg m msg
-> (Maybe ThreadId -> Maybe UTCTime -> msg -> Text) -> m Text
fmtRichMessageCustomDefault RichMsg m SimpleMsg
msg Maybe ThreadId -> Maybe UTCTime -> SimpleMsg -> Text
formatRichMessage
  where
    formatRichMessage :: Maybe ThreadId -> Maybe C.UTCTime -> SimpleMsg -> Text
    formatRichMessage :: Maybe ThreadId -> Maybe UTCTime -> SimpleMsg -> Text
formatRichMessage (Text -> (ThreadId -> Text) -> Maybe ThreadId -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" ThreadId -> Text
showThreadId -> Text
thread) (Text -> (UTCTime -> Text) -> Maybe UTCTime -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" UTCTime -> Text
showTime -> Text
time) SimpleMsg{CallStack
Text
simpleMsgStack :: SimpleMsg -> CallStack
simpleMsgText :: SimpleMsg -> Text
simpleMsgStack :: CallStack
simpleMsgText :: Text
..} =
        Text
time
     Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> CallStack -> Text
showSourceLoc CallStack
simpleMsgStack
     Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
thread
     Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
simpleMsgText
{- | Custom formatting function for 'RichMsg'. It extracts 'ThreadId'
and 'C.Time' from fields and allows you to specify how to format them.

@since 0.4.0.0
-}
fmtRichMessageCustomDefault
    :: MonadIO m
    => RichMsg m msg
    -> (Maybe ThreadId -> Maybe C.UTCTime -> msg -> Text)
    -> m Text
fmtRichMessageCustomDefault :: forall (m :: * -> *) msg.
MonadIO m =>
RichMsg m msg
-> (Maybe ThreadId -> Maybe UTCTime -> msg -> Text) -> m Text
fmtRichMessageCustomDefault RichMsg{msg
FieldMap m
richMsgMsg :: forall (m :: * -> *) msg. RichMsg m msg -> msg
richMsgMap :: forall (m :: * -> *) msg. RichMsg m msg -> FieldMap m
richMsgMsg :: msg
richMsgMap :: FieldMap m
..} Maybe ThreadId -> Maybe UTCTime -> msg -> Text
formatter = do
    Maybe ThreadId
maybeThreadId <- Maybe (MessageField m "threadId")
-> m (Maybe (FieldType "threadId"))
forall (m :: * -> *) (fieldName :: Symbol).
Applicative m =>
Maybe (MessageField m fieldName) -> m (Maybe (FieldType fieldName))
extractField (Maybe (MessageField m "threadId")
 -> m (Maybe (FieldType "threadId")))
-> Maybe (MessageField m "threadId")
-> m (Maybe (FieldType "threadId"))
forall a b. (a -> b) -> a -> b
$ TypeRep "threadId"
-> FieldMap m -> Maybe (MessageField m "threadId")
forall {k1} (k2 :: k1 -> *) (f :: k1 -> *) (v :: k1).
GCompare k2 =>
k2 v -> DMap k2 f -> Maybe (f v)
lookup (forall {k} (a :: k). Typeable a => TypeRep a
forall (a :: Symbol). Typeable a => TypeRep a
typeRep @"threadId")  FieldMap m
richMsgMap
    Maybe UTCTime
maybeUtcTime  <- Maybe (MessageField m "utcTime") -> m (Maybe (FieldType "utcTime"))
forall (m :: * -> *) (fieldName :: Symbol).
Applicative m =>
Maybe (MessageField m fieldName) -> m (Maybe (FieldType fieldName))
extractField (Maybe (MessageField m "utcTime")
 -> m (Maybe (FieldType "utcTime")))
-> Maybe (MessageField m "utcTime")
-> m (Maybe (FieldType "utcTime"))
forall a b. (a -> b) -> a -> b
$ TypeRep "utcTime" -> FieldMap m -> Maybe (MessageField m "utcTime")
forall {k1} (k2 :: k1 -> *) (f :: k1 -> *) (v :: k1).
GCompare k2 =>
k2 v -> DMap k2 f -> Maybe (f v)
lookup (forall {k} (a :: k). Typeable a => TypeRep a
forall (a :: Symbol). Typeable a => TypeRep a
typeRep @"utcTime") FieldMap m
richMsgMap
    Text -> m Text
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> m Text) -> Text -> m Text
forall a b. (a -> b) -> a -> b
$ Maybe ThreadId -> Maybe UTCTime -> msg -> Text
formatter Maybe ThreadId
maybeThreadId Maybe UTCTime
maybeUtcTime msg
richMsgMsg

{- | Shows time in the following format:

>>> showTime $ C.UTCTime (C.fromGregorian 2019 12 29) (C.secondsToDiffTime 3600 * 22)
"[29 Dec 2019 22:00:00.000 +00:00] "
-}
showTime :: C.UTCTime -> Text
showTime :: UTCTime -> Text
showTime = ZonedTime -> Text
showTimeOffset (ZonedTime -> Text) -> (UTCTime -> ZonedTime) -> UTCTime -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeZone -> UTCTime -> ZonedTime
C.utcToZonedTime TimeZone
C.utc

{- | Shows time in the following format:

>>> showTimeOffset $ C.utcToZonedTime (C.hoursToTimeZone (-2)) (C.UTCTime (C.fromGregorian 2019 12 29) (C.secondsToDiffTime 3600 * 22))
"[29 Dec 2019 20:00:00.000 -02:00] "
-}
showTimeOffset :: C.ZonedTime -> Text
showTimeOffset :: ZonedTime -> Text
showTimeOffset = String -> Text
T.pack (String -> Text) -> (ZonedTime -> String) -> ZonedTime -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeLocale -> String -> ZonedTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
C.formatTime TimeLocale
C.defaultTimeLocale String
"[%d %b %Y %H:%M:%S%3Q %Ez] "

----------------------------------------------------------------------------
-- Utility functions
----------------------------------------------------------------------------

{- | Shows a thread id in the following format:

__>>__ showThreadId <$> Control.Concurrent.myThreadId
"[ThreadId 4898] "
-}
showThreadId :: ThreadId -> Text
showThreadId :: ThreadId -> Text
showThreadId = Text -> Text
square (Text -> Text) -> (ThreadId -> Text) -> ThreadId -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (ThreadId -> String) -> ThreadId -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ThreadId -> String
forall a. Show a => a -> String
show

{- | Allows to extend basic 'Message' type with given dependent map of fields.
-}
upgradeMessageAction
    :: forall m msg .
       FieldMap m
    -> LogAction m (RichMsg m msg)
    -> LogAction m msg
upgradeMessageAction :: forall (m :: * -> *) msg.
FieldMap m -> LogAction m (RichMsg m msg) -> LogAction m msg
upgradeMessageAction FieldMap m
fieldMap = (msg -> RichMsg m msg)
-> LogAction m (RichMsg m msg) -> LogAction m msg
forall a b (m :: * -> *).
(a -> b) -> LogAction m b -> LogAction m a
cmap msg -> RichMsg m msg
addMap
  where
    addMap :: msg -> RichMsg m msg
    addMap :: msg -> RichMsg m msg
addMap msg
msg = msg -> FieldMap m -> RichMsg m msg
forall (m :: * -> *) msg. msg -> FieldMap m -> RichMsg m msg
RichMsg msg
msg FieldMap m
fieldMap