| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Colog.Core.Action
Contents
Description
Implements core data types and combinators for logging actions.
Synopsis
- newtype LogAction m msg = LogAction {
- unLogAction :: msg -> m ()
- (<&) :: LogAction m msg -> msg -> m ()
- (&>) :: msg -> LogAction m msg -> m ()
- foldActions :: (Foldable t, Applicative m) => t (LogAction m a) -> LogAction m a
- cfilter :: Applicative m => (msg -> Bool) -> LogAction m msg -> LogAction m msg
- cmap :: (a -> b) -> LogAction m b -> LogAction m a
- (>$<) :: (a -> b) -> LogAction m b -> LogAction m a
- (>$) :: b -> LogAction m b -> LogAction m a
- cmapM :: Monad m => (a -> m b) -> LogAction m b -> LogAction m a
- divide :: Applicative m => (a -> (b, c)) -> LogAction m b -> LogAction m c -> LogAction m a
- conquer :: Applicative m => LogAction m a
- (>*<) :: Applicative m => LogAction m a -> LogAction m b -> LogAction m (a, b)
- (>*) :: Applicative m => LogAction m a -> LogAction m () -> LogAction m a
- (*<) :: Applicative m => LogAction m () -> LogAction m a -> LogAction m a
- lose :: (a -> Void) -> LogAction m a
- choose :: (a -> Either b c) -> LogAction m b -> LogAction m c -> LogAction m a
- (>|<) :: LogAction m a -> LogAction m b -> LogAction m (Either a b)
- extract :: Monoid msg => LogAction m msg -> m ()
- extend :: Semigroup msg => (LogAction m msg -> m ()) -> LogAction m msg -> LogAction m msg
- (=>>) :: Semigroup msg => LogAction m msg -> (LogAction m msg -> m ()) -> LogAction m msg
- (<<=) :: Semigroup msg => (LogAction m msg -> m ()) -> LogAction m msg -> LogAction m msg
Core type and instances
newtype LogAction m msg Source #
Polymorphic and very general logging action type.
msgtype variables is an input for logger. It can beTextor custom logging messsage with different fields that you want to format in future.mtype variable is for monadic action inside which logging is happening. It can be eitherIOor some custom pure monad.
Key design point here is that LogAction is:
Semigroup- Contravariant
- Comonad
Constructors
| LogAction | |
Fields
| |
Instances
| Contravariant (LogAction m) Source # | |
| 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 :: You can create new logToBoth :: |
| Applicative m => Monoid (LogAction m a) Source # | |
| HasLog (LogAction m msg) msg m Source # | |
Defined in Colog.Core.Class | |
(<&) :: LogAction m msg -> msg -> m () infix 5 Source #
Operator version of unLogAction. Note that because of the types, something like:
action <& msg1 <& msg2
doesn't make sense. Instead you want:
action msg1> action <& msg2
In addition, because <& has higher precedence than the other operators in this
module, the following:
f >$< action <& msg
is equivalent to:
(f >$< action) <& msg
Semigroup combinators
foldActions :: (Foldable t, Applicative m) => t (LogAction m a) -> LogAction m a Source #
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 ::LogActionm LogRecord logRecordAction =cmaplrMesssage 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.
>>>1 &> (show >$< logStringStdout)1
(>$) :: 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.
>>>"Hello?" &> ("OUT OF SERVICE" >$ logStringStdout)OUT OF SERVICE>>>("OUT OF SERVICE" >$ logStringStdout) <& 42OUT OF SERVICE
cmapM :: Monad m => (a -> m b) -> LogAction m b -> LogAction m a Source #
cmapM 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->IOLogRecord withTime msg = do time <- getCurrentTime pure (LR time msg)
you can achieve desired behavior with cmapM in the following way:
logTextAction ::LogActionIO Text logTextAction =cmapMwithTime 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.
>>>logInt = LogAction print>>>"ABC" &> divide (\s -> (s, length s)) logStringStdout logIntABC 3
conquer :: Applicative m => LogAction m a Source #
conquer combinator from Divisible type class.
Concretely, this is a LogAction that does nothing:
>>>conquer <& "hello?">>>"hello?" &> conquer
(>*) :: Applicative m => LogAction m a -> LogAction m () -> LogAction m a infixr 4 Source #
Perform a constant log action after another.
>>>logHello = LogAction (const (putStrLn "Hello!"))>>>"Greetings!" &> (logStringStdout >* logHello)Greetings! Hello!
(*<) :: Applicative m => LogAction m () -> LogAction m a -> LogAction m a infixr 4 Source #
A flipped version of >*
Decidable combinators
choose :: (a -> Either b c) -> LogAction m b -> LogAction m c -> LogAction m a Source #
choose combinator from Decidable type class.
>>>logInt = LogAction print>>>f = choose (\a -> if a < 0 then Left "Negative" else Right a)>>>f logStringStdout logInt <& 11>>>f logStringStdout logInt <& (-1)Negative
Comonadic combinators
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.
>>>f (LogAction l) = l ".f1" *> l ".f2">>>g (LogAction l) = l ".g">>>unLogAction logStringStdout "foo"foo>>>unLogAction (extend f logStringStdout) "foo"foo.f1 foo.f2>>>unLogAction (extend g $ extend f logStringStdout) "foo"foo.g.f1 foo.g.f2>>>unLogAction (logStringStdout =>> f =>> g) "foo"foo.g.f1 foo.g.f2