trace-embrace: Smart version of Debug.Trace module
Writing tracing code is very boring activity, especially in Haskell. The trace-embrace package minimizes the hassle of writing traces and maintaining them in codebase. Thanks to TH-driven DSL whole chunks of code containing function arguments could be quickly copy-pasted for tracing without massaging in a text editor.
There are several issues with functions from standand GHC module Debug.Trace:
no trace emitting location
tracing expressions solicit to write lot of boilerplate code
not possible to disable tracing without recompilation
tracing is coupled with optimizaiton flag
no per module granularity - all trace messages are disabled all at once
Let’s look how trace-embrace deals with these issues.
Location
TH macros with help of GHC lib, besides the module and the line of exrpession emitting a trace message, find function or method name where the expression is.
The trace message format is customizable through a config file
(trace-embrace.yaml
) located next to a cabal one, which is
automatically generated if it is missing at build time. The trace line
pattern can include location related fields such as
PackageName,
FullyQualifiedModule,
ModuleName,
FunctionName,
and
LineNumber.
traceMessage: traceLinePattern: - tag: FullyQualifiedModule - contents: ':' tag: Delimiter - tag: FunctionName - contents: ' ' tag: Delimiter - tag: LiteralMessage - tag: Variables
In a small function, a trace expression, containing only a space separated list of variables, is still very informative, because the rest is done by the library based on the expression context and configuration. The function name gives literal part for tracing. The library understands Haskell syntax very well and variables can be copy/pasted in bulk “AS-IS” with comments and even pattern matching.
module Module where fun x (Just y) = $(tr "/x (Just y)") $ x + y
The expression and config from above following trace message is produced:
Module:fun ; x: 123; y: 777
The argument of tr
consists of literal message and list of variables
for tracing. These parts are split by right slash.
Trace control
Trace control has several dimensions.
Compile/run time
Tracing code generation can be disabled at compile time in the
config file or later at launch runtime via an
environment variable. The variable name depends on configuration and by
default it is a cabal package name (in upper case) prefixed with
TRACE_EMBRACE_
.
mode: # expand all tracing macros to 'id' or 'pure ()' depending on the context tag: TraceDisabled
________________________________________________________________________
mode: # use Debug.Trace.trace group of functions tag: TraceStd runtimeLevelsOverrideEnvVar: # disable runtime configuration tag: Ignored
________________________________________________________________________
If the environment variable is not defined then tracing is enabled. If
the variable expands to a dash (-
) then tracing is disabled. Otherwise
the variable should contain a path to a file with module prefixes
specifing trace levels. Structure of runtime config file is equal to the
structure of levels
section.
levels: - '!Data.Map.Strict' # exclamation mark is warning level - '|Control.Concurrent' # bar - bottom -> is error level - 'Foo.Bar' # default is info level - '-' # dash is trace level mode: tag: TraceStd runtimeLevelsOverrideEnvVar: tag: CapsPackageName # default
________________________________________________________________________
Tracing levels
Both Haskell modules and tracing expressions have tracing levels. If expression tracing level is greater or equal to thershold tracing level of containing module then the message is emitted. Modules by default have threshold trace and unprefixed literal message has tracing level info.
module Module where yes x = $(tr "!I am emitted/") x yep x $(tr "|I am emitted/") x no x = $(tr "I am not emitted/") x nope x = $(tr "-I am not emitted/") x
________________________________________________________________________
levels: - '!Foo' - '-Fo' - '#Foo.Bar'
Runtime tracing level for a module cannot relax compile time tracing level.
Every cabal package uses a dedicated envirnonment variable so no conflict between dependencies using trace-embarce library is likely possible.
Trace Sink
Besides
Debug.Trace.trace
and /dev/null
,
trIo,
tr
tw
and
tw'
functions can forward tracing messages to
hPutStrLn
or
Debug.Trace.traceEvent.
mode: tag: TraceEvent
________________________________________________________________________
mode: sink: contents: /tmp/log.log tag: FileSink tag: TraceUnsafeIo
________________________________________________________________________
mode: sink: tag: StdErrSink tag: TraceUnsafeIo
Configuration file
The file is generanted on build if missing.
Default compile time config file (trace-embrace.yaml)
levels: - '-' mode: tag: TraceStd runtimeLevelsOverrideEnvVar: tag: CapsPackageName traceMessage: entrySeparator: '; ' keyValueSeparator: ': ' retValPrefix: ' => ' traceLinePattern: - tag: FullyQualifiedModule - contents: '::' tag: Delimiter - tag: FunctionName - contents: ': ' tag: Delimiter - tag: LiteralMessage - tag: Variables version: 1
Sample of runtime config file
Runtime config file is also in YAML format, but its structure is way simpler.
- '-' # empty prefix set default thershold equal to trace level - '!Foo' - 'Fo' - '#Foo.Bar' # threshold higher than error - disable tracing expression
Passing runtime config to foo-bar.cabal
:
TRACE_EMBRACE_FOO_BAR=- ./foo # disable tracing TRACE_EMBRACE_FOO_BAR=rtc.yaml ./foo # override threshold levels
The variable name can be specified explicitly:
runtimeLevelsOverrideEnvVar: tag: EnvironmentVariable varName: "FOO_BAR"
Examples
TH version of traceWith
{-# LANGUAGE TemplateHaskell #-} module Module where import Debug.TraceEmbrace fun :: Int -> Int -> Int -> Int fun x y z = $(tw "get/x y z") (x + y + z)
A trace line for the snippet above would be:
Module:fun: 7 get; x: 1; y: 2; z: 3 => 6
Trace lazy ByteString structure
ByteString
Show
instance does not show chunks, but it can be important in parser
debugging (attoparsec). Value of a type with not enough informative
Show
instance could be wrapped into
ShowTrace
and more detailed Show
instance should be provided.
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Module where import Debug.TraceEmbrace import Data.ByteString.Lazy -- instance Show (ShowTrace ByteString) where -- show ... fun :: ByteString -> ByteString fun bs = $(tr "get/bs;bs") bs
A trace line for the snippet above would be:
Module:fun: 11 get; bs: “abc”; bs: [“ab”, “c”]
For tracing returning values wrapped into ShowTrace use tw'.
Pattern matching syntax
Template tracing functions support Haskell pattern syntax and comments, so function arguments can be quickly copy-pasted as-is:
{-# LANGUAGE TemplateHaskell #-} module Module where import Debug.TraceEmbrace fun :: Maybe ([Int], Int) -> Int fun v@(Just ([x], {-ignore-} _)) = $(tr "get/v@(Just ([x], {-ignore-} _))") x fun _ = 0
A trace line for the snippet above would be:
Module:fun: 7 get; v: 1; x: 1
Unlifted vars
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE MagicHash #-} module Module where import Debug.TraceEmbrace import GHC.Exts fun :: Int -> Int fun (I# x#) = (I# ($(tr "get/x#") x#))
A trace line for the snippet above would be:
Module:fun: 7 get; x#: 1#
Modules
[Index] [Quick Jump]
- Debug
- Debug.TraceEmbrace
- Debug.TraceEmbrace.ByteString
- Debug.TraceEmbrace.Config
- Debug.TraceEmbrace.FileIndex
- Debug.TraceEmbrace.Haddock
- Internal
- Debug.TraceEmbrace.Internal.Rewrap
- Debug.TraceEmbrace.Internal.TH
- Debug.TraceEmbrace.Show
- Debug.TraceEmbrace.ShowTh
- Debug.TraceEmbrace.TH
- Debug.TraceEmbrace
Downloads
- trace-embrace-1.0.3.tar.gz [browse] (Cabal source package)
- Package description (as included in the package)
Maintainer's Corner
For package maintainers and hackage trustees
Candidates
Versions [RSS] | 1.0.2, 1.0.3 |
---|---|
Change log | changelog.md |
Dependencies | aeson (<3.0), base (<5), bytestring (>0.11 && <0.12.3), containers (<0.9), cpphs (<2.0), deepseq (<1.8), directory (<2.0), generic-lens (<3.0), ghc (<9.12), lens (<6.0), lrucache (<1.3), radix-tree (<2.0), refined (<1.0), tagged (<1.0), template-haskell (<2.24.0.0), text (<3.0), transformers (<1.0), yaml (<0.12) [details] |
Tested with | ghc ==9.10.1 |
License | BSD-3-Clause |
Author | Daniil Iaitskov <dyaitskov@gmail.com> |
Maintainer | Daniil Iaitskov <dyaitskov@gmail.com> |
Category | Development |
Home page | https://github.com/yaitskov/trace-embrace |
Bug tracker | https://github.com/yaitskov/trace-embrace/issues |
Source repo | head: git clone https://github.com/yaitskov/trace-embrace.git |
Uploaded | by DaniilIaitskov at 2025-03-08T00:49:21Z |
Distributions | |
Downloads | 6 total (6 in the last 30 days) |
Rating | (no votes yet) [estimated by Bayesian average] |
Your Rating | |
Status | Docs uploaded by user Build status unknown [no reports yet] |