{-# LANGUAGE PatternSynonyms #-}
module Colog.Core.Severity
       ( Severity (..)
         
         
       , pattern D
       , pattern I
       , pattern W
       , pattern E
       , filterBySeverity
       , WithSeverity (..)
       , mapSeverity
       ) where
import Data.Ix (Ix)
import Colog.Core.Action (LogAction (..), cfilter)
data Severity
    
    = Debug
    
    | Info
    
    | Warning
    
    | Error
    deriving stock (Int -> Severity -> ShowS
[Severity] -> ShowS
Severity -> String
(Int -> Severity -> ShowS)
-> (Severity -> String) -> ([Severity] -> ShowS) -> Show Severity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Severity -> ShowS
showsPrec :: Int -> Severity -> ShowS
$cshow :: Severity -> String
show :: Severity -> String
$cshowList :: [Severity] -> ShowS
showList :: [Severity] -> ShowS
Show, ReadPrec [Severity]
ReadPrec Severity
Int -> ReadS Severity
ReadS [Severity]
(Int -> ReadS Severity)
-> ReadS [Severity]
-> ReadPrec Severity
-> ReadPrec [Severity]
-> Read Severity
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Severity
readsPrec :: Int -> ReadS Severity
$creadList :: ReadS [Severity]
readList :: ReadS [Severity]
$creadPrec :: ReadPrec Severity
readPrec :: ReadPrec Severity
$creadListPrec :: ReadPrec [Severity]
readListPrec :: ReadPrec [Severity]
Read, Severity -> Severity -> Bool
(Severity -> Severity -> Bool)
-> (Severity -> Severity -> Bool) -> Eq Severity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Severity -> Severity -> Bool
== :: Severity -> Severity -> Bool
$c/= :: Severity -> Severity -> Bool
/= :: Severity -> Severity -> Bool
Eq, Eq Severity
Eq Severity =>
(Severity -> Severity -> Ordering)
-> (Severity -> Severity -> Bool)
-> (Severity -> Severity -> Bool)
-> (Severity -> Severity -> Bool)
-> (Severity -> Severity -> Bool)
-> (Severity -> Severity -> Severity)
-> (Severity -> Severity -> Severity)
-> Ord Severity
Severity -> Severity -> Bool
Severity -> Severity -> Ordering
Severity -> Severity -> Severity
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Severity -> Severity -> Ordering
compare :: Severity -> Severity -> Ordering
$c< :: Severity -> Severity -> Bool
< :: Severity -> Severity -> Bool
$c<= :: Severity -> Severity -> Bool
<= :: Severity -> Severity -> Bool
$c> :: Severity -> Severity -> Bool
> :: Severity -> Severity -> Bool
$c>= :: Severity -> Severity -> Bool
>= :: Severity -> Severity -> Bool
$cmax :: Severity -> Severity -> Severity
max :: Severity -> Severity -> Severity
$cmin :: Severity -> Severity -> Severity
min :: Severity -> Severity -> Severity
Ord, Int -> Severity
Severity -> Int
Severity -> [Severity]
Severity -> Severity
Severity -> Severity -> [Severity]
Severity -> Severity -> Severity -> [Severity]
(Severity -> Severity)
-> (Severity -> Severity)
-> (Int -> Severity)
-> (Severity -> Int)
-> (Severity -> [Severity])
-> (Severity -> Severity -> [Severity])
-> (Severity -> Severity -> [Severity])
-> (Severity -> Severity -> Severity -> [Severity])
-> Enum Severity
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Severity -> Severity
succ :: Severity -> Severity
$cpred :: Severity -> Severity
pred :: Severity -> Severity
$ctoEnum :: Int -> Severity
toEnum :: Int -> Severity
$cfromEnum :: Severity -> Int
fromEnum :: Severity -> Int
$cenumFrom :: Severity -> [Severity]
enumFrom :: Severity -> [Severity]
$cenumFromThen :: Severity -> Severity -> [Severity]
enumFromThen :: Severity -> Severity -> [Severity]
$cenumFromTo :: Severity -> Severity -> [Severity]
enumFromTo :: Severity -> Severity -> [Severity]
$cenumFromThenTo :: Severity -> Severity -> Severity -> [Severity]
enumFromThenTo :: Severity -> Severity -> Severity -> [Severity]
Enum, Severity
Severity -> Severity -> Bounded Severity
forall a. a -> a -> Bounded a
$cminBound :: Severity
minBound :: Severity
$cmaxBound :: Severity
maxBound :: Severity
Bounded, Ord Severity
Ord Severity =>
((Severity, Severity) -> [Severity])
-> ((Severity, Severity) -> Severity -> Int)
-> ((Severity, Severity) -> Severity -> Int)
-> ((Severity, Severity) -> Severity -> Bool)
-> ((Severity, Severity) -> Int)
-> ((Severity, Severity) -> Int)
-> Ix Severity
(Severity, Severity) -> Int
(Severity, Severity) -> [Severity]
(Severity, Severity) -> Severity -> Bool
(Severity, Severity) -> Severity -> Int
forall a.
Ord a =>
((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
$crange :: (Severity, Severity) -> [Severity]
range :: (Severity, Severity) -> [Severity]
$cindex :: (Severity, Severity) -> Severity -> Int
index :: (Severity, Severity) -> Severity -> Int
$cunsafeIndex :: (Severity, Severity) -> Severity -> Int
unsafeIndex :: (Severity, Severity) -> Severity -> Int
$cinRange :: (Severity, Severity) -> Severity -> Bool
inRange :: (Severity, Severity) -> Severity -> Bool
$crangeSize :: (Severity, Severity) -> Int
rangeSize :: (Severity, Severity) -> Int
$cunsafeRangeSize :: (Severity, Severity) -> Int
unsafeRangeSize :: (Severity, Severity) -> Int
Ix)
pattern D, I, W, E :: Severity
pattern $mD :: forall {r}. Severity -> ((# #) -> r) -> ((# #) -> r) -> r
$bD :: Severity
D <- Debug   where D = Severity
Debug
pattern $mI :: forall {r}. Severity -> ((# #) -> r) -> ((# #) -> r) -> r
$bI :: Severity
I <- Info    where I = Severity
Info
pattern $mW :: forall {r}. Severity -> ((# #) -> r) -> ((# #) -> r) -> r
$bW :: Severity
W <- Warning where W = Severity
Warning
pattern $mE :: forall {r}. Severity -> ((# #) -> r) -> ((# #) -> r) -> r
$bE :: Severity
E <- Error   where E = Severity
Error
{-# COMPLETE D, I, W, E #-}
filterBySeverity
    :: Applicative m
    => Severity
    -> (a -> Severity)
    -> LogAction m a
    -> LogAction m a
filterBySeverity :: forall (m :: * -> *) a.
Applicative m =>
Severity -> (a -> Severity) -> LogAction m a -> LogAction m a
filterBySeverity Severity
s a -> Severity
fs = (a -> Bool) -> LogAction m a -> LogAction m a
forall (m :: * -> *) msg.
Applicative m =>
(msg -> Bool) -> LogAction m msg -> LogAction m msg
cfilter (\a
a -> a -> Severity
fs a
a Severity -> Severity -> Bool
forall a. Ord a => a -> a -> Bool
>= Severity
s)
{-# INLINE filterBySeverity #-}
data WithSeverity msg = WithSeverity { forall msg. WithSeverity msg -> msg
getMsg :: msg , forall msg. WithSeverity msg -> Severity
getSeverity :: Severity }
  deriving stock (Int -> WithSeverity msg -> ShowS
[WithSeverity msg] -> ShowS
WithSeverity msg -> String
(Int -> WithSeverity msg -> ShowS)
-> (WithSeverity msg -> String)
-> ([WithSeverity msg] -> ShowS)
-> Show (WithSeverity msg)
forall msg. Show msg => Int -> WithSeverity msg -> ShowS
forall msg. Show msg => [WithSeverity msg] -> ShowS
forall msg. Show msg => WithSeverity msg -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall msg. Show msg => Int -> WithSeverity msg -> ShowS
showsPrec :: Int -> WithSeverity msg -> ShowS
$cshow :: forall msg. Show msg => WithSeverity msg -> String
show :: WithSeverity msg -> String
$cshowList :: forall msg. Show msg => [WithSeverity msg] -> ShowS
showList :: [WithSeverity msg] -> ShowS
Show, WithSeverity msg -> WithSeverity msg -> Bool
(WithSeverity msg -> WithSeverity msg -> Bool)
-> (WithSeverity msg -> WithSeverity msg -> Bool)
-> Eq (WithSeverity msg)
forall msg. Eq msg => WithSeverity msg -> WithSeverity msg -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall msg. Eq msg => WithSeverity msg -> WithSeverity msg -> Bool
== :: WithSeverity msg -> WithSeverity msg -> Bool
$c/= :: forall msg. Eq msg => WithSeverity msg -> WithSeverity msg -> Bool
/= :: WithSeverity msg -> WithSeverity msg -> Bool
Eq, Eq (WithSeverity msg)
Eq (WithSeverity msg) =>
(WithSeverity msg -> WithSeverity msg -> Ordering)
-> (WithSeverity msg -> WithSeverity msg -> Bool)
-> (WithSeverity msg -> WithSeverity msg -> Bool)
-> (WithSeverity msg -> WithSeverity msg -> Bool)
-> (WithSeverity msg -> WithSeverity msg -> Bool)
-> (WithSeverity msg -> WithSeverity msg -> WithSeverity msg)
-> (WithSeverity msg -> WithSeverity msg -> WithSeverity msg)
-> Ord (WithSeverity msg)
WithSeverity msg -> WithSeverity msg -> Bool
WithSeverity msg -> WithSeverity msg -> Ordering
WithSeverity msg -> WithSeverity msg -> WithSeverity msg
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall msg. Ord msg => Eq (WithSeverity msg)
forall msg. Ord msg => WithSeverity msg -> WithSeverity msg -> Bool
forall msg.
Ord msg =>
WithSeverity msg -> WithSeverity msg -> Ordering
forall msg.
Ord msg =>
WithSeverity msg -> WithSeverity msg -> WithSeverity msg
$ccompare :: forall msg.
Ord msg =>
WithSeverity msg -> WithSeverity msg -> Ordering
compare :: WithSeverity msg -> WithSeverity msg -> Ordering
$c< :: forall msg. Ord msg => WithSeverity msg -> WithSeverity msg -> Bool
< :: WithSeverity msg -> WithSeverity msg -> Bool
$c<= :: forall msg. Ord msg => WithSeverity msg -> WithSeverity msg -> Bool
<= :: WithSeverity msg -> WithSeverity msg -> Bool
$c> :: forall msg. Ord msg => WithSeverity msg -> WithSeverity msg -> Bool
> :: WithSeverity msg -> WithSeverity msg -> Bool
$c>= :: forall msg. Ord msg => WithSeverity msg -> WithSeverity msg -> Bool
>= :: WithSeverity msg -> WithSeverity msg -> Bool
$cmax :: forall msg.
Ord msg =>
WithSeverity msg -> WithSeverity msg -> WithSeverity msg
max :: WithSeverity msg -> WithSeverity msg -> WithSeverity msg
$cmin :: forall msg.
Ord msg =>
WithSeverity msg -> WithSeverity msg -> WithSeverity msg
min :: WithSeverity msg -> WithSeverity msg -> WithSeverity msg
Ord, (forall a b. (a -> b) -> WithSeverity a -> WithSeverity b)
-> (forall a b. a -> WithSeverity b -> WithSeverity a)
-> Functor WithSeverity
forall a b. a -> WithSeverity b -> WithSeverity a
forall a b. (a -> b) -> WithSeverity a -> WithSeverity b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> WithSeverity a -> WithSeverity b
fmap :: forall a b. (a -> b) -> WithSeverity a -> WithSeverity b
$c<$ :: forall a b. a -> WithSeverity b -> WithSeverity a
<$ :: forall a b. a -> WithSeverity b -> WithSeverity a
Functor, (forall m. Monoid m => WithSeverity m -> m)
-> (forall m a. Monoid m => (a -> m) -> WithSeverity a -> m)
-> (forall m a. Monoid m => (a -> m) -> WithSeverity a -> m)
-> (forall a b. (a -> b -> b) -> b -> WithSeverity a -> b)
-> (forall a b. (a -> b -> b) -> b -> WithSeverity a -> b)
-> (forall b a. (b -> a -> b) -> b -> WithSeverity a -> b)
-> (forall b a. (b -> a -> b) -> b -> WithSeverity a -> b)
-> (forall a. (a -> a -> a) -> WithSeverity a -> a)
-> (forall a. (a -> a -> a) -> WithSeverity a -> a)
-> (forall a. WithSeverity a -> [a])
-> (forall a. WithSeverity a -> Bool)
-> (forall a. WithSeverity a -> Int)
-> (forall a. Eq a => a -> WithSeverity a -> Bool)
-> (forall a. Ord a => WithSeverity a -> a)
-> (forall a. Ord a => WithSeverity a -> a)
-> (forall a. Num a => WithSeverity a -> a)
-> (forall a. Num a => WithSeverity a -> a)
-> Foldable WithSeverity
forall a. Eq a => a -> WithSeverity a -> Bool
forall a. Num a => WithSeverity a -> a
forall a. Ord a => WithSeverity a -> a
forall m. Monoid m => WithSeverity m -> m
forall a. WithSeverity a -> Bool
forall a. WithSeverity a -> Int
forall a. WithSeverity a -> [a]
forall a. (a -> a -> a) -> WithSeverity a -> a
forall m a. Monoid m => (a -> m) -> WithSeverity a -> m
forall b a. (b -> a -> b) -> b -> WithSeverity a -> b
forall a b. (a -> b -> b) -> b -> WithSeverity a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => WithSeverity m -> m
fold :: forall m. Monoid m => WithSeverity m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> WithSeverity a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> WithSeverity a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> WithSeverity a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> WithSeverity a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> WithSeverity a -> b
foldr :: forall a b. (a -> b -> b) -> b -> WithSeverity a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> WithSeverity a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> WithSeverity a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> WithSeverity a -> b
foldl :: forall b a. (b -> a -> b) -> b -> WithSeverity a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> WithSeverity a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> WithSeverity a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> WithSeverity a -> a
foldr1 :: forall a. (a -> a -> a) -> WithSeverity a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> WithSeverity a -> a
foldl1 :: forall a. (a -> a -> a) -> WithSeverity a -> a
$ctoList :: forall a. WithSeverity a -> [a]
toList :: forall a. WithSeverity a -> [a]
$cnull :: forall a. WithSeverity a -> Bool
null :: forall a. WithSeverity a -> Bool
$clength :: forall a. WithSeverity a -> Int
length :: forall a. WithSeverity a -> Int
$celem :: forall a. Eq a => a -> WithSeverity a -> Bool
elem :: forall a. Eq a => a -> WithSeverity a -> Bool
$cmaximum :: forall a. Ord a => WithSeverity a -> a
maximum :: forall a. Ord a => WithSeverity a -> a
$cminimum :: forall a. Ord a => WithSeverity a -> a
minimum :: forall a. Ord a => WithSeverity a -> a
$csum :: forall a. Num a => WithSeverity a -> a
sum :: forall a. Num a => WithSeverity a -> a
$cproduct :: forall a. Num a => WithSeverity a -> a
product :: forall a. Num a => WithSeverity a -> a
Foldable, Functor WithSeverity
Foldable WithSeverity
(Functor WithSeverity, Foldable WithSeverity) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> WithSeverity a -> f (WithSeverity b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    WithSeverity (f a) -> f (WithSeverity a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> WithSeverity a -> m (WithSeverity b))
-> (forall (m :: * -> *) a.
    Monad m =>
    WithSeverity (m a) -> m (WithSeverity a))
-> Traversable WithSeverity
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
WithSeverity (m a) -> m (WithSeverity a)
forall (f :: * -> *) a.
Applicative f =>
WithSeverity (f a) -> f (WithSeverity a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WithSeverity a -> m (WithSeverity b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WithSeverity a -> f (WithSeverity b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WithSeverity a -> f (WithSeverity b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WithSeverity a -> f (WithSeverity b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
WithSeverity (f a) -> f (WithSeverity a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
WithSeverity (f a) -> f (WithSeverity a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WithSeverity a -> m (WithSeverity b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WithSeverity a -> m (WithSeverity b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
WithSeverity (m a) -> m (WithSeverity a)
sequence :: forall (m :: * -> *) a.
Monad m =>
WithSeverity (m a) -> m (WithSeverity a)
Traversable)
mapSeverity :: (Severity -> Severity) -> WithSeverity msg -> WithSeverity msg
mapSeverity :: forall msg.
(Severity -> Severity) -> WithSeverity msg -> WithSeverity msg
mapSeverity Severity -> Severity
f (WithSeverity msg
msg Severity
sev) = msg -> Severity -> WithSeverity msg
forall msg. msg -> Severity -> WithSeverity msg
WithSeverity msg
msg (Severity -> Severity
f Severity
sev)
{-# INLINE mapSeverity #-}