{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-| A contextual version of "Logging.Monad.TH". Logging with context is very usefull for tracking issues through log records or analyzing log records through other tools. It also provides a solution to custom record fields other than 'LogRecord''s fileds. For example, by using the following 'Format1', a line of json string will be written to a file or printed to the stderr. @ "{{\\\"logger\\\": \\\"{logger}\\\", \\\"context\\\": {context}}}" @ @since 0.8.0 -} module Logging.Monad.TH.Context ( logv , debug , info , warn , error , fatal ) where import Control.Monad.IO.Class (MonadIO) import Data.Aeson import Language.Haskell.TH import Prelude hiding (error, log) import Logging.Class import Logging.Level import Logging.Logger import Logging.Monad.Internal -- | Log "message" with the severity "level". -- -- The missing type signature: -- ('MonadIO' m, 'IsMessage' s, 'ToJSON' c) => 'Logger' -> 'Level' -> s -> c -- -> 'LoggingT' m () logv :: ExpQ logv = do loc <- location let filename = loc_filename loc packagename = loc_package loc modulename = loc_module loc lineno = fst $ loc_start loc location = (filename, packagename, modulename, lineno) [| \logger level msg ctx -> log logger level msg ctx location |] -- | Log "message" with a specific severity. -- -- The missing type signature: -- ('MonadIO' m, 'IsMessage' s, 'ToJSON' c) => 'Logger' -> s -> c -- -> 'LoggingT' m () debug, info, warn, error, fatal :: ExpQ debug = [| \logger -> $(logv) logger $ read "DEBUG" |] info = [| \logger -> $(logv) logger $ read "INFO" |] warn = [| \logger -> $(logv) logger $ read "WARN" |] error = [| \logger -> $(logv) logger $ read "ERROR" |] fatal = [| \logger -> $(logv) logger $ read "FATAL" |]