| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Katip.Core
Description
This module is not meant to be imported directly and may contain internal mechanisms that will change without notice.
Synopsis
- readMay :: Read a => String -> Maybe a
- newtype Namespace = Namespace {- unNamespace :: [Text]
 
- intercalateNs :: Namespace -> [Text]
- newtype Environment = Environment {}
- data Severity
- data Verbosity
- renderSeverity :: Severity -> Text
- textToSeverity :: Text -> Maybe Severity
- newtype LogStr = LogStr {}
- logStr :: StringConv a Text => a -> LogStr
- ls :: StringConv a Text => a -> LogStr
- showLS :: Show a => a -> LogStr
- newtype ThreadIdText = ThreadIdText {}
- mkThreadIdText :: ThreadId -> ThreadIdText
- data Item a = Item {}
- 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
- class ToObject a => LogItem a where- payloadKeys :: Verbosity -> a -> PayloadSelection
 
- data AnyLogPayload = 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
- type PermitFunc = forall a. Item a -> IO Bool
- permitAND :: PermitFunc -> PermitFunc -> PermitFunc
- permitOR :: PermitFunc -> PermitFunc -> PermitFunc
- data Scribe = Scribe {- liPush :: forall a. LogItem a => Item a -> IO ()
- scribeFinalizer :: IO ()
- scribePermitItem :: PermitFunc
 
- whenM :: Monad m => m Bool -> m () -> m ()
- data ScribeHandle = ScribeHandle {}
- data WorkerMessage where- NewItem :: LogItem a => Item a -> WorkerMessage
- PoisonPill :: WorkerMessage
 
- permitItem :: Monad m => Severity -> Item a -> m Bool
- data LogEnv = LogEnv {}
- logEnvTimer :: Lens' LogEnv (IO UTCTime)
- logEnvScribes :: Lens' LogEnv (Map Text ScribeHandle)
- logEnvPid :: Lens' LogEnv ProcessID
- logEnvHost :: Lens' LogEnv HostName
- logEnvEnv :: Lens' LogEnv Environment
- logEnvApp :: Lens' LogEnv Namespace
- initLogEnv :: Namespace -> Environment -> IO LogEnv
- registerScribe :: Text -> Scribe -> ScribeSettings -> LogEnv -> IO LogEnv
- spawnScribeWorker :: Scribe -> TBQueue WorkerMessage -> IO (Async ())
- data ScribeSettings = ScribeSettings {}
- scribeBufferSize :: Lens' ScribeSettings Int
- defaultScribeSettings :: ScribeSettings
- unregisterScribe :: Text -> LogEnv -> LogEnv
- clearScribes :: LogEnv -> LogEnv
- closeScribe :: Text -> LogEnv -> IO LogEnv
- closeScribes :: LogEnv -> IO LogEnv
- class MonadIO m => Katip m where- getLogEnv :: m LogEnv
- localLogEnv :: (LogEnv -> LogEnv) -> m a -> m a
 
- newtype KatipT m a = KatipT {}
- runKatipT :: LogEnv -> KatipT m a -> m a
- katipNoLogging :: Katip m => m a -> m a
- logItem :: (Applicative m, LogItem a, Katip m) => a -> Namespace -> Maybe Loc -> Severity -> LogStr -> m ()
- tryWriteTBQueue :: TBQueue a -> a -> STM Bool
- 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 :: HasCallStack => Maybe Loc
- getLocTH :: ExpQ
- logT :: ExpQ
- logLoc :: (Applicative m, LogItem a, Katip m, HasCallStack) => 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"].
Constructors
| Namespace | |
| Fields 
 | |
Instances
| Eq Namespace Source # | |
| Ord Namespace Source # | |
| Read Namespace Source # | |
| Show Namespace Source # | |
| IsString Namespace Source # | |
| Defined in Katip.Core Methods fromString :: String -> Namespace # | |
| Generic Namespace Source # | |
| Semigroup Namespace Source # | |
| Monoid Namespace Source # | |
| Lift Namespace Source # | |
| ToJSON Namespace Source # | |
| Defined in Katip.Core | |
| FromJSON Namespace Source # | |
| type Rep Namespace Source # | |
| Defined in Katip.Core | |
intercalateNs :: Namespace -> [Text] Source #
Ready namespace for emission with dots to join the segments.
newtype Environment Source #
Application environment, like prod, devel, testing.
Constructors
| Environment | |
| Fields | |
Instances
Constructors
| DebugS | Debug messages | 
| InfoS | Information | 
| NoticeS | Normal runtime Conditions | 
| WarningS | General Warnings | 
| ErrorS | General Errors | 
| CriticalS | Severe situations | 
| AlertS | Take immediate action | 
| EmergencyS | System is unusable | 
Instances
| Bounded Severity Source # | |
| Enum Severity Source # | |
| Eq Severity Source # | |
| Ord Severity Source # | |
| Defined in Katip.Core | |
| Read Severity Source # | |
| Show Severity Source # | |
| Generic Severity Source # | |
| Lift Severity Source # | |
| ToJSON Severity Source # | |
| Defined in Katip.Core | |
| FromJSON Severity Source # | |
| type Rep Severity Source # | |
| Defined in Katip.Core type Rep Severity = D1 (MetaData "Severity" "Katip.Core" "katip-0.8.0.0-7EA1PNPydAx5lRUNSnm2Nb" False) (((C1 (MetaCons "DebugS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "InfoS" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NoticeS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WarningS" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ErrorS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CriticalS" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "AlertS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EmergencyS" PrefixI False) (U1 :: Type -> Type)))) | |
Verbosity controls the amount of information (columns) a Scribe
 emits during logging.
The convention is:
 - V0 implies no additional payload information is included in message.
 - V3 implies the maximum amount of payload information.
 - Anything in between is left to the discretion of the developer.
Instances
| Bounded Verbosity Source # | |
| Enum Verbosity Source # | |
| Defined in Katip.Core Methods succ :: Verbosity -> Verbosity # pred :: Verbosity -> Verbosity # fromEnum :: Verbosity -> Int # enumFrom :: Verbosity -> [Verbosity] # enumFromThen :: Verbosity -> Verbosity -> [Verbosity] # enumFromTo :: Verbosity -> Verbosity -> [Verbosity] # enumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity] # | |
| Eq Verbosity Source # | |
| Ord Verbosity Source # | |
| Read Verbosity Source # | |
| Show Verbosity Source # | |
| Generic Verbosity Source # | |
| Lift Verbosity Source # | |
| ToJSON Verbosity Source # | |
| Defined in Katip.Core | |
| FromJSON Verbosity Source # | |
| type Rep Verbosity Source # | |
| Defined in Katip.Core type Rep Verbosity = D1 (MetaData "Verbosity" "Katip.Core" "katip-0.8.0.0-7EA1PNPydAx5lRUNSnm2Nb" False) ((C1 (MetaCons "V0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "V1" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "V2" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "V3" PrefixI False) (U1 :: Type -> Type))) | |
renderSeverity :: Severity -> Text Source #
Log message with Builder underneath; use <> to concat in O(1).
newtype ThreadIdText Source #
Constructors
| ThreadIdText | |
| Fields | |
Instances
| Eq ThreadIdText Source # | |
| Defined in Katip.Core | |
| Ord ThreadIdText Source # | |
| Defined in Katip.Core Methods compare :: ThreadIdText -> ThreadIdText -> Ordering # (<) :: ThreadIdText -> ThreadIdText -> Bool # (<=) :: ThreadIdText -> ThreadIdText -> Bool # (>) :: ThreadIdText -> ThreadIdText -> Bool # (>=) :: ThreadIdText -> ThreadIdText -> Bool # max :: ThreadIdText -> ThreadIdText -> ThreadIdText # min :: ThreadIdText -> ThreadIdText -> ThreadIdText # | |
| Show ThreadIdText Source # | |
| Defined in Katip.Core Methods showsPrec :: Int -> ThreadIdText -> ShowS # show :: ThreadIdText -> String # showList :: [ThreadIdText] -> ShowS # | |
| ToJSON ThreadIdText Source # | |
| Defined in Katip.Core Methods toJSON :: ThreadIdText -> Value # toEncoding :: ThreadIdText -> Encoding # toJSONList :: [ThreadIdText] -> Value # toEncodingList :: [ThreadIdText] -> Encoding # | |
| FromJSON ThreadIdText Source # | |
| Defined in Katip.Core | |
This has everything each log message will contain.
Constructors
| Item | |
| Fields 
 | |
Instances
itemThread :: forall a. Lens' (Item a) ThreadIdText Source #
processIDToText :: ProcessID -> Text Source #
newtype ProcessIDJs Source #
Constructors
| ProcessIDJs | |
| Fields | |
Instances
| ToJSON ProcessIDJs Source # | |
| Defined in Katip.Core Methods toJSON :: ProcessIDJs -> Value # toEncoding :: ProcessIDJs -> Encoding # toJSONList :: [ProcessIDJs] -> Value # toEncodingList :: [ProcessIDJs] -> Encoding # | |
| FromJSON ProcessIDJs Source # | |
| Defined in Katip.Core | |
data PayloadSelection Source #
Field selector by verbosity within JSON payload.
Instances
| Eq PayloadSelection Source # | |
| Defined in Katip.Core Methods (==) :: PayloadSelection -> PayloadSelection -> Bool # (/=) :: PayloadSelection -> PayloadSelection -> Bool # | |
| Show PayloadSelection Source # | |
| Defined in Katip.Core Methods showsPrec :: Int -> PayloadSelection -> ShowS # show :: PayloadSelection -> String # showList :: [PayloadSelection] -> ShowS # | |
| Semigroup PayloadSelection Source # | |
| Defined in Katip.Core Methods (<>) :: PayloadSelection -> PayloadSelection -> PayloadSelection # sconcat :: NonEmpty PayloadSelection -> PayloadSelection # stimes :: Integral b => b -> PayloadSelection -> PayloadSelection # | |
| Monoid PayloadSelection Source # | |
| Defined in Katip.Core Methods mappend :: PayloadSelection -> PayloadSelection -> PayloadSelection # mconcat :: [PayloadSelection] -> PayloadSelection # | |
class ToObject a where Source #
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
Minimal complete definition
Nothing
Instances
| ToObject () Source # | |
| Defined in Katip.Core | |
| ToObject Object Source # | |
| ToObject SimpleLogPayload Source # | |
| Defined in Katip.Core Methods toObject :: SimpleLogPayload -> Object Source # | |
| ToObject LogContexts Source # | |
| Defined in Katip.Monadic Methods toObject :: LogContexts -> Object Source # | |
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.
Methods
payloadKeys :: Verbosity -> a -> PayloadSelection Source #
List of keys in the JSON object that should be included in message.
Instances
| LogItem () Source # | |
| Defined in Katip.Core Methods payloadKeys :: Verbosity -> () -> PayloadSelection Source # | |
| LogItem SimpleLogPayload Source # | |
| Defined in Katip.Core Methods payloadKeys :: Verbosity -> SimpleLogPayload -> PayloadSelection Source # | |
| LogItem LogContexts Source # | |
| Defined in Katip.Monadic Methods payloadKeys :: Verbosity -> LogContexts -> PayloadSelection Source # | |
data AnyLogPayload Source #
Constructors
| ToJSON a => AnyLogPayload a | 
newtype SimpleLogPayload Source #
Constructors
| SimpleLogPayload | |
| Fields 
 | |
Instances
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.
type PermitFunc = forall a. Item a -> IO Bool Source #
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 lower than
 the provided Severity. For instance, if the user passes InfoS,
 DebugS items should be ignored. Katip provides the permitItem
 utility for this. The user or the scribe may use permitAND and
 permitOR to further customize this filtering, even dynamically if
 they wish to.
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 written.
Scribes provide a finalizer IO action (scribeFinalizer) that is
 meant to synchronously flush any remaining writes and clean up any
 resources acquired when the scribe was created. Internally, katip
 keeps a buffer for each scribe's writes. When closeScribe or
 closeScribes is called, that buffer stops accepting new log
 messages and after the last item in its buffer is sent to liPush,
 calls the finalizer. Thus, when the finalizer returns, katip can
 assume that all resources are cleaned up and all log messages are
 durably written.
While katip internally buffers messages per ScribeSettings, it
 sends them one at a time to the scribe. Depending on the scribe
 itself, it may make sense for that scribe to keep its own internal
 buffer to batch-send logs if writing items one at a time is not
 efficient. The scribe implementer must be sure that on
 finalization, all writes are committed synchronously.
Signature of a function passed to Scribe constructor and
   mkScribe* functions that decides which messages to be
   logged. Typically filters based on Severity, but can be
   combined with other, custom logic with permitAND and permitOR
permitAND :: PermitFunc -> PermitFunc -> PermitFunc Source #
AND together 2 permit functions
permitOR :: PermitFunc -> PermitFunc -> PermitFunc Source #
OR together 2 permit functions
Constructors
| Scribe | |
| Fields 
 | |
data ScribeHandle Source #
Constructors
| ScribeHandle | |
| Fields 
 | |
data WorkerMessage where Source #
Constructors
| NewItem :: LogItem a => Item a -> WorkerMessage | |
| PoisonPill :: WorkerMessage | 
permitItem :: Monad m => Severity -> Item a -> m Bool Source #
Should this item be logged given the user's maximum severity?
 Most new scribes will use this as a base for their PermitFunc
Constructors
| LogEnv | |
| Fields 
 | |
Arguments
| :: Namespace | A base namespace for this application | 
| -> Environment | Current run environment (e.g.  | 
| -> IO LogEnv | 
Create a reasonable default InitLogEnv. Uses an AutoUdate which
 updates the timer every 1ms. If you need even more timestamp
 precision at the cost of performance, consider setting
 _logEnvTimer with getCurrentTime.
Add a scribe to the list. All future log calls will go to this scribe in addition to the others. Writes will be buffered per the ScribeSettings to prevent slow scribes from slowing down logging. Writes will be dropped if the buffer fills.
spawnScribeWorker :: Scribe -> TBQueue WorkerMessage -> IO (Async ()) Source #
data ScribeSettings Source #
Constructors
| ScribeSettings | |
| Fields | |
Instances
| Eq ScribeSettings Source # | |
| Defined in Katip.Core Methods (==) :: ScribeSettings -> ScribeSettings -> Bool # (/=) :: ScribeSettings -> ScribeSettings -> Bool # | |
| Show ScribeSettings Source # | |
| Defined in Katip.Core Methods showsPrec :: Int -> ScribeSettings -> ShowS # show :: ScribeSettings -> String # showList :: [ScribeSettings] -> ShowS # | |
defaultScribeSettings :: ScribeSettings Source #
Reasonable defaults for a scribe. Buffer size of 4096.
Remove a scribe from the environment. This does not finalize
 the scribe. This mainly only makes sense to use with something like
 MonadReader's local function to temporarily disavow a single
 logger for a block of code.
clearScribes :: LogEnv -> LogEnv Source #
Unregister all scribes. Note that this is not for closing or
 finalizing scribes, use closeScribes for that. This mainly only
 makes sense to use with something like MonadReader's local
 function to temporarily disavow any loggers for a block of code.
Finalize a scribe. The scribe is removed from the environment, its finalizer is called so that it can never be written to again and all pending writes are flushed. Note that this will throw any exceptions yoru finalizer will throw, and that LogEnv is immutable, so it will not be removed in that case.
closeScribes :: LogEnv -> IO LogEnv Source #
Call this at the end of your program. This is a blocking call that stop writing to a scribe's queue, waits for the queue to empty, finalizes each scribe in the log environment and then removes it. Finalizers are all run even if one of them throws, but the exception will be re-thrown at the end.
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.
localLogEnv was added to allow for lexically-scoped modifications
 of the log env that are reverted when the supplied monad
 completes. katipNoLogging, for example, uses this to temporarily
 pause log outputs.
Instances
| Katip m => Katip (MaybeT m) Source # | |
| Katip m => Katip (ResourceT m) Source # | |
| MonadIO m => Katip (KatipT m) Source # | |
| MonadIO m => Katip (NoLoggingT m) Source # | |
| Defined in Katip.Monadic Methods getLogEnv :: NoLoggingT m LogEnv Source # localLogEnv :: (LogEnv -> LogEnv) -> NoLoggingT m a -> NoLoggingT m a Source # | |
| MonadIO m => Katip (KatipContextT m) Source # | |
| Defined in Katip.Monadic Methods getLogEnv :: KatipContextT m LogEnv Source # localLogEnv :: (LogEnv -> LogEnv) -> KatipContextT m a -> KatipContextT m a Source # | |
| Katip m => Katip (ExceptT s m) Source # | |
| (Katip m, Monoid s) => Katip (WriterT s m) Source # | |
| Katip m => Katip (StateT s m) Source # | |
| Katip m => Katip (StateT s m) Source # | |
| (Katip m, Monoid s) => Katip (WriterT s m) Source # | |
| Katip m => Katip (ReaderT s m) Source # | |
| (Katip m, Monoid w) => Katip (RWST r w s m) Source # | |
| (Katip m, Monoid w) => Katip (RWST r w s m) Source # | |
A concrete monad you can use to run logging actions. Use this if
 you prefer an explicit monad transformer stack and adding layers as
 opposed to implementing Katip for your monad.
Instances
katipNoLogging :: Katip m => m a -> m a Source #
Disable all scribes for the given monadic action, then restore them afterwards. Works in any Katip monad.
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.
Arguments
| :: (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.
Arguments
| :: (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 :: HasCallStack => 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, HasCallStack) => a -> Namespace -> Severity -> LogStr -> m () Source #
Loc-tagged logging using Stack 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 #