monad-log: A simple and fast logging monad

[ development, library, mit ] [ Propose Tags ]

This package provide a mtl style MonadLog class and a concrete monad transformer LogT, the main difference between this package and monad-logger are:

  • Base monad has to be an instance of MonadIO.

  • Parametrized logging environment for extensibility.

  • Basic logging environment type(Label,Loc,NameSpace,ThreadId) are included, and you can easily make your own.

  • JSON logging built-in.

  • default to fast-logger backend, with good stdout and file support.

If you are an application author, you can use LogT transformer, it's just a specialized reader monad to inject `Logger env`.

If you are a library author, you should do following two things:

  • make your monad stack an instance of MonadLog, usually you can do this by embedding `Logger env` into your monad's reader part.

  • provide a default formatter, and API to run with customized formatter.


[Skip to Readme]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.1.0 (info)
Change log CHANGELOG.md
Dependencies aeson (>=0.4 && <1.5), base (>=4.6 && <5), bytestring, exceptions (>=0.6 && <0.11), fast-logger (>=2.4.5 && <2.5), lifted-base, monad-control (>=0.3 && <1.1), template-haskell, text, text-show, transformers (>=0.2) [details]
License MIT
Author winterland1989
Maintainer winterland1989@gmail.com
Revised Revision 1 made by CarterSchonwald at 2018-11-15T19:17:47Z
Category Development
Source repo head: git clone https://github.com/winterland1989/monad-log
Uploaded by winterland at 2016-04-25T15:06:03Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 1644 total (7 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2016-04-25 [all 1 reports]

Readme for monad-log-0.1.1.0

[back to package description]

A fast & simple logging monad

Hackage Travis-CI

This package provide a mtl style MonadLog class and a concrete monad transformer LogT, the main difference between this package and monad-logger are:

  • Base monad has to be an instance of MonadIO.

  • Parametrized logging environment for extensibility.

  • Basic logging environment type(Label,Loc,NameSpace,ThreadId) are included, and you can easily make your own.

  • JSON logging built-in.

  • default to fast-logger backend, with good stdout and file support.

If you are an application author, you can use LogT transformer, a specialized reader monad to inject Logger env.

If you are a library author, you should:

  • make your monad stack an instance of 'MonadLog', usually you can do this by embedding Logger env into your monad's reader part.

  • provide a default formatter, and API to run with customized formatter.

Example

  • A simple labelled logger:
{-# LANGUAGE OverloadedStrings #-}

module Main where

import Control.Monad.Log
import Control.Monad.Log.Label

-- Following log will be output to stdout:
-- [INFO] [25-Apr-2016 12:51:56] [main] This is simple log 1
-- [INFO] [25-Apr-2016 12:51:56] [foo] This is simple log 2

main :: IO ()
main = do
    logger <- makeDefaultLogger
        simpleTimeFormat'
        (LogStdout 4096)
        levelDebug
        (Label "main")

    runLogTSafe logger $ do
        info "This is simple log 1"

        withLabel (Label "foo") $ do
            info "This is simple log 2"

  • Logging with ThreadId:
{-# LANGUAGE OverloadedStrings #-}

module Main where

import Control.Monad.Log
import Control.Monad.IO.Class
import Control.Monad
import Control.Concurrent
import Control.Monad.Log.LogThreadId

-- Following log will be output to stdout:
-- [INFO] [25-Apr-2016 15:06:10] [ThreadId 671] This is simple log 1
-- [INFO] [25-Apr-2016 15:06:10] [ThreadId 674] This is simple log 2
-- [INFO] [25-Apr-2016 15:06:10] [ThreadId 675] This is simple log 2
-- [INFO] [25-Apr-2016 15:06:10] [ThreadId 676] This is simple log 2
-- [INFO] [25-Apr-2016 15:06:10] [ThreadId 677] This is simple log 2
-- [INFO] [25-Apr-2016 15:06:10] [ThreadId 678] This is simple log 2
-- [INFO] [25-Apr-2016 15:06:10] [ThreadId 679] This is simple log 2
...

main :: IO ()
main = do
    tid <- myLogThreadId
    logger <- makeDefaultLogger
        simpleTimeFormat'
        (LogStdout 4096)
        levelDebug
        tid

    runLogTSafe logger $ do
        info "This is simple log 1"

    replicateM_ 100 $
        forkIO . runLogT' logger . withMyLogThreadId $ do
            info "This is simple log 2"
  • Customized logging environment:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}

module Main where

import Control.Monad.Log
import Control.Monad.Log.LogLoc
import Control.Monad.Log.NameSpace
import Data.Aeson.TH
import Data.Text (Text)

-- Following JSON log will be output to stdout:
-- {"level":"INFO","time":"25-Apr-2016 13:54:32"
-- ,"env":{"loc":{"filename":"Test.hs","module":"Test","package":"monad_GM54RwU2jZ84vGJIhnMYMH","line":33},"ns":["root"]}
-- ,"msg":"This is simple log 1"}
-- {"level":"INFO","time":"25-Apr-2016 13:54:32"
-- ,"env":{"loc":{"filename":"Test.hs","module":"Test","package":"monad_GM54RwU2jZ84vGJIhnMYMH","line":33},"ns":["foo","root"]}
-- ,"msg":"This is simple log 2"}

-- | Define your logging environment type.
-- To use 'defaultFomatter', provide a 'TextShow' instance
-- To use 'defaultJSONFomatter', provide a 'ToJSON' instance

data MyEnv = MyEnv {
        loc :: LogLoc  -- This is shared by every log within one 'MonadLog'.
    ,   ns  :: NameSpace
    } deriving (Show, Eq)

$(deriveJSON defaultOptions ''MyEnv)

subMyNS :: (MonadLog MyEnv m) => Text -> m a -> m a
subMyNS sub = localEnv $ \env -> env { ns = pushNameSpace sub (ns env) }

main :: IO ()
main = do
    logger <- makeDefaultJSONLogger
        simpleTimeFormat'
        (LogStdout 4096)
        levelDebug
        (MyEnv $myLogLoc (NameSpace ["root"]))

    runLogTSafe logger $ do
        info "This is simple log 1"

        subMyNS "foo" $ do
            info "This is simple log 2"