Stdout JSON logger a (too) naive approach?

Hi,
I was wondering if I could quickly draft a JSON logger without using the “big” logging libs.

I just need it to output in the stdout and to be a valid JSON.

I came up with this draft which seems to work fine with very few lines of code and I’m wondering if I’m missing something…

{-# LANGUAGE Rank2Types #-}

module JsonLogger
  ( idErrLogM,
    idErrLog,
    idWarnLog,
    idWarnLogM,
    idInfoLog,
    idInfoLogM,
  )
where

import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Aeson (ToJSON (toJSON), Value, (.=))
import Data.Aeson.Text (encodeToLazyText)
import Data.Aeson.Types (object)
import Data.Text (Text)
import Data.Text.IO as Txt (putStrLn)
import Data.Text.Lazy (toStrict)
import Data.Time.Clock.POSIX (getPOSIXTime)

data LogLevel = Err | Warn | Info

instance ToJSON LogLevel where
  toJSON Err = "err"
  toJSON Warn = "warn"
  toJSON Info = "info"

type LogPure m a = (MonadIO m, ToJSON a) => Text -> a -> m a

type LogMonad m a = (MonadIO m, ToJSON a) => Text -> m a -> m a

idErrLog :: LogPure m a
idErrLog = logPure Err

idErrLogM :: LogMonad m a
idErrLogM = logMonad Err

idWarnLog :: LogPure m a
idWarnLog = logPure Warn

idWarnLogM :: LogMonad m a
idWarnLogM = logMonad Warn

idInfoLog :: LogPure m a
idInfoLog = logPure Info

idInfoLogM :: LogMonad m a
idInfoLogM = logMonad Info

-- private helpers
logMonad :: LogLevel -> LogMonad m a
logMonad lvl msg ioData = do
  d <- ioData
  logPure lvl msg d

logPure :: LogLevel -> LogPure m a
logPure lvl msg d = do
  log_ lvl msg d
  pure d

log_ :: (MonadIO m, ToJSON a) => LogLevel -> Text -> a -> m ()
log_ lvl msg d = liftIO $ do
  ts <- nowTs
  printLog $ MkLogLine lvl msg (toJSON d) ts
  where
    printLog = Txt.putStrLn . toStrict . encodeToLazyText
    nowTs = round . (* 1000) <$> getPOSIXTime

data LogLine = MkLogLine
  { _level :: !LogLevel,
    _msg :: !Text,
    _data :: !Value,
    _ts :: !Int
  }

instance ToJSON LogLine where
  toJSON (MkLogLine lvl msg d ts) = object ["lvl" .= lvl, "msg" .= msg, "data" .= d, "ts" .= ts]

3 Likes

Depends on your requirements obviously, but IIRC getPOSIXTime (as any system call) can be surprisingly expensive, so if you’re logging a lot then it may actually become a bottleneck.

Logging libraries get complicated when providing many features. Some examples:

  • Configuration of the output destination (stdout, stderr, file Handle, Syslog, etc.)
  • Configuration of the output format (message formatting, time formatting, colors, etc.)
  • Configuration of log level filtering (only output debug logging when enabled, etc.)
  • Support for testing code that includes logging (accumulating logs instead of outputting them, mocking, simply disable logging while testing, etc.)

Creating logging functionality for your exact needs, without having to provide options for various use cases, indeed enables great simplification! Assuming that the API meets your needs, I think that your draft is looking good.

Regarding getting the time, I think that it is an essential requirement for most logging, in which case that system call is a necessary expense. You are logging the integral timestamp value, which is fast. Formatting times can be expensive, and that is where many “big” logging libraries implement optimizations.

By the way, I think there might be a bug in your draft logMonad function. It runs the ioData action to log a value and then runs it again to return a value. I think you would rather like to return the value that was logged (pure d). Edit: Your edit resolves this issue.

2 Likes

Thanks a lot for your explanation @tcard !
That’s actually what I was wondering : is it complex because it has to handle lots of different usages or because I overlooked something.

Wow, good catch for the bug ( :upside_down_face:) I updated my original snippet in order to fix this, thanks !

@BardurArantsson I do need to log a timestamp, are there some more efficient way to do this (didn’t find anything) ?

I have a Haskell program running on my VPS; each log entry is just a single line of JSON, without timestamp, since the program is run as a systemd user service, I can just grep the journalctl output and see the time.

2 Likes