Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module is not meant to be imported directly and may contain internal mechanisms that will change without notice.
- readMay :: Read a => String -> Maybe a
- newtype Namespace = Namespace {
- unNamespace :: [Text]
- intercalateNs :: Namespace -> [Text]
- newtype Environment = Environment {
- getEnvironment :: Text
- data Severity
- data Verbosity
- renderSeverity :: Severity -> Text
- textToSeverity :: Text -> Maybe Severity
- newtype LogStr = LogStr {
- unLogStr :: Builder
- logStr :: StringConv a Text => a -> LogStr
- ls :: StringConv a Text => a -> LogStr
- showLS :: Show a => a -> LogStr
- newtype ThreadIdText = ThreadIdText {
- getThreadIdText :: Text
- mkThreadIdText :: ThreadId -> ThreadIdText
- data Item a = Item {
- _itemApp :: Namespace
- _itemEnv :: Environment
- _itemSeverity :: Severity
- _itemThread :: ThreadIdText
- _itemHost :: HostName
- _itemProcess :: ProcessID
- _itemPayload :: a
- _itemMessage :: LogStr
- _itemTime :: UTCTime
- _itemNamespace :: Namespace
- _itemLoc :: Maybe Loc
- itemTime :: forall a. Lens' (Item a) UTCTime
- itemThread :: forall a. Lens' (Item a) ThreadIdText
- itemSeverity :: forall a. Lens' (Item a) Severity
- itemProcess :: forall a. Lens' (Item a) ProcessID
- itemPayload :: forall a a. Lens (Item a) (Item a) a a
- itemNamespace :: forall a. Lens' (Item a) Namespace
- itemMessage :: forall a. Lens' (Item a) LogStr
- itemLoc :: forall a. Lens' (Item a) (Maybe Loc)
- itemHost :: forall a. Lens' (Item a) HostName
- itemEnv :: forall a. Lens' (Item a) Environment
- itemApp :: forall a. Lens' (Item a) Namespace
- newtype LocShow = LocShow Loc
- newtype LocJs = LocJs {}
- processIDToText :: ProcessID -> Text
- textToProcessID :: Text -> Maybe ProcessID
- newtype ProcessIDJs = ProcessIDJs {}
- data PayloadSelection
- class ToObject a where
- toObject :: a -> Object
- class ToObject a => LogItem a where
- payloadKeys :: Verbosity -> a -> PayloadSelection
- data AnyLogPayload = forall a . ToJSON a => AnyLogPayload a
- newtype SimpleLogPayload = SimpleLogPayload {
- unSimpleLogPayload :: [(Text, AnyLogPayload)]
- sl :: ToJSON a => Text -> a -> SimpleLogPayload
- payloadObject :: LogItem a => Verbosity -> a -> Object
- itemJson :: LogItem a => Verbosity -> Item a -> Value
- data Scribe = Scribe {}
- permitItem :: Severity -> Item a -> Bool
- data LogEnv = LogEnv {
- _logEnvHost :: HostName
- _logEnvPid :: ProcessID
- _logEnvApp :: Namespace
- _logEnvEnv :: Environment
- _logEnvTimer :: IO UTCTime
- _logEnvScribes :: Map Text Scribe
- logEnvTimer :: Lens' LogEnv (IO UTCTime)
- logEnvScribes :: Lens' LogEnv (Map Text Scribe)
- logEnvPid :: Lens' LogEnv ProcessID
- logEnvHost :: Lens' LogEnv HostName
- logEnvEnv :: Lens' LogEnv Environment
- logEnvApp :: Lens' LogEnv Namespace
- initLogEnv :: Namespace -> Environment -> IO LogEnv
- registerScribe :: Text -> Scribe -> LogEnv -> LogEnv
- unregisterScribe :: Text -> LogEnv -> LogEnv
- clearScribes :: LogEnv -> LogEnv
- class MonadIO m => Katip m where
- newtype KatipT m a = KatipT {}
- runKatipT :: LogEnv -> KatipT m a -> m a
- logItem :: (Applicative m, LogItem a, Katip m) => a -> Namespace -> Maybe Loc -> Severity -> LogStr -> m ()
- logF :: (Applicative m, LogItem a, Katip m) => a -> Namespace -> Severity -> LogStr -> m ()
- logException :: (Katip m, LogItem a, MonadCatch m, Applicative m) => a -> Namespace -> Severity -> m b -> m b
- logMsg :: (Applicative m, Katip m) => Namespace -> Severity -> LogStr -> m ()
- liftLoc :: Loc -> Q Exp
- getLoc :: (?loc :: CallStack) => Maybe Loc
- getLocTH :: ExpQ
- logT :: ExpQ
- logLoc :: (Applicative m, LogItem a, Katip m) => a -> Namespace -> Severity -> LogStr -> m ()
- locationToString :: Loc -> String
Documentation
Represents a heirarchy of namespaces going from general to specific. For instance: ["processname", "subsystem"]. Note that single-segment namespaces can be created using IsString/OverloadedStrings, so "foo" will result in Namespace ["foo"].
Namespace | |
|
intercalateNs :: Namespace -> [Text] Source
Ready namespace for emission with dots to join the segments.
newtype Environment Source
Application environment, like prod
, devel
, testing
.
Environment | |
|
renderSeverity :: Severity -> Text Source
textToSeverity :: Text -> Maybe Severity Source
Log message with Builder unerneath; use <>
to concat in O(1).
newtype ThreadIdText Source
ThreadIdText | |
|
Eq ThreadIdText Source | |
Ord ThreadIdText Source | |
Show ThreadIdText Source | |
ToJSON ThreadIdText Source | |
FromJSON ThreadIdText Source |
This has everything each log message will contain.
Item | |
|
itemThread :: forall a. Lens' (Item a) ThreadIdText Source
itemSeverity :: forall a. Lens' (Item a) Severity Source
itemProcess :: forall a. Lens' (Item a) ProcessID Source
itemPayload :: forall a a. Lens (Item a) (Item a) a a Source
itemNamespace :: forall a. Lens' (Item a) Namespace Source
itemMessage :: forall a. Lens' (Item a) LogStr Source
itemEnv :: forall a. Lens' (Item a) Environment Source
processIDToText :: ProcessID -> Text Source
textToProcessID :: Text -> Maybe ProcessID Source
newtype ProcessIDJs Source
ToJSON ProcessIDJs Source | |
FromJSON ProcessIDJs Source |
data PayloadSelection Source
Field selector by verbosity within JSON payload.
Katip requires JSON objects to be logged as context. This
typeclass provides a default instance which uses ToJSON and
produces an empty object if toJSON
results in any type other than
object. If you have a type you want to log that produces an Array
or Number for example, you'll want to write an explicit instance
here. You can trivially add a ToObject instance for something with
a ToJSON instance like:
instance ToObject Foo
Nothing
class ToObject a => LogItem a where Source
Payload objects need instances of this class. LogItem makes it so
that you can have very verbose items getting logged with lots of
extra fields but under normal circumstances, if your scribe is
configured for a lower verbosity level, it will only log a
selection of those keys. Furthermore, each Scribe
can be
configured with a different Verbosity
level. You could even use
registerScribe
, unregisterScribe
, and clearScribes
to at
runtime swap out your existing scribes for more verbose debugging
scribes if you wanted to.
When defining payloadKeys
, don't redundantly declare the same
keys for higher levels of verbosity. Each level of verbosity
automatically and recursively contains all keys from the level
before it.
payloadKeys :: Verbosity -> a -> PayloadSelection Source
List of keys in the JSON object that should be included in message.
data AnyLogPayload Source
forall a . ToJSON a => AnyLogPayload a |
newtype SimpleLogPayload Source
SimpleLogPayload | |
|
Monoid SimpleLogPayload Source | |
Semigroup SimpleLogPayload Source | |
ToJSON SimpleLogPayload Source | A built-in convenience log payload that won't log anything on Construct using |
LogItem SimpleLogPayload Source | |
ToObject SimpleLogPayload Source |
sl :: ToJSON a => Text -> a -> SimpleLogPayload Source
Construct a simple log from any JSON item.
payloadObject :: LogItem a => Verbosity -> a -> Object Source
Constrain payload based on verbosity. Backends should use this to automatically bubble higher verbosity levels to lower ones.
itemJson :: LogItem a => Verbosity -> Item a -> Value Source
Convert log item to its JSON representation while trimming its payload based on the desired verbosity. Backends that push JSON messages should use this to obtain their payload.
Scribes are handlers of incoming items. Each registered scribe knows how to push a log item somewhere.
Guidelines for writing your own Scribe
Scribes should always take a Severity
and Verbosity
.
Severity is used to *exclude log messages* that are < the provided
Severity. For instance, if the user passes InfoS, DebugS items
should be ignored. Katip provides the permitItem
utility for this.
Verbosity is used to select keys from the log item's payload. Each
LogItem
instance describes what keys should be retained for each
Verbosity level. Use the payloadObject
utility for extracting the keys
that should be permitted.
There is no built-in mechanism in katip for telling a scribe that
its time to shut down. unregisterScribe
merely drops it from the
LogEnv
. This means there are 2 ways to handle resources as a scribe:
- Pass in the resource when the scribe is created. Handle allocation and release of the resource elsewhere. This is what the Handle scribe does.
- Return a finalizing function that tells the scribe to shut
down.
katip-elasticsearch
'smkEsScribe
returns aIO (Scribe, IO ())
. The finalizer will flush any queued log messages and shut down gracefully before returning. This can be hooked into your application's shutdown routine to ensure you never miss any log messages on shutdown.
permitItem :: Severity -> Item a -> Bool Source
Should this item be logged given the user's maximum severity?
LogEnv | |
|
logEnvTimer :: Lens' LogEnv (IO UTCTime) Source
logEnvScribes :: Lens' LogEnv (Map Text Scribe) Source
logEnvHost :: Lens' LogEnv HostName Source
logEnvEnv :: Lens' LogEnv Environment Source
:: Namespace | A base namespace for this application |
-> Environment | Current run environment (e.g. |
-> IO LogEnv |
Create a reasonable default InitLogEnv. Uses an AutoUdate
with
the default settings as the timer. If you are concerned about
timestamp precision or event ordering in log outputs like
ElasticSearch, you should replace the timer with getCurrentTime
Add a scribe to the list. All future log calls will go to this scribe in addition to the others.
Remove a scribe from the list. All future log calls will no longer use this scribe. If the given scribe doesn't exist, its a no-op.
clearScribes :: LogEnv -> LogEnv Source
Unregister *all* scribes. Logs will go off into space from this
point onward until new scribes are added. Note that you could use
this with local
if you're using a Reader based stack to
temporarily disable log output. See katipNoLogging
for an
example.
class MonadIO m => Katip m where Source
Monads where katip logging actions can be performed. Katip is the most basic logging monad. You will typically use this directly if you either don't want to use namespaces/contexts heavily or if you want to pass in specific contexts and/or namespaces at each log site.
For something more powerful, look at the docs for KatipContext
,
which keeps a namespace and merged context. You can write simple
functions that add additional namespacing and merges additional
context on the fly.
Katip m => Katip (MaybeT m) Source | |
Katip m => Katip (ResourceT m) Source | |
MonadIO m => Katip (KatipT m) Source | |
MonadIO m => Katip (KatipContextT m) Source | |
Katip m => Katip (ReaderT s m) Source | |
Katip m => Katip (StateT s m) Source | |
Katip m => Katip (ExceptT s m) Source | |
(Katip m, Monoid s) => Katip (WriterT s m) Source | |
Katip m => Katip (EitherT s m) Source |
A concrete monad you can use to run logging actions.
MonadTrans KatipT Source | |
MonadTransControl KatipT Source | |
MonadBase b m => MonadBase b (KatipT m) Source | |
MonadBaseControl b m => MonadBaseControl b (KatipT m) Source | |
Monad m => Monad (KatipT m) Source | |
Functor m => Functor (KatipT m) Source | |
Applicative m => Applicative (KatipT m) Source | |
MonadIO m => MonadIO (KatipT m) Source | |
MonadThrow m => MonadThrow (KatipT m) Source | |
MonadMask m => MonadMask (KatipT m) Source | |
MonadCatch m => MonadCatch (KatipT m) Source | |
MonadIO m => Katip (KatipT m) Source | |
(Monad m, KatipContext m) => KatipContext (KatipT m) Source | |
type StT KatipT a = a Source | |
type StM (KatipT m) a = ComposeSt KatipT m a Source |
logItem :: (Applicative m, LogItem a, Katip m) => a -> Namespace -> Maybe Loc -> Severity -> LogStr -> m () Source
Log with everything, including a source code location. This is
very low level and you typically can use logT
in its place.
:: (Applicative m, LogItem a, Katip m) | |
=> a | Contextual payload for the log |
-> Namespace | Specific namespace of the message. |
-> Severity | Severity of the message |
-> LogStr | The log message |
-> m () |
Log with full context, but without any code location.
:: (Katip m, LogItem a, MonadCatch m, Applicative m) | |
=> a | Log context |
-> Namespace | Namespace |
-> Severity | Severity |
-> m b | Main action being run |
-> m b |
Perform an action while logging any exceptions that may occur.
Inspired by onException
.
>>>
> logException () mempty ErrorS (error "foo")
logMsg :: (Applicative m, Katip m) => Namespace -> Severity -> LogStr -> m () Source
Log a message without any payload/context or code location.
getLoc :: (?loc :: CallStack) => Maybe Loc Source
For use when you want to include location in your logs. This will
fill the 'Maybe Loc' gap in logF
of this module, and relies on implicit
callstacks when available (GHC > 7.8).
Loc
-tagged logging when using template-haskell.
$(logT) obj mempty InfoS "Hello world"
logLoc :: (Applicative m, LogItem a, Katip m) => a -> Namespace -> Severity -> LogStr -> m () Source
Loc
-tagged logging using implicit-callstacks when available.
This function does not require template-haskell as it
automatically uses implicit-callstacks
when the code is compiled using GHC > 7.8. Using an older version of the
compiler will result in the emission of a log line without any location information,
so be aware of it. Users using GHC <= 7.8 may want to use the template-haskell function
logT
for maximum compatibility.
logLoc obj mempty InfoS "Hello world"
locationToString :: Loc -> String Source