df1-0.3.1: Type, render and parse the df1 hierarchical structured log format

Safe HaskellSafe
LanguageHaskell2010

Df1

Contents

Description

This module exports tools for typing, parsing, and rendering logs in the df1 hierarchical structured logging format.

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

Draft BNF specification of the df1 log line format (TO BE VERIFIED):

<log> ::= <timestamp> " " <path> " " <level> " " <message>
<path> ::= <path1> " " <path> | <path1> | ""
<path1> ::= "/" <segment> | <key> "=" <value>
<segment> ::= zero or more characters until " "
<key> ::= zero or more characters until (" " | "=")
<value> ::= zero or more characters until " "
<message> ::= zero or more characters until LF ("\n")
<level> ::= "DEBUG" | "INFO" | "NOTICE" | "WARNING" | "ERROR" | "CRITICAL" | "ALERT" | "EMERGENCY"
<timestamp> ::= <year> "-" <month> "-" <day> "T" <hour> ":" <minute> ":" <second> "." <nanosecond> "Z"
<year> ::= <digit> <digit> <digit> <digit>
<month> ::= <digit> <digit>
<day> ::= <digit> <digit>
<hour> ::= <digit> <digit>
<minute> ::= <digit> <digit>
<second> ::= <digit> <digit>
<nanosecond> ::= <digit> <digit> <digit> <digit> <digit> <digit> <digit> <digit> <digit>
<digit> ::= "0" | "1" | "2" | "3" | "4" | "5" | "6" | "7" | "8" | "9"
Synopsis

Types

data Log Source #

Constructors

Log 

Fields

Instances
Eq Log Source # 
Instance details

Defined in Df1.Types

Methods

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

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

Show Log Source # 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Log -> ShowS #

show :: Log -> String #

showList :: [Log] -> ShowS #

data Level Source #

Importance of the logged message.

These levels, listed in increasing order of importance, correspond to the levels used by syslog(3).

Constructors

Debug

Message intended to be useful only when deliberately debugging a program.

Info

Informational message.

Notice

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

Warning

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

Error

Error condition, such as an unhandled exception.

Critical

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

Alert

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

Emergency

System is unusable.

Instances
Bounded Level Source # 
Instance details

Defined in Df1.Types

Enum Level Source # 
Instance details

Defined in Df1.Types

Eq Level Source # 
Instance details

Defined in Df1.Types

Methods

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

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

Ord Level Source #

Order of importance. For example, Emergency is more important than Debug:

Emergency > Debug  ==  True
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 Source # 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

data Path Source #

Path represents the hierarchical structure of logged messages.

For example, consider a df1 log line as like the following:

1999-12-20T07:11:39.230553031Z /foo x=a y=b /bar /qux z=c z=d WARNING Something

For that line, the log_path attribute of the Log datatype will contain the following:

[ Push (segment "foo")
, Attr (key "x") (value "a")
, Attr (key "y") (value "b")
, Push (segment "bar")
, Push (segment "qux")
, Attr (key "z") (value "c")
, Attr (key "z") (value "d")
] :: Seq Path

Please notice that [] :: Seq Path is a valid path insofar as df1 is concerned, and that Attr and Push can be juxtapositioned in any order.

Constructors

Push !Segment 
Attr !Key !Value 
Instances
Eq Path Source # 
Instance details

Defined in Df1.Types

Methods

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

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

Show Path Source # 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

data Segment Source #

A path segment.

If you have the OverloadedStrings GHC extension enabled, you can build a Segment using a string literal:

"foo" :: Segment

Otherwise, you can use fromString or segment.

Notice that "" :: Segment is acceptable, and will be correctly rendered and parsed back.

Instances
Eq Segment Source # 
Instance details

Defined in Df1.Types

Methods

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

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

Show Segment Source # 
Instance details

Defined in Df1.Types

IsString Segment Source # 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Segment #

Semigroup Segment Source # 
Instance details

Defined in Df1.Types

Monoid Segment Source # 
Instance details

Defined in Df1.Types

ToSegment Segment Source #

Identity.

Instance details

Defined in Df1.Types

class ToSegment a where Source #

Convert an arbitrary type to a Segment.

You are encouraged to create custom ToSegment instances for your types making sure you avoid rendering sensitive details such as passwords, so that they don't accidentally end up in logs.

Any characters that need to be escaped for rendering will be automatically escaped at rendering time. You don't need to escape them here.

Methods

segment :: a -> Segment Source #

Instances
ToSegment Text Source #
x :: Text == unSegment (segment x)
Instance details

Defined in Df1.Types

Methods

segment :: Text -> Segment Source #

ToSegment Text Source #
x :: Text == toStrict (unSegment (segment x))
Instance details

Defined in Df1.Types

Methods

segment :: Text -> Segment Source #

ToSegment String Source #
x :: String == unpack (unSegment (segment x))
Instance details

Defined in Df1.Types

ToSegment Segment Source #

Identity.

Instance details

Defined in Df1.Types

data Key Source #

An attribute key (see Attr).

If you have the OverloadedStrings GHC extension enabled, you can build a Key using a string literal:

"foo" :: Key

Otherwise, you can use fromString or key.

Notice that "" :: Key is acceptable, and will be correctly rendered and parsed back.

Instances
Eq Key Source # 
Instance details

Defined in Df1.Types

Methods

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

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

Show Key Source # 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key Source # 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Key #

Semigroup Key Source # 
Instance details

Defined in Df1.Types

Methods

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

sconcat :: NonEmpty Key -> Key #

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

Monoid Key Source # 
Instance details

Defined in Df1.Types

Methods

mempty :: Key #

mappend :: Key -> Key -> Key #

mconcat :: [Key] -> Key #

ToKey Key Source #

Identity.

Instance details

Defined in Df1.Types

Methods

key :: Key -> Key Source #

class ToKey a where Source #

Convert an arbitrary type to a Key.

You are encouraged to create custom ToKey instances for your types making sure you avoid rendering sensitive details such as passwords, so that they don't accidentally end up in logs.

Any characters that need to be escaped for rendering will be automatically escaped at rendering time. You don't need to escape them here.

Methods

key :: a -> Key Source #

Instances
ToKey Text Source #
x :: Text == unKey (key x)
Instance details

Defined in Df1.Types

Methods

key :: Text -> Key Source #

ToKey Text Source #
x :: Text == toStrict (unKey (key x))
Instance details

Defined in Df1.Types

Methods

key :: Text -> Key Source #

ToKey String Source #
x :: String == unpack (unKey (key x))
Instance details

Defined in Df1.Types

Methods

key :: String -> Key Source #

ToKey Key Source #

Identity.

Instance details

Defined in Df1.Types

Methods

key :: Key -> Key Source #

data Value Source #

An attribute value (see Attr).

If you have the OverloadedStrings GHC extension enabled, you can build a Value using a string literal:

"foo" :: Value

Otherwise, you can use fromString or value.

Notice that "" :: Value is acceptable, and will be correctly rendered and parsed back.

Instances
Eq Value Source # 
Instance details

Defined in Df1.Types

Methods

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

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

Show Value Source # 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value Source # 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Value #

Semigroup Value Source # 
Instance details

Defined in Df1.Types

Methods

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

sconcat :: NonEmpty Value -> Value #

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

Monoid Value Source # 
Instance details

Defined in Df1.Types

Methods

mempty :: Value #

mappend :: Value -> Value -> Value #

mconcat :: [Value] -> Value #

ToValue Value Source #

Identity.

Instance details

Defined in Df1.Types

Methods

value :: Value -> Value Source #

class ToValue a where Source #

Convert an arbitrary type to a Value.

You are encouraged to create custom ToValue instances for your types making sure you avoid rendering sensitive details such as passwords, so that they don't accidentally end up in logs.

Any characters that need to be escaped for rendering will be automatically escaped at rendering time. You don't need to escape them here.

Methods

value :: a -> Value Source #

Instances
ToValue Text Source #
x :: Text == unValue (value x)
Instance details

Defined in Df1.Types

Methods

value :: Text -> Value Source #

ToValue Text Source #
x :: Text == toStrict (unValue (value x))
Instance details

Defined in Df1.Types

Methods

value :: Text -> Value Source #

ToValue String Source #
x :: String == unpack (unValue (value x))
Instance details

Defined in Df1.Types

Methods

value :: String -> Value Source #

ToValue Value Source #

Identity.

Instance details

Defined in Df1.Types

Methods

value :: Value -> Value Source #

data Message Source #

A message text.

If you have the OverloadedStrings GHC extension enabled, you can build a Message using a string literal:

"foo" :: Message

Otherwise, you can use fromString or message.

Notice that "" :: Message is acceptable, and will be correctly rendered and parsed back.

Instances
Eq Message Source # 
Instance details

Defined in Df1.Types

Methods

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

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

Show Message Source # 
Instance details

Defined in Df1.Types

IsString Message Source # 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Message #

Semigroup Message Source # 
Instance details

Defined in Df1.Types

Monoid Message Source # 
Instance details

Defined in Df1.Types

ToMessage Message Source #

Identity.

Instance details

Defined in Df1.Types

class ToMessage a where Source #

Convert an arbitrary type to a Message.

You are encouraged to create custom ToMessage instances for your types making sure you avoid rendering sensitive details such as passwords, so that they don't accidentally end up in logs.

Any characters that need to be escaped for rendering will be automatically escaped at rendering time. You don't need to escape them here.

Methods

message :: a -> Message Source #

Instances
ToMessage Text Source #
x :: Text == unMessage (message x)
Instance details

Defined in Df1.Types

Methods

message :: Text -> Message Source #

ToMessage Text Source #
x :: Text == toStrict (unMessage (message x))
Instance details

Defined in Df1.Types

Methods

message :: Text -> Message Source #

ToMessage String Source #
x :: String == unpack (unMessage (message x))
Instance details

Defined in Df1.Types

ToMessage Message Source #

Identity.

Instance details

Defined in Df1.Types

Parsing

parse :: Parser Log Source #

If sucessful, parsing will stop after the first CR or LF newline marker if any, otherwise it will consume all input.

Rendering

render :: Log -> Builder Source #

Like renderColor, but without color.