co-log-core-0.0.0: Logging library

Safe HaskellSafe
LanguageHaskell2010

Colog.Core.Action

Contents

Description

Implements core data types and combinators for logging actions.

Synopsis

Core type and instances

newtype LogAction m msg Source #

Polymorphic and very general logging action type.

  • msg type variables is an input for logger. It can be Text or custom logging messsage with different fields that you want to format in future.
  • m type variable is for monadic action inside which logging is happening. It can be either IO or some custom pure monad.

Key design point here is that LogAction is:

Constructors

LogAction 

Fields

Instances
Applicative m => Semigroup (LogAction m a) Source #

This instance allows you to join multiple logging actions into single one.

For example, if you have two actions like these:

logToStdout :: LogAction IO String  -- outputs String to terminal
logToFile   :: LogAction IO String  -- appends String to some file

You can create new LogAction that perform both actions one after another using Semigroup:

logToBoth :: LogAction IO String  -- outputs String to both terminal and some file
logToBoth = logToStdout <> logToFile
Instance details

Defined in Colog.Core.Action

Methods

(<>) :: LogAction m a -> LogAction m a -> LogAction m a #

sconcat :: NonEmpty (LogAction m a) -> LogAction m a #

stimes :: Integral b => b -> LogAction m a -> LogAction m a #

Applicative m => Monoid (LogAction m a) Source # 
Instance details

Defined in Colog.Core.Action

Methods

mempty :: LogAction m a #

mappend :: LogAction m a -> LogAction m a -> LogAction m a #

mconcat :: [LogAction m a] -> LogAction m a #

HasLog (LogAction m msg) msg m Source # 
Instance details

Defined in Colog.Core.Class

Methods

getLogAction :: LogAction m msg -> LogAction m msg Source #

setLogAction :: LogAction m msg -> LogAction m msg -> LogAction m msg Source #

Semigroup combinators

foldActions :: (Foldable t, Applicative m) => t (LogAction m a) -> LogAction m a Source #

Joins some Foldable of LogActions into single LogAction using Semigroup instance for LogAction. This is basically specialized version of fold function.

Contravariant combinators

cfilter :: Applicative m => (msg -> Bool) -> LogAction m msg -> LogAction m msg Source #

Takes predicate and performs given logging action only if predicate returns True on input logging message.

cmap :: (a -> b) -> LogAction m b -> LogAction m a Source #

This combinator is contramap from contravariant functor. It is useful when you have something like

data LogRecord = LR
    { lrName    :: LoggerName
    , lrMessage :: Text
    }

and you need to provide LogAction which consumes LogRecord

logRecordAction :: LogAction m LogRecord

when you only have action that consumes Text

logTextAction :: LogAction m Text

With cmap you can do the following:

logRecordAction :: LogAction m LogRecord
logRecordAction = cmap lrMesssage logTextAction

This action will print only lrMessage from LogRecord. But if you have formatting function like this:

formatLogRecord :: LogRecord -> Text

you can apply it instead of lrMessage to log formatted LogRecord as Text.

(>$<) :: (a -> b) -> LogAction m b -> LogAction m a infixr 3 Source #

Operator version of cmap.

(>$) :: b -> LogAction m b -> LogAction m a infixl 4 Source #

This combinator is >$ from contravariant functor. Replaces all locations in the output with the same value. The default definition is contramap . const, so this is a more efficient version.

cbind :: Monad m => (a -> m b) -> LogAction m b -> LogAction m a Source #

cbind combinator is similar to cmap but allows to call monadic functions (functions that require extra context) to extend consumed value. Consider the following example.

You have this logging record:

data LogRecord = LR
    { lrTime    :: UTCTime
    , lrMessage :: Text
    }

and you also have logging consumer inside IO for such record:

logRecordAction :: LogAction IO LogRecord

But you need to return consumer only for Text messages:

logTextAction :: LogAction IO Text

If you have function that can extend Text to LogRecord like the function below:

withTime :: Text -> IO LogRecord
withTime msg = do
    time <- getCurrentTime
    pure (LR time msg)

you can achieve desired behavior with cbind in the following way:

logTextAction :: LogAction IO Text
logTextAction = cbind withTime myAction

Divisible combinators

divide :: Applicative m => (a -> (b, c)) -> LogAction m b -> LogAction m c -> LogAction m a Source #

divide combinator from Divisible type class.

conquer :: Applicative m => LogAction m a Source #

conquer combinator from Divisible type class.

(>*<) :: Applicative m => LogAction m a -> LogAction m b -> LogAction m (a, b) infixr 4 Source #

Operator version of divide id.

(>*) :: Applicative m => LogAction m a -> LogAction m () -> LogAction m a infixr 4 Source #

(*<) :: Applicative m => LogAction m () -> LogAction m a -> LogAction m a infixr 4 Source #

Decidable combinators

lose :: (a -> Void) -> LogAction m a Source #

lose combinator from Decidable type class.

choose :: (a -> Either b c) -> LogAction m b -> LogAction m c -> LogAction m a Source #

choose combinator from Decidable type class.

(>|<) :: LogAction m a -> LogAction m b -> LogAction m (Either a b) infixr 3 Source #

Operator version of choose id.

Comonadic combinators

extract :: Monoid msg => LogAction m msg -> m () Source #

If msg is Monoid then extract performs given log action by passing mempty to it.

extend :: Semigroup msg => (LogAction m msg -> m ()) -> LogAction m msg -> LogAction m msg Source #

This is a comonadic extend. It allows you to chain different transformations on messages.

>>> logToStdout = LogAction putStrLn
>>> f (LogAction l) = l ".f1" *> l ".f2"
>>> g (LogAction l) = l ".g"
>>> unLogAction logToStdout "foo"
foo
>>> unLogAction (extend f logToStdout) "foo"
foo.f1
foo.f2
>>> unLogAction (extend g $ extend f logToStdout) "foo"
foo.g.f1
foo.g.f2
>>> unLogAction (logToStdout =>> f =>> g) "foo"
foo.g.f1
foo.g.f2

(=>>) :: Semigroup msg => LogAction m msg -> (LogAction m msg -> m ()) -> LogAction m msg infixl 1 Source #

extend with the arguments swapped. Dual to >>= for a Monad.

(<<=) :: Semigroup msg => (LogAction m msg -> m ()) -> LogAction m msg -> LogAction m msg infixr 1 Source #

extend in operator form.