unclogging: a library which implements easy, concurrent and pretty logging

[ agpl, concurrency, library, program ] [ Propose Tags ]

Simple, yet extensible concurrent logging system based on publish/subscribe. The library is supposed to be easy to use, concurrent and pretty. It is practical for small applications like web-servers or command line programs.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.0.1, 0.1.0.2
Change log CHANGELOG.md
Dependencies aeson (<2.3), async (<2.3), base (<5), bytestring (<0.13), chronos (<1.2), colourista (<0.2), fused-effects (<1.2), kan-extensions (<6), template-haskell (<2.23), text (<2.2), unclogging, unliftio (<0.3) [details]
License AGPL-3.0-or-later
Author mangoiv
Maintainer contact@mangoiv.com
Category Concurrency
Source repo head: git clone git://git.mangoiv.com/mangoiv/unclogging.git
Uploaded by mangoiv at 2024-09-24T09:02:41Z
Distributions
Executables unclogging
Downloads 35 total (35 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for unclogging-0.1.0.2

[back to package description]

ci hackage

unclogging

View repository: https://git.mangoiv.com/mangoiv/unclogging

Simple, yet extensible concurrent logging system based on publish/subscribe.

The frontend to this library is based on importing a specific logging frontend. Currently there are Control.Effect.Unclog.{Json,Text} and Unclog.IO.{Json,Text} for aeson and text based logging and use with fused-effects and MonadUnliftIO respectively, exposing functions with the same names, debug, info, warn and fatal for the four common log levels.

Subscribers watch a channel of logs and are constructed and destructed by the toplevel logging handler, like runUnclogging or withLoggingWithSubscribers. To construct your own subscribers, check out the Unclog.Subscriber module, more specifically, the mkSubscriber, mkSubscriberSimple and bracketSubscriber functions.

The library makes use of template haskell to efficiently create static information at compile time. This means that the logging frontend functions are of type Q Exp, which isn't very telling. Due to limitations for typed template haskell we currently cannot perform better though. If you're familiar with typed template haskell, you can imagine the logging functions to have a type similar to Code m (frontend -> m ()) (more about this right below).

In reality, as soon as you're splicing in a logging function, e.g. by using $info, the type will "materialise" and you will obtain a function of type frontend -> m () where frontend is either Data.Aeson.Object if you're using the json frontend or Data.Text.Text if you're using the text frontend. m will be something according to the effect system you're using. E.g. in the fused-effects case it will emit a Has Log sig m constraint and in the io case it will emit a MonadUnliftIO constraint.

example for standalone usage, i.e. MonadUnliftIO and text frontend

-- import utilities that are useful for logging
import Unclog
-- the logging frontend has to be specific to the effect system used
import Unclog.Text
import Unclog.Subscribers (withLoggingWithSubscribers)

main :: IO ()
main = do
  let subs = [colourSubscriber Info stdout, simpleSubscriber Fatal stderr, fileSubscriber Debug "bla.log"]

  withLoggingWithSubscribers subs \logger -> do
    $info logger "info"
    $debug logger "some important debug info"

example for use with fused-effects and aeson frontend

import Unclog
-- logging frontend specific to fused-effects
import Control.Effect.Unclog.Json
import Control.Carrier.Unclog

-- for the construction of JSON objects.
import Data.Aeson

main :: IO ()
main = do
  let subs = [colourSubscriber Info stdout, simpleSubscriber Fatal stderr, fileSubscriber Debug "bla.log"]

  -- as you can see, we don't have to pass around the logger explicitly, which makes it a bit more concise and 
  -- also a tad more safe 
  runUnclogging subs do
    $info ["msg" .= String "hello world"]
    $debug ["msg" .= String "message with number", "number" .= Number 1]

more verbose example with multiple threads involved

import Unclog
import Unclog.Json

import Data.Aeson
import UnliftIO
import Data.String (fromString)
import Control.Monad (replicateM_, void)

main :: IO ()
main = do
  let subs = [colourSubscriber Info stdout, simpleSubscriber Fatal stderr, fileSubscriber Debug "bla.log"]

  withLoggingWithSubscribers subs \logger -> do
    -- spawn a couple of tasks that write to the logger channel concurrently
    let spawnTask (i :: Int) = do
          $info logger ["msg" .= String ("I am task " <> fromString (show i))]
          replicateM_ 2 do
            replicateM_ 2 do
              $debug logger ["msg" .= String ("debugging from " <> fromString (show i))]
            $warn logger ["warning" .= String ("warning from " <> fromString (show i))]
          $fatal logger ["error" .= String ("fatal from " <> fromString (show i))]
    void $ runConcurrently $ traverse @[] (Concurrently . spawnTask) [1 .. 5]

the looks of it

This is how the coloured logging looks with above example, as you can see, both the simple logger writes the fatal events to stderr witout colouring them, and the coloured logger writes everything from Info upwards.

screenshot of coloured log scenario