Skip to content

Commit

Permalink
Merge pull request #96 from lanl/rc-07
Browse files Browse the repository at this point in the history
more updates from Rc 07
  • Loading branch information
rfiorella authored Sep 29, 2023
2 parents 4ff1236 + ceb7cb7 commit cd56ec1
Show file tree
Hide file tree
Showing 9 changed files with 131 additions and 145 deletions.
12 changes: 11 additions & 1 deletion R/calibrate_standards_water.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,10 +8,20 @@
#' calibrate standards data. Default is 0.95. Calibrated reference
#' gas measurements occurring during calibration periods
#' with r2 values less than `r2_thres` will be marked NA.
#' @param correct_bad_refvals Should we correct known/suspected incorrect
#' reference values in the NEON HDF5 files? (Default = `FALSE`).
#' @param site Four letter NEON site code.
#' Only used if `correct_bad_refvals = TRUE`.
#' @param refGas One of "low", "med", or "high."
#' Only used if `correct_bad_refvals = TRUE`.
#'
#' @export
calibrate_standards_water <- function(cal_df,
ref_df,
r2_thres = 0.95) {
r2_thres = 0.95,
correct_bad_refvals = FALSE,
site,
refGas) {

# want to implement same tolerances used to generate calibration regression!
# need to assess the CO2 and d13C tolerances wrt reference values.
Expand Down
189 changes: 55 additions & 134 deletions R/output_functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -463,160 +463,51 @@ write_water_reference_data <- function(inname, outname, site,

#' calibrate_water_reference_data
#'
#' @param inname Input file name.
#' @param outname Output file name.
#' @param standard Which standard are we working on? Must be "Low",
#' "Med", or "High"
#' @param site NEON 4-letter site code.
#' @param calDf Calibration data frame -
#' this is the output from fit_water_regression
#' @param standard Which reference material is being 'calibrated'?
#' (Low, med, or high)
#' @param stdDf Data frame of reference material measurements.
#' this is the output from fit_carbon_regression
#'
#' @return Nothing to the environment.
#'
# - problem here: in some contexts standard is a df,
# others its a string (e.g., which standard?)
calibrate_water_reference_data <- function(outname,
calibrate_water_reference_data <- function(inname,
outname,
standard,
site,
stdDf,
calDf) {

rhdf5::h5createGroup(outname,
paste0("/", site,
"/dp01/data/isoH2o/h2o",
standard, "_03m"))


std <- rhdf5::h5read(inname,
paste0("/", site, "/dp01/data/isoH2o/h2o", standard, "_03m"))

std <- calibrate_standards_water(calDf, std, correct_bad_refvals = TRUE,
site = site, refGas = standard)


fid <- rhdf5::H5Fopen(outname)
std_outloc <- rhdf5::H5Gopen(fid,
paste0("/", site,
"/dp01/data/isoH2o/h2o",
standard, "_03m"))

# restructure variables to be more suitable for output file.
dlta18OH2o <- restructure_water_variables(stdDf,
"dlta18OH2o",
"reference")
dlta2HH2o <- restructure_water_variables(stdDf,
"dlta2HH2o",
"reference")
dlta18OH2oRefe <- restructure_water_variables(stdDf,
"dlta18OH2oRefe",
"reference")
dlta2HH2oRefe <- restructure_water_variables(stdDf,
"dlta2HH2oRefe",
"reference")
pres <- restructure_water_variables(stdDf,
"pres",
"reference")
presEnvHut <- restructure_water_variables(stdDf,
"presEnvHut",
"reference")
rhEnvHut <- restructure_water_variables(stdDf,
"rhEnvHut",
"reference")
rtioMoleWetH2o <- restructure_water_variables(stdDf,
"rtioMoleWetH2o",
"reference")
rtioMoleWetH2oEnvHut <- restructure_water_variables(stdDf,
"rtioMoleWetH2oEnvHut",
"reference")
temp <- restructure_water_variables(stdDf,
"temp",
"reference")
tempEnvHut <- restructure_water_variables(stdDf,
"tempEnvHut",
"reference")

data_out_all <- do.call(rbind, list(dlta18OH2o[[1]], dlta2HH2o[[1]],
dlta18OH2oRefe[[1]], dlta2HH2oRefe[[1]],
pres[[1]], presEnvHut[[1]], rhEnvHut[[1]],
rtioMoleWetH2o[[1]],
rtioMoleWetH2oEnvHut[[1]], temp[[1]],
tempEnvHut[[1]]))

std <- base::split(data_out_all, factor(data_out_all$varname))

std <- calibrate_standards_water(calDf, std)

# and write out as a dataframe.
lapply(names(std), function(x) {
rhdf5::h5writeDataset(obj = std[[x]],
h5loc = std_outloc,
name = x,
DataFrameAsCompound = TRUE)})

rhdf5::H5Gclose(std_outloc)

# write qfqm
rhdf5::h5createGroup(outname, paste0("/",
site,
"/dp01/qfqm/isoH2o/h2o",
standard,
"_03m"))

std_outloc <- rhdf5::H5Gopen(fid,
paste0("/",
site,
"/dp01/qfqm/isoH2o/h2o",
standard,
"_03m"))

data_out_all <- do.call(rbind, list(dlta18OH2o[[2]],
dlta2HH2o[[2]],
pres[[2]],
presEnvHut[[2]],
rhEnvHut[[2]],
rtioMoleWetH2o[[2]],
rtioMoleWetH2oEnvHut[[2]],
temp[[2]],
tempEnvHut[[2]]))

std <- base::split(data_out_all, factor(data_out_all$varname))

# and write out as a dataframe.
lapply(names(std), function(x) {
rhdf5::h5writeDataset(obj = std[[x]],
h5loc = std_outloc,
name = x,
DataFrameAsCompound = TRUE)
})

rhdf5::H5Gclose(std_outloc)

# write ucrt
rhdf5::h5createGroup(outname, paste0("/",
site,
"/dp01/ucrt/isoH2o/h2o",
standard,
"_03m"))

rhdf5::H5Gcreate(fid,
paste0("/", site, "/dp01/data/isoH2o/h2o", standard, "_03m"))
std_outloc <- rhdf5::H5Gopen(fid,
paste0("/",
site,
"/dp01/ucrt/isoH2o/h2o",
"/dp01/data/isoH2o/h2o",
standard,
"_03m"))

data_out_all <- do.call(rbind, list(dlta18OH2o[[3]],
dlta2HH2o[[3]],
pres[[3]],
presEnvHut[[3]],
rhEnvHut[[3]],
rtioMoleWetH2o[[3]],
rtioMoleWetH2oEnvHut[[3]],
temp[[3]],
tempEnvHut[[3]]))

std <- base::split(data_out_all, factor(data_out_all$varname))

# and write out as a dataframe.
# loop through each variable amb.data.list and write out as a dataframe.
lapply(names(std), function(x) {
rhdf5::h5writeDataset(obj = std[[x]],
h5loc = std_outloc,
name = x,
DataFrameAsCompound = TRUE)})

h5loc = std_outloc,
name = x,
DataFrameAsCompound = TRUE)})
rhdf5::H5Gclose(std_outloc)
rhdf5::H5Fclose(fid)
rhdf5::h5closeAll()
}


Expand All @@ -637,5 +528,35 @@ calibrate_water_reference_data <- function(outname,
#'
write_water_ambient_data <- function(outname, site, amb_data_list) {

stop("write_water_ambient_data not written yet.") # curretnly a stub to just get R CMD CHECK working...
print("Writing calibrated ambient data...")

fid <- rhdf5::H5Fopen(outname)

if (length(amb_data_list) > 0) {
for (i in 1:length(amb_data_list)) {
amb_data_subset <- amb_data_list[i]

h2o_data_outloc <- rhdf5::H5Gcreate(fid,
paste0("/",
site,
"/dp01/data/isoH2o/",
names(amb_data_subset)))

amb_data_subset <- amb_data_subset[[1]] # list hack

# loop through variables in amb_data_list and write as a dataframe.
lapply(names(amb_data_subset), function(x) {
rhdf5::h5writeDataset(obj = amb_data_subset[[x]],
h5loc = h2o_data_outloc,
name = x,
DataFrameAsCompound = TRUE)})
rhdf5::H5Gclose(h2o_data_outloc)
}

}

# close all open handles.
rhdf5::H5Fclose(fid)
rhdf5::h5closeAll()
# curretnly a stub to just get R CMD CHECK working...
}
3 changes: 2 additions & 1 deletion R/quality_control.R
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,8 @@ validate_output_file <- function(inname, outname, site, analyte) {
site,
"/dp01/data/isoH2o"), ]$name
#only care about the 9m vars!
target_in <- target_in[grep("09m", target_in) &
target_in <- target_in[(grepl("03m", target_in) |
grepl("09m", target_in)) &
!grepl("Arch", target_in)]
target_out <- groups_out[groups_out$group ==
paste0("/",
Expand Down
2 changes: 1 addition & 1 deletion R/restructure_data.R
Original file line number Diff line number Diff line change
Expand Up @@ -271,7 +271,7 @@ ingest_data <- function(inname,

if (name_fix) {
if (analyte == "H2o") {
avg_char <- paste0("0", ref_avg, "m")
avgChar <- paste0("0", ref_avg, "m")
}
# append _09m to refe_out....MAY CAUSE PROBLEMS FOR OTHER METHODS!!!!!!
names(refe_out) <- paste0(names(refe_out), "_", avgChar)
Expand Down
18 changes: 17 additions & 1 deletion man/calibrate_standards_water.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

12 changes: 6 additions & 6 deletions man/calibrate_water_reference_data.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

16 changes: 16 additions & 0 deletions tests/testthat/test-data_regression.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,22 @@ test_that("calibration data frames have 14 columns", {
expect_equal(ncol(calDf_LR), 14)
})

test_that("carbon calibration data frames correct even when no input data", {
skip_on_cran()
# empty ref data frame:
empty_df <- data.frame(matrix(nrow = 0, ncol = ncol(co2data)))
names(empty_df) <- names(co2data)
expect_no_error(fit_carbon_regression(empty_df,
method = "Bowling_2003"))
expect_no_error(fit_carbon_regression(empty_df,
method = "linreg"))
expect_equal(ncol(fit_carbon_regression(empty_df,
method = "Bowling_2003")), 14)
expect_equal(ncol(fit_carbon_regression(empty_df,
method = "linreg",
calibration_half_width = 2)), 14)
})


# work through ambient calibrations

Expand Down
8 changes: 7 additions & 1 deletion tests/testthat/test-high_level_functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -44,12 +44,18 @@ test_that("calibrate_carbon returns no error", {
})


fout3 <- tempfile()

test_that("calibrate_water returns no error", {

skip_on_cran()
# these tests could probably be made more useful!!
expect_no_error(calibrate_water(fin, fout, "ONAQ",
expect_no_error(calibrate_water(fin, '/dev/null', "ONAQ",
correct_refData = TRUE,
write_to_file = FALSE))

expect_no_error(calibrate_water(fin, fout3, "ONAQ",
correct_refData = TRUE,
write_to_file = TRUE))

})
16 changes: 16 additions & 0 deletions tests/testthat/test-output_values.R
Original file line number Diff line number Diff line change
Expand Up @@ -66,3 +66,19 @@ test_that("calibrated ambient co2 mixing ratios linreg are within a plausible ra
expect_gt(min(ciso_subset_cal$`000_010_09m`$rtioMoleDryCo2$mean_cal, na.rm = TRUE), 300)
})


#---------------------------------------
# test some of the output data functions

fout <- tempfile()

test_that("setup_output_file returns no errors", {
expect_no_error(setup_output_file(fin,
fout,
site = "YELL",
analyte = "H2o"))
expect_no_error(setup_output_file(fin,
fout,
site = "YELL",
analyte = "Co2"))
})

0 comments on commit cd56ec1

Please sign in to comment.