@@ -34,6 +34,8 @@ module Colog.Core.Severity
34
34
, pattern W
35
35
, pattern E
36
36
, filterBySeverity
37
+ , WithSeverity (.. )
38
+ , mapSeverity
37
39
) where
38
40
39
41
import Data.Ix (Ix )
@@ -102,3 +104,36 @@ filterBySeverity
102
104
-> LogAction m a
103
105
filterBySeverity s fs = cfilter (\ a -> fs a >= s)
104
106
{-# INLINE filterBySeverity #-}
107
+
108
+ -- Note: the order of the fields here is to allow the constructor to be used infix.
109
+ {-| A message tagged with a 'Severity'.
110
+
111
+ It is common to want to log various types of messages tagged with a severity.
112
+ 'WithSeverity' provides a standard way to do so while allowing the messages to be processed independently of the severity.
113
+
114
+ It is easy to 'cmap' over a 'LogAction m (WithSeverity a)', or to filter based on the severity.
115
+
116
+ @
117
+ logSomething :: LogAction m (WithSeverity String) -> m ()
118
+ logSomething logger = logger <& "hello" `WithSeverity` Info
119
+
120
+ cmap' :: (b -> a) -> LogAction m (WithSeverity a) -> LogAction m (WithSeverity b)
121
+ cmap' f action = cmap (fmap f) action
122
+
123
+ filterBySeverity' :: (Applicative m) => Severity -> LogAction m (WithSeverity a) -> LogAction m (WithSeverity a)
124
+ filterBySeverity' threshold action = filterBySeverity threshold getSeverity action
125
+ @
126
+ -}
127
+ data WithSeverity msg = WithSeverity { getMsg :: msg , getSeverity :: Severity }
128
+ deriving stock (Show , Eq , Ord , Functor , Foldable , Traversable )
129
+
130
+ {- | Map the given function over the severity of a 'WithSeverity'.
131
+
132
+ This can be useful to operate generically over the severity, for example:
133
+ @
134
+ suppressErrors :: LogAction m (WithSeverity msg) -> LogAction m (WithSeverity msg)
135
+ suppressErrors = cmap (mapSeverity (\s -> if s == Error then Warning else s))
136
+ @
137
+ -}
138
+ mapSeverity :: (Severity -> Severity ) -> WithSeverity msg -> WithSeverity msg
139
+ mapSeverity f (WithSeverity msg sev) = WithSeverity msg (f sev)
0 commit comments