@@ -287,9 +287,9 @@ cfilter :: Applicative m => (msg -> Bool) -> LogAction m msg -> LogAction m msg
287
287
cfilter predicate (LogAction action) = LogAction $ \ a -> when (predicate a) (action a)
288
288
{-# INLINE cfilter #-}
289
289
290
- {- | Performs the given logging action only if satisfies the monadic predicate.
291
-
292
- Let's say you want to only to see logs that happened on weekends.
290
+ {- | Performs the given logging action only if satisfies the monadic
291
+ predicate. Let's say you want to only to see logs that happened on
292
+ weekends.
293
293
294
294
@
295
295
isWeekendM :: MessageWithTimestamp -> IO Bool
@@ -299,8 +299,12 @@ And use it with 'cfilterM' like this
299
299
300
300
@
301
301
logMessageAction :: 'LogAction' m MessageWithTimestamp
302
+
303
+ logWeekendAction :: 'LogAction' m MessageWithTimestamp
304
+ logWeekendAction = cfilterM isWeekendM logMessageAction
302
305
@
303
306
307
+ @since 0.2.1.0
304
308
-}
305
309
cfilterM :: Monad m => (msg -> m Bool ) -> LogAction m msg -> LogAction m msg
306
310
cfilterM predicateM (LogAction action) =
@@ -364,7 +368,11 @@ cmapMaybe :: Applicative m => (a -> Maybe b) -> LogAction m b -> LogAction m a
364
368
cmapMaybe f (LogAction action) = LogAction (maybe (pure () ) action . f)
365
369
{-# INLINE cmapMaybe #-}
366
370
367
- -- | Similar to `cmapMaybe` but for convertions that may fail inside a monadic context.
371
+ {- | Similar to `cmapMaybe` but for convertions that may fail inside a
372
+ monadic context.
373
+
374
+ @since 0.2.1.0
375
+ -}
368
376
cmapMaybeM :: Monad m => (a -> m (Maybe b )) -> LogAction m b -> LogAction m a
369
377
cmapMaybeM f (LogAction action) = LogAction (maybe (pure () ) action <=< f)
370
378
{-# INLINE cmapMaybeM #-}
@@ -424,7 +432,6 @@ logTextAction :: 'LogAction' IO Text
424
432
logTextAction = 'cmapM' withTime myAction
425
433
@
426
434
-}
427
-
428
435
cmapM :: Monad m => (a -> m b ) -> LogAction m b -> LogAction m a
429
436
cmapM f (LogAction action) = LogAction (f >=> action)
430
437
{-# INLINE cmapM #-}
@@ -456,6 +463,10 @@ divide f (LogAction actionB) (LogAction actionC) = LogAction $ \(f -> (b, c)) ->
456
463
actionB b *> actionC c
457
464
{-# INLINE divide #-}
458
465
466
+ {- | Monadic version of 'divide'.
467
+
468
+ @since 0.2.1.0
469
+ -}
459
470
divideM :: (Monad m ) => (a -> m (b , c )) -> LogAction m b -> LogAction m c -> LogAction m a
460
471
divideM f (LogAction actionB) (LogAction actionC) =
461
472
LogAction $ \ (f -> mbc) -> mbc >>= (\ (b, c) -> actionB b *> actionC c)
@@ -541,6 +552,10 @@ choose :: (a -> Either b c) -> LogAction m b -> LogAction m c -> LogAction m a
541
552
choose f (LogAction actionB) (LogAction actionC) = LogAction (either actionB actionC . f)
542
553
{-# INLINE choose #-}
543
554
555
+ {- | Monadic version of 'choose'.
556
+
557
+ @since 0.2.1.0
558
+ -}
544
559
chooseM :: Monad m => (a -> m (Either b c )) -> LogAction m b -> LogAction m c -> LogAction m a
545
560
chooseM f (LogAction actionB) (LogAction actionC) = LogAction (either actionB actionC <=< f)
546
561
{-# INLINE chooseM #-}
@@ -726,6 +741,8 @@ to a one that performs the logging in the 'IO' monad using:
726
741
@
727
742
hoistLogAction performPureLogsInIO :: LogAction (PureLogger a) a -> LogAction IO a
728
743
@
744
+
745
+ @since 0.2.1.0
729
746
-}
730
747
hoistLogAction
731
748
:: (forall x . m x -> n x )
0 commit comments