| Copyright | (c) 2019 Version Cloud |
|---|---|
| License | BSD3 |
| Maintainer | Jorah Gao <log4hs@version.cloud> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Logging
Contents
Description
A python logging style log library.
A simple example:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Main ( main ) where
import Data.Aeson
import Data.Maybe
import Logging
import Prelude hiding (error)
main :: IO ()
main = fromJust (decode "{}") >>= 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.Aeson to lean more about decoding json into Manager
Synopsis
- module Logging.Aeson
- module Logging.Types
- runJson :: Value -> IO a -> IO a
- jsonToManager :: Value -> IO Manager
- run :: Manager -> IO a -> IO a
- stderrHandler :: StreamHandler
- stdoutHandler :: StreamHandler
- defaultRoot :: Sink
- logv :: ExpQ
- debug :: ExpQ
- info :: ExpQ
- warn :: ExpQ
- error :: ExpQ
- fatal :: ExpQ
Documentation
module Logging.Aeson
module Logging.Types
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 #
A StreamHandler bound to stderr
stdoutHandler :: StreamHandler Source #
A StreamHandler bound to stdout
defaultRoot :: Sink Source #
Default root sink which is used by jsonToManager when root is missed.
You can use it when you make Manager manually.