Copyright | (c) 2018-2020 Kowainik |
---|---|
License | MPL-2.0 |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
This module contains logging messages data types along with the formatting and logging actions for them.
Synopsis
- data SimpleMsg = SimpleMsg {
- simpleMsgStack :: !CallStack
- simpleMsgText :: !Text
- logText :: WithLog env SimpleMsg m => Text -> m ()
- fmtSimpleMessage :: SimpleMsg -> Text
- formatWith :: (msg -> Text) -> LogAction m Text -> LogAction m msg
- data Msg sev = Msg {
- msgSeverity :: !sev
- msgStack :: !CallStack
- msgText :: !Text
- type Message = Msg Severity
- log :: WithLog env (Msg sev) m => sev -> Text -> m ()
- logDebug :: WithLog env Message m => Text -> m ()
- logInfo :: WithLog env Message m => Text -> m ()
- logWarning :: WithLog env Message m => Text -> m ()
- logError :: WithLog env Message m => Text -> m ()
- logException :: forall e m env. (WithLog env Message m, Exception e) => e -> m ()
- fmtMessage :: Message -> Text
- showSeverity :: Severity -> Text
- showSourceLoc :: CallStack -> Text
- type family FieldType (fieldName :: Symbol) :: Type
- newtype MessageField (m :: Type -> Type) (fieldName :: Symbol) where
- MessageField :: forall fieldName m. m (FieldType fieldName) -> MessageField m fieldName
- unMessageField :: forall fieldName m. MessageField m fieldName -> m (FieldType fieldName)
- extractField :: Applicative m => Maybe (MessageField m fieldName) -> m (Maybe (FieldType fieldName))
- type FieldMap (m :: Type -> Type) = TypeRepMap (MessageField m)
- defaultFieldMap :: MonadIO m => FieldMap m
- type RichMessage m = RichMsg m Message
- data RichMsg (m :: Type -> Type) (msg :: Type) = RichMsg {
- richMsgMsg :: !msg
- richMsgMap :: !(FieldMap m)
- fmtRichMessageDefault :: MonadIO m => RichMessage m -> m Text
- fmtSimpleRichMessageDefault :: MonadIO m => RichMsg m SimpleMsg -> m Text
- fmtRichMessageCustomDefault :: MonadIO m => RichMsg m msg -> (Maybe ThreadId -> Maybe Time -> msg -> Text) -> m Text
- upgradeMessageAction :: forall m msg. FieldMap m -> LogAction m (RichMsg m msg) -> LogAction m msg
Simple message type
Type
Message data type without Severity
. Use logText
to log
messages of this type.
Since: 0.4.0.0
Logging
Formatting
fmtSimpleMessage :: SimpleMsg -> Text Source #
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
formatWith :: (msg -> Text) -> LogAction m Text -> LogAction m msg Source #
Alias for cmap
specialized for formatting purposes. If you have
an action that can output Text
(for example
logTextStdout
), you can convert it to the action that
can print SimpleMsg
or Message
:
logSimpleMsgStdout ::LogAction
IO
SimpleMsg
logSimpleMsgStdout =formatWith
fmtSimpleMessage
logTextStdout
logMessageStdout ::LogAction
IO
Message
logMessageStdout =formatWith
fmtMessage
logTextStdout
Since: 0.4.0.0
Core messaging
Types
General logging message data type. Contains the following fields:
- Polymorphic severity. This can be anything you want if you need more flexibility.
- Function
CallStack
. It provides useful information about source code locations where each particular function was called. - Custom text for logging.
type Message = Msg Severity Source #
Msg
parametrized by the Severity
type. Most formatting functions in
this module work with Severity
from co-log-core
.
Logging
log :: WithLog env (Msg sev) m => sev -> Text -> m () Source #
Logs the message with given severity sev
.
logWarning :: WithLog env Message m => Text -> m () Source #
Logs the message with the Warning
severity.
logException :: forall e m env. (WithLog env Message m, Exception e) => e -> m () Source #
Logs Exception
message with the Error
severity.
Formatting
fmtMessage :: Message -> Text Source #
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.
showSeverity :: Severity -> Text Source #
Formats severity in different colours with alignment.
showSourceLoc :: CallStack -> Text Source #
Shows source code locations in the following format:
[Main.example#35]
Externally extensible message type
Field of the dependent map
type family FieldType (fieldName :: Symbol) :: Type Source #
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.
newtype MessageField (m :: Type -> Type) (fieldName :: Symbol) where Source #
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) }
MessageField :: forall fieldName m. m (FieldType fieldName) -> MessageField m fieldName |
Instances
(KnownSymbol fieldName, a ~ m (FieldType fieldName)) => IsLabel fieldName (a -> WrapTypeable (MessageField m)) Source # | |
Defined in Colog.Message fromLabel :: a -> WrapTypeable (MessageField m) # |
unMessageField :: forall fieldName m. MessageField m fieldName -> m (FieldType fieldName) Source #
Extracts field from the MessageField
constructor.
extractField :: Applicative m => Maybe (MessageField m fieldName) -> m (Maybe (FieldType fieldName)) Source #
Helper function to deal with MessageField
when looking it up in the FieldMap
.
Dependent map that allows to extend logging message
type FieldMap (m :: Type -> Type) = TypeRepMap (MessageField m) Source #
Depedent map from type level strings to the corresponding types. See
FieldType
for mapping between names and types.
defaultFieldMap :: MonadIO m => FieldMap m Source #
Default message map that contains actions to extract ThreadId
and
Time
. Basically, the following mapping:
"threadId" ->myThreadId
"posixTime" ->now
Extensible message
type RichMessage m = RichMsg m Message Source #
Specialised version of RichMsg
that stores severity, callstack and text message.
data RichMsg (m :: Type -> Type) (msg :: Type) Source #
Contains additional data to Message
to display more verbose information.
Since: 0.4.0.0
RichMsg | |
|
fmtRichMessageDefault :: MonadIO m => RichMessage m -> m Text Source #
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.
fmtSimpleRichMessageDefault :: MonadIO m => RichMsg m SimpleMsg -> m Text Source #
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