co-log-0.3.0.0: Composable Contravariant Comonadic Logging Library

Copyright(c) 2018-2019 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Colog.Message

Contents

Description

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

Synopsis

Basic message type

data Msg sev Source #

General logging message data type. Contains the following fields:

  1. Polymorhic 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.

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.

Formatting functions

fmtMessage :: Message -> Text Source #

Formats the Message type in 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 richer format.

showSeverity :: Severity -> Text Source #

Formats severity in different colours with alignment.

showSourceLoc :: CallStack -> Text Source #

Show 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
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
(KnownSymbol fieldName, a ~ m (FieldType fieldName)) => IsLabel fieldName (a -> WrapTypeable (MessageField m)) Source # 
Instance details

Defined in Colog.Message

Methods

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

data RichMessage (m :: Type -> Type) Source #

Contains additional data to Message to display more verbose information.

Constructors

RichMessage 

fmtRichMessageDefault :: MonadIO m => RichMessage m -> m Text Source #

Formats RichMessage in the following way:

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

Examples:

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

See fmtMessage if you don't need both time and thread id.

upgradeMessageAction :: forall m. FieldMap m -> LogAction m (RichMessage m) -> LogAction m Message Source #

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