| Copyright | (c) 2018-2020 Kowainik 2021-2023 Co-Log | 
|---|---|
| License | MPL-2.0 | 
| Maintainer | Co-Log <xrom.xkov@gmail.com> | 
| Stability | Stable | 
| Portability | Portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Colog.Core.Action
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
- cfilterM :: Monad m => (msg -> m Bool) -> LogAction m msg -> LogAction m msg
- cmap :: (a -> b) -> LogAction m b -> LogAction m a
- (>$<) :: (a -> b) -> LogAction m b -> LogAction m a
- cmapMaybe :: Applicative m => (a -> Maybe b) -> LogAction m b -> LogAction m a
- cmapMaybeM :: Monad m => (a -> m (Maybe 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
- divideM :: Monad m => (a -> m (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
- chooseM :: Monad m => (a -> m (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
- duplicate :: forall msg m. Semigroup msg => LogAction m msg -> LogAction m (msg, msg)
- multiplicate :: forall f msg m. (Foldable f, Monoid msg) => LogAction m msg -> LogAction m (f msg)
- separate :: forall f msg m. (Traversable f, Applicative m) => LogAction m msg -> LogAction m (f msg)
- hoistLogAction :: (forall x. m x -> n x) -> LogAction m a -> LogAction n a
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 be- Textor 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 either- IOor some custom pure monad.
Key design point here is that LogAction is:
Constructors
| LogAction | |
| Fields 
 | |
Instances
| Contravariant (LogAction m) Source # | |
| UnrepresentableClass => Functor (LogAction m) Source # | ⚠️CAUTION⚠️ This instance is for custom error display only. 
 In case it is used by mistake, the user will see the following: 
 # 207 "srcCologCore/Action.hs" Since: 0.2.1.0 | 
| Applicative m => Monoid (LogAction m a) 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 ::  | 
| HasLog (LogAction m msg) msg m Source # | |
| 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 # overLogAction :: (LogAction m msg -> LogAction m msg) -> LogAction m msg -> LogAction m msg Source # logActionL :: Lens' (LogAction m msg) (LogAction m msg) Source # | |
(<&) :: 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
Combinators that implement interface in the spirit of the following typeclass:
class Contravariant f where
    contramap :: (a -> b) -> f b -> f a
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.
cfilterM :: Monad m => (msg -> m Bool) -> LogAction m msg -> LogAction m msg Source #
Performs the given logging action only if satisfies the monadic predicate. Let's say you want to only to see logs that happened on weekends.
isWeekendM :: MessageWithTimestamp -> IO Bool
And use it with cfilterM like this
logMessageAction ::LogActionm MessageWithTimestamp logWeekendAction ::LogActionm MessageWithTimestamp logWeekendAction = cfilterM isWeekendM logMessageAction
Since: 0.2.1.0
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
cmapMaybe :: Applicative m => (a -> Maybe b) -> LogAction m b -> LogAction m a Source #
cmap for convertions that may fail
cmapMaybeM :: Monad m => (a -> m (Maybe b)) -> LogAction m b -> LogAction m a Source #
Similar to cmapMaybe but for convertions that may fail inside a
monadic context.
Since: 0.2.1.0
(>$) :: 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
Combinators that implement interface in the spirit of the following typeclass:
class Contravariant f => Divisible f where
    conquer :: f a
    divide  :: (a -> (b, c)) -> f b -> f c -> f a
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
divideM :: Monad m => (a -> m (b, c)) -> LogAction m b -> LogAction m c -> LogAction m a Source #
Monadic version of divide.
Since: 0.2.1.0
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
Combinators that implement interface in the spirit of the following typeclass:
class Divisible f => Decidable f where
    lose   :: (a -> Void) -> f a
    choose :: (a -> Either b c) -> f b -> f c -> f a
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
chooseM :: Monad m => (a -> m (Either b c)) -> LogAction m b -> LogAction m c -> LogAction m a Source #
Monadic version of choose.
Since: 0.2.1.0
Comonadic combinators
Combinators that implement interface in the spirit of the following typeclass:
class Functor w => Comonad w where
    extract   :: w a -> a
    duplicate :: w a -> w (w a)
    extend    :: (w a -> b) -> w a -> w b
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">>>logStringStdout <& "foo"foo>>>extend f logStringStdout <& "foo"foo.f1 foo.f2>>>(extend g $ extend f logStringStdout) <& "foo"foo.g.f1 foo.g.f2>>>(logStringStdout =>> f =>> g) <& "foo"foo.g.f1 foo.g.f2
(=>>) :: Semigroup msg => LogAction m msg -> (LogAction m msg -> m ()) -> LogAction m msg infixl 1 Source #
(<<=) :: Semigroup msg => (LogAction m msg -> m ()) -> LogAction m msg -> LogAction m msg infixr 1 Source #
extend in operator form.
duplicate :: forall msg m. Semigroup msg => LogAction m msg -> LogAction m (msg, msg) Source #
Converts any LogAction that can log single message to the LogAction
that can log two messages. The new LogAction behaves in the following way:
- Joins two messages of type msgusing<>operator fromSemigroup.
- Passes resulted message to the given LogAction.
>>>:{let logger :: LogAction IO [Int] logger = logPrint in duplicate logger <& ([3, 4], [42, 10]) :} [3,4,42,10]
Implementation note:
True and fair translation of the duplicate function from the Comonad
interface should result in the LogAction of the following form:
msg -> msg -> m ()
In order to capture this behavior, duplicate should have the following type:
duplicate :: Semigroup msg => LogAction m msg -> LogAction (Compose ((->) msg) m) msg
However, it's quite awkward to work with such type. It's a known fact that the
following two types are isomorphic (see functions curry and uncurry):
a -> b -> c (a, b) -> c
So using this fact we can come up with the simpler interface.
multiplicate :: forall f msg m. (Foldable f, Monoid msg) => LogAction m msg -> LogAction m (f msg) Source #
separate :: forall f msg m. (Traversable f, Applicative m) => LogAction m msg -> LogAction m (f msg) Source #
Like multiplicate but instead of logging a batch of messages it logs each
of them separately.
>>>:{let logger :: LogAction IO Int logger = logPrint in separate logger <& [1..5] :} 1 2 3 4 5
Since: 0.2.1.0
Higher-order combinators
hoistLogAction :: (forall x. m x -> n x) -> LogAction m a -> LogAction n a Source #
Allows changing the internal monadic action.
Let's say we have a pure logger action using PureLogger
and we want to log all messages into IO instead.
If we provide the following function:
performPureLogsInIO :: PureLogger a -> IO a
then we can convert a logger action that uses a pure monad
to a one that performs the logging in the IO monad using:
hoistLogAction performPureLogsInIO :: LogAction (PureLogger a) a -> LogAction IO a
Since: 0.2.1.0