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/DESCRIPTION b/DESCRIPTION index 8b05267..b235843 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -8,6 +8,10 @@ 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", comment = "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."), person("European Union", role = "fnd", comment = "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."), person("TSCN-Lab", comment = c(URL = "www.tscnlab.org"), role = "cph")) @@ -43,6 +47,7 @@ Imports: rsconnect, scales, shiny, + slider, stats, stringr, tibble, diff --git a/NAMESPACE b/NAMESPACE index b74a2d2..0902555 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -7,11 +7,13 @@ export(Brown_rec) export(Datetime_breaks) export(Datetime_limits) export(aggregate_Datetime) +export(bright_dark_period) export(count_difftime) export(create_Timedata) export(cut_Datetime) export(data2reference) export(dominant_epoch) +export(duration_above_threshold) export(filter_Date) export(filter_Datetime) export(filter_Datetime_multiple) @@ -25,10 +27,13 @@ export(gg_overview) export(import) export(import_Dataset) 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 old mode 100644 new mode 100755 index a40a0af..a299b76 --- a/R/helper.R +++ b/R/helper.R @@ -86,3 +86,35 @@ pick.grouping.columns <- function(dataset) { dplyr::group_vars(dataset) ) } + +# Compare with threshold +compare_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) +} diff --git a/R/metric_bright_dark_period.R b/R/metric_bright_dark_period.R new file mode 100755 index 0000000..5b71821 --- /dev/null +++ b/R/metric_bright_dark_period.R @@ -0,0 +1,145 @@ +#' Brightest or darkest continuous period +#' +#' This function finds the brightest or darkest continuous period of a given +#' 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 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 +#' `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? 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 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}`. 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 +#' 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::reframe(bright_dark_period(MEDI, Datetime, "brightest", "10 hours", +#' as.df = TRUE)) +#' dataset1 %>% +#' dplyr::reframe(bright_dark_period(MEDI, Datetime, "darkest", "5 hours", +#' loop = TRUE, as.df = TRUE)) + +bright_dark_period <- function(Light.vector, + Time.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), + "`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" = + 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(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 = 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(Time.vector) - Time.vector[1] + Time.vector <- c(Time.vector, Time.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 <- 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, + "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" = 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 = "_")) + } + return(out) +} diff --git a/R/metric_duration_above_threshold.R b/R/metric_duration_above_threshold.R new file mode 100755 index 0000000..e447ffd --- /dev/null +++ b/R/metric_duration_above_threshold.R @@ -0,0 +1,113 @@ +#' #' 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. +#' +#' @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 +#' # 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::reframe("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) +#' +#' dataset1 %>% +#' dplyr::reframe(duration_above_threshold(MEDI, Datetime, threshold = 250, as.df = TRUE)) +#' +#' # Group by Id to account for different epochs +#' dataset.combined %>% +#' dplyr::group_by(Id) %>% +#' dplyr::reframe("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("duration_{comparison}_{threshold}" := tat)) + } else { + return(tat) + } +} diff --git a/R/metric_interdaily_stability.R b/R/metric_interdaily_stability.R new file mode 100755 index 0000000..b9965b8 --- /dev/null +++ b/R/metric_interdaily_stability.R @@ -0,0 +1,134 @@ +#' 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 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. +#' +#' @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 +#' +#' @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 +#' +#' 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 = dplyr::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( + utils::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( + utils::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 <- stats::var(avg_hourly$Light) / stats::var(total_hourly$Light) + + # Return data frame or numeric vector + if (as.df) { + return(tibble::tibble("interdaily_stability" = is)) + } else { + return(is) + } +} diff --git a/R/metric_intradaily_variability.R b/R/metric_intradaily_variability.R new file mode 100755 index 0000000..ef7dd79 --- /dev/null +++ b/R/metric_intradaily_variability.R @@ -0,0 +1,131 @@ +#' 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 with +#' 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 +#' +#' @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 +#' +#' 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 = dplyr::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( + utils::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( + utils::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 / stats::var(total_hourly$Light) + + # Return data frame or numeric vector + if (as.df) { + 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 new file mode 100755 index 0000000..e2d5040 --- /dev/null +++ b/R/metric_timing_above_threshold.R @@ -0,0 +1,111 @@ +#' Mean/first/last timing above/below threshold. +#' +#' 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 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 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. +#' +#' @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 +#' 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} +#' +#' @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)) +#' ) +#' +#' # Above threshold +#' dataset1 %>% +#' dplyr::reframe(timing_above_threshold(MEDI, Datetime, "above", 250, as.df = TRUE)) +#' +#' # Below threshold +#' dataset1 %>% +#' dplyr::reframe(timing_above_threshold(MEDI, Datetime, "below", 10, as.df = TRUE)) +#' +#' # Input = HMS -> Output = HMS +#' dataset1 %>% +#' dplyr::reframe(timing_above_threshold(MEDI, hms::as_hms(Datetime), "above", 250, as.df = TRUE)) +#' +timing_above_threshold <- function(Light.vector, + Time.vector, + comparison = c("above", "below"), + threshold, + na.rm = FALSE, + as.df = FALSE) { + # Match 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), + "`na.rm` must be logical!" = is.logical(na.rm), + "`as.df` must be logical!" = is.logical(as.df) + ) + + # Calculate timing metric + t <- Time.vector[compare_threshold(Light.vector, threshold, comparison, na.rm)] + mlit = t %>% as.numeric() %>% mean() %>% round() + flit = t %>% dplyr::first() + llit = t %>% dplyr::last() + + # Convert to 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 list + if (as.df) { + threshold <- stringr::str_flatten(sort(threshold), collapse = "-") + out <- tibble::as_tibble(out) %>% + dplyr::rename_with(~paste(.x, "timing", comparison, threshold, sep = "_")) + } + return(out) +} diff --git a/README.Rmd b/README.Rmd index c465046..56632e9 100644 --- a/README.Rmd +++ b/README.Rmd @@ -181,4 +181,4 @@ If we want to force the data to be regular, we can use the `aggregate_Datetime() dataset %>% aggregate_Datetime(unit = "15 sec") %>% gap_finder() ``` -Now, very few gaps are left (every time the the lagged epochs lead to a completely skipped regular epoch). The function can also be used to conveniently change the interval to arbitrary values, e.g., `"5 mins"`, or `"1 hour"`. +Now, very few gaps are left (every time the the lagged epochs lead to a completely skipped regular epoch). The function can also be used to conveniently change the interval to arbitrary values, e.g., `"5 mins"`, or `"1 hour"`. \ No newline at end of file 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/LightLogR-package.Rd b/man/LightLogR-package.Rd index 6c01eaf..2b35672 100644 --- a/man/LightLogR-package.Rd +++ b/man/LightLogR-package.Rd @@ -25,10 +25,12 @@ 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: \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 new file mode 100755 index 0000000..ec58054 --- /dev/null +++ b/man/bright_dark_period.Rd @@ -0,0 +1,90 @@ +% 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, + Time.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{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"}.} + +\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? 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}.} + +\item{as.df}{Logical. Should the output be returned as a data frame? Defaults +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\}}. 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 +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. +} +\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::reframe(bright_dark_period(MEDI, Datetime, "brightest", "10 hours", + as.df = TRUE)) +dataset1 \%>\% + 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{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 new file mode 100644 index 0000000..7eb9be9 --- /dev/null +++ b/man/duration_above_threshold.Rd @@ -0,0 +1,92 @@ +% 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::reframe("TAT >250lx" = duration_above_threshold(MEDI, Datetime, threshold = 250)) + +dataset1 \%>\% + dplyr::reframe(duration_above_threshold(MEDI, Datetime, threshold = 250, as.df = TRUE)) + +# Group by Id to account for different epochs +dataset.combined \%>\% + dplyr::group_by(Id) \%>\% + 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{interdaily_stability}()}, +\code{\link{intradaily_variability}()}, +\code{\link{timing_above_threshold}()} +} +\concept{metrics} diff --git a/man/import_Dataset.Rd b/man/import_Dataset.Rd index 0fec504..64eb033 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{
}}\if{html}{\out{ }}\if{html}{\out{}}Datetime\if{html}{\out{}}\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{ }}\if{html}{\out{}}LIGHT\if{html}{\out{}}\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{ }}\if{html}{\out{}}Id\if{html}{\out{}}\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{ }}\if{html}{\out{}}26.88\if{html}{\out{}}\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{ }}\if{html}{\out{}}202.08\if{html}{\out{}}\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{}}2023-08-28 12:57:54\if{html}{\out{}}\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{ }}\if{html}{\out{}}208.03\if{html}{\out{}}\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{ }}\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{}}2023-08-28 12:58:04\if{html}{\out{}}\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{ }}\if{html}{\out{}}204.85\if{html}{\out{}}\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{ }}\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{}}2023-08-28 12:58:14\if{html}{\out{}}\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{ }}\if{html}{\out{}}203.59\if{html}{\out{}}\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{ }}\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{}}2023-08-28 12:58:24\if{html}{\out{}}\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{ }}\if{html}{\out{}}203.44\if{html}{\out{}}\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{ }}\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{}}2023-08-28 12:58:34\if{html}{\out{}}\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{ }}\if{html}{\out{}}204.31\if{html}{\out{}}\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{ }}\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{}}Datetime\if{html}{\out{}}\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{ }}\if{html}{\out{}}LIGHT\if{html}{\out{}}\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{ }}\if{html}{\out{}}Id\if{html}{\out{}}\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{ }}\if{html}{\out{}}26.88\if{html}{\out{}}\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{ }}\if{html}{\out{}}202.08\if{html}{\out{}}\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{}}2023-08-28 12:57:54\if{html}{\out{}}\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{ }}\if{html}{\out{}}208.03\if{html}{\out{}}\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{ }}\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{}}2023-08-28 12:58:04\if{html}{\out{}}\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{ }}\if{html}{\out{}}204.85\if{html}{\out{}}\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{ }}\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{}}2023-08-28 12:58:14\if{html}{\out{}}\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{ }}\if{html}{\out{}}203.59\if{html}{\out{}}\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{ }}\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{}}2023-08-28 12:58:24\if{html}{\out{}}\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{ }}\if{html}{\out{}}203.44\if{html}{\out{}}\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{ }}\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{}}2023-08-28 12:58:34\if{html}{\out{}}\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{ }}\if{html}{\out{}}204.31\if{html}{\out{}}\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{ }}\if{html}{\out{}}205_actlumus_Log_1020_20230904101707532.txt\if{html}{\out{}}\if{html}{\out{ }}\if{html}{\out{ | }}\if{html}{\out{