| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
RIO.Prelude.Logger
Contents
- logDebug :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => DisplayBuilder -> m ()
- logInfo :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => DisplayBuilder -> m ()
- logWarn :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => DisplayBuilder -> m ()
- logError :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => DisplayBuilder -> m ()
- logOther :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Text -> DisplayBuilder -> m ()
- withLogFunc :: MonadUnliftIO m => LogOptions -> (LogFunc -> m a) -> m a
- data LogFunc
- class HasLogFunc env where
- logOptionsHandle :: MonadIO m => Handle -> Bool -> m LogOptions
- data LogOptions
- setLogMinLevel :: LogLevel -> LogOptions -> LogOptions
- setLogVerboseFormat :: Bool -> LogOptions -> LogOptions
- setLogTerminal :: Bool -> LogOptions -> LogOptions
- setLogUseTime :: Bool -> LogOptions -> LogOptions
- setLogUseColor :: Bool -> LogOptions -> LogOptions
- logSticky :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => DisplayBuilder -> m ()
- logStickyDone :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => DisplayBuilder -> m ()
- logDebugS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> DisplayBuilder -> m ()
- logInfoS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> DisplayBuilder -> m ()
- logWarnS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> DisplayBuilder -> m ()
- logErrorS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> DisplayBuilder -> m ()
- logOtherS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Text -> LogSource -> DisplayBuilder -> m ()
- logGeneric :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogLevel -> DisplayBuilder -> m ()
- mkLogFunc :: (CallStack -> LogSource -> LogLevel -> DisplayBuilder -> IO ()) -> LogFunc
- logOptionsMemory :: MonadIO m => m (IORef Builder, LogOptions)
- data LogLevel
- type LogSource = Text
- data CallStack :: *
- displayCallStack :: CallStack -> DisplayBuilder
Standard logging functions
logDebug :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => DisplayBuilder -> m () Source #
Log a debug level message with no source.
Since: 0.0.0.0
logInfo :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => DisplayBuilder -> m () Source #
Log an info level message with no source.
Since: 0.0.0.0
logWarn :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => DisplayBuilder -> m () Source #
Log a warn level message with no source.
Since: 0.0.0.0
logError :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => DisplayBuilder -> m () Source #
Log an error level message with no source.
Since: 0.0.0.0
Arguments
| :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) | |
| => Text | level |
| -> DisplayBuilder | |
| -> m () |
Log a message with the specified textual level and no source.
Since: 0.0.0.0
Running with logging
withLogFunc :: MonadUnliftIO m => LogOptions -> (LogFunc -> m a) -> m a Source #
Given a LogOptions value, run the given function with the
specified LogFunc. A common way to use this function is:
let isVerbose = False -- get from the command line instead
logOptions' <- logOptionsHandle stderr isVerbose
let logOptions = setLogUseTime True logOptions'
withLogFunc logOptions $ lf -> do
let app = App -- application specific environment
{ appLogFunc = lf
, appOtherStuff = ...
}
runRIO app $ do
logInfo "Starting app"
myApp
Since: 0.0.0.0
A logging function, wrapped in a newtype for better error messages.
An implementation may choose any behavior of this value it wishes, including printing to standard output or no action at all.
Since: 0.0.0.0
class HasLogFunc env where Source #
Environment values with a logging function.
Since: 0.0.0.0
Minimal complete definition
Instances
Arguments
| :: MonadIO m | |
| => Handle | |
| -> Bool | verbose? |
| -> m LogOptions |
Create a LogOptions value from the given Handle and whether
to perform verbose logging or not. Individiual settings can be
overridden using appropriate set functions.
Since: 0.0.0.0
Log options
data LogOptions Source #
Configuration for how to create a LogFunc. Intended to be used
with the withLogFunc function.
Since: 0.0.0.0
setLogMinLevel :: LogLevel -> LogOptions -> LogOptions Source #
Set the minimum log level. Messages below this level will not be printed.
Default: in verbose mode, LevelDebug. Otherwise, LevelInfo.
Since: 0.0.0.0
setLogVerboseFormat :: Bool -> LogOptions -> LogOptions Source #
Use the verbose format for printing log messages.
Default: follows the value of the verbose flag.
Since: 0.0.0.0
setLogTerminal :: Bool -> LogOptions -> LogOptions Source #
Do we treat output as a terminal. If True, we will enabled
sticky logging functionality.
Default: checks if the Handle provided to logOptionsHandle is a
terminal with hIsTerminalDevice.
Since: 0.0.0.0
setLogUseTime :: Bool -> LogOptions -> LogOptions Source #
Include the time when printing log messages.
Default: true in debug mode, false otherwise.
Since: 0.0.0.0
setLogUseColor :: Bool -> LogOptions -> LogOptions Source #
Use ANSI color codes in the log output.
Default: true if in verbose mode and the Handle is a terminal device.
Since: 0.0.0.0
Advanced logging functions
Sticky logging
logSticky :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => DisplayBuilder -> 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.
Note that not all LogFunc implementations will support sticky
messages as described. However, the withLogFunc implementation
provided by this module does.
Since: 0.0.0.0
logStickyDone :: (MonadIO m, HasCallStack, MonadReader env m, HasLogFunc env) => DisplayBuilder -> 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.
Since: 0.0.0.0
With source
logDebugS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> DisplayBuilder -> m () Source #
Log a debug level message with the given source.
Since: 0.0.0.0
logInfoS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> DisplayBuilder -> m () Source #
Log an info level message with the given source.
Since: 0.0.0.0
logWarnS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> DisplayBuilder -> m () Source #
Log a warn level message with the given source.
Since: 0.0.0.0
logErrorS :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> DisplayBuilder -> m () Source #
Log an error level message with the given source.
Since: 0.0.0.0
Arguments
| :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) | |
| => Text | level |
| -> LogSource | |
| -> DisplayBuilder | |
| -> m () |
Log a message with the specified textual level and the given source.
Since: 0.0.0.0
Generic log function
logGeneric :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) => LogSource -> LogLevel -> DisplayBuilder -> m () Source #
Generic, basic function for creating other logging functions.
Since: 0.0.0.0
Advanced running functions
mkLogFunc :: (CallStack -> LogSource -> LogLevel -> DisplayBuilder -> IO ()) -> LogFunc Source #
Create a LogFunc from the given function.
Since: 0.0.0.0
logOptionsMemory :: MonadIO m => m (IORef Builder, LogOptions) Source #
Create a LogOptions value which will store its data in
memory. This is primarily intended for testing purposes. This will
return both a LogOptions value and an IORef containing the
resulting Builder value.
This will default to non-verbose settings and assume there is a
terminal attached. These assumptions can be overridden using the
appropriate set functions.
Since: 0.0.0.0
Data types
The log level of a message.
Since: 0.0.0.0
Constructors
| LevelDebug | |
| LevelInfo | |
| LevelWarn | |
| LevelError | |
| LevelOther !Text |
type LogSource = Text Source #
Where in the application a log message came from. Used for display purposes only.
Since: 0.0.0.0
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
Convenience functions
displayCallStack :: CallStack -> DisplayBuilder Source #
Convert a CallStack value into a DisplayBuilder indicating
the first source location.
TODO Consider showing the entire call stack instead.
Since: 0.0.0.0