co-log-core-0.3.2.0: Composable Contravariant Comonadic Logging Library
Copyright(c) 2018-2020 Kowainik 2021-2022 Co-Log
LicenseMPL-2.0
MaintainerCo-Log <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Colog.Core.Severity

Contents

Description

This module introduces Severity data type for expressing how severe the message is. Also, it contains useful functions and patterns for work with Severity.

SeverityPatternMeaningExample
DebugDInformation useful for debug purposesInternal function call logs
InfoINormal operational informationFinish file uploading
WarningWGeneral warnings, non-critical failuresImage load error
ErrorEGeneral errors/severe errorsCould not connect to the DB
Synopsis

Documentation

data Severity Source #

Severity for the log messages.

Constructors

Debug

Information useful for debug purposes.

E.g. output of the function that is important for the internal development, not for users. Like, the result of SQL query.

Info

Normal operational information.

E.g. describing general steps: starting application, finished downloading.

Warning

General warnings, non-critical failures.

E.g. couldn't download icon from some service to display.

Error

General errors/severe errors.

E.g. exceptional situations: couldn't syncronize accounts.

Instances

Instances details
Bounded Severity Source # 
Instance details

Defined in Colog.Core.Severity

Enum Severity Source # 
Instance details

Defined in Colog.Core.Severity

Ix Severity Source # 
Instance details

Defined in Colog.Core.Severity

Read Severity Source # 
Instance details

Defined in Colog.Core.Severity

Show Severity Source # 
Instance details

Defined in Colog.Core.Severity

Eq Severity Source # 
Instance details

Defined in Colog.Core.Severity

Ord Severity Source # 
Instance details

Defined in Colog.Core.Severity

Patterns

Instead of using full names of the constructors you can instead use one-letter patterns. To do so you can import and use the pattern:

import Colog (pattern D)

example :: WithLog env Message m => m ()
example = log D "I'm using severity pattern"

Moreover, you could use patterns when pattern-matching on severity

errorToStderr :: Severity -> IO ()
errorToStderr E = hputStrLn stderr "Error severity"
errorToStderr _ = putStrLn "Something else"

pattern D :: Severity Source #

pattern I :: Severity Source #

pattern W :: Severity Source #

pattern E :: Severity Source #

filterBySeverity :: Applicative m => Severity -> (a -> Severity) -> LogAction m a -> LogAction m a Source #

Filters messages by the given Severity.

data WithSeverity msg Source #

A message tagged with a Severity.

It is common to want to log various types of messages tagged with a severity. WithSeverity provides a standard way to do so while allowing the messages to be processed independently of the severity.

It is easy to cmap over a 'LogAction m (WithSeverity a)', or to filter based on the severity.

logSomething :: LogAction m (WithSeverity String) -> m ()
logSomething logger = logger <& "hello" `WithSeverity` Info

cmap' :: (b -> a) -> LogAction m (WithSeverity a) -> LogAction m (WithSeverity b)
cmap' f action = cmap (fmap f) action

filterBySeverity' :: (Applicative m) => Severity -> LogAction m (WithSeverity a) -> LogAction m (WithSeverity a)
filterBySeverity' threshold action = filterBySeverity threshold getSeverity action

Since: 0.3.1.0

Constructors

WithSeverity 

Fields

Instances

Instances details
Foldable WithSeverity Source # 
Instance details

Defined in Colog.Core.Severity

Methods

fold :: Monoid m => WithSeverity m -> m #

foldMap :: Monoid m => (a -> m) -> WithSeverity a -> m #

foldMap' :: Monoid m => (a -> m) -> WithSeverity a -> m #

foldr :: (a -> b -> b) -> b -> WithSeverity a -> b #

foldr' :: (a -> b -> b) -> b -> WithSeverity a -> b #

foldl :: (b -> a -> b) -> b -> WithSeverity a -> b #

foldl' :: (b -> a -> b) -> b -> WithSeverity a -> b #

foldr1 :: (a -> a -> a) -> WithSeverity a -> a #

foldl1 :: (a -> a -> a) -> WithSeverity a -> a #

toList :: WithSeverity a -> [a] #

null :: WithSeverity a -> Bool #

length :: WithSeverity a -> Int #

elem :: Eq a => a -> WithSeverity a -> Bool #

maximum :: Ord a => WithSeverity a -> a #

minimum :: Ord a => WithSeverity a -> a #

sum :: Num a => WithSeverity a -> a #

product :: Num a => WithSeverity a -> a #

Traversable WithSeverity Source # 
Instance details

Defined in Colog.Core.Severity

Methods

traverse :: Applicative f => (a -> f b) -> WithSeverity a -> f (WithSeverity b) #

sequenceA :: Applicative f => WithSeverity (f a) -> f (WithSeverity a) #

mapM :: Monad m => (a -> m b) -> WithSeverity a -> m (WithSeverity b) #

sequence :: Monad m => WithSeverity (m a) -> m (WithSeverity a) #

Functor WithSeverity Source # 
Instance details

Defined in Colog.Core.Severity

Methods

fmap :: (a -> b) -> WithSeverity a -> WithSeverity b #

(<$) :: a -> WithSeverity b -> WithSeverity a #

Show msg => Show (WithSeverity msg) Source # 
Instance details

Defined in Colog.Core.Severity

Eq msg => Eq (WithSeverity msg) Source # 
Instance details

Defined in Colog.Core.Severity

Methods

(==) :: WithSeverity msg -> WithSeverity msg -> Bool #

(/=) :: WithSeverity msg -> WithSeverity msg -> Bool #

Ord msg => Ord (WithSeverity msg) Source # 
Instance details

Defined in Colog.Core.Severity

mapSeverity :: (Severity -> Severity) -> WithSeverity msg -> WithSeverity msg Source #

Map the given function over the severity of a WithSeverity.

This can be useful to operate generically over the severity, for example:

suppressErrors :: LogAction m (WithSeverity msg) -> LogAction m (WithSeverity msg)
suppressErrors = cmap (mapSeverity (s -> if s == Error then Warning else s))

Since: 0.3.1.0