| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
RIO.Logger
- data LogLevel
- type LogSource = Text
- type LogStr = DisplayBuilder
- type LogFunc = CallStack -> LogSource -> LogLevel -> LogStr -> IO ()
- data CallStack :: *
- class HasLogFunc env where
- logGeneric :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogLevel -> LogStr -> m ()
- logDebug :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogStr -> m ()
- logInfo :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogStr -> m ()
- logWarn :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogStr -> m ()
- logError :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogStr -> m ()
- logDebugS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogStr -> m ()
- logInfoS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogStr -> m ()
- logWarnS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogStr -> m ()
- logErrorS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogStr -> m ()
- logOther :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Text -> LogStr -> m ()
- logSticky :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => LogStr -> m ()
- logStickyDone :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => LogStr -> m ()
- runNoLogging :: MonadIO m => ReaderT NoLogging m a -> m a
- data NoLogging = NoLogging
- withStickyLogger :: MonadUnliftIO m => LogOptions -> (LogFunc -> m a) -> m a
- data LogOptions = LogOptions {
- logMinLevel :: !LogLevel
- logVerboseFormat :: !Bool
- logTerminal :: !Bool
- logUseTime :: !Bool
- logUseColor :: !Bool
- logSend :: !(Builder -> IO ())
- displayCallStack :: CallStack -> DisplayBuilder
- mkLogOptions :: MonadIO m => Handle -> Bool -> m LogOptions
Documentation
Constructors
| LevelDebug | |
| LevelInfo | |
| LevelWarn | |
| LevelError | |
| LevelOther !Text |
type LogStr = DisplayBuilder Source #
CallStacks are a lightweight method of obtaining a
partial call-stack at any point in the program.
A function can request its call-site with the HasCallStack constraint.
For example, we can define
errorWithCallStack :: HasCallStack => String -> a
as a variant of error that will get its call-site. We can access the
call-stack inside errorWithCallStack with callStack.
errorWithCallStack :: HasCallStack => String -> a errorWithCallStack msg = error (msg ++ "n" ++ prettyCallStack callStack)
Thus, if we call errorWithCallStack we will get a formatted call-stack
alongside our error message.
>>>errorWithCallStack "die"*** Exception: die CallStack (from HasCallStack): errorWithCallStack, called at <interactive>:2:1 in interactive:Ghci1
GHC solves HasCallStack constraints in three steps:
- If there is a
CallStackin scope -- i.e. the enclosing function has aHasCallStackconstraint -- GHC will append the new call-site to the existingCallStack. - If there is no
CallStackin scope -- e.g. in the GHCi session above -- and the enclosing definition does not have an explicit type signature, GHC will infer aHasCallStackconstraint for the enclosing definition (subject to the monomorphism restriction). - If there is no
CallStackin scope and the enclosing definition has an explicit type signature, GHC will solve theHasCallStackconstraint for the singletonCallStackcontaining just the current call-site.
CallStacks do not interact with the RTS and do not require compilation
with -prof. On the other hand, as they are built up explicitly via the
HasCallStack constraints, they will generally not contain as much
information as the simulated call-stacks maintained by the RTS.
A CallStack is a [(String, SrcLoc)]. The String is the name of
function that was called, the SrcLoc is the call-site. The list is
ordered with the most recently called function at the head.
NOTE: The intrepid user may notice that HasCallStack is just an
alias for an implicit parameter ?callStack :: CallStack. This is an
implementation detail and should not be considered part of the
CallStack API, we may decide to change the implementation in the
future.
Since: 4.8.1.0
class HasLogFunc env where Source #
Minimal complete definition
Methods
logFuncL :: SimpleGetter env LogFunc Source #
Instances
logGeneric :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogLevel -> LogStr -> m () Source #
logDebug :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogStr -> m () Source #
logInfo :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogStr -> m () Source #
logWarn :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogStr -> m () Source #
logError :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogStr -> m () Source #
logDebugS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogStr -> m () Source #
logInfoS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogStr -> m () Source #
logWarnS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogStr -> m () Source #
logErrorS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogStr -> m () Source #
Arguments
| :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) | |
| => Text | level |
| -> LogStr | |
| -> m () |
logSticky :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => LogStr -> m () Source #
Write a "sticky" line to the terminal. Any subsequent lines will
overwrite this one, and that same line will be repeated below
again. In other words, the line sticks at the bottom of the output
forever. Running this function again will replace the sticky line
with a new sticky line. When you want to get rid of the sticky
line, run logStickyDone.
logStickyDone :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => LogStr -> m () Source #
This will print out the given message with a newline and disable
any further stickiness of the line until a new call to logSticky
happens.
It might be better at some point to have a runSticky function
that encompasses the logSticky->logStickyDone pairing.
withStickyLogger :: MonadUnliftIO m => LogOptions -> (LogFunc -> m a) -> m a Source #
data LogOptions Source #
Constructors
| LogOptions | |
Fields
| |
Arguments
| :: MonadIO m | |
| => Handle | |
| -> Bool | verbose? |
| -> m LogOptions |