From fc8d232c45506b5a2e9fe991ea2f609bec023153 Mon Sep 17 00:00:00 2001 From: steffenhartmeyer Date: Mon, 27 Nov 2023 12:27:25 +0100 Subject: [PATCH 1/6] Added five new metrics. --- DESCRIPTION | 3 + NAMESPACE | 5 ++ R/helper.R | 32 +++++++ R/metric_bright_dark_period.R | 129 ++++++++++++++++++++++++++++ R/metric_duration_above_threshold.R | 102 ++++++++++++++++++++++ R/metric_interdaily_stability.R | 127 +++++++++++++++++++++++++++ R/metric_intradaily_variability.R | 124 ++++++++++++++++++++++++++ R/metric_timing_above_threshold.R | 104 ++++++++++++++++++++++ README.Rmd | 25 +++--- man/LightLogR-package.Rd | 1 + man/bright_dark_period.Rd | 74 ++++++++++++++++ man/duration_above_threshold.Rd | 75 ++++++++++++++++ man/interdaily_stability.Rd | 59 +++++++++++++ man/intradaily_variability.Rd | 56 ++++++++++++ man/timing_above_threshold.Rd | 74 ++++++++++++++++ 15 files changed, 980 insertions(+), 10 deletions(-) create mode 100644 R/metric_bright_dark_period.R create mode 100644 R/metric_duration_above_threshold.R create mode 100644 R/metric_interdaily_stability.R create mode 100755 R/metric_intradaily_variability.R create mode 100755 R/metric_timing_above_threshold.R create mode 100644 man/bright_dark_period.Rd create mode 100644 man/duration_above_threshold.Rd create mode 100644 man/interdaily_stability.Rd create mode 100644 man/intradaily_variability.Rd create mode 100644 man/timing_above_threshold.Rd diff --git a/DESCRIPTION b/DESCRIPTION index 4ea93ba..427ae72 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -8,6 +8,9 @@ Authors@R: c( person("Manuel", "Spitschan", email = "manuel.spitschan@tum.de", role = "aut", comment = c(ORCID = "0000-0002-8572-9268")), + person("Steffen", "Hartmeyer", + email = "steffen.hartmeyer@epfl.ch", role = "aut", + comment = c(ORCID = "0000-0002-2813-2668")), person("MeLiDos", role = "fnd"), person("EURAMET", role = "fnd"), person("TSCN-Lab", comment = c(URL = "www.tscnlab.org"), role = "cph")) diff --git a/NAMESPACE b/NAMESPACE index 092369c..b73915e 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -5,10 +5,12 @@ export(Brown.check) export(Brown.rec) export(Brown2reference) export(aggregate_Datetime) +export(bright_dark_period) export(create_Time.data) export(cut_Datetime) export(data2reference) export(dominant_epoch) +export(duration_above_threshold) export(filter_Date) export(filter_Datetime) export(filter_Time) @@ -21,10 +23,13 @@ export(import.ActLumus) export(import.Dataset) export(import.LYS) export(import.Statechanges) +export(interdaily_stability) export(interval2state) +export(intradaily_variability) export(join.datasets) export(sc2interval) export(sleep.int2Brown) export(symlog_trans) +export(timing_above_threshold) importFrom(magrittr,"%>%") importFrom(rlang,":=") diff --git a/R/helper.R b/R/helper.R index 804ca4d..c9a824f 100644 --- a/R/helper.R +++ b/R/helper.R @@ -107,4 +107,36 @@ pick.grouping.columns <- function(dataset) { dplyr::pick( dplyr::group_vars(dataset) ) +} + +# Compare with threshold +threshold <- function(Light.vector, + threshold, + comparison = c("above", "below"), + na.replace = FALSE){ + + comparison = match.arg(comparison) + + stopifnot( + "`Light.vector` must be numeric!" = is.numeric(Light.vector), + "`threshold` must be numeric!" = is.numeric(threshold), + "`threshold` must be either one or two values!" = length(threshold) %in% c(1, 2), + "`na.replace` must be logical!" = is.logical(na.replace) + ) + + if(length(threshold) == 1){ + out <- switch(comparison, + "above" = Light.vector >= threshold, + "below" = Light.vector <= threshold) + } + else{ + threshold <- sort(threshold) + out <- Light.vector >= threshold[1] & Light.vector <= threshold[2] + } + + if(na.replace){ + out <- tidyr::replace_na(out, FALSE) + } + + return(out) } \ No newline at end of file diff --git a/R/metric_bright_dark_period.R b/R/metric_bright_dark_period.R new file mode 100644 index 0000000..09b763c --- /dev/null +++ b/R/metric_bright_dark_period.R @@ -0,0 +1,129 @@ +#' Brightest or darkest continuous period +#' +#' This function finds the brightest or darkest continuous period of a given +#' timespan and calculates its \code{mean} light level, \code{onset}, +#' \code{midpoint}, and \code{offset}. Defined as the period with the maximum +#' or minimum mean light level. +#' +#' @param Light.vector Numeric vector containing the light data. +#' @param Datetime.vector Vector containing the time data. Can be POSIXct or numeric. +#' @param period String indicating the type of period to look for. Can be either +#' `"brightest"`(the default) or `"darkest"`. +#' @param timespan The timespan across which to calculate. Can be either a +#' `lubridate::duration()` or a `lubridate::duration()` string, e.g., +#' `"1 day"` or `"10 sec"`. +#' @param epoch The epoch at which the data was sampled. Can be either a +#' `lubridate::duration()` or a string. If it is a string, it needs to be +#' either `"dominant.epoch"` (the default) for a guess based on the data, or a valid +#' `lubridate::duration()` string, e.g., `"1 day"` or `"10 sec"`. +#' @param loop Logical. Should the data be looped? Defaults to `FALSE`. +#' @param na.rm Logical. Should missing values be removed for the calculation? +#' Defaults to `FALSE`. +#' @param as.df Logical. Should the output be returned as a data frame? Defaults +#' to `TRUE`. +#' +#' @return Data frame or matrix with pairs of timespan and calculated values. +#' If wide is TRUE then variable names will be concatenated with the timespan. +#' +#' @details Assumes regular 24h light data. Otherwise, results may not be +#' meaningful. Looping the data is recommended for finding the darkest period. +#' Missing light values will be removed by default. +#' +#' @export +#' +#' @examples +# Dataset with light > 250lx between 06:00 and 18:00 +#' dataset1 <- +#' tibble::tibble( +#' Id = rep("A", 24), +#' Datetime = lubridate::as_datetime(0) + lubridate::hours(0:23), +#' MEDI = c(rep(1, 6), rep(250, 13), rep(1, 5)) +#' ) +#' +#' dataset1 %>% +#' dplyr::summarise(bright_dark_period(MEDI, Datetime, "brightest", "10 hours", +#' as.df = TRUE +#' )) +#' dataset1 %>% +#' dplyr::summarise(bright_dark_period(MEDI, Datetime, "darkest", "5 hours", +#' loop = TRUE, as.df = TRUE +#' )) +bright_dark_period <- function(Light.vector, + Datetime.vector, + period = c("brightest", "darkest"), + timespan = "10 hours", + epoch = "dominant.epoch", + loop = FALSE, + na.rm = FALSE, + as.df = FALSE) { + # Match arguments + period <- match.arg(period) + + # Perform argument checks + stopifnot( + "`Light.vector` must be numeric!" = is.numeric(Light.vector), + "`Datetime.vector` must be POSIXct" = lubridate::is.POSIXct(Datetime.vector), + "`epoch` must either be a duration or a string" = + lubridate::is.duration(epoch) | is.character(epoch), + "`timespan` must either be a duration or a string" = + lubridate::is.duration(timespan) | is.character(timespan), + "`na.rm` must be logical!" = is.logical(na.rm), + "`as.df` must be logical!" = is.logical(as.df) + ) + + # Check whether time series is regularly spaced + if (length(unique(diff(Datetime.vector))) > 1) { + warning("`Datetime.vector` is not regularly spaced. Calculated results may be incorrect!") + } + + # Get the epochs based on the data + if (epoch == "dominant.epoch") { + epoch <- count.difftime(tibble::tibble(Datetime = Datetime.vector))$difftime[1] + } + # If the user specified an epoch, use that instead + epoch <- lubridate::as.duration(epoch) + + # Convert timespan to seconds + timespan <- lubridate::as.duration(timespan) + + # Loop data + if (loop) { + Light.vector <- c(Light.vector, Light.vector) + span <- dplyr::last(Datetime.vector) - Datetime.vector[1] + Datetime.vector <- c(Datetime.vector, Datetime.vector + span + epoch) + } + + # Calculate window size + window <- floor(as.numeric(timespan) / as.numeric(epoch)) + if (window %% 2 != 0) { + window <- window + 1 + } + + # Calculate rolling means + means <- zoo::rollapply(Light.vector, window, mean, + na.rm = na.rm, + partial = FALSE, fill = NA + ) + + # Find maximum/minimum mean value + center <- switch(period, + "brightest" = which(means == max(means, na.rm = TRUE))[1], + "darkest" = which(means == min(means, na.rm = TRUE))[1] + ) + + # Prepare output + out <- list( + mean = means[center], + midpoint = hms::as_hms(Datetime.vector[center]), + onset = hms::as_hms(Datetime.vector[center - (window / 2) + 1]), + offset = hms::as_hms(Datetime.vector[center + (window / 2)]) + ) + + # Return as data frame or numeric matrix + if (as.df) { + ts <- paste0(as.numeric(timespan, unit = "hours"), "h") + out <- tibble::as_tibble(out) %>% + dplyr::rename_with(~ paste(period, ts, .x, sep = "_")) + } + return(out) +} diff --git a/R/metric_duration_above_threshold.R b/R/metric_duration_above_threshold.R new file mode 100644 index 0000000..939da40 --- /dev/null +++ b/R/metric_duration_above_threshold.R @@ -0,0 +1,102 @@ +#' #' Time above/below threshold or within threshold range +#' +#' This function calculates the time spent above/below a specified threshold +#' light level or within a specified range of light levels. +#' +#' @param Light.vector Numeric vector containing the light data. +#' @param Time.vector Vector containing the time data. Can be numeric, HMS or POSIXct. +#' @param comparison String specifying whether the time above or below threshold +#' should be calculated. Can be either `"above"` (the default) or `"below"`. If +#' two values are provided for `threshold`, this argument will be ignored. +#' @param threshold Single numeric value or two numeric values specifying the +#' threshold light level(s) to compare with. If a vector with two values is provided, +#' the time within the two thresholds will be calculated. +#' @param epoch The epoch at which the data was sampled. Can be either a +#' `lubridate::duration()` or a string. If it is a string, it needs to be +#' either `"dominant.epoch"` (the default) for a guess based on the data, or a valid +#' `lubridate::duration()` string, e.g., `"1 day"` or `"10 sec"`. +#' @param na.rm Logical. Should missing values (NA) be removed for the calculation? +#' Defaults to `FALSE`. +#' @param as.df Logical. Should a data frame with be returned? If `TRUE`, a data +#' frame with a single column named `TAT_{threshold}` will be returned. +#' Defaults to `FALSE`. +#' +#' @return A duration object (see \code{\link[lubridate]{duration}}) as single value, +#' or single column data frame. +#' +#' @export +#' +#' @examples +#' N <- 50 +#' # Dataset with epoch = 1min +#' dataset1 <- +#' tibble::tibble( +#' Id = rep("A", N), +#' Datetime = lubridate::as_datetime(0) + lubridate::minutes(1:N), +#' MEDI = sample(c(sample(1:249, N / 2), sample(250:1000, N / 2))), +#' ) +#' # Dataset with epoch = 30s +#' dataset2 <- +#' tibble::tibble( +#' Id = rep("B", N), +#' Datetime = lubridate::as_datetime(0) + lubridate::seconds(seq(30, N * 30, 30)), +#' MEDI = sample(c(sample(1:249, N / 2), sample(250:1000, N / 2))), +#' ) +#' dataset.combined <- rbind(dataset1, dataset2) +#' +#' dataset1 %>% +#' dplyr::summarise("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) +#' +#' # Group by Id to account for different epochs +#' dataset.combined %>% +#' dplyr::group_by(Id) %>% +#' dplyr::summarise("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) +duration_above_threshold <- function(Light.vector, + Time.vector, + comparison = c("above", "below"), + threshold, + epoch = "dominant.epoch", + na.rm = FALSE, + as.df = FALSE) { + # Match input arguments + comparison <- match.arg(comparison) + + # Perform argument checks + stopifnot( + "`Light.vector` must be numeric!" = is.numeric(Light.vector), + "`Time.vector` must be numeric, HMS, or POSIXct" = + is.numeric(Time.vector) | hms::is_hms(Time.vector) | lubridate::is.POSIXct(Time.vector), + "`threshold` must be numeric!" = is.numeric(threshold), + "`threshold` must be either one or two values!" = length(threshold) %in% c(1, 2), + "`epoch` must either be a duration or a string" = + lubridate::is.duration(epoch) | is.character(epoch), + "`na.rm` must be logical!" = is.logical(na.rm), + "`as.df` must be logical!" = is.logical(as.df) + ) + + # Get the epochs based on the data + if (epoch == "dominant.epoch") { + epoch <- count.difftime(tibble::tibble(Datetime = Time.vector))$difftime[1] + epoch <- ifelse(hms::is_hms(Time.vector) | lubridate::is.POSIXct(Time.vector), + lubridate::as.duration(epoch), epoch + ) + } + # If the user specified an epoch, use that instead + else { + epoch <- lubridate::as.duration(epoch) + } + + # Calculate TAT + tat <- sum(compare_threshold(Light.vector, threshold, comparison, na.rm)) * as.numeric(epoch) + + # As duration object + tat <- lubridate::as.duration(tat) + + # Return data frame or numeric value + if (as.df) { + threshold <- stringr::str_flatten(sort(threshold), collapse = "-") + return(tibble::tibble("TAT_{threshold}" := tat)) + } else { + return(tat) + } +} diff --git a/R/metric_interdaily_stability.R b/R/metric_interdaily_stability.R new file mode 100644 index 0000000..b5f9593 --- /dev/null +++ b/R/metric_interdaily_stability.R @@ -0,0 +1,127 @@ +#' Interdaily stability (IS) +#' +#' This function calculates the variability of 24h light exposure patterns across +#' multiple days. Calculated as the ratio of the variance of the average daily +#' pattern to the total variance across all days. Calculated for mean hourly +#' light levels. Ranges between 0 (Gaussian noise) and 1 (Perfect Stability). +#' +#' Note that this metric will always be 1 if the data contains only one 24 h day. +#' +#' @param Light.vector Numeric vector containing the light data. +#' @param Datetime.vector Vector containing the time data. Must be POSIXct. +#' @param na.rm Logical. Should missing values be removed? Defaults to `FALSE`. +#' @param as.df Logical. Should the output be returned as a data frame? Defaults +#' to `FALSE`. +#' +#' @return Numeric value or dataframe with column 'IS'. +#' @export +#' +#' @references Van Someren, E. J. W., Swaab, D. F., Colenda, C. C., Cohen, W., +#' McCall, W. V., & Rosenquist, P. B. (1999). Bright Light Therapy: Improved +#' Sensitivity to Its Effects on Rest-Activity Rhythms in Alzheimer Patients +#' by Application of Nonparametric Methods. \emph{Chronobiology International}, +#' 16(4), 505–518. \url{https://doi.org/10.3109/07420529908998724} +#' +#' @examples +#' +#' set.seed(1) +#' N <- 24 * 7 +#' # Calculate metric for seven 24 h days with two measurements per hour +#' dataset1 <- +#' tibble::tibble( +#' Id = rep("A", N * 2), +#' Datetime = lubridate::as_datetime(0) + c(lubridate::minutes(seq(0, N * 60 - 30, 30))), +#' MEDI = sample(1:1000, N * 2) +#' ) +#' dataset1 %>% +#' dplyr::summarise( +#' "Interdaily stability" = interdaily_stability(MEDI, Datetime) +#' ) +#' +interdaily_stability <- function(Light.vector, + Datetime.vector, + na.rm = FALSE, + as.df = FALSE) { + # Initial checks + stopifnot( + "`Light.vector` must be numeric!" = is.numeric(Light.vector), + "`Datetime.vector` must be POSIXct!" = lubridate::is.POSIXct(Datetime.vector), + "`na.rm` must be logical!" = is.logical(na.rm), + "`as.df` must be logical!" = is.logical(as.df) + ) + + # Make data frame + df <- tibble::tibble(Light = Light.vector, Datetime = Datetime.vector) + + # Count hours per day and missing data per hour + hours_per_day <- df %>% + dplyr::group_by( + Day = lubridate::floor_date(Datetime, unit = "1 day") %>% lubridate::as_date(), + Hour = lubridate::floor_date(Datetime, unit = "1 hour") + ) %>% + dplyr::summarise(is_missing = all(is.na(Light))) %>% + dplyr::ungroup() + + N_hours <- hours_per_day %>% + dplyr::group_by(Day) %>% + dplyr::summarise(N = n()) %>% + dplyr::select(Day, N) + + # Warning if days are not full 24h + if (any(N_hours$N < 24)) { + warning(paste( + "One or more days in the data do not consist of 24 h.", + "Interdaily stability might not be meaningful for non-24 h days.", + "These days contain less than 24 h:", + paste( + capture.output(print( + dplyr::filter(N_hours, N < 24) %>% dplyr::pull(Day) + )), + sep = "\n", collapse = "\n" + ), + "", + sep = "\n" + )) + } + + # Warning if some hours are completely missing + if (any(hours_per_day$is_missing)) { + warning(paste( + "Data contains some hours with only missing values", + "These hours contain only missing values: ", + paste( + capture.output(print( + dplyr::filter(hours_per_day, is_missing) %>% dplyr::pull(Hour) + )), + sep = "\n", collapse = "\n" + ), + "", + sep = "\n" + )) + } + + # Remove missing values + if (na.rm) { + df <- df %>% tidyr::drop_na(Light) + } + + # Hourly averages for each day + total_hourly <- df %>% + dplyr::group_by(Datetime = lubridate::floor_date(Datetime, unit = "1 hour")) %>% + dplyr::summarise(Light = mean(Light)) + + # Hourly average across all days + avg_hourly <- total_hourly %>% + dplyr::group_by(Hour = lubridate::hour(Datetime)) %>% + dplyr::summarise(Light = mean(Light)) + + # Variance across average day / variance across all days + is <- var(avg_hourly$Light) / var(total_hourly$Light) + + # Return data frame or numeric vector + if (as.df) { + return(tibble::tibble("IS" = is)) + } else { + return(is) + } +} diff --git a/R/metric_intradaily_variability.R b/R/metric_intradaily_variability.R new file mode 100755 index 0000000..5d20fce --- /dev/null +++ b/R/metric_intradaily_variability.R @@ -0,0 +1,124 @@ +#' Intradaily variability (IV) +#' +#' This function calculates the variability of consecutive Light levels within +#' a 24h day. Calculated as the ratio of the variance of the differences between +#' consecutive Light levels to the total variance across the day. Calculated for +#' mean hourly Light levels. Higher values indicate more fragmentation. +#' +#' @param Light.vector Numeric vector containing the light data. +#' @param Datetime.vector Vector containing the time data. Must be POSIXct. +#' @param na.rm Logical. Should missing values be removed? Defaults to `FALSE`. +#' @param as.df Logical. Should the output be returned as a data frame? Defaults +#' to `FALSE`. +#' +#' @return Numeric value or dataframe with column 'IV'. +#' @export +#' +#' @references Van Someren, E. J. W., Swaab, D. F., Colenda, C. C., Cohen, W., +#' McCall, W. V., & Rosenquist, P. B. (1999). Bright Light Therapy: Improved +#' Sensitivity to Its Effects on Rest-Activity Rhythms in Alzheimer Patients +#' by Application of Nonparametric Methods. \emph{Chronobiology International}, +#' 16(4), 505–518. \url{https://doi.org/10.3109/07420529908998724} +#' +#' @examples +#' +#' set.seed(1) +#' N <- 24 * 2 +#' # Calculate metric for two 24 h days with two measurements per hour +#' dataset1 <- +#' tibble::tibble( +#' Id = rep("A", N * 2), +#' Datetime = lubridate::as_datetime(0) + c(lubridate::minutes(seq(0, N * 60 - 30, 30))), +#' MEDI = sample(1:1000, N * 2) +#' ) +#' dataset1 %>% +#' dplyr::summarise( +#' "Intradaily variability" = intradaily_variability(MEDI, Datetime) +#' ) +#' +intradaily_variability <- function(Light.vector, + Datetime.vector, + na.rm = FALSE, + as.df = FALSE) { + # Initial checks + stopifnot( + "`Light.vector` must be numeric!" = is.numeric(Light.vector), + "`Datetime.vector` must be POSIXct!" = lubridate::is.POSIXct(Datetime.vector), + "`na.rm` must be logical!" = is.logical(na.rm), + "`as.df` must be logical!" = is.logical(as.df) + ) + + # Make data frame + df <- tibble::tibble(Light = Light.vector, Datetime = Datetime.vector) + + # Count hours per day and missing data per hour + hours_per_day <- df %>% + dplyr::group_by( + Day = lubridate::floor_date(Datetime, unit = "1 day") %>% lubridate::as_date(), + Hour = lubridate::floor_date(Datetime, unit = "1 hour") + ) %>% + dplyr::summarise(is_missing = all(is.na(Light))) %>% + dplyr::ungroup() + + N_hours <- hours_per_day %>% + dplyr::group_by(Day) %>% + dplyr::summarise(N = n()) %>% + dplyr::select(Day, N) + + # Warning if days are not full 24h + if (any(N_hours$N < 24)) { + warning(paste( + "One or more days in the data do not consist of 24 h.", + "Intradaily variability might not be meaningful for non-24 h days.", + "These days contain less than 24 h:", + paste( + capture.output(print( + dplyr::filter(N_hours, N < 24) %>% dplyr::pull(Day) + )), + sep = "\n", collapse = "\n" + ), + "", + sep = "\n" + )) + } + + # Warning if some hours are completely missing + if (any(hours_per_day$is_missing)) { + warning(paste( + "Data contains some hours with only missing values", + "These hours contain only missing values: ", + paste( + capture.output(print( + dplyr::filter(hours_per_day, is_missing) %>% dplyr::pull(Hour) + )), + sep = "\n", collapse = "\n" + ), + "", + sep = "\n" + )) + } + + # Remove missing values + if (na.rm) { + df <- df %>% tidyr::drop_na(Light) + } + + # Hourly averages for each day + total_hourly <- df %>% + dplyr::group_by(lubridate::floor_date(Datetime, unit = "1 hour")) %>% + dplyr::summarise(Light = mean(Light)) + + # Variance of consecutive hourly differences + var_hourly_diff <- + sum(diff(total_hourly$Light)^2) / (length(total_hourly$Light) - 1) + + # Variance of consecutive differences / variance across all days + iv <- var_hourly_diff / var(total_hourly$Light) + + # Return data frame or numeric vector + if (as.df) { + return(tibble::tibble("IV" = iv)) + } else { + return(iv) + } +} diff --git a/R/metric_timing_above_threshold.R b/R/metric_timing_above_threshold.R new file mode 100755 index 0000000..004a5b2 --- /dev/null +++ b/R/metric_timing_above_threshold.R @@ -0,0 +1,104 @@ +#' Mean/first/last timing above/below threshold. +#' +#' This function calculates the mean/first/last timepoint where light levels are +#' above or below a given threshold intensity within the given interval. +#' +#' @param Light.vector Numeric vector containing the light data. +#' @param Time.vector Vector containing the time data. Can be numeric, HMS or POSIXct. +#' @param metric String indicating which timing metrics to calculate. Possible values +#' are `"mean"` (default), `"first"`, and `"last"` timing above threshold. +#' @param comparison String specifying whether the time above or below threshold +#' should be calculated. Can be either `"above"` (the default) or `"below"`. If +#' two values are provided for `threshold`, this argument will be ignored. +#' @param threshold Single numeric value or two numeric values specifying the +#' threshold light level(s) to compare with. If a vector with two values is provided, +#' the timing corresponding to light levels between the two thresholds will be +#' calculated. +#' @param na.rm Logical. Should missing values be removed for the calculation? +#' Defaults to `FALSE`. +#' @param as.df Logical. Should a data frame with be returned? If `TRUE`, a data +#' frame with a single column named `{metric}_{threshold}` will be returned. +#' Defaults to `FALSE`. +#' +#' @return Single value or single column dataframe. If `Time.vector` is of type +#' HMS or POSIXct a HMS object (see \code{\link[hms]{hms}}) will be returned, +#' otherwise a numeric object. +#' +#' @references Reid, K. J., Santostasi, G., Baron, K. G., Wilson, J., Kang, J., +#' & Zee, P. C. (2014). Timing and Intensity of Light Correlate with Body Weight +#' in Adults. \emph{PLOS ONE}, 9(4), e92251. +#' \url{https://doi.org/10.1371/journal.pone.0092251} +#' +#' @export +#' +#' @examples +#' # Dataset with light > 250lx between 06:00 and 18:00 +#' dataset1 <- +#' tibble::tibble( +#' Id = rep("A", 24), +#' Datetime = lubridate::as_datetime(0) + lubridate::hours(0:23), +#' MEDI = c(rep(1, 6), rep(250, 13), rep(1, 5)) +#' ) +#' +#' dataset1 %>% +#' dplyr::summarise(timing_above_threshold(MEDI, Datetime, "mean", "above", 250)) +#' +#' dataset1 %>% +#' dplyr::summarise(timing_above_threshold(MEDI, Datetime, "first", "above", 250)) +#' +#' dataset1 %>% +#' dplyr::summarise(timing_above_threshold(MEDI, Datetime, "last", "above", 250)) +#' +timing_above_threshold <- function(Light.vector, + Time.vector, + metric = c("mean", "first", "last"), + comparison = c("above", "below"), + threshold, + na.rm = FALSE, + as.df = FALSE) { + # Match arguments + metric <- match.arg(metric) + comparison <- match.arg(comparison) + + # Perform argument checks + stopifnot( + "`Light.vector` must be numeric!" = is.numeric(Light.vector), + "`Time.vector` must be numeric, HMS, or POSIXct" = + is.numeric(Time.vector) | hms::is_hms(Time.vector) | lubridate::is.POSIXct(Time.vector), + "`threshold` must be numeric!" = is.numeric(threshold), + "`threshold` must be either one or two values!" = length(threshold) %in% c(1, 2), + "`na.rm` must be logical!" = is.logical(na.rm), + "`as.df` must be logical!" = is.logical(as.df) + ) + + # Convert to HMS + if (hms::is_hms(Time.vector) | lubridate::is.POSIXct(Time.vector)) { + Time.vector <- Time.vector %>% hms::as_hms() + } + + # Calculate timing metric + t <- Time.vector[compare_threshold(Light.vector, threshold, comparison, na.rm)] + xlit <- switch(metric, + "mean" = t %>% as.numeric() %>% mean() %>% round(), + "first" = t %>% dplyr::first(), + "last" = t %>% dplyr::last() + ) + + # Convert to HMS + if (hms::is_hms(Time.vector) | lubridate::is.POSIXct(Time.vector)) { + xlit <- xlit %>% hms::as_hms() + } + + # Return data frame or numeric value + if (as.df) { + name <- switch(metric, + "mean" = "MLiT", + "first" = "FLiT", + "last" = "LLiT" + ) + threshold <- stringr::str_flatten(sort(threshold), collapse = "-") + return(tibble::tibble("{name}_{threshold}" = xlit)) + } else { + return(xlit) + } +} diff --git a/README.Rmd b/README.Rmd index 0ed631b..7cc6191 100644 --- a/README.Rmd +++ b/README.Rmd @@ -59,7 +59,7 @@ Here is a quick starter on how do use **LightLogR**. ```{r, message = FALSE} library(LightLogR) -#these packages are just needed for the examples as shown. +# these packages are just needed for the examples as shown. library(flextable) library(dplyr) library(ggplot2) @@ -73,8 +73,11 @@ You can import a light logger dataset with ease. The import functions give quick filename <- system.file("extdata/sample_data_LYS.csv", package = "LightLogR") dataset <- import.LYS(filename, tz = "Europe/Berlin") -dataset %>% select(Datetime, lux, kelvin, MEDI) %>% slice(8000:8005) %>% - flextable() %>% autofit() +dataset %>% + select(Datetime, lux, kelvin, MEDI) %>% + slice(8000:8005) %>% + flextable() %>% + autofit() ``` ### Visualize @@ -87,8 +90,8 @@ dataset %>% gg_day() There is a wide range of options to the `gg_day()` function to customize the output. Have a look at the reference page (`?gg_day`) to see all options. You can also override most of the defaults, e.g., for different `color`, `facetting`, `theme` options. ```{r, fig.retina=2} -dataset %>% - gg_day(col = MEDI >= 250, scales = "fixed", size = 0.5) + +dataset %>% + gg_day(col = MEDI >= 250, scales = "fixed", size = 0.5) + scale_color_discrete(type = c("orange", "skyblue")) ``` @@ -97,25 +100,27 @@ dataset %>% The built-in dataset `sample.data.environment` shows a combined dataset of light logger data and a second set of data - in this case unobstructed outdoor light measurements. Combined datasets can be easily visualized with `gg_day()`. The `col` parameter used on the `Source` column of the dataset allows for a color separation. ```{r, fig.height= 6, fig.retina=2} -sample.data.environment %>% +sample.data.environment %>% gg_day( start.date = "2023-08-18", y.axis = `MELANOPIC EDI`, col = Source, scales = "fixed", - geom = "line") + geom = "line" + ) ``` With the `cut_Datetime()` function, the data can further be broken up into arbitrary time intervals. This can be used to easily compare different datasets. Just put the function in between the dataset and `gg_day()`. This makes a new variable available for plotting: `Datetime.rounded`. Just make sure, that the `geom` parameter is set to *boxplot* and the `group` parameter uses both the info from the rounded time interval (`Datetime.rounded`) and the different datasets (`Source`). The `interaction` function can easily combine them. The default interval for `cut_Datetime()` is 3 hours. ```{r, fig.retina=2} -sample.data.environment %>% - cut_Datetime() %>% +sample.data.environment %>% + cut_Datetime() %>% gg_day( end.date = "2023-08-15", y.axis = `MELANOPIC EDI`, col = Source, scales = "fixed", geom = "boxplot", - group = interaction(Source, Datetime.rounded)) + + group = interaction(Source, Datetime.rounded) + ) + theme(legend.position = "bottom") ``` diff --git a/man/LightLogR-package.Rd b/man/LightLogR-package.Rd index c4bee8f..92c32d8 100644 --- a/man/LightLogR-package.Rd +++ b/man/LightLogR-package.Rd @@ -25,6 +25,7 @@ Useful links: Authors: \itemize{ \item Manuel Spitschan \email{manuel.spitschan@tum.de} (\href{https://orcid.org/0000-0002-8572-9268}{ORCID}) + \item Steffen Hartmeyer \email{steffen.hartmeyer@epfl.ch} (\href{https://orcid.org/0000-0002-2813-2668}{ORCID}) } Other contributors: diff --git a/man/bright_dark_period.Rd b/man/bright_dark_period.Rd new file mode 100644 index 0000000..6a00316 --- /dev/null +++ b/man/bright_dark_period.Rd @@ -0,0 +1,74 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/metric_bright_dark_period.R +\name{bright_dark_period} +\alias{bright_dark_period} +\title{Brightest or darkest continuous period} +\usage{ +bright_dark_period( + Light.vector, + Datetime.vector, + period = c("brightest", "darkest"), + timespan = "10 hours", + epoch = "dominant.epoch", + loop = FALSE, + na.rm = FALSE, + as.df = FALSE +) +} +\arguments{ +\item{Light.vector}{Numeric vector containing the light data.} + +\item{Datetime.vector}{Vector containing the time data. Can be POSIXct or numeric.} + +\item{period}{String indicating the type of period to look for. Can be either +\code{"brightest"}(the default) or \code{"darkest"}.} + +\item{timespan}{The timespan across which to calculate. Can be either a +\code{lubridate::duration()} or a \code{lubridate::duration()} string, e.g., +\code{"1 day"} or \code{"10 sec"}.} + +\item{epoch}{The epoch at which the data was sampled. Can be either a +\code{lubridate::duration()} or a string. If it is a string, it needs to be +either \code{"dominant.epoch"} (the default) for a guess based on the data, or a valid +\code{lubridate::duration()} string, e.g., \code{"1 day"} or \code{"10 sec"}.} + +\item{loop}{Logical. Should the data be looped? Defaults to \code{FALSE}.} + +\item{na.rm}{Logical. Should missing values be removed for the calculation? +Defaults to \code{FALSE}.} + +\item{as.df}{Logical. Should the output be returned as a data frame? Defaults +to \code{TRUE}.} +} +\value{ +Data frame or matrix with pairs of timespan and calculated values. +If wide is TRUE then variable names will be concatenated with the timespan. +} +\description{ +This function finds the brightest or darkest continuous period of a given +timespan and calculates its \code{mean} light level, \code{onset}, +\code{midpoint}, and \code{offset}. Defined as the period with the maximum +or minimum mean light level. +} +\details{ +Assumes regular 24h light data. Otherwise, results may not be +meaningful. Looping the data is recommended for finding the darkest period. +Missing light values will be removed by default. +} +\examples{ +dataset1 <- + tibble::tibble( + Id = rep("A", 24), + Datetime = lubridate::as_datetime(0) + lubridate::hours(0:23), + MEDI = c(rep(1, 6), rep(250, 13), rep(1, 5)) + ) + +dataset1 \%>\% + dplyr::summarise(bright_dark_period(MEDI, Datetime, "brightest", "10 hours", + as.df = TRUE + )) +dataset1 \%>\% + dplyr::summarise(bright_dark_period(MEDI, Datetime, "darkest", "5 hours", + loop = TRUE, as.df = TRUE + )) +} diff --git a/man/duration_above_threshold.Rd b/man/duration_above_threshold.Rd new file mode 100644 index 0000000..e5d932c --- /dev/null +++ b/man/duration_above_threshold.Rd @@ -0,0 +1,75 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/metric_duration_above_threshold.R +\name{duration_above_threshold} +\alias{duration_above_threshold} +\title{#' Time above/below threshold or within threshold range} +\usage{ +duration_above_threshold( + Light.vector, + Time.vector, + comparison = c("above", "below"), + threshold, + epoch = "dominant.epoch", + na.rm = FALSE, + as.df = FALSE +) +} +\arguments{ +\item{Light.vector}{Numeric vector containing the light data.} + +\item{Time.vector}{Vector containing the time data. Can be numeric, HMS or POSIXct.} + +\item{comparison}{String specifying whether the time above or below threshold +should be calculated. Can be either \code{"above"} (the default) or \code{"below"}. If +two values are provided for \code{threshold}, this argument will be ignored.} + +\item{threshold}{Single numeric value or two numeric values specifying the +threshold light level(s) to compare with. If a vector with two values is provided, +the time within the two thresholds will be calculated.} + +\item{epoch}{The epoch at which the data was sampled. Can be either a +\code{lubridate::duration()} or a string. If it is a string, it needs to be +either \code{"dominant.epoch"} (the default) for a guess based on the data, or a valid +\code{lubridate::duration()} string, e.g., \code{"1 day"} or \code{"10 sec"}.} + +\item{na.rm}{Logical. Should missing values (NA) be removed for the calculation? +Defaults to \code{FALSE}.} + +\item{as.df}{Logical. Should a data frame with be returned? If \code{TRUE}, a data +frame with a single column named \verb{TAT_\{threshold\}} will be returned. +Defaults to \code{FALSE}.} +} +\value{ +A duration object (see \code{\link[lubridate]{duration}}) as single value, +or single column data frame. +} +\description{ +This function calculates the time spent above/below a specified threshold +light level or within a specified range of light levels. +} +\examples{ +N <- 50 +# Dataset with epoch = 1min +dataset1 <- + tibble::tibble( + Id = rep("A", N), + Datetime = lubridate::as_datetime(0) + lubridate::minutes(1:N), + MEDI = sample(c(sample(1:249, N / 2), sample(250:1000, N / 2))), + ) +# Dataset with epoch = 30s +dataset2 <- + tibble::tibble( + Id = rep("B", N), + Datetime = lubridate::as_datetime(0) + lubridate::seconds(seq(30, N * 30, 30)), + MEDI = sample(c(sample(1:249, N / 2), sample(250:1000, N / 2))), + ) +dataset.combined <- rbind(dataset1, dataset2) + +dataset1 \%>\% + dplyr::summarise("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) + +# Group by Id to account for different epochs +dataset.combined \%>\% + dplyr::group_by(Id) \%>\% + dplyr::summarise("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) +} diff --git a/man/interdaily_stability.Rd b/man/interdaily_stability.Rd new file mode 100644 index 0000000..e9f4c6c --- /dev/null +++ b/man/interdaily_stability.Rd @@ -0,0 +1,59 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/metric_interdaily_stability.R +\name{interdaily_stability} +\alias{interdaily_stability} +\title{Interdaily stability (IS)} +\usage{ +interdaily_stability( + Light.vector, + Datetime.vector, + na.rm = FALSE, + as.df = FALSE +) +} +\arguments{ +\item{Light.vector}{Numeric vector containing the light data.} + +\item{Datetime.vector}{Vector containing the time data. Must be POSIXct.} + +\item{na.rm}{Logical. Should missing values be removed? Defaults to \code{FALSE}.} + +\item{as.df}{Logical. Should the output be returned as a data frame? Defaults +to \code{FALSE}.} +} +\value{ +Numeric value or dataframe with column 'IS'. +} +\description{ +This function calculates the variability of 24h light exposure patterns across +multiple days. Calculated as the ratio of the variance of the average daily +pattern to the total variance across all days. Calculated for mean hourly +light levels. Ranges between 0 (Gaussian noise) and 1 (Perfect Stability). +} +\details{ +Note that this metric will always be 1 if the data contains only one 24 h day. +} +\examples{ + +set.seed(1) +N <- 24 * 7 +# Calculate metric for seven 24 h days with two measurements per hour +dataset1 <- + tibble::tibble( + Id = rep("A", N * 2), + Datetime = lubridate::as_datetime(0) + c(lubridate::minutes(seq(0, N * 60 - 30, 30))), + MEDI = sample(1:1000, N * 2) + ) +dataset1 \%>\% + dplyr::summarise( + "Interdaily stability" = interdaily_stability(MEDI, Datetime) + ) + +} +\references{ +Van Someren, E. J. W., Swaab, D. F., Colenda, C. C., Cohen, W., +McCall, W. V., & Rosenquist, P. B. (1999). Bright Light Therapy: Improved +Sensitivity to Its Effects on Rest-Activity Rhythms in Alzheimer Patients +by Application of Nonparametric Methods. \emph{Chronobiology International}, +16(4), 505–518. \url{https://doi.org/10.3109/07420529908998724} +} diff --git a/man/intradaily_variability.Rd b/man/intradaily_variability.Rd new file mode 100644 index 0000000..7679056 --- /dev/null +++ b/man/intradaily_variability.Rd @@ -0,0 +1,56 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/metric_intradaily_variability.R +\name{intradaily_variability} +\alias{intradaily_variability} +\title{Intradaily variability (IV)} +\usage{ +intradaily_variability( + Light.vector, + Datetime.vector, + na.rm = FALSE, + as.df = FALSE +) +} +\arguments{ +\item{Light.vector}{Numeric vector containing the light data.} + +\item{Datetime.vector}{Vector containing the time data. Must be POSIXct.} + +\item{na.rm}{Logical. Should missing values be removed? Defaults to \code{FALSE}.} + +\item{as.df}{Logical. Should the output be returned as a data frame? Defaults +to \code{FALSE}.} +} +\value{ +Numeric value or dataframe with column 'IV'. +} +\description{ +This function calculates the variability of consecutive Light levels within +a 24h day. Calculated as the ratio of the variance of the differences between +consecutive Light levels to the total variance across the day. Calculated for +mean hourly Light levels. Higher values indicate more fragmentation. +} +\examples{ + +set.seed(1) +N <- 24 * 2 +# Calculate metric for two 24 h days with two measurements per hour +dataset1 <- + tibble::tibble( + Id = rep("A", N * 2), + Datetime = lubridate::as_datetime(0) + c(lubridate::minutes(seq(0, N * 60 - 30, 30))), + MEDI = sample(1:1000, N * 2) + ) +dataset1 \%>\% + dplyr::summarise( + "Intradaily variability" = intradaily_variability(MEDI, Datetime) + ) + +} +\references{ +Van Someren, E. J. W., Swaab, D. F., Colenda, C. C., Cohen, W., +McCall, W. V., & Rosenquist, P. B. (1999). Bright Light Therapy: Improved +Sensitivity to Its Effects on Rest-Activity Rhythms in Alzheimer Patients +by Application of Nonparametric Methods. \emph{Chronobiology International}, +16(4), 505–518. \url{https://doi.org/10.3109/07420529908998724} +} diff --git a/man/timing_above_threshold.Rd b/man/timing_above_threshold.Rd new file mode 100644 index 0000000..5105b28 --- /dev/null +++ b/man/timing_above_threshold.Rd @@ -0,0 +1,74 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/metric_timing_above_threshold.R +\name{timing_above_threshold} +\alias{timing_above_threshold} +\title{Mean/first/last timing above/below threshold.} +\usage{ +timing_above_threshold( + Light.vector, + Time.vector, + metric = c("mean", "first", "last"), + comparison = c("above", "below"), + threshold, + na.rm = FALSE, + as.df = FALSE +) +} +\arguments{ +\item{Light.vector}{Numeric vector containing the light data.} + +\item{Time.vector}{Vector containing the time data. Can be numeric, HMS or POSIXct.} + +\item{metric}{String indicating which timing metrics to calculate. Possible values +are \code{"mean"} (default), \code{"first"}, and \code{"last"} timing above threshold.} + +\item{comparison}{String specifying whether the time above or below threshold +should be calculated. Can be either \code{"above"} (the default) or \code{"below"}. If +two values are provided for \code{threshold}, this argument will be ignored.} + +\item{threshold}{Single numeric value or two numeric values specifying the +threshold light level(s) to compare with. If a vector with two values is provided, +the timing corresponding to light levels between the two thresholds will be +calculated.} + +\item{na.rm}{Logical. Should missing values be removed for the calculation? +Defaults to \code{FALSE}.} + +\item{as.df}{Logical. Should a data frame with be returned? If \code{TRUE}, a data +frame with a single column named \verb{\{metric\}_\{threshold\}} will be returned. +Defaults to \code{FALSE}.} +} +\value{ +Single value or single column dataframe. If \code{Time.vector} is of type +HMS or POSIXct a HMS object (see \code{\link[hms]{hms}}) will be returned, +otherwise a numeric object. +} +\description{ +This function calculates the mean/first/last timepoint where light levels are +above or below a given threshold intensity within the given interval. +} +\examples{ +# Dataset with light > 250lx between 06:00 and 18:00 +dataset1 <- + tibble::tibble( + Id = rep("A", 24), + Datetime = lubridate::as_datetime(0) + lubridate::hours(0:23), + MEDI = c(rep(1, 6), rep(250, 13), rep(1, 5)) + ) + +dataset1 \%>\% + dplyr::summarise(timing_above_threshold(MEDI, Datetime, "mean", "above", 250)) + +dataset1 \%>\% + dplyr::summarise(timing_above_threshold(MEDI, Datetime, "first", "above", 250)) + +dataset1 \%>\% + dplyr::summarise(timing_above_threshold(MEDI, Datetime, "last", "above", 250)) + +} +\references{ +Reid, K. J., Santostasi, G., Baron, K. G., Wilson, J., Kang, J., +& Zee, P. C. (2014). Timing and Intensity of Light Correlate with Body Weight +in Adults. \emph{PLOS ONE}, 9(4), e92251. +\url{https://doi.org/10.1371/journal.pone.0092251} +} From 88e4fee31050027e859f7ea844fd7456013b69a8 Mon Sep 17 00:00:00 2001 From: steffenhartmeyer Date: Tue, 28 Nov 2023 10:12:51 +0100 Subject: [PATCH 2/6] Uodated documentation for bright_dark_period --- .gitignore | 3 +++ R/metric_bright_dark_period.R | 25 ++++++++++++++----------- man/bright_dark_period.Rd | 17 ++++++++++------- 3 files changed, 27 insertions(+), 18 deletions(-) diff --git a/.gitignore b/.gitignore index 20e257d..2216890 100644 --- a/.gitignore +++ b/.gitignore @@ -50,3 +50,6 @@ rsconnect/ .Rproj.user docs inst/doc + +# DS_Store file +.DS_Store diff --git a/R/metric_bright_dark_period.R b/R/metric_bright_dark_period.R index 09b763c..7009b68 100644 --- a/R/metric_bright_dark_period.R +++ b/R/metric_bright_dark_period.R @@ -1,9 +1,10 @@ #' Brightest or darkest continuous period #' #' This function finds the brightest or darkest continuous period of a given -#' timespan and calculates its \code{mean} light level, \code{onset}, -#' \code{midpoint}, and \code{offset}. Defined as the period with the maximum -#' or minimum mean light level. +#' timespan and calculates its `mean` light level, as well as the timing of the period's +#' `onset`, `midpoint`, and `offset`. It is defined as the period with the maximum +#' or minimum mean light level. Note that the data need to be regularly spaced +#' (i.e., no gaps) for correct results. #' #' @param Light.vector Numeric vector containing the light data. #' @param Datetime.vector Vector containing the time data. Can be POSIXct or numeric. @@ -16,18 +17,20 @@ #' `lubridate::duration()` or a string. If it is a string, it needs to be #' either `"dominant.epoch"` (the default) for a guess based on the data, or a valid #' `lubridate::duration()` string, e.g., `"1 day"` or `"10 sec"`. -#' @param loop Logical. Should the data be looped? Defaults to `FALSE`. +#' @param loop Logical. Should the data be looped? If `TRUE`, a full copy of the data +#' will be concatenated at the end of the data. Makes only sense for 24 h data. +#' Defaults to `FALSE`. #' @param na.rm Logical. Should missing values be removed for the calculation? #' Defaults to `FALSE`. #' @param as.df Logical. Should the output be returned as a data frame? Defaults #' to `TRUE`. #' -#' @return Data frame or matrix with pairs of timespan and calculated values. -#' If wide is TRUE then variable names will be concatenated with the timespan. +#' @return A named list with the `mean`, `onset`, `midpoint`, and `offset` of the +#' calculated brightest or darkest period, or if `as.df == TRUE` a data frame +#' with columns named `{period}_{timespan}_{metric}`. #' #' @details Assumes regular 24h light data. Otherwise, results may not be #' meaningful. Looping the data is recommended for finding the darkest period. -#' Missing light values will be removed by default. #' #' @export #' @@ -113,10 +116,10 @@ bright_dark_period <- function(Light.vector, # Prepare output out <- list( - mean = means[center], - midpoint = hms::as_hms(Datetime.vector[center]), - onset = hms::as_hms(Datetime.vector[center - (window / 2) + 1]), - offset = hms::as_hms(Datetime.vector[center + (window / 2)]) + "mean" = means[center], + "midpoint" = hms::as_hms(Datetime.vector[center]), + "onset" = hms::as_hms(Datetime.vector[center - (window / 2) + 1]), + "offset" = hms::as_hms(Datetime.vector[center + (window / 2)]) ) # Return as data frame or numeric matrix diff --git a/man/bright_dark_period.Rd b/man/bright_dark_period.Rd index 6a00316..801c1bc 100644 --- a/man/bright_dark_period.Rd +++ b/man/bright_dark_period.Rd @@ -32,7 +32,9 @@ bright_dark_period( either \code{"dominant.epoch"} (the default) for a guess based on the data, or a valid \code{lubridate::duration()} string, e.g., \code{"1 day"} or \code{"10 sec"}.} -\item{loop}{Logical. Should the data be looped? Defaults to \code{FALSE}.} +\item{loop}{Logical. Should the data be looped? If \code{TRUE}, a full copy of the data +will be concatenated at the end of the data. Makes only sense for 24 h data. +Defaults to \code{FALSE}.} \item{na.rm}{Logical. Should missing values be removed for the calculation? Defaults to \code{FALSE}.} @@ -41,19 +43,20 @@ Defaults to \code{FALSE}.} to \code{TRUE}.} } \value{ -Data frame or matrix with pairs of timespan and calculated values. -If wide is TRUE then variable names will be concatenated with the timespan. +A named list with the \code{mean}, \code{onset}, \code{midpoint}, and \code{offset} of the +calculated brightest or darkest period, or if \code{as.df == TRUE} a data frame +with columns named \verb{\{period\}_\{timespan\}_\{metric\}}. } \description{ This function finds the brightest or darkest continuous period of a given -timespan and calculates its \code{mean} light level, \code{onset}, -\code{midpoint}, and \code{offset}. Defined as the period with the maximum -or minimum mean light level. +timespan and calculates its \code{mean} light level, as well as the timing of the period's +\code{onset}, \code{midpoint}, and \code{offset}. It is defined as the period with the maximum +or minimum mean light level. Note that the data need to be regularly spaced +(i.e., no gaps) for correct results. } \details{ Assumes regular 24h light data. Otherwise, results may not be meaningful. Looping the data is recommended for finding the darkest period. -Missing light values will be removed by default. } \examples{ dataset1 <- From 90f3ff26e3993882509f50984ee68a088b39680c Mon Sep 17 00:00:00 2001 From: steffenhartmeyer Date: Wed, 6 Dec 2023 00:19:00 +0100 Subject: [PATCH 3/6] Reworked metric functions --- R/helper.R | 2 +- R/metric_bright_dark_period.R | 61 ++++++++++-------- R/metric_duration_above_threshold.R | 21 +++++-- R/metric_interdaily_stability.R | 11 +++- R/metric_intradaily_variability.R | 11 +++- R/metric_timing_above_threshold.R | 95 ++++++++++++++++------------- man/bright_dark_period.Rd | 32 +++++++--- man/duration_above_threshold.Rd | 22 ++++++- man/interdaily_stability.Rd | 15 ++++- man/intradaily_variability.Rd | 15 ++++- man/timing_above_threshold.Rd | 42 ++++++++----- 11 files changed, 222 insertions(+), 105 deletions(-) mode change 100644 => 100755 R/helper.R mode change 100644 => 100755 R/metric_bright_dark_period.R mode change 100644 => 100755 R/metric_duration_above_threshold.R mode change 100644 => 100755 R/metric_interdaily_stability.R mode change 100644 => 100755 man/bright_dark_period.Rd mode change 100644 => 100755 man/interdaily_stability.Rd mode change 100644 => 100755 man/intradaily_variability.Rd mode change 100644 => 100755 man/timing_above_threshold.Rd diff --git a/R/helper.R b/R/helper.R old mode 100644 new mode 100755 index c9a824f..8314560 --- a/R/helper.R +++ b/R/helper.R @@ -110,7 +110,7 @@ pick.grouping.columns <- function(dataset) { } # Compare with threshold -threshold <- function(Light.vector, +compare_threshold <- function(Light.vector, threshold, comparison = c("above", "below"), na.replace = FALSE){ diff --git a/R/metric_bright_dark_period.R b/R/metric_bright_dark_period.R old mode 100644 new mode 100755 index 7009b68..76df0fc --- a/R/metric_bright_dark_period.R +++ b/R/metric_bright_dark_period.R @@ -7,7 +7,7 @@ #' (i.e., no gaps) for correct results. #' #' @param Light.vector Numeric vector containing the light data. -#' @param Datetime.vector Vector containing the time data. Can be POSIXct or numeric. +#' @param Time.vector Vector containing the time data. Can be HMS or POSIXct. #' @param period String indicating the type of period to look for. Can be either #' `"brightest"`(the default) or `"darkest"`. #' @param timespan The timespan across which to calculate. Can be either a @@ -27,12 +27,21 @@ #' #' @return A named list with the `mean`, `onset`, `midpoint`, and `offset` of the #' calculated brightest or darkest period, or if `as.df == TRUE` a data frame -#' with columns named `{period}_{timespan}_{metric}`. +#' with columns named `{period}_{timespan}_{metric}`. The output type corresponds +#' to the type of `Time.vector`, e.g., if `Time.vector` is HMS, the timing metrics +#' will be also HMS, and vice versa for POSIXct and numeric. #' #' @details Assumes regular 24h light data. Otherwise, results may not be #' meaningful. Looping the data is recommended for finding the darkest period. #' +#' @references +#' Hartmeyer, S.L., Andersen, M. (2023). Towards a framework for light-dosimetry studies: +#' Quantification metrics. \emph{Lighting Research & Technology}. +#' \url{https://doi.org/10.1177/14771535231170500} +#' #' @export +#' +#' @family metrics #' #' @examples # Dataset with light > 250lx between 06:00 and 18:00 @@ -42,17 +51,16 @@ #' Datetime = lubridate::as_datetime(0) + lubridate::hours(0:23), #' MEDI = c(rep(1, 6), rep(250, 13), rep(1, 5)) #' ) -#' +#' #' dataset1 %>% -#' dplyr::summarise(bright_dark_period(MEDI, Datetime, "brightest", "10 hours", -#' as.df = TRUE -#' )) +#' dplyr::reframe(bright_dark_period(MEDI, Datetime, "brightest", "10 hours", +#' as.df = TRUE)) #' dataset1 %>% -#' dplyr::summarise(bright_dark_period(MEDI, Datetime, "darkest", "5 hours", -#' loop = TRUE, as.df = TRUE -#' )) +#' dplyr::reframe(bright_dark_period(MEDI, Datetime, "darkest", "5 hours", +#' loop = TRUE, as.df = TRUE)) + bright_dark_period <- function(Light.vector, - Datetime.vector, + Time.vector, period = c("brightest", "darkest"), timespan = "10 hours", epoch = "dominant.epoch", @@ -65,7 +73,8 @@ bright_dark_period <- function(Light.vector, # Perform argument checks stopifnot( "`Light.vector` must be numeric!" = is.numeric(Light.vector), - "`Datetime.vector` must be POSIXct" = lubridate::is.POSIXct(Datetime.vector), + "`Time.vector` must be POSIXct or HMS" = lubridate::is.POSIXct(Time.vector) | + hms::is_hms(Time.vector), "`epoch` must either be a duration or a string" = lubridate::is.duration(epoch) | is.character(epoch), "`timespan` must either be a duration or a string" = @@ -75,25 +84,30 @@ bright_dark_period <- function(Light.vector, ) # Check whether time series is regularly spaced - if (length(unique(diff(Datetime.vector))) > 1) { - warning("`Datetime.vector` is not regularly spaced. Calculated results may be incorrect!") + if (length(unique(diff(Time.vector))) > 1) { + warning("`Time.vector` is not regularly spaced. Calculated results may be incorrect!") } # Get the epochs based on the data if (epoch == "dominant.epoch") { - epoch <- count.difftime(tibble::tibble(Datetime = Datetime.vector))$difftime[1] + epoch <- count.difftime(tibble::tibble(Datetime = Time.vector))$difftime[1] } # If the user specified an epoch, use that instead epoch <- lubridate::as.duration(epoch) # Convert timespan to seconds timespan <- lubridate::as.duration(timespan) + + # Check if timespan longer than Time.vector + time.total <- dplyr::last(Time.vector) - dplyr::first(Time.vector) + stopifnot("Timespan must be shorter than length of `Time.vector` interval!" = + timespan < time.total) # Loop data if (loop) { Light.vector <- c(Light.vector, Light.vector) - span <- dplyr::last(Datetime.vector) - Datetime.vector[1] - Datetime.vector <- c(Datetime.vector, Datetime.vector + span + epoch) + span <- dplyr::last(Time.vector) - Time.vector[1] + Time.vector <- c(Time.vector, Time.vector + span + epoch) } # Calculate window size @@ -103,10 +117,9 @@ bright_dark_period <- function(Light.vector, } # Calculate rolling means - means <- zoo::rollapply(Light.vector, window, mean, - na.rm = na.rm, - partial = FALSE, fill = NA - ) + means <- slider::slide_vec(Light.vector, .f = mean, na.rm = na.rm, + .before = window/2-1, .after = window/2, + .complete = TRUE) # Find maximum/minimum mean value center <- switch(period, @@ -117,16 +130,16 @@ bright_dark_period <- function(Light.vector, # Prepare output out <- list( "mean" = means[center], - "midpoint" = hms::as_hms(Datetime.vector[center]), - "onset" = hms::as_hms(Datetime.vector[center - (window / 2) + 1]), - "offset" = hms::as_hms(Datetime.vector[center + (window / 2)]) + "midpoint" = Time.vector[center], + "onset" = Time.vector[center - (window / 2 - 1)], + "offset" = Time.vector[center + (window / 2)] ) # Return as data frame or numeric matrix if (as.df) { ts <- paste0(as.numeric(timespan, unit = "hours"), "h") out <- tibble::as_tibble(out) %>% - dplyr::rename_with(~ paste(period, ts, .x, sep = "_")) + dplyr::rename_with(~paste(period, ts, .x, sep = "_")) } return(out) } diff --git a/R/metric_duration_above_threshold.R b/R/metric_duration_above_threshold.R old mode 100644 new mode 100755 index 939da40..6cb0132 --- a/R/metric_duration_above_threshold.R +++ b/R/metric_duration_above_threshold.R @@ -23,8 +23,15 @@ #' #' @return A duration object (see \code{\link[lubridate]{duration}}) as single value, #' or single column data frame. +#' +#' @references +#' Hartmeyer, S.L., Andersen, M. (2023). Towards a framework for light-dosimetry studies: +#' Quantification metrics. \emph{Lighting Research & Technology}. +#' \url{https://doi.org/10.1177/14771535231170500} #' #' @export +#' +#' @family metrics #' #' @examples #' N <- 50 @@ -43,14 +50,18 @@ #' MEDI = sample(c(sample(1:249, N / 2), sample(250:1000, N / 2))), #' ) #' dataset.combined <- rbind(dataset1, dataset2) -#' +#' #' dataset1 %>% -#' dplyr::summarise("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) -#' +#' dplyr::reframe("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) +#' +#' dataset1 %>% +#' dplyr::reframe(duration_above_threshold(MEDI, Datetime, threshold = 250, as.df = T)) +#' #' # Group by Id to account for different epochs #' dataset.combined %>% #' dplyr::group_by(Id) %>% -#' dplyr::summarise("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) +#' dplyr::reframe("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) +#' duration_above_threshold <- function(Light.vector, Time.vector, comparison = c("above", "below"), @@ -95,7 +106,7 @@ duration_above_threshold <- function(Light.vector, # Return data frame or numeric value if (as.df) { threshold <- stringr::str_flatten(sort(threshold), collapse = "-") - return(tibble::tibble("TAT_{threshold}" := tat)) + return(tibble::tibble("duration_{comparison}_{threshold}" := tat)) } else { return(tat) } diff --git a/R/metric_interdaily_stability.R b/R/metric_interdaily_stability.R old mode 100644 new mode 100755 index b5f9593..3dabd44 --- a/R/metric_interdaily_stability.R +++ b/R/metric_interdaily_stability.R @@ -2,7 +2,7 @@ #' #' This function calculates the variability of 24h light exposure patterns across #' multiple days. Calculated as the ratio of the variance of the average daily -#' pattern to the total variance across all days. Calculated for mean hourly +#' pattern to the total variance across all days. Calculated with mean hourly #' light levels. Ranges between 0 (Gaussian noise) and 1 (Perfect Stability). #' #' Note that this metric will always be 1 if the data contains only one 24 h day. @@ -14,13 +14,20 @@ #' to `FALSE`. #' #' @return Numeric value or dataframe with column 'IS'. +#' #' @export #' +#' @family metrics +#' #' @references Van Someren, E. J. W., Swaab, D. F., Colenda, C. C., Cohen, W., #' McCall, W. V., & Rosenquist, P. B. (1999). Bright Light Therapy: Improved #' Sensitivity to Its Effects on Rest-Activity Rhythms in Alzheimer Patients #' by Application of Nonparametric Methods. \emph{Chronobiology International}, #' 16(4), 505–518. \url{https://doi.org/10.3109/07420529908998724} +#' +#' Hartmeyer, S.L., Andersen, M. (2023). Towards a framework for light-dosimetry studies: +#' Quantification metrics. \emph{Lighting Research & Technology}. +#' \url{https://doi.org/10.1177/14771535231170500} #' #' @examples #' @@ -120,7 +127,7 @@ interdaily_stability <- function(Light.vector, # Return data frame or numeric vector if (as.df) { - return(tibble::tibble("IS" = is)) + return(tibble::tibble("interdaily_stability" = is)) } else { return(is) } diff --git a/R/metric_intradaily_variability.R b/R/metric_intradaily_variability.R index 5d20fce..efb4caa 100755 --- a/R/metric_intradaily_variability.R +++ b/R/metric_intradaily_variability.R @@ -2,7 +2,7 @@ #' #' This function calculates the variability of consecutive Light levels within #' a 24h day. Calculated as the ratio of the variance of the differences between -#' consecutive Light levels to the total variance across the day. Calculated for +#' consecutive Light levels to the total variance across the day. Calculated with #' mean hourly Light levels. Higher values indicate more fragmentation. #' #' @param Light.vector Numeric vector containing the light data. @@ -12,13 +12,20 @@ #' to `FALSE`. #' #' @return Numeric value or dataframe with column 'IV'. +#' #' @export #' +#' @family metrics +#' #' @references Van Someren, E. J. W., Swaab, D. F., Colenda, C. C., Cohen, W., #' McCall, W. V., & Rosenquist, P. B. (1999). Bright Light Therapy: Improved #' Sensitivity to Its Effects on Rest-Activity Rhythms in Alzheimer Patients #' by Application of Nonparametric Methods. \emph{Chronobiology International}, #' 16(4), 505–518. \url{https://doi.org/10.3109/07420529908998724} +#' +#' Hartmeyer, S.L., Andersen, M. (2023). Towards a framework for light-dosimetry studies: +#' Quantification metrics. \emph{Lighting Research & Technology}. +#' \url{https://doi.org/10.1177/14771535231170500} #' #' @examples #' @@ -117,7 +124,7 @@ intradaily_variability <- function(Light.vector, # Return data frame or numeric vector if (as.df) { - return(tibble::tibble("IV" = iv)) + return(tibble::tibble("intradaily_variability" = iv)) } else { return(iv) } diff --git a/R/metric_timing_above_threshold.R b/R/metric_timing_above_threshold.R index 004a5b2..e2d5040 100755 --- a/R/metric_timing_above_threshold.R +++ b/R/metric_timing_above_threshold.R @@ -1,12 +1,11 @@ #' Mean/first/last timing above/below threshold. #' -#' This function calculates the mean/first/last timepoint where light levels are -#' above or below a given threshold intensity within the given interval. +#' This function calculates the mean, first, and last timepoint (MLiT, FLiT, LLiT) +#' where light levels are above or below a given threshold intensity within the given +#' time interval. #' #' @param Light.vector Numeric vector containing the light data. #' @param Time.vector Vector containing the time data. Can be numeric, HMS or POSIXct. -#' @param metric String indicating which timing metrics to calculate. Possible values -#' are `"mean"` (default), `"first"`, and `"last"` timing above threshold. #' @param comparison String specifying whether the time above or below threshold #' should be calculated. Can be either `"above"` (the default) or `"below"`. If #' two values are provided for `threshold`, this argument will be ignored. @@ -17,19 +16,27 @@ #' @param na.rm Logical. Should missing values be removed for the calculation? #' Defaults to `FALSE`. #' @param as.df Logical. Should a data frame with be returned? If `TRUE`, a data -#' frame with a single column named `{metric}_{threshold}` will be returned. -#' Defaults to `FALSE`. +#' frame with three columns (MLiT, FLiT, LLiT) and the threshold (e.g., `MLiT_{threshold}`) +#' will be returned. Defaults to `FALSE`. +#' +#' @return List or dataframe with the three values: `mean`, `first`, and `last` timing +#' above threshold. The output type corresponds to the type of `Time.vector`, +#' e.g., if `Time.vector` is HMS, the timing metrics will be also +#' HMS, and vice versa for POSIXct and numeric. #' -#' @return Single value or single column dataframe. If `Time.vector` is of type -#' HMS or POSIXct a HMS object (see \code{\link[hms]{hms}}) will be returned, -#' otherwise a numeric object. +#' @export +#' +#' @family metrics #' -#' @references Reid, K. J., Santostasi, G., Baron, K. G., Wilson, J., Kang, J., -#' & Zee, P. C. (2014). Timing and Intensity of Light Correlate with Body Weight +#' @references +#' Reid, K. J., Santostasi, G., Baron, K. G., Wilson, J., Kang, J., +#' & Zee, P. C. (2014). Timing and Intensity of Light Correlate with Body Weight #' in Adults. \emph{PLOS ONE}, 9(4), e92251. #' \url{https://doi.org/10.1371/journal.pone.0092251} -#' -#' @export +#' +#' Hartmeyer, S.L., Andersen, M. (2023). Towards a framework for light-dosimetry studies: +#' Quantification metrics. \emph{Lighting Research & Technology}. +#' \url{https://doi.org/10.1177/14771535231170500} #' #' @examples #' # Dataset with light > 250lx between 06:00 and 18:00 @@ -39,25 +46,26 @@ #' Datetime = lubridate::as_datetime(0) + lubridate::hours(0:23), #' MEDI = c(rep(1, 6), rep(250, 13), rep(1, 5)) #' ) -#' +#' +#' # Above threshold #' dataset1 %>% -#' dplyr::summarise(timing_above_threshold(MEDI, Datetime, "mean", "above", 250)) -#' +#' dplyr::reframe(timing_above_threshold(MEDI, Datetime, "above", 250, as.df = TRUE)) +#' +#' # Below threshold #' dataset1 %>% -#' dplyr::summarise(timing_above_threshold(MEDI, Datetime, "first", "above", 250)) -#' +#' dplyr::reframe(timing_above_threshold(MEDI, Datetime, "below", 10, as.df = TRUE)) +#' +#' # Input = HMS -> Output = HMS #' dataset1 %>% -#' dplyr::summarise(timing_above_threshold(MEDI, Datetime, "last", "above", 250)) -#' +#' dplyr::reframe(timing_above_threshold(MEDI, hms::as_hms(Datetime), "above", 250, as.df = TRUE)) +#' timing_above_threshold <- function(Light.vector, Time.vector, - metric = c("mean", "first", "last"), comparison = c("above", "below"), threshold, na.rm = FALSE, as.df = FALSE) { # Match arguments - metric <- match.arg(metric) comparison <- match.arg(comparison) # Perform argument checks @@ -71,34 +79,33 @@ timing_above_threshold <- function(Light.vector, "`as.df` must be logical!" = is.logical(as.df) ) - # Convert to HMS - if (hms::is_hms(Time.vector) | lubridate::is.POSIXct(Time.vector)) { - Time.vector <- Time.vector %>% hms::as_hms() - } - # Calculate timing metric t <- Time.vector[compare_threshold(Light.vector, threshold, comparison, na.rm)] - xlit <- switch(metric, - "mean" = t %>% as.numeric() %>% mean() %>% round(), - "first" = t %>% dplyr::first(), - "last" = t %>% dplyr::last() - ) - + mlit = t %>% as.numeric() %>% mean() %>% round() + flit = t %>% dplyr::first() + llit = t %>% dplyr::last() + # Convert to HMS - if (hms::is_hms(Time.vector) | lubridate::is.POSIXct(Time.vector)) { - xlit <- xlit %>% hms::as_hms() + if(hms::is_hms(Time.vector)) { + mlit <- mlit %>% hms::as_hms() } + if(lubridate::is.POSIXct(Time.vector)){ + mlit <- mlit %>% + lubridate::as_datetime(tz = lubridate::tz(Time.vector)) + } + + # Prepare output + out <- list( + "mean" = mlit, + "first" = flit, + "last" = llit + ) - # Return data frame or numeric value + # Return data frame or list if (as.df) { - name <- switch(metric, - "mean" = "MLiT", - "first" = "FLiT", - "last" = "LLiT" - ) threshold <- stringr::str_flatten(sort(threshold), collapse = "-") - return(tibble::tibble("{name}_{threshold}" = xlit)) - } else { - return(xlit) + out <- tibble::as_tibble(out) %>% + dplyr::rename_with(~paste(.x, "timing", comparison, threshold, sep = "_")) } + return(out) } diff --git a/man/bright_dark_period.Rd b/man/bright_dark_period.Rd old mode 100644 new mode 100755 index 801c1bc..d62677a --- a/man/bright_dark_period.Rd +++ b/man/bright_dark_period.Rd @@ -6,7 +6,7 @@ \usage{ bright_dark_period( Light.vector, - Datetime.vector, + Time.vector, period = c("brightest", "darkest"), timespan = "10 hours", epoch = "dominant.epoch", @@ -18,7 +18,7 @@ bright_dark_period( \arguments{ \item{Light.vector}{Numeric vector containing the light data.} -\item{Datetime.vector}{Vector containing the time data. Can be POSIXct or numeric.} +\item{Time.vector}{Vector containing the time data. Can be HMS or POSIXct.} \item{period}{String indicating the type of period to look for. Can be either \code{"brightest"}(the default) or \code{"darkest"}.} @@ -45,7 +45,9 @@ to \code{TRUE}.} \value{ A named list with the \code{mean}, \code{onset}, \code{midpoint}, and \code{offset} of the calculated brightest or darkest period, or if \code{as.df == TRUE} a data frame -with columns named \verb{\{period\}_\{timespan\}_\{metric\}}. +with columns named \verb{\{period\}_\{timespan\}_\{metric\}}. The output type corresponds +to the type of \code{Time.vector}, e.g., if \code{Time.vector} is HMS, the timing metrics +will be also HMS, and vice versa for POSIXct and numeric. } \description{ This function finds the brightest or darkest continuous period of a given @@ -67,11 +69,23 @@ dataset1 <- ) dataset1 \%>\% - dplyr::summarise(bright_dark_period(MEDI, Datetime, "brightest", "10 hours", - as.df = TRUE - )) + dplyr::reframe(bright_dark_period(MEDI, Datetime, "brightest", "10 hours", + as.df = TRUE)) dataset1 \%>\% - dplyr::summarise(bright_dark_period(MEDI, Datetime, "darkest", "5 hours", - loop = TRUE, as.df = TRUE - )) + dplyr::reframe(bright_dark_period(MEDI, Datetime, "darkest", "5 hours", + loop = TRUE, as.df = TRUE)) } +\references{ +Hartmeyer, S.L., Andersen, M. (2023). Towards a framework for light-dosimetry studies: +Quantification metrics. \emph{Lighting Research & Technology}. +\url{https://doi.org/10.1177/14771535231170500} +} +\seealso{ +Other metrics: +\code{\link{centroidLE}()}, +\code{\link{duration_above_threshold}()}, +\code{\link{interdaily_stability}()}, +\code{\link{intradaily_variability}()}, +\code{\link{timing_above_threshold}()} +} +\concept{metrics} diff --git a/man/duration_above_threshold.Rd b/man/duration_above_threshold.Rd index e5d932c..44ecebc 100644 --- a/man/duration_above_threshold.Rd +++ b/man/duration_above_threshold.Rd @@ -66,10 +66,28 @@ dataset2 <- dataset.combined <- rbind(dataset1, dataset2) dataset1 \%>\% - dplyr::summarise("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) + dplyr::reframe("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) + +dataset1 \%>\% + dplyr::reframe(duration_above_threshold(MEDI, Datetime, threshold = 250, as.df = T)) # Group by Id to account for different epochs dataset.combined \%>\% dplyr::group_by(Id) \%>\% - dplyr::summarise("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) + dplyr::reframe("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) + +} +\references{ +Hartmeyer, S.L., Andersen, M. (2023). Towards a framework for light-dosimetry studies: +Quantification metrics. \emph{Lighting Research & Technology}. +\url{https://doi.org/10.1177/14771535231170500} +} +\seealso{ +Other metrics: +\code{\link{bright_dark_period}()}, +\code{\link{centroidLE}()}, +\code{\link{interdaily_stability}()}, +\code{\link{intradaily_variability}()}, +\code{\link{timing_above_threshold}()} } +\concept{metrics} diff --git a/man/interdaily_stability.Rd b/man/interdaily_stability.Rd old mode 100644 new mode 100755 index e9f4c6c..7565b0a --- a/man/interdaily_stability.Rd +++ b/man/interdaily_stability.Rd @@ -27,7 +27,7 @@ Numeric value or dataframe with column 'IS'. \description{ This function calculates the variability of 24h light exposure patterns across multiple days. Calculated as the ratio of the variance of the average daily -pattern to the total variance across all days. Calculated for mean hourly +pattern to the total variance across all days. Calculated with mean hourly light levels. Ranges between 0 (Gaussian noise) and 1 (Perfect Stability). } \details{ @@ -56,4 +56,17 @@ McCall, W. V., & Rosenquist, P. B. (1999). Bright Light Therapy: Improved Sensitivity to Its Effects on Rest-Activity Rhythms in Alzheimer Patients by Application of Nonparametric Methods. \emph{Chronobiology International}, 16(4), 505–518. \url{https://doi.org/10.3109/07420529908998724} + +Hartmeyer, S.L., Andersen, M. (2023). Towards a framework for light-dosimetry studies: +Quantification metrics. \emph{Lighting Research & Technology}. +\url{https://doi.org/10.1177/14771535231170500} +} +\seealso{ +Other metrics: +\code{\link{bright_dark_period}()}, +\code{\link{centroidLE}()}, +\code{\link{duration_above_threshold}()}, +\code{\link{intradaily_variability}()}, +\code{\link{timing_above_threshold}()} } +\concept{metrics} diff --git a/man/intradaily_variability.Rd b/man/intradaily_variability.Rd old mode 100644 new mode 100755 index 7679056..68eaa07 --- a/man/intradaily_variability.Rd +++ b/man/intradaily_variability.Rd @@ -27,7 +27,7 @@ Numeric value or dataframe with column 'IV'. \description{ This function calculates the variability of consecutive Light levels within a 24h day. Calculated as the ratio of the variance of the differences between -consecutive Light levels to the total variance across the day. Calculated for +consecutive Light levels to the total variance across the day. Calculated with mean hourly Light levels. Higher values indicate more fragmentation. } \examples{ @@ -53,4 +53,17 @@ McCall, W. V., & Rosenquist, P. B. (1999). Bright Light Therapy: Improved Sensitivity to Its Effects on Rest-Activity Rhythms in Alzheimer Patients by Application of Nonparametric Methods. \emph{Chronobiology International}, 16(4), 505–518. \url{https://doi.org/10.3109/07420529908998724} + +Hartmeyer, S.L., Andersen, M. (2023). Towards a framework for light-dosimetry studies: +Quantification metrics. \emph{Lighting Research & Technology}. +\url{https://doi.org/10.1177/14771535231170500} +} +\seealso{ +Other metrics: +\code{\link{bright_dark_period}()}, +\code{\link{centroidLE}()}, +\code{\link{duration_above_threshold}()}, +\code{\link{interdaily_stability}()}, +\code{\link{timing_above_threshold}()} } +\concept{metrics} diff --git a/man/timing_above_threshold.Rd b/man/timing_above_threshold.Rd old mode 100644 new mode 100755 index 5105b28..5a99b1e --- a/man/timing_above_threshold.Rd +++ b/man/timing_above_threshold.Rd @@ -7,7 +7,6 @@ timing_above_threshold( Light.vector, Time.vector, - metric = c("mean", "first", "last"), comparison = c("above", "below"), threshold, na.rm = FALSE, @@ -19,9 +18,6 @@ timing_above_threshold( \item{Time.vector}{Vector containing the time data. Can be numeric, HMS or POSIXct.} -\item{metric}{String indicating which timing metrics to calculate. Possible values -are \code{"mean"} (default), \code{"first"}, and \code{"last"} timing above threshold.} - \item{comparison}{String specifying whether the time above or below threshold should be calculated. Can be either \code{"above"} (the default) or \code{"below"}. If two values are provided for \code{threshold}, this argument will be ignored.} @@ -35,17 +31,19 @@ calculated.} Defaults to \code{FALSE}.} \item{as.df}{Logical. Should a data frame with be returned? If \code{TRUE}, a data -frame with a single column named \verb{\{metric\}_\{threshold\}} will be returned. -Defaults to \code{FALSE}.} +frame with three columns (MLiT, FLiT, LLiT) and the threshold (e.g., \verb{MLiT_\{threshold\}}) +will be returned. Defaults to \code{FALSE}.} } \value{ -Single value or single column dataframe. If \code{Time.vector} is of type -HMS or POSIXct a HMS object (see \code{\link[hms]{hms}}) will be returned, -otherwise a numeric object. +List or dataframe with the three values: \code{mean}, \code{first}, and \code{last} timing +above threshold. The output type corresponds to the type of \code{Time.vector}, +e.g., if \code{Time.vector} is HMS, the timing metrics will be also +HMS, and vice versa for POSIXct and numeric. } \description{ -This function calculates the mean/first/last timepoint where light levels are -above or below a given threshold intensity within the given interval. +This function calculates the mean, first, and last timepoint (MLiT, FLiT, LLiT) +where light levels are above or below a given threshold intensity within the given +time interval. } \examples{ # Dataset with light > 250lx between 06:00 and 18:00 @@ -56,14 +54,17 @@ dataset1 <- MEDI = c(rep(1, 6), rep(250, 13), rep(1, 5)) ) +# Above threshold dataset1 \%>\% - dplyr::summarise(timing_above_threshold(MEDI, Datetime, "mean", "above", 250)) + dplyr::reframe(timing_above_threshold(MEDI, Datetime, "above", 250, as.df = TRUE)) +# Below threshold dataset1 \%>\% - dplyr::summarise(timing_above_threshold(MEDI, Datetime, "first", "above", 250)) + dplyr::reframe(timing_above_threshold(MEDI, Datetime, "below", 10, as.df = TRUE)) +# Input = HMS -> Output = HMS dataset1 \%>\% - dplyr::summarise(timing_above_threshold(MEDI, Datetime, "last", "above", 250)) + dplyr::reframe(timing_above_threshold(MEDI, hms::as_hms(Datetime), "above", 250, as.df = TRUE)) } \references{ @@ -71,4 +72,17 @@ Reid, K. J., Santostasi, G., Baron, K. G., Wilson, J., Kang, J., & Zee, P. C. (2014). Timing and Intensity of Light Correlate with Body Weight in Adults. \emph{PLOS ONE}, 9(4), e92251. \url{https://doi.org/10.1371/journal.pone.0092251} + +Hartmeyer, S.L., Andersen, M. (2023). Towards a framework for light-dosimetry studies: +Quantification metrics. \emph{Lighting Research & Technology}. +\url{https://doi.org/10.1177/14771535231170500} +} +\seealso{ +Other metrics: +\code{\link{bright_dark_period}()}, +\code{\link{centroidLE}()}, +\code{\link{duration_above_threshold}()}, +\code{\link{interdaily_stability}()}, +\code{\link{intradaily_variability}()} } +\concept{metrics} From 97a769595d770f32945ee1e05d4933bce675cdcd Mon Sep 17 00:00:00 2001 From: steffenhartmeyer Date: Wed, 10 Jan 2024 15:26:32 +0100 Subject: [PATCH 4/6] Resolved errors and warnings --- DESCRIPTION | 1 + NAMESPACE | 5 +++-- R/metric_bright_dark_period.R | 2 +- R/metric_duration_above_threshold.R | 2 +- R/metric_interdaily_stability.R | 6 +++--- R/metric_intradaily_variability.R | 6 +++--- man/LightLogR-package.Rd | 1 + man/bright_dark_period.Rd | 1 - man/duration_above_threshold.Rd | 1 - man/import_Dataset.Rd | 13 +++++++------ man/interdaily_stability.Rd | 1 - man/intradaily_variability.Rd | 1 - man/timing_above_threshold.Rd | 1 - 13 files changed, 20 insertions(+), 21 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 440d2fe..b235843 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -47,6 +47,7 @@ Imports: rsconnect, scales, shiny, + slider, stats, stringr, tibble, diff --git a/NAMESPACE b/NAMESPACE index c958614..111f715 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -8,6 +8,7 @@ export(Datetime_breaks) export(Datetime_limits) export(aggregate_Datetime) export(bright_dark_period) +export(centroidLE) export(count_difftime) export(create_Timedata) export(cut_Datetime) @@ -24,12 +25,12 @@ export(gapless_Datetimes) export(gg_day) export(gg_days) export(gg_overview) -export(interdaily_stability) -export(intradaily_variability) export(import) export(import_Dataset) export(import_Statechanges) +export(interdaily_stability) export(interval2state) +export(intradaily_variability) export(join_datasets) export(sc2interval) export(sleep_int2Brown) diff --git a/R/metric_bright_dark_period.R b/R/metric_bright_dark_period.R index 76df0fc..5b71821 100755 --- a/R/metric_bright_dark_period.R +++ b/R/metric_bright_dark_period.R @@ -90,7 +90,7 @@ bright_dark_period <- function(Light.vector, # Get the epochs based on the data if (epoch == "dominant.epoch") { - epoch <- count.difftime(tibble::tibble(Datetime = Time.vector))$difftime[1] + epoch <- count_difftime(tibble::tibble(Datetime = Time.vector))$difftime[1] } # If the user specified an epoch, use that instead epoch <- lubridate::as.duration(epoch) diff --git a/R/metric_duration_above_threshold.R b/R/metric_duration_above_threshold.R index 6cb0132..7d9411d 100755 --- a/R/metric_duration_above_threshold.R +++ b/R/metric_duration_above_threshold.R @@ -87,7 +87,7 @@ duration_above_threshold <- function(Light.vector, # Get the epochs based on the data if (epoch == "dominant.epoch") { - epoch <- count.difftime(tibble::tibble(Datetime = Time.vector))$difftime[1] + epoch <- count_difftime(tibble::tibble(Datetime = Time.vector))$difftime[1] epoch <- ifelse(hms::is_hms(Time.vector) | lubridate::is.POSIXct(Time.vector), lubridate::as.duration(epoch), epoch ) diff --git a/R/metric_interdaily_stability.R b/R/metric_interdaily_stability.R index 3dabd44..512a2ec 100755 --- a/R/metric_interdaily_stability.R +++ b/R/metric_interdaily_stability.R @@ -81,7 +81,7 @@ interdaily_stability <- function(Light.vector, "Interdaily stability might not be meaningful for non-24 h days.", "These days contain less than 24 h:", paste( - capture.output(print( + utils::capture.output(print( dplyr::filter(N_hours, N < 24) %>% dplyr::pull(Day) )), sep = "\n", collapse = "\n" @@ -97,7 +97,7 @@ interdaily_stability <- function(Light.vector, "Data contains some hours with only missing values", "These hours contain only missing values: ", paste( - capture.output(print( + utils::capture.output(print( dplyr::filter(hours_per_day, is_missing) %>% dplyr::pull(Hour) )), sep = "\n", collapse = "\n" @@ -123,7 +123,7 @@ interdaily_stability <- function(Light.vector, dplyr::summarise(Light = mean(Light)) # Variance across average day / variance across all days - is <- var(avg_hourly$Light) / var(total_hourly$Light) + is <- stats::var(avg_hourly$Light) / stats::var(total_hourly$Light) # Return data frame or numeric vector if (as.df) { diff --git a/R/metric_intradaily_variability.R b/R/metric_intradaily_variability.R index efb4caa..9b087b2 100755 --- a/R/metric_intradaily_variability.R +++ b/R/metric_intradaily_variability.R @@ -79,7 +79,7 @@ intradaily_variability <- function(Light.vector, "Intradaily variability might not be meaningful for non-24 h days.", "These days contain less than 24 h:", paste( - capture.output(print( + utils::capture.output(print( dplyr::filter(N_hours, N < 24) %>% dplyr::pull(Day) )), sep = "\n", collapse = "\n" @@ -95,7 +95,7 @@ intradaily_variability <- function(Light.vector, "Data contains some hours with only missing values", "These hours contain only missing values: ", paste( - capture.output(print( + utils::capture.output(print( dplyr::filter(hours_per_day, is_missing) %>% dplyr::pull(Hour) )), sep = "\n", collapse = "\n" @@ -120,7 +120,7 @@ intradaily_variability <- function(Light.vector, sum(diff(total_hourly$Light)^2) / (length(total_hourly$Light) - 1) # Variance of consecutive differences / variance across all days - iv <- var_hourly_diff / var(total_hourly$Light) + iv <- var_hourly_diff / stats::var(total_hourly$Light) # Return data frame or numeric vector if (as.df) { diff --git a/man/LightLogR-package.Rd b/man/LightLogR-package.Rd index 395b941..2b35672 100644 --- a/man/LightLogR-package.Rd +++ b/man/LightLogR-package.Rd @@ -30,6 +30,7 @@ Authors: Other contributors: \itemize{ + \item MeLiDos [funder] \item EURAMET (European Association of National Metrology Institutes. Website: www.euramet.org. Grant Number: 22NRM05 MeLiDos. Grant Statement: The project (22NRM05 MeLiDos) has received funding from the European Partnership on Metrology, co-financed from the European Union’s Horizon Europe Research and Innovation Programme and by the Participating States.) [funder] \item European Union (Co-funded by the European Union. Views and opinions expressed are however those of the author(s) only and do not necessarily reflect those of the European Union or EURAMET. Neither the European Union nor the granting authority can be held responsible for them.) [funder] \item TSCN-Lab (www.tscnlab.org) [copyright holder] diff --git a/man/bright_dark_period.Rd b/man/bright_dark_period.Rd index d62677a..ec58054 100755 --- a/man/bright_dark_period.Rd +++ b/man/bright_dark_period.Rd @@ -82,7 +82,6 @@ Quantification metrics. \emph{Lighting Research & Technology}. } \seealso{ Other metrics: -\code{\link{centroidLE}()}, \code{\link{duration_above_threshold}()}, \code{\link{interdaily_stability}()}, \code{\link{intradaily_variability}()}, diff --git a/man/duration_above_threshold.Rd b/man/duration_above_threshold.Rd index 44ecebc..70dcb38 100644 --- a/man/duration_above_threshold.Rd +++ b/man/duration_above_threshold.Rd @@ -85,7 +85,6 @@ Quantification metrics. \emph{Lighting Research & Technology}. \seealso{ Other metrics: \code{\link{bright_dark_period}()}, -\code{\link{centroidLE}()}, \code{\link{interdaily_stability}()}, \code{\link{intradaily_variability}()}, \code{\link{timing_above_threshold}()} diff --git a/man/import_Dataset.Rd b/man/import_Dataset.Rd index 0fec504..87f5ab5 100644 --- a/man/import_Dataset.Rd +++ b/man/import_Dataset.Rd @@ -6,7 +6,7 @@ \alias{import} \title{Import a light logger dataset or related data} \format{ -An object of class \code{list} of length 6. +An object of class \code{list} of length 7. } \usage{ import_Dataset(device, ...) @@ -75,7 +75,8 @@ is maintained. \if{html}{\out{
}}\preformatted{supported.devices #> [1] "Actiwatch_Spectrum" "ActLumus" "DeLux" -#> [4] "LiDo" "LYS" "Speccy" +#> [4] "LiDo" "LYS" "Speccy" +#> [7] "SpectraWear" }\if{html}{\out{
}} \subsection{ActLumus}{ @@ -112,7 +113,7 @@ such as the intervals between measurements or the start and end dates. dataset <- import_Dataset("LYS", filepath) #> Successfully read in 11422 observations from LYS-file #> Timezone set is UTC. -#> The system timezone is Europe/Berlin. Please correct if necessary! +#> The system timezone is Europe/Zurich. Please correct if necessary! #> Start: 2023-06-21 00:00:12 #> End: 2023-06-22 23:59:48 #> Timespan: 2 days @@ -130,7 +131,7 @@ Import functions can also be called directly: dataset <- import$ActLumus(filepath) #> Successfully read in 61016 observations from ActLumus-file #> Timezone set is UTC. -#> The system timezone is Europe/Berlin. Please correct if necessary! +#> The system timezone is Europe/Zurich. Please correct if necessary! #> Start: 2023-08-28 08:47:54 #> End: 2023-09-04 10:17:04 #> Timespan: 7.1 days @@ -145,7 +146,7 @@ dplyr::slice(1500:1505) \%>\% flextable::flextable() \%>\% flextable::autofit() }\if{html}{\out{}}\if{html}{\out{ -
}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}Datetime\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}TEMPERATURE\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}LIGHT\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}MEDI\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}Id\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:57:44\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}211.74\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}202.08\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:57:54\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}208.03\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}198.66\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:04\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}204.85\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}195.55\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:14\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.81\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}203.59\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}194.36\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:24\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}203.44\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}194.42\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:34\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.81\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}204.31\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}195.30\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{
}} +}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}Datetime\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}TEMPERATURE\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}LIGHT\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}MEDI\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}Id\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:57:44\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}211.74\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}202.08\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:57:54\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}208.03\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}198.66\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:04\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}204.85\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}195.55\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:14\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.81\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}203.59\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}194.36\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:24\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}203.44\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}194.42\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:34\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.81\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}204.31\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}195.30\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{}} } } diff --git a/man/interdaily_stability.Rd b/man/interdaily_stability.Rd index 7565b0a..d8801d2 100755 --- a/man/interdaily_stability.Rd +++ b/man/interdaily_stability.Rd @@ -64,7 +64,6 @@ Quantification metrics. \emph{Lighting Research & Technology}. \seealso{ Other metrics: \code{\link{bright_dark_period}()}, -\code{\link{centroidLE}()}, \code{\link{duration_above_threshold}()}, \code{\link{intradaily_variability}()}, \code{\link{timing_above_threshold}()} diff --git a/man/intradaily_variability.Rd b/man/intradaily_variability.Rd index 68eaa07..ceae379 100755 --- a/man/intradaily_variability.Rd +++ b/man/intradaily_variability.Rd @@ -61,7 +61,6 @@ Quantification metrics. \emph{Lighting Research & Technology}. \seealso{ Other metrics: \code{\link{bright_dark_period}()}, -\code{\link{centroidLE}()}, \code{\link{duration_above_threshold}()}, \code{\link{interdaily_stability}()}, \code{\link{timing_above_threshold}()} diff --git a/man/timing_above_threshold.Rd b/man/timing_above_threshold.Rd index 5a99b1e..bcd504f 100755 --- a/man/timing_above_threshold.Rd +++ b/man/timing_above_threshold.Rd @@ -80,7 +80,6 @@ Quantification metrics. \emph{Lighting Research & Technology}. \seealso{ Other metrics: \code{\link{bright_dark_period}()}, -\code{\link{centroidLE}()}, \code{\link{duration_above_threshold}()}, \code{\link{interdaily_stability}()}, \code{\link{intradaily_variability}()} From 6b444a06952e7a36b768b6daa5ccd58304d9dfa8 Mon Sep 17 00:00:00 2001 From: steffenhartmeyer Date: Wed, 10 Jan 2024 15:33:37 +0100 Subject: [PATCH 5/6] Resolved error --- NAMESPACE | 1 - 1 file changed, 1 deletion(-) diff --git a/NAMESPACE b/NAMESPACE index 111f715..0902555 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -8,7 +8,6 @@ export(Datetime_breaks) export(Datetime_limits) export(aggregate_Datetime) export(bright_dark_period) -export(centroidLE) export(count_difftime) export(create_Timedata) export(cut_Datetime) From cabbfdf60daf6b3eeea34aa0c3f1119a33db3307 Mon Sep 17 00:00:00 2001 From: steffenhartmeyer Date: Wed, 10 Jan 2024 15:51:05 +0100 Subject: [PATCH 6/6] Final resolve --- R/metric_duration_above_threshold.R | 2 +- R/metric_interdaily_stability.R | 2 +- R/metric_intradaily_variability.R | 2 +- _pkgdown.yml | 10 ++++++++++ man/duration_above_threshold.Rd | 2 +- man/import_Dataset.Rd | 4 ++-- 6 files changed, 16 insertions(+), 6 deletions(-) diff --git a/R/metric_duration_above_threshold.R b/R/metric_duration_above_threshold.R index 7d9411d..e447ffd 100755 --- a/R/metric_duration_above_threshold.R +++ b/R/metric_duration_above_threshold.R @@ -55,7 +55,7 @@ #' dplyr::reframe("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) #' #' dataset1 %>% -#' dplyr::reframe(duration_above_threshold(MEDI, Datetime, threshold = 250, as.df = T)) +#' dplyr::reframe(duration_above_threshold(MEDI, Datetime, threshold = 250, as.df = TRUE)) #' #' # Group by Id to account for different epochs #' dataset.combined %>% diff --git a/R/metric_interdaily_stability.R b/R/metric_interdaily_stability.R index 512a2ec..b9965b8 100755 --- a/R/metric_interdaily_stability.R +++ b/R/metric_interdaily_stability.R @@ -71,7 +71,7 @@ interdaily_stability <- function(Light.vector, N_hours <- hours_per_day %>% dplyr::group_by(Day) %>% - dplyr::summarise(N = n()) %>% + dplyr::summarise(N = dplyr::n()) %>% dplyr::select(Day, N) # Warning if days are not full 24h diff --git a/R/metric_intradaily_variability.R b/R/metric_intradaily_variability.R index 9b087b2..ef7dd79 100755 --- a/R/metric_intradaily_variability.R +++ b/R/metric_intradaily_variability.R @@ -69,7 +69,7 @@ intradaily_variability <- function(Light.vector, N_hours <- hours_per_day %>% dplyr::group_by(Day) %>% - dplyr::summarise(N = n()) %>% + dplyr::summarise(N = dplyr::n()) %>% dplyr::select(Day, N) # Warning if days are not full 24h diff --git a/_pkgdown.yml b/_pkgdown.yml index 4d6b03b..87e4aaf 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -63,6 +63,16 @@ reference: - gg_overview - gg_day - gg_days + + - title: Metrics + desc: > + This section includes functions to calculate light exposure metrics . + contents: + - bright_dark_period + - duration_above_threshold + - intradaily_variability + - interdaily_stability + - timing_above_threshold - title: Helpers desc: > diff --git a/man/duration_above_threshold.Rd b/man/duration_above_threshold.Rd index 70dcb38..7eb9be9 100644 --- a/man/duration_above_threshold.Rd +++ b/man/duration_above_threshold.Rd @@ -69,7 +69,7 @@ dataset1 \%>\% dplyr::reframe("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) dataset1 \%>\% - dplyr::reframe(duration_above_threshold(MEDI, Datetime, threshold = 250, as.df = T)) + dplyr::reframe(duration_above_threshold(MEDI, Datetime, threshold = 250, as.df = TRUE)) # Group by Id to account for different epochs dataset.combined \%>\% diff --git a/man/import_Dataset.Rd b/man/import_Dataset.Rd index 87f5ab5..64eb033 100644 --- a/man/import_Dataset.Rd +++ b/man/import_Dataset.Rd @@ -146,7 +146,7 @@ dplyr::slice(1500:1505) \%>\% flextable::flextable() \%>\% flextable::autofit() }\if{html}{\out{}}\if{html}{\out{ -
}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}Datetime\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}TEMPERATURE\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}LIGHT\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}MEDI\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}Id\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:57:44\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}211.74\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}202.08\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:57:54\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}208.03\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}198.66\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:04\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}204.85\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}195.55\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:14\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.81\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}203.59\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}194.36\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:24\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}203.44\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}194.42\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:34\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.81\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}204.31\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}195.30\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{
}} +}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}Datetime\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}TEMPERATURE\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}LIGHT\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}MEDI\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}Id\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:57:44\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}211.74\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}202.08\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:57:54\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}208.03\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}198.66\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:04\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}204.85\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}195.55\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:14\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.81\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}203.59\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}194.36\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:24\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.88\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}203.44\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}194.42\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}2023-08-28 12:58:34\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}26.81\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}204.31\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}195.30\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{

}}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{

}}\if{html}{\out{
}}\if{html}{\out{}} } }