extensible-effects-concurrent-0.3.0.1: Message passing concurrency as extensible-effect

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Log

Contents

Description

A logging effect based on MonadLog.

Synopsis

Logging Effect

data Logs message a where Source #

Logging effect type, parameterized by a log message type.

Constructors

LogMsg :: message -> Logs message () 

logMsg :: Member (Logs m) r => m -> Eff r () Source #

Log a message.

foldLog :: forall r m a. Member (Logs m) r => (m -> Eff r ()) -> Eff r a -> Eff r a Source #

Change, add or remove log messages.

Requirements:

  • All log meta data for typical prod code can be added without changing much of the code
  • Add timestamp to a log messages of a sub-computation.
  • Write some messages to a file.
  • Log something extra, e.g. runtime memory usage in load tests

Approach: Install a callback that sneaks into to log message sending/receiving, to intercept the messages and execute some code and then return a new message.

foldLogFast :: forall r m a f. (Foldable f, Member (Logs m) r) => (m -> f m) -> Eff r a -> Eff r a Source #

Change, add or remove log messages without side effects, faster than foldLog.

Requirements:

  • Tests run fast in unit tests so travis won't time out
  • Drop debug logs
  • Grep like log filtering

Approach: Install a callback that sneaks into to log message sending/receiving, to intercept the messages and execute some code and then return a new message.

captureLogs :: Eff (Logs message ': r) a -> Eff r (a, Seq message) Source #

Capture the logs in a Seq.

ignoreLogs :: Eff (Logs message ': r) a -> Eff r a Source #

Throw away all log messages.

handleLogsWith :: forall m r message a. (Monad m, SetMember Lift (Lift m) r) => Eff (Logs message ': r) a -> (forall b. (Handler m message -> m b) -> m b) -> Eff r a Source #

Handle Logs effects using LoggingT Handlers.

Concurrent Logging

data LogChannel message Source #

A log channel processes logs from the Logs effect by en-queuing them in a shared queue read from a seperate processes. A channel can contain log message filters.

logToChannel :: forall r message a. SetMember Lift (Lift IO) r => LogChannel message -> Eff (Logs message ': r) a -> Eff r a Source #

Send the log messages to a LogChannel.

noLogger :: LogChannel message Source #

Create a LogChannel that will discard all messages sent via forwardLogstochannel or logChannelPutIO.

forkLogger Source #

Arguments

:: (Typeable message, Show message) 
=> Int

Size of the log message input queue. If the queue is full, message are dropped silently.

-> (message -> IO ())

An IO action to log the messages

-> Maybe message

Optional first message to log

-> IO (LogChannel message) 

Fork a new process, that applies a monadic action to all log messages sent via logToChannel or logChannelPutIO.

filterLogChannel :: (message -> Bool) -> LogChannel message -> LogChannel message Source #

Filter logs sent to a LogChannel using a predicate.

joinLogChannel :: (Show message, Typeable message) => Maybe message -> LogChannel message -> IO () Source #

Close a log channel created by e.g. forkLogger. Message already enqueue are handled, as well as an optional final message. Subsequent log message will not be handled anymore. If the log channel must be closed immediately, use killLogChannel instead.

killLogChannel :: (Show message, Typeable message) => Maybe message -> LogChannel message -> IO () Source #

Close a log channel quickly, without logging messages already in the queue. Subsequent logging requests will not be handled anymore. If the log channel must be closed without loosing any messages, use joinLogChannel instead.

closeLogChannelAfter :: (Show message, Typeable message, IsString message) => Maybe message -> LogChannel message -> IO a -> IO a Source #

Run an action and close a LogChannel created by noLogger, forkLogger or filterLogChannel afterwards using joinLogChannel. If a SomeException was thrown, the log channel is killed with killLogChannel, and the exception is re-thrown.

logChannelBracket Source #

Arguments

:: (Show message, Typeable message) 
=> Int

Size of the log message input queue. If the queue is full, message are dropped silently.

-> Maybe message

Optional first message to log

-> Maybe message

Optional last message to log

-> (LogChannel message -> IO a)

An IO action that will use the LogChannel, after the action returns (even because of an exception) the log channel is destroyed.

-> LoggingT message IO a 

Wrap LogChannel creation and destruction around a monad action in brackety manner. This function uses joinLogChannel, so en-queued messages are flushed on exit. The resulting action in in the LoggingT monad, which is essentially a reader for the log handler function.

logChannelPutIO :: LogChannel message -> message -> IO () Source #

Enqueue a log message into a log channel