| Copyright | (c) 2019 Version Cloud |
|---|---|
| License | BSD3 |
| Maintainer | Jorah Gao <log4hs@version.cloud> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Logging
Description
A python logging style log library.
A simple example:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Main ( main ) where
import Logging (run)
import Logging.Config.Json (getManager)
import Logging.TH (debug, error, fatal, info, logv, warn)
import Prelude hiding (error)
main :: IO ()
main = getManager "{}" >>= flip run app
myLogger = "MyLogger.Main"
app :: IO ()
app = do
$(debug) myLogger "this is a test message"
$(info) myLogger "this is a test message"
$(warn) myLogger "this is a test message"
$(error) myLogger "this is a test message"
$(fatal) myLogger "this is a test message"
$(logv) myLogger "LEVEL 100" "this is a test message"
See Logging.Config.Json and Logging.Config.Yaml to lean more about
decoding Manager from json or yaml
Synopsis
- module Logging.Types
- module Logging.TH
- run :: Manager -> IO a -> IO a
- stderrHandler :: StreamHandler
- stdoutHandler :: StreamHandler
- defaultRoot :: Sink
Documentation
module Logging.Types
module Logging.TH
run :: Manager -> IO a -> IO a Source #
Run a logging environment.
You should always write you application inside a logging environment.
- rename "main" function to "originMain" (or whatever you call it)
- write "main" as below
main :: IO () main = run manager originMain ...
stderrHandler :: StreamHandler Source #
Deprecated: Will be removed
A StreamHandler bound to stderr
stdoutHandler :: StreamHandler Source #
Deprecated: Will be removed
A StreamHandler bound to stdout
defaultRoot :: Sink Source #
Deprecated: Will be removed
Default root sink which is used by Logging.Config.Json and Logging.Config.Yaml when root sink is omitted.