log4hs-0.0.2.0: A python logging style log library

Copyright(c) 2019 Version Cloud
LicenseBSD3
MaintainerJorah Gao <gqk007@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Logging

Contents

Description

A python logging style log library.

A full example:

  {-# LANGUAGE OverloadedStrings #-}
  {-# LANGUAGE QuasiQuotes       #-}
  {-# LANGUAGE RecordWildCards   #-}
  {-# LANGUAGE TemplateHaskell   #-}


  module Main (main) where

  import           Data.Aeson.QQ.Simple (aesonQQ)
  import           Prelude hiding (error)
  import           Logging (runJson, debug, info, warn, error, fatal, logv)

  main :: IO ()
  main = runJson manager app

  myLogger = "MyLogger.Main"

  app :: IO ()
  app = do
    $(debug) myLogger "this message should print into MyLogger"
    $(info) myLogger "this message should print into MyLogger"
    $(warn) myLogger "this message should print into MyLogger"
    $(error) myLogger "this message should print into MyLogger"
    $(fatal) myLogger "this message should print into MyLogger"
    $(logv) myLogger "LEVEL 100" "this message should print into MyLogger"

  -- The best practice is putting all config into a separate file,
  -- e.g "Logging.json"
  manager = [aesonQQ|{
    "loggers": {
      "root": {
        "level": "DEBUG",
        "handlers": ["console"],
        "propagate": false
      },
      "MyLogger": {
        "level": "INFO",
        "filterer": ["MyLogger.Main"],
        "handlers": ["file"],
        "propagate": false
      }
    },
    "handlers": {
      "console": {
        "type": "StreamHandler",
        "stream": "stderr",
        "level": "DEBUG",
        "formatter": "defaultFormatter"
      },
      "file": {
        "type": "FileHandler",
        "level": "INFO",
        "formatter": "defaultFormatter",
        "file": "./default.log"
      }
    },
    "formatters": {
      "defaultFormatter": {
        "fmt": "%(asctime)s - %(level)s - %(logger)s - %(pathname)s/%(filename)s:%(lineno)d] %(message)s"
      }
    }
  }|]
Synopsis

Documentation

run :: Manager -> IO a -> IO a Source #

Run a logging environment.

You should always write you application inside a logging environment.

  1. rename "main" function to "originMain" (or whatever you call it)
  2. write "main" as below
main :: IO ()
main = run manager originMain
...

runJson :: Value -> IO a -> IO a Source #

Run a logging environment from JSON Value.

A combinator of run and jsonToManager.

defaultRoot :: Sink Source #

Default root sink which is used by jsonToManager when root is missed.

You can use it when you make Manager manually.

Logging THs

logv :: ExpQ Source #

Log "message" with the severity "level".

The missing type signature: MonadIO m => Logger -> Level -> String -> m ()

debug :: ExpQ Source #

Log "message" with a specific severity.

The missing type signature: MonadIO m => Logger -> String -> m ()

info :: ExpQ Source #

Log "message" with a specific severity.

The missing type signature: MonadIO m => Logger -> String -> m ()

warn :: ExpQ Source #

Log "message" with a specific severity.

The missing type signature: MonadIO m => Logger -> String -> m ()

error :: ExpQ Source #

Log "message" with a specific severity.

The missing type signature: MonadIO m => Logger -> String -> m ()

fatal :: ExpQ Source #

Log "message" with a specific severity.

The missing type signature: MonadIO m => Logger -> String -> m ()

Types

data Manager Source #

There is under normal circumstances just one Manager, which holds the hierarchy of sinks.

data Sink Source #

Sink represents a single logging channel.

A "logging channel" indicates an area of an application. Exactly how an "area" is defined is up to the application developer. Since an application can have any number of areas, logging channels are identified by a unique string. Application areas can be nested (e.g. an area of "input processing" might include sub-areas "read CSV files", "read XLS files" and "read Gnumeric files"). To cater for this natural nesting, channel names are organized into a namespace hierarchy where levels are separated by periods, much like the Haskell module namespace. So in the instance given above, channel names might be Input for the upper level, and Input.Csv, Input.Xls and Input.Gnu for the sub-levels. There is no arbitrary limit to the depth of nesting.

Note: The namespaces are case sensitive.

Constructors

Sink 

data HandlerT where Source #

A GADT represents any Handler instance

Constructors

HandlerT :: Handler a => a -> HandlerT 

data StreamHandler Source #

A handler type which writes logging records, appropriately formatted, to a stream.

Note that this class does not close the stream when the stream is a terminal device, e.g. stderr and stdout.

Constructors

StreamHandler 

data Formatter Source #

Formatters are used to convert a LogRecord to text.

Formatters need to know how a LogRecord is constructed. They are responsible for converting a LogRecord to (usually) a string which can be interpreted by either a human or an external system. The base Formatter allows a formatting string to be specified. If none is supplied, the default value, "%(message)s" is used.

The Formatter can be initialized with a format string which makes use of knowledge of the LogRecord attributes - e.g. the default value mentioned above makes use of a LogRecord's message attribute. Currently, the useful attributes in a LogRecord are described by:

%(logger)s
Name of the logger (logging channel)
%(level)s
Numeric logging level for the message (DEBUG, INFO, WARN, ERROR, FATAL, LEVEL v)
%(pathname)s
Full pathname of the source file where the logging call was issued (if available)
%(filename)s
Filename portion of pathname
%(module)s
Module (name portion of filename)
%(lineno)d
Source line number where the logging call was issued (if available)
%(created)f
Time when the LogRecord was created (picoseconds since '1970-01-01 00:00:00')
%(asctime)s
Textual time when the LogRecord was created
%(msecs)d
Millisecond portion of the creation time
%(message)s
The main message passed to logv debug info ..

Constructors

Formatter 

Fields

Instances
Eq Formatter Source # 
Instance details

Defined in Logging.Types

Default Formatter Source # 
Instance details

Defined in Logging.Types

Methods

def :: Formatter #

type Filterer = [Filter] Source #

List of Filter

data Filter Source #

Filters are used to perform arbitrary filtering of LogRecords.

Sinks and Handlers can optionally use Filter to filter records as desired. It allows events which are below a certain point in the sink hierarchy. For example, a filter initialized with A.B will allow events logged by loggers A.B, A.B.C, A.B.C.D, A.B.D etc. but not A.BB, B.A.B etc. If initialized name with the empty string, all events are passed.

Constructors

Filter 

Fields

Instances
Eq Filter Source # 
Instance details

Defined in Logging.Types

Methods

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

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

IsString Filter Source # 
Instance details

Defined in Logging.Types

Methods

fromString :: String -> Filter #

data LogRecord Source #

A LogRecord represents an event being logged.

LogRecords are created every time something is logged. They contain all the information related to the event being logged.

It includes the main message as well as information such as when the record was created, the source line where the logging call was made.

newtype Level Source #

Level also known as severity, a higher Level means a bigger Int.

Constructors

Level Int 
Instances
Enum Level Source # 
Instance details

Defined in Logging.Types

Eq Level Source # 
Instance details

Defined in Logging.Types

Methods

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

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

Ord Level Source # 
Instance details

Defined in Logging.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 #

Read Level Source # 
Instance details

Defined in Logging.Types

Show Level Source # 
Instance details

Defined in Logging.Types

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

IsString Level Source # 
Instance details

Defined in Logging.Types

Methods

fromString :: String -> Level #

Lift Level Source # 
Instance details

Defined in Logging.Types

Methods

lift :: Level -> Q Exp #

Default Level Source # 
Instance details

Defined in Logging.Types

Methods

def :: Level #

type Logger = String Source #

Logger is just a name.