Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hledger.Utils.Debug
Description
Here are debug tracing/logging helpers built on Debug.Trace, extracted from the hledger project. Features:
- they can be built in to your program permanently, and activated by a --debug [LEVEL] option
- they can optionally log to a file instead of stderr (for TUI apps)
- they can be used in IO, pure, or startup code
- values are printed with a label, and pretty-printed (using pretty-simple)
- ANSI colour is used when appropriate.
Insert these dbg*
helpers at points of interest in your code,
either temporarily while debugging,
or permanently in production code, and activate them with --debug [1-9]
on the command line
(--debug
with no value means level 1).
For example, this expression:
dbg4 "foo" foo
will pretty-print foo with a "foo:" label when it is evaluated, but only if --debug's value is 4 or greater. In other words: use dbg1 for the most useful debug output, dbg9 for the most specialised/verbose.
They are intended to be easy to use and to find in your code, with a consistent naming scheme:
dbg<LEVEL>Msg STR VAL -- trace/log a string in pure code dbg<LEVEL>MsgIO STR -- trace/log a string in IO dbg<LEVEL> STR VAL -- trace/log a showable value in pure code dbg<LEVEL>IO STR VAL -- trace/log a showable value in IO dbg<LEVEL>With SHOWFN VAL -- trace/log any value
Or if you prefer you can ignore the numbered variants and write an extra argument:
dbgMsg LEVEL STR VAL dbgMsgIO LEVEL STR dbg LEVEL STR VAL dbgIO LEVEL STR VAL dbgWith LEVEL SHOWFN VAL
Haskell values will be pretty-printed by default, using pretty-simple.
ANSI color will also be used if appropriate,
respecting output capabilities, NO_COLOR
, and/or a --color [YNA]
(or --colour
) command line option.
These helpers normally print output on stderr, but can automatically log to a file instead,
which can be useful for TUI apps which are redrawing the screen.
To enable this logging mode, use withProgName
to add a ".log" suffix to the program name:
main = withProgName "PROGRAM.log" $ do ...
Now all dbg calls will log to PROGRAM.log
in the current directory.
Logging, and reading the command line/program name/output context use unsafePerformIO, so that these can be used anywhere, including early in your program before command line parsing is complete. As a consequence, if you are testing in GHCI and want to change the debug level, you'll need to reload this module.
The dbg
function name clashes with the one in Text.Megaparsec.Debug, unfortunately; sorry about that.
If you are also using that, use qualified imports, or our dbg_
alias, to avoid the clash.
The meaning of debug levels is up to you. Eg hledger uses them as follows:
Debug level: What to show: ------------ --------------------------------------------------------- 0 normal program output only 1 useful warnings, most common troubleshooting info 2 common troubleshooting info, more detail 3 report options selection 4 report generation 5 report generation, more detail 6 input file reading 7 input file reading, more detail 8 command line parsing 9 any other rarely needed / more in-depth info
It's not yet possible to select debug output by topic; that would be useful.
Synopsis
- debugLevel :: Int
- dbgMsg :: Int -> String -> a -> a
- dbg0Msg :: String -> a -> a
- dbg1Msg :: String -> a -> a
- dbg2Msg :: String -> a -> a
- dbg3Msg :: String -> a -> a
- dbg4Msg :: String -> a -> a
- dbg5Msg :: String -> a -> a
- dbg6Msg :: String -> a -> a
- dbg7Msg :: String -> a -> a
- dbg8Msg :: String -> a -> a
- dbg9Msg :: String -> a -> a
- dbgMsgIO :: MonadIO m => Int -> String -> m ()
- dbg0MsgIO :: MonadIO m => String -> m ()
- dbg1MsgIO :: MonadIO m => String -> m ()
- dbg2MsgIO :: MonadIO m => String -> m ()
- dbg3MsgIO :: MonadIO m => String -> m ()
- dbg4MsgIO :: MonadIO m => String -> m ()
- dbg5MsgIO :: MonadIO m => String -> m ()
- dbg6MsgIO :: MonadIO m => String -> m ()
- dbg7MsgIO :: MonadIO m => String -> m ()
- dbg8MsgIO :: MonadIO m => String -> m ()
- dbg9MsgIO :: MonadIO m => String -> m ()
- dbg :: Show a => Int -> String -> a -> a
- dbg_ :: Show a => Int -> String -> a -> a
- dbg0 :: Show a => String -> a -> a
- dbg1 :: Show a => String -> a -> a
- dbg2 :: Show a => String -> a -> a
- dbg3 :: Show a => String -> a -> a
- dbg4 :: Show a => String -> a -> a
- dbg5 :: Show a => String -> a -> a
- dbg6 :: Show a => String -> a -> a
- dbg7 :: Show a => String -> a -> a
- dbg8 :: Show a => String -> a -> a
- dbg9 :: Show a => String -> a -> a
- dbgIO :: (MonadIO m, Show a) => Int -> String -> a -> m ()
- dbg0IO :: (MonadIO m, Show a) => String -> a -> m ()
- dbg1IO :: (MonadIO m, Show a) => String -> a -> m ()
- dbg2IO :: (MonadIO m, Show a) => String -> a -> m ()
- dbg3IO :: (MonadIO m, Show a) => String -> a -> m ()
- dbg4IO :: (MonadIO m, Show a) => String -> a -> m ()
- dbg5IO :: (MonadIO m, Show a) => String -> a -> m ()
- dbg6IO :: (MonadIO m, Show a) => String -> a -> m ()
- dbg7IO :: (MonadIO m, Show a) => String -> a -> m ()
- dbg8IO :: (MonadIO m, Show a) => String -> a -> m ()
- dbg9IO :: (MonadIO m, Show a) => String -> a -> m ()
- dbgWith :: Int -> (a -> String) -> a -> a
- dbg0With :: (a -> String) -> a -> a
- dbg1With :: (a -> String) -> a -> a
- dbg2With :: (a -> String) -> a -> a
- dbg3With :: (a -> String) -> a -> a
- dbg4With :: (a -> String) -> a -> a
- dbg5With :: (a -> String) -> a -> a
- dbg6With :: (a -> String) -> a -> a
- dbg7With :: (a -> String) -> a -> a
- dbg8With :: (a -> String) -> a -> a
- dbg9With :: (a -> String) -> a -> a
- lbl_ :: String -> String -> String -> String
- progName :: String
- ghcDebugSupportedInLib :: Bool
- data GhcDebugMode
- ghcDebugMode :: GhcDebugMode
- withGhcDebug' :: a -> a
- ghcDebugPause' :: IO ()
- trace :: String -> a -> a
- traceIO :: String -> IO ()
- traceShowId :: Show a => a -> a
Debug level
debugLevel :: Int Source #
The program's debug output verbosity, from 0 to 9. The default is 0 meaning no debug output. This can be overridden by running the program with a --debug [1-9] command line option; a --debug flag with no value means 1. Uses unsafePerformIO to read the command line. When running in GHCI, changing this requires reloading this module.
Trace/log a string
dbgMsg :: Int -> String -> a -> a Source #
Trace or log a string if the program debug level is at or above the specified level, then return the second argument.
Trace/log a string in IO
Trace/log a value
dbg :: Show a => Int -> String -> a -> a Source #
Trace or log a label and showable value, pretty-printed, if the program debug level is at or above the specified level; then return the value.
dbg_ :: Show a => Int -> String -> a -> a Source #
Alias for dbg, can be used to avoid namespace clashes.
Trace/log a value in IO
dbgIO :: (MonadIO m, Show a) => Int -> String -> a -> m () Source #
Like dbg, but sequences properly in IO.
Trace/log a value with a show function
Utilities
lbl_ :: String -> String -> String -> String Source #
Helper for producing debug messages: concatenates a name (eg a function name), short description of the value being logged, and string representation of the value.
Eg: let lbl = lbl_ "print"
,
dbg1With (lbl "part 1".show) ...
.
ghc-debug helpers
ghcDebugSupportedInLib :: Bool Source #
Is the hledger-lib package built with ghc-debug support ?
data GhcDebugMode Source #
Whether ghc-debug support is included in this build, and if so, how it will behave.
When hledger is built with the ghcdebug
cabal flag (off by default, because of extra deps),
it can listen (on unix ?) for connections from ghc-debug clients like ghc-debug-brick,
for pausing/resuming the program and inspecting memory usage and profile information.
With a ghc-debug-supporting build, ghc-debug can be enabled by running hledger with a negative --debug level. There are three different modes: --debug=-1 - run normally (can be paused/resumed by a ghc-debug client), --debug=-2 - pause and await client commands at program start (not useful currently), --debug=-3 - pause and await client commands at program end.
Constructors
GDNotSupported | |
GDDisabled | |
GDNoPause | |
GDPauseAtStart | |
GDPauseAtEnd |
Instances
Show GhcDebugMode Source # | |
Defined in Hledger.Utils.Debug Methods showsPrec :: Int -> GhcDebugMode -> ShowS # show :: GhcDebugMode -> String # showList :: [GhcDebugMode] -> ShowS # | |
Eq GhcDebugMode Source # | |
Defined in Hledger.Utils.Debug | |
Ord GhcDebugMode Source # | |
Defined in Hledger.Utils.Debug Methods compare :: GhcDebugMode -> GhcDebugMode -> Ordering # (<) :: GhcDebugMode -> GhcDebugMode -> Bool # (<=) :: GhcDebugMode -> GhcDebugMode -> Bool # (>) :: GhcDebugMode -> GhcDebugMode -> Bool # (>=) :: GhcDebugMode -> GhcDebugMode -> Bool # max :: GhcDebugMode -> GhcDebugMode -> GhcDebugMode # min :: GhcDebugMode -> GhcDebugMode -> GhcDebugMode # |
ghcDebugMode :: GhcDebugMode Source #
Should the program open a socket allowing control by ghc-debug-brick or similar ghc-debug client ? See GhcDebugMode.
withGhcDebug' :: a -> a Source #
When ghc-debug support has been built into the program and enabled at runtime with --debug=-N, this calls ghc-debug's withGhcDebug; otherwise it's a no-op.
ghcDebugPause' :: IO () Source #
When ghc-debug support has been built into the program, this calls ghc-debug's pause, otherwise it's a no-op.
Re-exports: Debug.Trace
The trace
function outputs the trace message given as its first argument,
before returning the second argument as its result.
For example, this returns the value of f x
and outputs the message to stderr.
Depending on your terminal (settings), they may or may not be mixed.
>>>
let x = 123; f = show
>>>
trace ("calling f with x = " ++ show x) (f x)
calling f with x = 123 "123"
The trace
function should only be used for debugging, or for monitoring
execution. The function is not referentially transparent: its type indicates
that it is a pure function but it has the side effect of outputting the
trace message.
The traceIO
function outputs the trace message from the IO monad.
This sequences the output with respect to other IO actions.
Since: base-4.5.0.0
traceShowId :: Show a => a -> a #
Like traceShow
but returns the shown value instead of a third value.
>>>
traceShowId (1+2+3, "hello" ++ "world")
(6,"helloworld") (6,"helloworld")
Since: base-4.7.0.0