log4hs-0.1.0.0: A python logging style log library

Copyright(c) 2019 Version Cloud
LicenseBSD3
MaintainerJorah Gao <log4hs@version.cloud>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

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

Documentation

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

Deprecated: will be removed in 1.0.0

Run a logging environment from JSON Value.

A combinator of run and fromJSON

A combinator of jsonToManager and run

See Aeson

jsonToManager :: Value -> IO Manager Source #

Deprecated: will be removed in 1.0.0

Make a Manager from JSON Value

Decode Value into Manager

See Aeson

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
...

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 ()