df1-0.4.2: Type, render and parse the df1 hierarchical structured log format
Safe HaskellSafe-Inferred
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

Instances details
Show Log Source # 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Log -> ShowS #

show :: Log -> String #

showList :: [Log] -> ShowS #

Eq Log Source # 
Instance details

Defined in Df1.Types

Methods

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

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

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

Instances details
Bounded Level Source # 
Instance details

Defined in Df1.Types

Enum Level Source # 
Instance details

Defined in Df1.Types

Read Level Source # 
Instance details

Defined in Df1.Types

Show Level Source # 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

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 #

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

Instances details
Show Path Source # 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Eq Path Source # 
Instance details

Defined in Df1.Types

Methods

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

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

ToPath (Seq Path) Source #

Identity.

Instance details

Defined in Df1.Types

Methods

path :: Seq Path -> Seq Path Source #

Foldable f => ToPath (f Path) Source #
path = fromList . toList
Instance details

Defined in Df1.Types

Methods

path :: f Path -> Seq Path Source #

class ToPath a where Source #

Convert an arbitrary type to a Sequence of Paths.

You are encouraged to create custom ToPath 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

path :: a -> Seq Path Source #

The leftmost Path is the closest to the root. The rightmost Path is the one closest to where the log was generated.

See the documentation for Path.

Instances

Instances details
ToPath (Seq Path) Source #

Identity.

Instance details

Defined in Df1.Types

Methods

path :: Seq Path -> Seq Path Source #

Foldable f => ToPath (f Path) Source #
path = fromList . toList
Instance details

Defined in Df1.Types

Methods

path :: f Path -> Seq Path Source #

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

Instances details
IsString Segment Source # 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Segment #

Monoid Segment Source # 
Instance details

Defined in Df1.Types

Semigroup Segment Source # 
Instance details

Defined in Df1.Types

Show Segment Source # 
Instance details

Defined in Df1.Types

ToSegment Segment Source #

Identity.

Instance details

Defined in Df1.Types

Eq Segment Source # 
Instance details

Defined in Df1.Types

Methods

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

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

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

Instances details
ToSegment Segment Source #

Identity.

Instance details

Defined in Df1.Types

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

Defined in Df1.Types

Methods

segment :: Text -> Segment Source #

ToSegment Text Source #
x :: Text == 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 Char Source # 
Instance details

Defined in Df1.Types

Methods

segment :: Char -> Segment Source #

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

Instances details
IsString Key Source # 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Key #

Monoid Key Source # 
Instance details

Defined in Df1.Types

Methods

mempty :: Key #

mappend :: Key -> Key -> Key #

mconcat :: [Key] -> Key #

Semigroup Key Source # 
Instance details

Defined in Df1.Types

Methods

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

sconcat :: NonEmpty Key -> Key #

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

Show Key Source # 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

ToKey Key Source #

Identity.

Instance details

Defined in Df1.Types

Methods

key :: Key -> Key Source #

Eq Key Source # 
Instance details

Defined in Df1.Types

Methods

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

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

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

Instances details
ToKey Key Source #

Identity.

Instance details

Defined in Df1.Types

Methods

key :: Key -> Key Source #

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

Defined in Df1.Types

Methods

key :: Text -> Key Source #

ToKey Text Source #
x :: Text == 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 Char Source # 
Instance details

Defined in Df1.Types

Methods

key :: Char -> 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

Instances details
IsString Value Source # 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Value #

Monoid Value Source # 
Instance details

Defined in Df1.Types

Methods

mempty :: Value #

mappend :: Value -> Value -> Value #

mconcat :: [Value] -> Value #

Semigroup Value Source # 
Instance details

Defined in Df1.Types

Methods

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

sconcat :: NonEmpty Value -> Value #

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

Show Value Source # 
Instance details

Defined in Df1.Types

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

ToValue Value Source #

Identity.

Instance details

Defined in Df1.Types

Methods

value :: Value -> Value Source #

Eq Value Source # 
Instance details

Defined in Df1.Types

Methods

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

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

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

Instances details
ToValue SomeException Source # 
Instance details

Defined in Df1.Types

ToValue Int16 Source # 
Instance details

Defined in Df1.Types

Methods

value :: Int16 -> Value Source #

ToValue Int32 Source # 
Instance details

Defined in Df1.Types

Methods

value :: Int32 -> Value Source #

ToValue Int64 Source # 
Instance details

Defined in Df1.Types

Methods

value :: Int64 -> Value Source #

ToValue Int8 Source # 
Instance details

Defined in Df1.Types

Methods

value :: Int8 -> Value Source #

ToValue Word16 Source # 
Instance details

Defined in Df1.Types

Methods

value :: Word16 -> Value Source #

ToValue Word32 Source # 
Instance details

Defined in Df1.Types

Methods

value :: Word32 -> Value Source #

ToValue Word64 Source # 
Instance details

Defined in Df1.Types

Methods

value :: Word64 -> Value Source #

ToValue Word8 Source # 
Instance details

Defined in Df1.Types

Methods

value :: Word8 -> Value Source #

ToValue Value Source #

Identity.

Instance details

Defined in Df1.Types

Methods

value :: Value -> Value Source #

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

Defined in Df1.Types

Methods

value :: Text -> Value Source #

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

Defined in Df1.Types

Methods

value :: Text -> Value Source #

ToValue CalendarDiffDays Source #

See ISO8601.

Instance details

Defined in Df1.Types

ToValue Day Source #

See ISO8601.

Instance details

Defined in Df1.Types

Methods

value :: Day -> Value Source #

ToValue DayOfWeek Source #

Lowercase monday, tuesday, etc.

Instance details

Defined in Df1.Types

ToValue DiffTime Source #
123456s
Instance details

Defined in Df1.Types

Methods

value :: DiffTime -> Value Source #

ToValue NominalDiffTime Source #
123456s
Instance details

Defined in Df1.Types

ToValue SystemTime Source #

See iso8601.

Instance details

Defined in Df1.Render

ToValue UTCTime Source #

See iso8601.

Instance details

Defined in Df1.Render

Methods

value :: UTCTime -> Value Source #

ToValue CalendarDiffTime Source #

See ISO8601.

Instance details

Defined in Df1.Types

ToValue LocalTime Source #

See ISO8601.

Instance details

Defined in Df1.Types

ToValue TimeOfDay Source #

See ISO8601.

Instance details

Defined in Df1.Types

ToValue TimeZone Source #

See ISO8601.

Instance details

Defined in Df1.Types

Methods

value :: TimeZone -> Value Source #

ToValue ZonedTime Source #

See ISO8601.

Instance details

Defined in Df1.Types

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

Defined in Df1.Types

Methods

value :: String -> Value Source #

ToValue Integer Source # 
Instance details

Defined in Df1.Types

Methods

value :: Integer -> Value Source #

ToValue Natural Source # 
Instance details

Defined in Df1.Types

Methods

value :: Natural -> Value Source #

ToValue Bool Source # 
Instance details

Defined in Df1.Types

Methods

value :: Bool -> Value Source #

ToValue Char Source # 
Instance details

Defined in Df1.Types

Methods

value :: Char -> Value Source #

ToValue Double Source # 
Instance details

Defined in Df1.Types

Methods

value :: Double -> Value Source #

ToValue Float Source # 
Instance details

Defined in Df1.Types

Methods

value :: Float -> Value Source #

ToValue Int Source # 
Instance details

Defined in Df1.Types

Methods

value :: Int -> Value Source #

ToValue Word Source # 
Instance details

Defined in Df1.Types

Methods

value :: Word -> Value Source #

HasResolution a => ToValue (Fixed a) Source #

Chops trailing zeros.

Instance details

Defined in Df1.Types

Methods

value :: Fixed a -> 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

Instances details
IsString Message Source # 
Instance details

Defined in Df1.Types

Methods

fromString :: String -> Message #

Monoid Message Source # 
Instance details

Defined in Df1.Types

Semigroup Message Source # 
Instance details

Defined in Df1.Types

Show Message Source # 
Instance details

Defined in Df1.Types

ToMessage Message Source #

Identity.

Instance details

Defined in Df1.Types

Eq Message Source # 
Instance details

Defined in Df1.Types

Methods

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

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

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

Instances details
ToMessage SomeException Source # 
Instance details

Defined in Df1.Types

ToMessage Message Source #

Identity.

Instance details

Defined in Df1.Types

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

Defined in Df1.Types

Methods

message :: Text -> Message Source #

ToMessage Text Source #
x :: Text == 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