feat(otel): Add withOtelCollect() and localOtelCollect() (#4333)

This commit is contained in:
Barret Schloerke
2025-12-08 14:30:40 -05:00
committed by GitHub
parent 63a00f775f
commit f24f71e4e0
10 changed files with 612 additions and 18 deletions

View File

@@ -191,6 +191,7 @@ Collate:
'otel-reactive-update.R'
'otel-session.R'
'otel-shiny.R'
'otel-with.R'
'priorityqueue.R'
'progress.R'
'react.R'

View File

@@ -165,6 +165,7 @@ export(isTruthy)
export(isolate)
export(key_missing)
export(loadSupport)
export(localOtelCollect)
export(mainPanel)
export(makeReactiveBinding)
export(markRenderFunction)
@@ -329,6 +330,7 @@ export(verticalLayout)
export(wellPanel)
export(withLogErrors)
export(withMathJax)
export(withOtelCollect)
export(withProgress)
export(withReactiveDomain)
export(withTags)

View File

@@ -1,5 +1,6 @@
# shiny (development version)
* Added `withOtelCollect()` and `localOtelCollect()` functions to temporarily control OpenTelemetry collection levels during reactive expression creation. These functions allow you to enable or disable telemetry collection for specific modules or sections of code where reactive expressions are being created. (#4333)
* OpenTelemetry code attributes now include both preferred (`code.file.path`, `code.line.number`, `code.column.number`) and deprecated (`code.filepath`, `code.lineno`, `code.column`) attribute names to follow OpenTelemetry semantic conventions while maintaining backward compatibility. The deprecated names will be removed in a future release after Logfire supports the preferred names. (#4325)
* Timer tests are now skipped on CRAN. (#4327)

View File

@@ -30,12 +30,7 @@ has_otel_collect <- function(collect) {
# Run expr with otel collection disabled
with_no_otel_collect <- function(expr) {
withr::with_options(
list(
shiny.otel.collect = "none"
),
expr
)
withOtelCollect("none", expr)
}

136
R/otel-with.R Normal file
View File

@@ -0,0 +1,136 @@
#' Temporarily set OpenTelemetry collection level
#'
#' @description
#' `withOtelCollect()` temporarily sets the OpenTelemetry collection level for
#' the duration of evaluating `expr`. `localOtelCollect()` sets the collection
#' level for the remainder of the current function scope.
#'
#' These functions are useful for temporarily controlling telemetry collection
#' during reactive expression creation. Only the following levels are allowed:
#' * `"none"` - No telemetry data collected
#' * `"reactivity"` - Collect reactive execution spans (includes session and
#' reactive update events)
#' * `"all"` - All available telemetry (currently equivalent to `"reactivity"`)
#'
#' Note that `"session"` and `"reactive_update"` levels are not permitted as
#' these are runtime-specific levels that should only be set permanently via
#' `options(shiny.otel.collect = ...)` or the `SHINY_OTEL_COLLECT` environment
#' variable, not temporarily during reactive expression creation.
#'
#' @section Intended Usage:
#'
#' These functions are designed to perform sweeping changes to telemetry
#' collection, such as enabling or disabling OpenTelemetry for an entire module
#' or section of code where reactive expressions are being **created**:
#'
#' ```r
#' # Enable telemetry for an entire module
#' withOtelCollect("all", {
#' my_result <- my_module("my_id")
#' })
#'
#' # Disable telemetry for expensive development-only reactives
#' withOtelCollect("none", {
#' debug_reactive <- reactive({ expensive_debug_computation() })
#' })
#' ```
#'
#' @section Pipe Usage (Not Recommended):
#'
#' While using `withOtelCollect()` as a pipe-able method, it is not recommended due to the use case where the reactive object is created before the `withOtelCollect()` call. In such cases, the reactive object will not inherit the intended OpenTelemetry settings.
#'
#' Therefore, to avoid this hard-to-debug situation, we recommend that you only create your reactive objects within the `withOtelCollect()` call or after setting the local collection level with `localOtelCollect()`.
#'
#' ```r
#' # Technically works, but not recommended
#' x <- reactive({ ... }) %>% withOtelCollect(collect = "all")
#' x <- reactive({ ... }) |> withOtelCollect(collect = "all")
#' # Equivalent to:
#' x <- withOtelCollect("all", reactive({ ... }))
#'
#' # Does NOT work as intended
#' x <- reactive({ ... })
#' # `x` was created outside of `withOtelCollect()`,
#' # therefore no OTel settings are applied
#' x_no_otel <- withOtelCollect("all", x)
#'
#' # Best practice: Create the reactive object within `expr=`
#' withOtelCollect("all", {
#' x_with_otel <- reactive({ ... })
#' y_with_otel <- reactive({ ... })
#' })
#' ```
#'
#' @param collect Character string specifying the OpenTelemetry collection level.
#' Must be one of `"none"`, `"reactivity"`, or `"all"`.
#' @param expr Expression to evaluate with the specified collection level
#' (for `withOtelCollect()`).
#' @param envir Environment where the collection level should be set
#' (for `localOtelCollect()`). Defaults to the parent frame.
#'
#' @return
#' * `withOtelCollect()` returns the value of `expr`.
#' * `localOtelCollect()` is called for its side effect and returns the previous
#' `collect` value invisibly.
#'
#' @seealso See the `shiny.otel.collect` option within [`shinyOptions`]. Setting
#' this value will globally control OpenTelemetry collection levels.
#'
#' @examples
#' \dontrun{
#' # Temporarily disable telemetry collection
#' withOtelCollect("none", {
#' # Code here won't generate telemetry
#' reactive({ input$x + 1 })
#' })
#'
#' # Collect reactivity telemetry but not other events
#' withOtelCollect("reactivity", {
#' # Reactive execution will be traced
#' observe({ print(input$x) })
#' })
#'
#' # Use local variant in a function
#' my_function <- function() {
#' localOtelCollect("none")
#' # Rest of function executes without telemetry
#' reactive({ input$y * 2 })
#' }
#' }
#'
#' @rdname withOtelCollect
#' @export
withOtelCollect <- function(collect, expr) {
collect <- as_otel_collect_with(collect)
withr::with_options(
list(shiny.otel.collect = collect),
expr
)
}
#' @rdname withOtelCollect
#' @export
localOtelCollect <- function(collect, envir = parent.frame()) {
collect <- as_otel_collect_with(collect)
old <- withr::local_options(
list(shiny.otel.collect = collect),
.local_envir = envir
)
invisible(old)
}
# Helper function to validate collect levels for with/local functions
# Only allows "none", "reactivity", and "all" - not "session" or "reactive_update"
as_otel_collect_with <- function(collect) {
if (!is.character(collect)) {
stop("`collect` must be a character vector.")
}
allowed_levels <- c("none", "reactivity", "all")
collect <- match.arg(collect, allowed_levels, several.ok = FALSE)
return(collect)
}

View File

@@ -160,20 +160,30 @@ getShinyOption <- function(name, default = NULL) {
# ' side devmode features. Currently the primary feature is the client-side
# ' error console.}
### end shiny.client_devmode
#' \item{shiny.otel.collect (defaults to `Sys.getenv("SHINY_OTEL_COLLECT", "all")`)}{Determines how Shiny will
#' interact with OpenTelemetry.
#' \item{shiny.otel.collect (defaults to `Sys.getenv("SHINY_OTEL_COLLECT",
#' "all")`)}{Determines how Shiny will interact with OpenTelemetry.
#'
#' Supported values:
#' * `"none"` - No Shiny OpenTelemetry tracing.
#' * `"session"` - Adds session start/end spans.
#' * `"reactive_update"` - Spans for any synchronous/asynchronous reactive update. (Includes `"session"` features).
#' * `"reactivity"` - Spans for all reactive expressions. (Includes `"reactive_update"` features).
#' * `"all"` - All Shiny OpenTelemetry tracing. Currently equivalent to `"reactivity"`.
#' * `"reactive_update"` - Spans for any synchronous/asynchronous reactive
#' update. (Includes `"session"` features).
#' * `"reactivity"` - Spans for all reactive expressions and logs for setting
#' reactive vals and values. (Includes `"reactive_update"` features). This
#' option must be set when creating any reactive objects that should record
#' OpenTelemetry spans / logs. See [`withOtelCollect()`] and
#' [`localOtelCollect()`] for ways to set this option locally when creating
#' your reactive expressions.
#' * `"all"` - All Shiny OpenTelemetry tracing. Currently equivalent to
#' `"reactivity"`.
#'
#' This option is useful for debugging and profiling while in production. This
#' option will only be useful if the `otelsdk` package is installed and
#' `otel::is_tracing_enabled()` returns `TRUE`. Please have any OpenTelemetry
#' environment variables set before starting your Shiny app.}
#' environment variables set before loading any relevant R packages.
#'
#' To set this option locally within a specific part of your Shiny
#' application, see [`withOtelCollect()`] and [`localOtelCollect()`].}
#' \item{shiny.otel.sanitize.errors (defaults to `TRUE`)}{If `TRUE`, fatal and unhandled errors will be sanitized before being sent to the OpenTelemetry backend. The default value of `TRUE` is set to avoid potentially sending sensitive information to the OpenTelemetry backend. If you want the full error message and stack trace to be sent to the OpenTelemetry backend, set this option to `FALSE` or use `safeError(e)`.}
#' }
#'

View File

@@ -130,22 +130,31 @@ ragg package. See \code{\link[=plotPNG]{plotPNG()}} for more information.}
Cairo package. See \code{\link[=plotPNG]{plotPNG()}} for more information.}
\item{shiny.devmode (defaults to \code{NULL})}{Option to enable Shiny Developer Mode. When set,
different default \code{getOption(key)} values will be returned. See \code{\link[=devmode]{devmode()}} for more details.}
\item{shiny.otel.collect (defaults to \code{Sys.getenv("SHINY_OTEL_COLLECT", "all")})}{Determines how Shiny will
interact with OpenTelemetry.
\item{shiny.otel.collect (defaults to \code{Sys.getenv("SHINY_OTEL_COLLECT", "all")})}{Determines how Shiny will interact with OpenTelemetry.
Supported values:
\itemize{
\item \code{"none"} - No Shiny OpenTelemetry tracing.
\item \code{"session"} - Adds session start/end spans.
\item \code{"reactive_update"} - Spans for any synchronous/asynchronous reactive update. (Includes \code{"session"} features).
\item \code{"reactivity"} - Spans for all reactive expressions. (Includes \code{"reactive_update"} features).
\item \code{"all"} - All Shiny OpenTelemetry tracing. Currently equivalent to \code{"reactivity"}.
\item \code{"reactive_update"} - Spans for any synchronous/asynchronous reactive
update. (Includes \code{"session"} features).
\item \code{"reactivity"} - Spans for all reactive expressions and logs for setting
reactive vals and values. (Includes \code{"reactive_update"} features). This
option must be set when creating any reactive objects that should record
OpenTelemetry spans / logs. See \code{\link[=withOtelCollect]{withOtelCollect()}} and
\code{\link[=localOtelCollect]{localOtelCollect()}} for ways to set this option locally when creating
your reactive expressions.
\item \code{"all"} - All Shiny OpenTelemetry tracing. Currently equivalent to
\code{"reactivity"}.
}
This option is useful for debugging and profiling while in production. This
option will only be useful if the \code{otelsdk} package is installed and
\code{otel::is_tracing_enabled()} returns \code{TRUE}. Please have any OpenTelemetry
environment variables set before starting your Shiny app.}
environment variables set before loading any relevant R packages.
To set this option locally within a specific part of your Shiny
application, see \code{\link[=withOtelCollect]{withOtelCollect()}} and \code{\link[=localOtelCollect]{localOtelCollect()}}.}
\item{shiny.otel.sanitize.errors (defaults to \code{TRUE})}{If \code{TRUE}, fatal and unhandled errors will be sanitized before being sent to the OpenTelemetry backend. The default value of \code{TRUE} is set to avoid potentially sending sensitive information to the OpenTelemetry backend. If you want the full error message and stack trace to be sent to the OpenTelemetry backend, set this option to \code{FALSE} or use \code{safeError(e)}.}
}
}

120
man/withOtelCollect.Rd Normal file
View File

@@ -0,0 +1,120 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/otel-with.R
\name{withOtelCollect}
\alias{withOtelCollect}
\alias{localOtelCollect}
\title{Temporarily set OpenTelemetry collection level}
\usage{
withOtelCollect(collect, expr)
localOtelCollect(collect, envir = parent.frame())
}
\arguments{
\item{collect}{Character string specifying the OpenTelemetry collection level.
Must be one of \code{"none"}, \code{"reactivity"}, or \code{"all"}.}
\item{expr}{Expression to evaluate with the specified collection level
(for \code{withOtelCollect()}).}
\item{envir}{Environment where the collection level should be set
(for \code{localOtelCollect()}). Defaults to the parent frame.}
}
\value{
\itemize{
\item \code{withOtelCollect()} returns the value of \code{expr}.
\item \code{localOtelCollect()} is called for its side effect and returns the previous
\code{collect} value invisibly.
}
}
\description{
\code{withOtelCollect()} temporarily sets the OpenTelemetry collection level for
the duration of evaluating \code{expr}. \code{localOtelCollect()} sets the collection
level for the remainder of the current function scope.
These functions are useful for temporarily controlling telemetry collection
during reactive expression creation. Only the following levels are allowed:
\itemize{
\item \code{"none"} - No telemetry data collected
\item \code{"reactivity"} - Collect reactive execution spans (includes session and
reactive update events)
\item \code{"all"} - All available telemetry (currently equivalent to \code{"reactivity"})
}
Note that \code{"session"} and \code{"reactive_update"} levels are not permitted as
these are runtime-specific levels that should only be set permanently via
\code{options(shiny.otel.collect = ...)} or the \code{SHINY_OTEL_COLLECT} environment
variable, not temporarily during reactive expression creation.
}
\section{Intended Usage}{
These functions are designed to perform sweeping changes to telemetry
collection, such as enabling or disabling OpenTelemetry for an entire module
or section of code where reactive expressions are being \strong{created}:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{# Enable telemetry for an entire module
withOtelCollect("all", \{
my_result <- my_module("my_id")
\})
# Disable telemetry for expensive development-only reactives
withOtelCollect("none", \{
debug_reactive <- reactive(\{ expensive_debug_computation() \})
\})
}\if{html}{\out{</div>}}
}
\section{Pipe Usage (Not Recommended)}{
While using \code{withOtelCollect()} as a pipe-able method, it is not recommended due to the use case where the reactive object is created before the \code{withOtelCollect()} call. In such cases, the reactive object will not inherit the intended OpenTelemetry settings.
Therefore, to avoid this hard-to-debug situation, we recommend that you only create your reactive objects within the \code{withOtelCollect()} call or after setting the local collection level with \code{localOtelCollect()}.
\if{html}{\out{<div class="sourceCode r">}}\preformatted{# Technically works, but not recommended
x <- reactive(\{ ... \}) \%>\% withOtelCollect(collect = "all")
x <- reactive(\{ ... \}) |> withOtelCollect(collect = "all")
# Equivalent to:
x <- withOtelCollect("all", reactive(\{ ... \}))
# Does NOT work as intended
x <- reactive(\{ ... \})
# `x` was created outside of `withOtelCollect()`,
# therefore no OTel settings are applied
x_no_otel <- withOtelCollect("all", x)
# Best practice: Create the reactive object within `expr=`
withOtelCollect("all", \{
x_with_otel <- reactive(\{ ... \})
y_with_otel <- reactive(\{ ... \})
\})
}\if{html}{\out{</div>}}
}
\examples{
\dontrun{
# Temporarily disable telemetry collection
withOtelCollect("none", {
# Code here won't generate telemetry
reactive({ input$x + 1 })
})
# Collect reactivity telemetry but not other events
withOtelCollect("reactivity", {
# Reactive execution will be traced
observe({ print(input$x) })
})
# Use local variant in a function
my_function <- function() {
localOtelCollect("none")
# Rest of function executes without telemetry
reactive({ input$y * 2 })
}
}
}
\seealso{
See the \code{shiny.otel.collect} option within \code{\link{shinyOptions}}. Setting
this value will globally control OpenTelemetry collection levels.
}

View File

@@ -0,0 +1,316 @@
test_that("withOtelCollect sets collection level temporarily", {
# Save original option
original <- getOption("shiny.otel.collect")
on.exit(options(shiny.otel.collect = original), add = TRUE)
# Set a baseline option
options(shiny.otel.collect = "all")
# Test that withOtelCollect temporarily changes the option
result <- withOtelCollect("none", {
getOption("shiny.otel.collect")
})
expect_equal(result, "none")
# Verify option is restored after expression
expect_equal(getOption("shiny.otel.collect"), "all")
})
test_that("withOtelCollect returns value of expr", {
result <- withOtelCollect("none", {
42
})
expect_equal(result, 42)
# Test with more complex return value
result <- withOtelCollect("reactivity", {
list(a = 1, b = "test")
})
expect_equal(result, list(a = 1, b = "test"))
})
test_that("withOtelCollect validates collect level", {
expect_error(
withOtelCollect("invalid", { 1 }),
"'arg' should be one of"
)
expect_error(
withOtelCollect(123, { 1 }),
"`collect` must be a character vector"
)
expect_error(
withOtelCollect(c("all", "none"), { 1 }),
"'arg' must be of length 1"
)
})
test_that("withOtelCollect rejects session and reactive_update levels", {
expect_error(
withOtelCollect("session", { 1 }),
"'arg' should be one of"
)
expect_error(
withOtelCollect("reactive_update", { 1 }),
"'arg' should be one of"
)
})
test_that("withOtelCollect works with all valid collect levels", {
for (level in c("none", "reactivity", "all")) {
result <- withOtelCollect(level, {
getOption("shiny.otel.collect")
})
expect_equal(result, level)
}
})
test_that("withOtelCollect nests correctly", {
original <- getOption("shiny.otel.collect")
on.exit(options(shiny.otel.collect = original), add = TRUE)
options(shiny.otel.collect = "all")
result <- withOtelCollect("reactivity", {
outer <- getOption("shiny.otel.collect")
inner <- withOtelCollect("none", {
getOption("shiny.otel.collect")
})
restored <- getOption("shiny.otel.collect")
list(outer = outer, inner = inner, restored = restored)
})
expect_equal(result$outer, "reactivity")
expect_equal(result$inner, "none")
expect_equal(result$restored, "reactivity")
expect_equal(getOption("shiny.otel.collect"), "all")
})
test_that("withOtelCollect restores option even on error", {
original <- getOption("shiny.otel.collect")
on.exit(options(shiny.otel.collect = original), add = TRUE)
options(shiny.otel.collect = "all")
expect_error(
withOtelCollect("none", {
stop("test error")
}),
"test error"
)
# Option should still be restored
expect_equal(getOption("shiny.otel.collect"), "all")
})
test_that("localOtelCollect sets collection level in function scope", {
original <- getOption("shiny.otel.collect")
on.exit(options(shiny.otel.collect = original), add = TRUE)
options(shiny.otel.collect = "all")
test_func <- function() {
localOtelCollect("none")
getOption("shiny.otel.collect")
}
result <- test_func()
expect_equal(result, "none")
# Option should be restored after function exits
expect_equal(getOption("shiny.otel.collect"), "all")
})
test_that("localOtelCollect returns previous collect value invisibly", {
original <- getOption("shiny.otel.collect")
on.exit(options(shiny.otel.collect = original), add = TRUE)
options(shiny.otel.collect = "all")
result <- withVisible(localOtelCollect("none"))
# Should return a list with the old option value
expect_type(result$value, "list")
expect_equal(result$value$shiny.otel.collect, "all")
expect_false(result$visible)
})
test_that("localOtelCollect validates collect level", {
expect_error(
localOtelCollect("invalid"),
"'arg' should be one of"
)
expect_error(
localOtelCollect(NULL),
"`collect` must be a character vector"
)
expect_error(
localOtelCollect(c("all", "none")),
"'arg' must be of length 1"
)
})
test_that("localOtelCollect rejects session and reactive_update levels", {
expect_error(
localOtelCollect("session"),
"'arg' should be one of"
)
expect_error(
localOtelCollect("reactive_update"),
"'arg' should be one of"
)
})
test_that("localOtelCollect works with all valid collect levels", {
for (level in c("none", "reactivity", "all")) {
test_func <- function() {
localOtelCollect(level)
getOption("shiny.otel.collect")
}
result <- test_func()
expect_equal(result, level)
}
})
test_that("localOtelCollect respects envir parameter", {
original <- getOption("shiny.otel.collect")
on.exit(options(shiny.otel.collect = original), add = TRUE)
options(shiny.otel.collect = "all")
outer_func <- function() {
env <- environment()
inner_func <- function() {
localOtelCollect("none", envir = env)
}
inner_func()
getOption("shiny.otel.collect")
}
result <- outer_func()
expect_equal(result, "none")
expect_equal(getOption("shiny.otel.collect"), "all")
})
test_that("localOtelCollect scope is limited to function", {
original <- getOption("shiny.otel.collect")
on.exit(options(shiny.otel.collect = original), add = TRUE)
options(shiny.otel.collect = "all")
func1 <- function() {
localOtelCollect("reactivity")
getOption("shiny.otel.collect")
}
func2 <- function() {
localOtelCollect("none")
getOption("shiny.otel.collect")
}
result1 <- func1()
result2 <- func2()
expect_equal(result1, "reactivity")
expect_equal(result2, "none")
expect_equal(getOption("shiny.otel.collect"), "all")
})
test_that("withOtelCollect and localOtelCollect work together", {
original <- getOption("shiny.otel.collect")
on.exit(options(shiny.otel.collect = original), add = TRUE)
options(shiny.otel.collect = "all")
result <- withOtelCollect("reactivity", {
outer <- getOption("shiny.otel.collect")
test_func <- function() {
localOtelCollect("none")
getOption("shiny.otel.collect")
}
inner <- test_func()
restored <- getOption("shiny.otel.collect")
list(outer = outer, inner = inner, restored = restored)
})
expect_equal(result$outer, "reactivity")
expect_equal(result$inner, "none")
expect_equal(result$restored, "reactivity")
expect_equal(getOption("shiny.otel.collect"), "all")
})
test_that("withOtelCollect affects otel_collect_is_enabled", {
# This tests integration with the otel collection system
original <- getOption("shiny.otel.collect")
on.exit(options(shiny.otel.collect = original), add = TRUE)
options(shiny.otel.collect = "all")
# With "none", nothing except "none" should be enabled
result <- withOtelCollect("none", {
list(
none = otel_collect_is_enabled("none"),
session = otel_collect_is_enabled("session"),
reactivity = otel_collect_is_enabled("reactivity")
)
})
expect_true(result$none)
expect_false(result$session)
expect_false(result$reactivity)
# With "reactivity", reactivity and below should be enabled, but not "all"
result <- withOtelCollect("reactivity", {
list(
none = otel_collect_is_enabled("none"),
session = otel_collect_is_enabled("session"),
reactive_update = otel_collect_is_enabled("reactive_update"),
reactivity = otel_collect_is_enabled("reactivity"),
all = otel_collect_is_enabled("all")
)
})
expect_true(result$none)
expect_true(result$session)
expect_true(result$reactive_update)
expect_true(result$reactivity)
expect_false(result$all)
})
test_that("localOtelCollect affects otel_collect_is_enabled", {
original <- getOption("shiny.otel.collect")
on.exit(options(shiny.otel.collect = original), add = TRUE)
options(shiny.otel.collect = "all")
test_func <- function() {
localOtelCollect("reactivity")
list(
session = otel_collect_is_enabled("session"),
reactive_update = otel_collect_is_enabled("reactive_update"),
reactivity = otel_collect_is_enabled("reactivity"),
all = otel_collect_is_enabled("all")
)
}
result <- test_func()
expect_true(result$session)
expect_true(result$reactive_update)
expect_true(result$reactivity)
expect_false(result$all)
})

View File

@@ -214,6 +214,10 @@ reference:
- runTests
- testServer
- MockShinySession
- title: OpenTelemetry
desc: Functions for OpenTelemetry tracing integration
contents:
- withOtelCollect
- title: Superseded
desc: Functions that have been `r lifecycle::badge("superseded")`
contents: