co-log-0.4.0.1: Composable Contravariant Comonadic Logging Library
Copyright(c) 2018-2020 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Colog.Message

Description

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

Synopsis

Simple message type

Type

data SimpleMsg Source #

Message data type without Severity. Use logText to log messages of this type.

Since: 0.4.0.0

Constructors

SimpleMsg 

Logging

logText :: WithLog env SimpleMsg m => Text -> m () Source #

Logs SimpleMsg without severity, only CallStack and Text body message.

Since: 0.4.0.0

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

data Msg sev Source #

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.

Constructors

Msg 

Fields

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.

logDebug :: WithLog env Message m => Text -> m () Source #

Logs the message with the Debug severity.

logInfo :: WithLog env Message m => Text -> m () Source #

Logs the message with the Info severity.

logWarning :: WithLog env Message m => Text -> m () Source #

Logs the message with the Warning severity.

logError :: WithLog env Message m => Text -> m () Source #

Logs the message with the Error 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.

Instances

Instances details
type FieldType "posixTime" Source # 
Instance details

Defined in Colog.Message

type FieldType "posixTime" = Time
type FieldType "threadId" Source # 
Instance details

Defined in Colog.Message

type FieldType "threadId" = ThreadId

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)
    }

Constructors

MessageField :: forall fieldName m. m (FieldType fieldName) -> MessageField m fieldName 

Instances

Instances details
(KnownSymbol fieldName, a ~ m (FieldType fieldName)) => IsLabel fieldName (a -> WrapTypeable (MessageField m)) Source # 
Instance details

Defined in Colog.Message

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

Constructors

RichMsg 

Fields

Instances

Instances details
Functor (RichMsg m) Source # 
Instance details

Defined in Colog.Message

Methods

fmap :: (a -> b) -> RichMsg m a -> RichMsg m b #

(<$) :: a -> RichMsg m b -> RichMsg m a #

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

fmtRichMessageCustomDefault :: MonadIO m => RichMsg m msg -> (Maybe ThreadId -> Maybe Time -> msg -> Text) -> m Text Source #

Custom formatting function for RichMsg. It extracts ThreadId and Time from fields and allows you to specify how to format them.

Since: 0.4.0.0

upgradeMessageAction :: forall m msg. FieldMap m -> LogAction m (RichMsg m msg) -> LogAction m msg Source #

Allows to extend basic Message type with given dependent map of fields.