Safe Haskell | None |
---|---|
Language | GHC2021 |
Unclog.Subscriber
Synopsis
- newtype Subscriber (m :: Type -> Type) = MkSubscriber {
- runSubscriber :: Codensity m (LogEntry -> m ())
- colourSubscriber :: forall (m :: Type -> Type). MonadIO m => LogLevel -> Handle -> Subscriber m
- simpleSubscriber :: forall (m :: Type -> Type). MonadIO m => LogLevel -> Handle -> Subscriber m
- fileSubscriber :: forall (m :: Type -> Type). MonadUnliftIO m => LogLevel -> FilePath -> Subscriber m
- withLoggingWithSubscribers :: MonadUnliftIO m => [Subscriber m] -> (PLogChan -> m r) -> m r
- newLogChan :: STM PLogChan
- newLogChanIO :: MonadIO m => m PLogChan
- subscribeLog :: PLogChan -> STM SLogChan
- readLogEntry :: SLogChan -> STM LogEntry
- withSubscriber :: Subscriber m -> ((LogEntry -> m ()) -> m b) -> m b
- mkSubscriber :: (forall r. ((LogEntry -> m ()) -> m r) -> m r) -> Subscriber m
- mkSubscriberSimple :: (LogEntry -> m ()) -> Subscriber m
- bracketSubscriber :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> LogEntry -> m ()) -> Subscriber m
- refSubscriber :: forall (m :: Type -> Type). MonadIO m => IORef [LogEntry] -> Subscriber m
subscribing to a log channel
newtype Subscriber (m :: Type -> Type) Source #
a Subscriber
is something that can observe log entries and do something with them in the Monad m
Constructors
MkSubscriber | |
Fields
|
Arguments
:: forall (m :: Type -> Type). MonadIO m | |
=> LogLevel | the lowest loglevel to still log |
-> Handle | the handle to log to |
-> Subscriber m |
write a log entry to a handle, printing all information, but use colour
Arguments
:: forall (m :: Type -> Type). MonadIO m | |
=> LogLevel | the lowest loglevel to still log |
-> Handle | the handle to log to |
-> Subscriber m |
write a log entry to a handle, printing all information
Arguments
:: forall (m :: Type -> Type). MonadUnliftIO m | |
=> LogLevel | the lowest loglevel to still log |
-> FilePath | the file to log (append) to |
-> Subscriber m |
create a simple subscriber that writes to a file
run a logging situation
withLoggingWithSubscribers Source #
Arguments
:: MonadUnliftIO m | |
=> [Subscriber m] | a list of subscribers |
-> (PLogChan -> m r) | a channel, a client can write to |
-> m r |
it is not a priori unsafe to escape the chan out of the context, it will just mean that all the subscribers are gone and nothing is logged anymore
creating, subscribing and reading from channels
newLogChan :: STM PLogChan Source #
create a new LogChan
subscribeLog :: PLogChan -> STM SLogChan Source #
subscribe to a publishing log chan to obtain a subscriber log chan
helpers
withSubscriber :: Subscriber m -> ((LogEntry -> m ()) -> m b) -> m b Source #
destruct a subscriber
mkSubscriber :: (forall r. ((LogEntry -> m ()) -> m r) -> m r) -> Subscriber m Source #
make a subscriber with a possible clean up (useful if you need to bracket your subscriber)
mkSubscriberSimple :: (LogEntry -> m ()) -> Subscriber m Source #
make a subscriber from a simple log function
Arguments
:: MonadUnliftIO m | |
=> m a | acquire the resource |
-> (a -> m b) | release the resource |
-> (a -> LogEntry -> m ()) | how to write a log entry given a resource |
-> Subscriber m |
build a subscriber that requires a resource
refSubscriber :: forall (m :: Type -> Type). MonadIO m => IORef [LogEntry] -> Subscriber m Source #
write log entries to an IORef