di-df1-1.1: Write logs in the df1 format using the di logging framework

Safe HaskellNone
LanguageHaskell2010

Di.Df1

Contents

Description

This module extends extends the di logging ecosystem with support for the df1 hierarchical structured logging format.

Particularly, it exports df1 for rendering df1-formatted logs, an extension to the Di.Core API with vocabulary specific to df1, and functions like fromDiLog or fromDf1Log to convert back and forth between di and df1 types.

The Di.Df1.Monad module belonging to this same package exports an extension to the Di.Monad API, rather than to Di.Core.

Consider this a preview release: The API is likely to stay stable, but extensive testing, formalization and tooling is due.

Synopsis

Documentation

type Df1 = Di Level Path Message Source #

Convenience type-synonym for a Di restricted to all the df1 monomorphic types.

Df1 == Di Level Path Message
   :: *

This type-synonym is not used within the di-df1 library itself because all functions exposed in the library have more general types. However, users are encouraged to use Df1 if they find it useful to reduce boilerplate and improve type inference.

Hierarchy

push Source #

Arguments

:: Segment 
-> Di level Path msg 
-> Di level Path msg 

Push a new Segment to the Di

Metadata

attr Source #

Arguments

:: ToValue value 
=> Key 
-> value 
-> Di level Path msg 
-> Di level Path msg 

Push a new attribute Key and Value to the Di.

Logging from IO

debug :: (MonadIO m, ToMessage msg) => Di Level path Message -> msg -> m () Source #

Log a message intended to be useful only when deliberately debugging a program.

info :: (MonadIO m, ToMessage msg) => Di Level path Message -> msg -> m () Source #

Log an informational message.

notice :: (MonadIO m, ToMessage msg) => Di Level path Message -> msg -> m () Source #

Log a condition that is not an error, but should possibly be handled specially.

warning :: (MonadIO m, ToMessage msg) => Di Level path Message -> msg -> m () Source #

Log a warning condition, such as an exception being gracefully handled or some missing configuration setting being assigned a default value.

error :: (MonadIO m, ToMessage msg) => Di Level path Message -> msg -> m () Source #

Log an error condition, such as an unhandled exception.

alert :: (MonadIO m, ToMessage msg) => Di Level path Message -> msg -> m () Source #

Log a condition that should be corrected immediately, such as a corrupted database.

critical :: (MonadIO m, ToMessage msg) => Di Level path Message -> msg -> m () Source #

Log a critical condition that could result in system failure, such as a disk running out of space.

emergency :: (MonadIO m, ToMessage msg) => Di Level path Message -> msg -> m () Source #

Log a message stating that the system is unusable.

Type-inference helpers

debug' :: MonadIO m => Di Level path Message -> Message -> m () Source #

Like debug, but takes a Message rather than any ToMessage.

This helps with type inference in case you are trying to log a literal string and have the OverloadedStrings GHC extension enabled.

info' :: MonadIO m => Di Level path Message -> Message -> m () Source #

Like info, but takes a Message rather than any ToMessage.

This helps with type inference in case you are trying to log a literal string and have the OverloadedStrings GHC extension enabled.

notice' :: MonadIO m => Di Level path Message -> Message -> m () Source #

Like notice, but takes a Message rather than any ToMessage.

This helps with type inference in case you are trying to log a literal string and have the OverloadedStrings GHC extension enabled.

warning' :: MonadIO m => Di Level path Message -> Message -> m () Source #

Like warning, but takes a Message rather than any ToMessage.

This helps with type inference in case you are trying to log a literal string and have the OverloadedStrings GHC extension enabled.

error' :: MonadIO m => Di Level path Message -> Message -> m () Source #

Like error, but takes a Message rather than any ToMessage.

This helps with type inference in case you are trying to log a literal string and have the OverloadedStrings GHC extension enabled.

alert' :: MonadIO m => Di Level path Message -> Message -> m () Source #

Like alert, but takes a Message rather than any ToMessage.

This helps with type inference in case you are trying to log a literal string and have the OverloadedStrings GHC extension enabled.

critical' :: MonadIO m => Di Level path Message -> Message -> m () Source #

Like critical, but takes a Message rather than any ToMessage.

This helps with type inference in case you are trying to log a literal string and have the OverloadedStrings GHC extension enabled.

emergency' :: MonadIO m => Di Level path Message -> Message -> m () Source #

Like emergency, but takes a Message rather than any ToMessage.

This helps with type inference in case you are trying to log a literal string and have the OverloadedStrings GHC extension enabled.

Logging from STM

debugSTM :: (Monad m, ToMessage msg) => (forall x. STM x -> m x) -> Di Level path Message -> msg -> m () Source #

Like debug, but can be used from any Monad supporting STM.

infoSTM :: (Monad m, ToMessage msg) => (forall x. STM x -> m x) -> Di Level path Message -> msg -> m () Source #

Like info, but can be used from any Monad supporting STM.

noticeSTM :: (Monad m, ToMessage msg) => (forall x. STM x -> m x) -> Di Level path Message -> msg -> m () Source #

Like notice, but can be used from any Monad supporting STM.

warningSTM :: (Monad m, ToMessage msg) => (forall x. STM x -> m x) -> Di Level path Message -> msg -> m () Source #

Like warning, but can be used from any Monad supporting STM.

errorSTM :: (Monad m, ToMessage msg) => (forall x. STM x -> m x) -> Di Level path Message -> msg -> m () Source #

Like error, but can be used from any Monad supporting STM.

alertSTM :: (Monad m, ToMessage msg) => (forall x. STM x -> m x) -> Di Level path Message -> msg -> m () Source #

Like alert, but can be used from any Monad supporting STM.

criticalSTM :: (Monad m, ToMessage msg) => (forall x. STM x -> m x) -> Di Level path Message -> msg -> m () Source #

Like critical, but can be used from any Monad supporting STM.

emergencySTM :: (Monad m, ToMessage msg) => (forall x. STM x -> m x) -> Di Level path Message -> msg -> m () Source #

Like emergency, but can be used from any Monad supporting STM.

Support for Di.Handle

df1 :: LineRenderer Level Path Message Source #

A LineRenderer to be used with tools like handle or stderr from the Di.Handle module.

Conversion

fromDiLog :: Log Level Path Message -> Log Source #

Convert a Log from Df1 to a Log from Di.Core.

fromDiLog . fromDf1Log  ==  id
fromDf1Log . fromDiLog  ==  id

fromDf1Log :: Log -> Log Level Path Message Source #

Convert a Log from Di.Core to a Log from Df1.

fromDiLog . fromDf1Log  ==  id
fromDf1Log . fromDiLog  ==  id

Types from Df1

data Level #

Instances
Bounded Level 
Instance details

Defined in Df1.Types

Enum Level 
Instance details

Defined in Df1.Types

Eq Level 
Instance details

Defined in Df1.Types

Methods

(==) :: Level -> Level -> Bool #

(/=) :: Level -> Level -> Bool #

Ord Level 
Instance details

Defined in Df1.Types

Methods

compare :: Level -> Level -> Ordering #

(<) :: Level -> Level -> Bool #

(<=) :: Level -> Level -> Bool #

(>) :: Level -> Level -> Bool #

(>=) :: Level -> Level -> Bool #

max :: Level -> Level -> Level #

min :: Level -> Level -> Level #

Show Level 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

data Path #

Instances
Eq Path 
Instance details

Defined in Df1.Types

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Show Path 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

data Segment #

Instances
Eq Segment 
Instance details

Defined in Df1.Types

Methods

(==) :: Segment -> Segment -> Bool #

(/=) :: Segment -> Segment -> Bool #

Show Segment 
Instance details

Defined in Df1.Types

IsString Segment 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Segment #

Semigroup Segment 
Instance details

Defined in Df1.Types

Monoid Segment 
Instance details

Defined in Df1.Types

ToSegment Segment 
Instance details

Defined in Df1.Types

Methods

segment :: Segment -> Segment #

class ToSegment a where #

Methods

segment :: a -> Segment #

Instances
ToSegment Text 
Instance details

Defined in Df1.Types

Methods

segment :: Text -> Segment #

ToSegment Text 
Instance details

Defined in Df1.Types

Methods

segment :: Text -> Segment #

ToSegment String 
Instance details

Defined in Df1.Types

Methods

segment :: String -> Segment #

ToSegment Segment 
Instance details

Defined in Df1.Types

Methods

segment :: Segment -> Segment #

data Key #

Instances
Eq Key 
Instance details

Defined in Df1.Types

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Show Key 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Key #

Semigroup Key 
Instance details

Defined in Df1.Types

Methods

(<>) :: Key -> Key -> Key #

sconcat :: NonEmpty Key -> Key #

stimes :: Integral b => b -> Key -> Key #

Monoid Key 
Instance details

Defined in Df1.Types

Methods

mempty :: Key #

mappend :: Key -> Key -> Key #

mconcat :: [Key] -> Key #

ToKey Key 
Instance details

Defined in Df1.Types

Methods

key :: Key -> Key #

class ToKey a where #

Methods

key :: a -> Key #

Instances
ToKey Text 
Instance details

Defined in Df1.Types

Methods

key :: Text -> Key #

ToKey Text 
Instance details

Defined in Df1.Types

Methods

key :: Text -> Key #

ToKey String 
Instance details

Defined in Df1.Types

Methods

key :: String -> Key #

ToKey Key 
Instance details

Defined in Df1.Types

Methods

key :: Key -> Key #

data Value #

Instances
Eq Value 
Instance details

Defined in Df1.Types

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Show Value 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Value #

Semigroup Value 
Instance details

Defined in Df1.Types

Methods

(<>) :: Value -> Value -> Value #

sconcat :: NonEmpty Value -> Value #

stimes :: Integral b => b -> Value -> Value #

Monoid Value 
Instance details

Defined in Df1.Types

Methods

mempty :: Value #

mappend :: Value -> Value -> Value #

mconcat :: [Value] -> Value #

ToValue Value 
Instance details

Defined in Df1.Types

Methods

value :: Value -> Value #

class ToValue a where #

Methods

value :: a -> Value #

Instances
ToValue Bool 
Instance details

Defined in Df1.Types

Methods

value :: Bool -> Value #

ToValue Double 
Instance details

Defined in Df1.Types

Methods

value :: Double -> Value #

ToValue Float 
Instance details

Defined in Df1.Types

Methods

value :: Float -> Value #

ToValue Int 
Instance details

Defined in Df1.Types

Methods

value :: Int -> Value #

ToValue Int8 
Instance details

Defined in Df1.Types

Methods

value :: Int8 -> Value #

ToValue Int16 
Instance details

Defined in Df1.Types

Methods

value :: Int16 -> Value #

ToValue Int32 
Instance details

Defined in Df1.Types

Methods

value :: Int32 -> Value #

ToValue Int64 
Instance details

Defined in Df1.Types

Methods

value :: Int64 -> Value #

ToValue Integer 
Instance details

Defined in Df1.Types

Methods

value :: Integer -> Value #

ToValue Natural 
Instance details

Defined in Df1.Types

Methods

value :: Natural -> Value #

ToValue Word 
Instance details

Defined in Df1.Types

Methods

value :: Word -> Value #

ToValue Word8 
Instance details

Defined in Df1.Types

Methods

value :: Word8 -> Value #

ToValue Word16 
Instance details

Defined in Df1.Types

Methods

value :: Word16 -> Value #

ToValue Word32 
Instance details

Defined in Df1.Types

Methods

value :: Word32 -> Value #

ToValue Word64 
Instance details

Defined in Df1.Types

Methods

value :: Word64 -> Value #

ToValue Text 
Instance details

Defined in Df1.Types

Methods

value :: Text -> Value #

ToValue Text 
Instance details

Defined in Df1.Types

Methods

value :: Text -> Value #

ToValue String 
Instance details

Defined in Df1.Types

Methods

value :: String -> Value #

ToValue SomeException 
Instance details

Defined in Df1.Types

Methods

value :: SomeException -> Value #

ToValue Value 
Instance details

Defined in Df1.Types

Methods

value :: Value -> Value #

data Message #

Instances
Eq Message 
Instance details

Defined in Df1.Types

Methods

(==) :: Message -> Message -> Bool #

(/=) :: Message -> Message -> Bool #

Show Message 
Instance details

Defined in Df1.Types

IsString Message 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Message #

Semigroup Message 
Instance details

Defined in Df1.Types

Monoid Message 
Instance details

Defined in Df1.Types

ToMessage Message 
Instance details

Defined in Df1.Types

Methods

message :: Message -> Message #

class ToMessage a where #

Methods

message :: a -> Message #

Instances
ToMessage Text 
Instance details

Defined in Df1.Types

Methods

message :: Text -> Message #

ToMessage Text 
Instance details

Defined in Df1.Types

Methods

message :: Text -> Message #

ToMessage String 
Instance details

Defined in Df1.Types

Methods

message :: String -> Message #

ToMessage SomeException 
Instance details

Defined in Df1.Types

ToMessage Message 
Instance details

Defined in Df1.Types

Methods

message :: Message -> Message #