Blammo: Batteries-included Structured Logging library

[ library, mit, utils ] [ Propose Tags ]
Versions [RSS] 1.0.0.0, 1.0.0.1, 1.0.1.1, 1.0.2.1, 1.0.2.2, 1.0.2.3, 1.0.3.0, 1.1.0.0, 1.1.1.0, 1.1.1.1, 1.1.1.2, 1.1.2.0, 1.1.2.1, 1.1.2.2
Change log CHANGELOG.md
Dependencies aeson (>=1.5.2.0), base (>=4.11.1.0 && <5), bytestring (>=0.10.8.2), case-insensitive (>=1.2.0.11), clock (>=0.7.2), containers (>=0.5.11.0), dlist (>=0.8.0.5), envparse (>=0.5.0), exceptions (>=0.10.0), fast-logger (>=2.4.11), http-types (>=0.12.2), lens (>=4.16.1), monad-logger-aeson (>=0.3.0.2), mtl (>=2.2.2), text (>=1.2.3.1), time (>=1.8.0.2), unliftio (>=0.2.9.0), unliftio-core (>=0.1.2.0), unordered-containers (>=0.2.10.0), vector (>=0.12.0.2), wai (>=3.2.1.2) [details]
License MIT
Author
Maintainer Freckle Education
Category Utils
Home page https://github.com/freckle/blammo#readme
Bug tracker https://github.com/freckle/blammo/issues
Source repo head: git clone https://github.com/freckle/blammo
Uploaded by PatrickBrisbin at 2022-07-07T13:24:34Z
Distributions LTSHaskell:1.1.2.2, NixOS:1.1.2.1, Stackage:1.1.2.2
Reverse Dependencies 3 direct, 0 indirect [details]
Downloads 992 total (68 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2022-07-07 [all 1 reports]

Readme for Blammo-1.0.2.2

[back to package description]

Blammo

Blammo is a Structured Logging library that's

  • Easy to use: one import and go!
  • Easy to configure: environment variable parsing out of the box!
  • Easy to integrate: see below for Amazonka, Yesod, and more!
  • Produces beautiful, colorful output in development
  • Produces fast-fast JSON in production

All built on the well-known MonadLogger interface and using an efficient fast-logger implementation.

It's better than bad, it's good!

Simple Usage

import Blammo.Logging.Simple

Throughout your application, you should write against the ubiquitous MonadLogger interface:

action1 :: MonadLogger m => m ()
action1 = do
  logInfo "This is a message sans details"

And make use of monad-logger-aeson for structured details:

data MyError = MyError
  { code :: Int
  , messages :: [Text]
  }
  deriving stock Generic
  deriving anyclass ToJSON

action2 :: MonadLogger m => m ()
action2 = do
  logError $ "Something went wrong" :# ["error" .= MyError 100 ["x", "y"]]
  logDebug "This won't be seen in default settings"

When you run your transformer stack, wrap it in runLoggerLoggingT providing any value with a HasLogger instance (such as your main App). The Logger type itself has such an instance, and we provide runSimpleLoggingT for the simplest case: it creates one configured via environment variables and then calls runLoggerLoggingT with it.

You can use withThreadContext (from monad-logger-aeson) to add details that will appear in all the logged messages within that scope. Placing one of these at the very top-level adds details to all logged messages.

runner :: LoggingT IO a -> IO a
runner = runSimpleLoggingT . withThreadContext ["app" .= ("example" :: Text)]

main :: IO ()
main = runner $ do
  action1
  action2

The defaults are good for CLI applications, producing colorful output (if connected to a terminal device) suitable for a human:

Under the hood, Logging.Settings.Env is using envparse to configure logging through environment variables. See that module for full details. One thing we can adjust is LOG_LEVEL:

In production, you will probably want to set LOG_FORMAT=json and ship logs to some aggregator like Datadog or Mezmo (formerly LogDNA):

Configuration

Setting Setter Environment variable and format
Level(s) setLogSettingsLevels LOG_LEVEL=<level>[,<source:level>,...]
Destination setLogSettingsDestination LOG_DESTINATION=stdout|stderr|@<path>
Format setLogSettingsFormat LOG_FORMAT=tty|json

Advanced Usage

Add our environment variable parser to your own,

data AppSettings = AppSettings
  { appDryRun :: Bool
  , appLogSettings :: LogSettings
  , -- ...
  }

loadAppSettings :: IO AppSettings
loadAppSettings = Env.parse id $ AppSettings
  <$> var switch "DRY_RUN" mempty
  <*> LogSettingsEnv.parser
  <*> -- ...

Load a Logger into your App type and define HasLogger,

data App = App
  { appSettings :: AppSettings
  , appLogger :: Logger
  , -- ...
  }

instance HasLogger App where
  loggerL = lens appLogger $ \x y -> x { appLogger = y }

loadApp :: IO App
loadApp = do
  appSettings <- loadAppSettings
  appLogger <- newLogger $ appLogSettings appSettings
  -- ...
  pure App {..}

Use runLoggerLoggingT,

runAppT :: App -> ReaderT App (LoggingT IO) a -> IO a
runAppT app f = runLoggerLoggingT app $ runReaderT f app

Integration with RIO

data App = App
  { appLogFunc :: LogFunc
  , -- ...
  }

instance HasLogFuncApp where
  logFuncL = lens appLogFunc $ \x y -> x { logFunc = y }

runApp :: MonadIO m => RIO App a -> m a
runApp f = runSimpleLoggingT $ do
  loggerIO <- askLoggerIO

  let
    logFunc = mkLogFunc $ \cs source level msg -> loggerIO
      (callStackLoc cs)
      source
      (fromRIOLevel level)
      (getUtf8Builder msg)

  app <- App logFunc
    <$> -- ...
    <*> -- ...

  runRIO app $ f

callStackLoc :: CallStack -> Loc
callStackLoc = undefined

fromRIOLevel :: RIO.LogLevel -> LogLevel
fromRIOLevel = undefined

Integration with Amazonka

data App = App
  { appLogger :: Logger
  , appAWS :: AWS.Env
  }

instance HasLogger App where
  -- ...

runApp :: ReaderT App (LoggingT IO) a -> IO a
runApp f = do
  logger <- newLogger defaultLogSettings
  app <- App logger <$> runLoggerLoggingT logger awsDiscover
  runLoggerLoggingT app $ runReaderT f app

awsDiscover :: (MonadIO m, MonadLoggerIO m) => m AWS.Env
awsDiscover = do
  loggerIO <- askLoggerIO
  env <- liftIO $ AWS.newEnv AWS.discover
  pure $ env
    { AWS.envLogger = \level msg -> do
      loggerIO
        defaultLoc -- TODO: there may be a way to get a CallStack/Loc
        "Amazonka"
        (case level of
          AWS.Info -> LevelInfo
          AWS.Error -> LevelError
          AWS.Debug -> LevelDebug
          AWS.Trace -> LevelOther "trace"
        )
        (toLogStr msg)
    }

Integration with WAI

import Network.Wai.Middleware.Logging

instance HasLogger App where
  -- ...

waiMiddleware :: App -> Middleware
waiMiddleware app =
  addThreadContext ["app" .= ("my-app" :: Text)]
    $ requestLogger app
    $ defaultMiddlewaresNoLogging

Integration with Warp

instance HasLogger App where
  -- ...

warpSettings :: App -> Settings
warpSettings app = setOnException onEx $ defaultSettings
 where
  onEx _req ex =
    when (defaultShouldDisplayException ex)
      $ runLoggerLoggingT app
      $ logError
      $ "Warp exception"
      :# ["exception" .= displayException ex]

Integration with Yesod

instance HasLogger App where
  -- ...

instance Yesod App where
  -- ...

  messageLoggerSource app _logger loc source level msg =
    runLoggerLoggingT app $ monadLoggerLog loc source level msg

LICENSE | CHANGELOG