diff --git a/.gitignore b/.gitignore index 1db65d8..315892e 100644 --- a/.gitignore +++ b/.gitignore @@ -6,3 +6,12 @@ .R* *.*~ .Rproj.user + +# Local package copy for autotest +.local/* + +# Tmp directory +tmp/* + +# Ignore plots created by testing functionality +tests/testthat/*.pdf \ No newline at end of file diff --git a/DESCRIPTION b/DESCRIPTION index 7a262d3..04e9bc6 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -12,10 +12,10 @@ LazyLoad: yes Depends: plyr, reshape2, + ggplot2, isotopia Suggests: testthat, - ggplot2, gridExtra, xlsx Roxygen: list(wrap = FALSE) @@ -28,6 +28,8 @@ Collate: 'IrmsContinuousFlowDataClass.R' 'IrmsDualInletDataClass.R' 'IsodatFileClass.R' + 'IsodatDualInletFileClass.R' + 'IsodatClumpedCO2FileClass.R' 'IsodatHydrogenContinuousFlowFileClass.R' 'export.R' 'isoread.R' diff --git a/Makefile b/Makefile index 7a8f9f4..a4fc167 100644 --- a/Makefile +++ b/Makefile @@ -27,3 +27,13 @@ check: build cd ..;\ R CMD check $(PKGNAME)_$(PKGVERS).tar.gz --as-cran +local-install: + rm -rf .local + mkdir .local + R CMD Install --library=.local . + +autotest: local-install + + R -q -e "library(isoread, lib.loc = '.local')" \ + -e "library(testthat)" \ + -e "auto_test_package(pkg='.')" diff --git a/NAMESPACE b/NAMESPACE index 350f6c6..3347aae 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,4 +1,4 @@ -# Generated by roxygen2 (4.0.0): do not edit by hand +# Generated by roxygen2 (4.0.2): do not edit by hand export(export_data) export(isoread) @@ -9,4 +9,6 @@ export(reload) export(summarize_all) exportClasses(BinaryFile) exportClasses(IrmsContinuousFlowData) +exportClasses(IsodatClumpedCO2File) +exportClasses(IsodatDualInletFile) exportClasses(IsodatHydrogenContinuousFlowFile) diff --git a/R/BinaryFileClass.R b/R/BinaryFileClass.R index 9613a1d..807abcc 100644 --- a/R/BinaryFileClass.R +++ b/R/BinaryFileClass.R @@ -83,6 +83,8 @@ BinaryFile <- setRefClass( return(read) }, + # IMPLEMENT skip_after_each for easy recuriing motive recognition + # current problem with that is that it loops through by type (=col) parse_array = function(types, n, id = NA, skip_first = 0) { "repeatedly read the same set of information into a data frame @@ -124,40 +126,48 @@ BinaryFile <- setRefClass( pos <<- as.integer(pos + nbyte) }, - find_key = function(pattern, occurence = 1) { - "find a key by a regexp pattern" + find_key = function(pattern, occurence = NULL, fixed = FALSE, byte_min = 0, byte_max = length(rawdata)) { + "finds all keys matching 'key' or a specific occurence of it (use -1 for last occurence) + #' @param fixed whether to find the key(s) by regexp match or fixed string (default = pattern) + #' @param byte_min only look for keys that start after this position + #' @param byte_max only look for keys that start before this position + #' @return the lines of the keys data frame with all the information about the found key(s)" if (nrow(keys) == 0) stop("no keys available, make sure load() was called") - if (nrow(match <- keys[grep(pattern, keys$value),]) == 0) - stop("pattern '", pattern, "' was not found") + sub_keys <- subset(keys, byteStart > byte_min & byteStart < byte_max) + if (nrow(sub_keys) == 0) + stop("no keys in this byte interval: ", byte_min, " - ", byte_max) - if (occurence == -1) occurence <- nrow(match) + if (length(idx <- grep(pattern, sub_keys$value, fixed = fixed)) == 0) + stop("key '", pattern, "' was not found") - if (occurence > nrow(match)) - stop("pattern '", pattern, "' was found but only has ", nrow(match), " occurences ", - "(trying to select occurence #", occurence, ")") + if (!is.null(occurence)) { + if (occurence == -1) occurence <- length(idx) - return(match[occurence, "value"]) + if (occurence > length(idx)) + stop("key '", key, "' was found but only has ", length(idx), " occurences ", + "(trying to select occurence #", occurence, ")") + } else { + occurence <- 1:length(idx) # return ALL found occurences + } + + return(sub_keys[idx[occurence], , drop=F]) }, - move_to_key = function(key, occurence = 1) { - "moves position to the end of a specific occurence of a key (use -1 for last occurence)" - - if (nrow(keys) == 0) - stop("no keys available, make sure load() was called") - - if (nrow(match <- subset(keys, value==key)) == 0) - stop("key '", key, "' was not found") - - if (occurence == -1) occurence <- nrow(match) - - if (occurence > nrow(match)) - stop("key '", key, "' was found but only has ", nrow(match), " occurences ", - "(trying to select occurence #", occurence, ")") - - pos <<- as.integer(match[occurence, "byteEnd"]) + 1L + move_to_key = function(key, occurence = 1, fixed = TRUE) { + "moves position to the end of a specific key or occurence of a key + #' @param key either a string or a data.frame line with key value and byteEnd (the way it is returned by find_key) + #' @param occurence if key is a string, which occurence to move to? (use -1 for last occurence) + #' @param fixed whether to find the key (if a string) by regexp match or fixed string (default = fixed string)" + + if (is(key, "character")) key <- find_key(key, occurence, fixed) + else if (is(key, "list")) key <- as.data.frame(key) + + if (!is(key, "data.frame") || nrow(key) != 1 || !("byteEnd" %in% names(key))) + stop("not a valid key entry, can't move there: ", key) + pos <<- as.integer(key["byteEnd"]) + 1L }, read_file = function(){ @@ -278,7 +288,10 @@ BinaryFile <- setRefClass( rbind( data.frame(Property = c("File location", "Date"), Value = c(file.path(filepath, filename), format(creation_date))), - data.frame(Property = names(data), Value = vapply(data, as.character, FUN.VALUE = character(1), USE.NAMES = FALSE)) + data.frame(Property = names(data), + Value = vapply(data, + function(i) if (is(i, "data.frame")) "data frame (not shown)" else as.character(i[1]), + FUN.VALUE = character(1), USE.NAMES = FALSE)) ) }, diff --git a/R/IrmsContinuousFlowDataClass.R b/R/IrmsContinuousFlowDataClass.R index 68520fa..f626da3 100644 --- a/R/IrmsContinuousFlowDataClass.R +++ b/R/IrmsContinuousFlowDataClass.R @@ -56,13 +56,15 @@ IrmsContinousFlowData <- setRefClass( # DATA CHECKS ============================ - check_data = function(...) { - "check the data consistency, calls \\code{check_crom_data} and \\code{check_peak_table}" - callSuper(...) + # FIXME: refactor such that check_chrom_data is renmaed directly to check_mass_data + check_mass_data = function(...) { check_chrom_data(...) - check_peak_table(...) }, + # FIXME: refactor such that check_data_table is renamed directly to check_peak_table + check_data_table = function(...) { + check_peak_table(...) + }, check_chrom_data = function(masses = names(.self$plotOptions$masses), ratios = names(.self$plotOptions$ratios), ..., warn = TRUE) { @@ -139,6 +141,11 @@ IrmsContinousFlowData <- setRefClass( # DATA RETRIEVAL ============== + # FIXME: refactor such that check_chrom_data is renmaed directly to check_mass_data + get_data_table = function(...){ + get_peak_table(...) + }, + get_peak_table = function(type = c("ref", "data", "both")) { "retrieve the peak table" diff --git a/R/IrmsDataClass.R b/R/IrmsDataClass.R index 3a630ba..492aff0 100644 --- a/R/IrmsDataClass.R +++ b/R/IrmsDataClass.R @@ -5,7 +5,10 @@ IrmsData <- setRefClass( "IrmsData", fields = list ( - plotOptions = 'list' + plotOptions = 'list', # stores options for plotting the data + massData = 'data.frame', # stores raw data for all measured masses (e.g. voltages) + dataTable = 'data.frame', # stores processed data table (=data summary) + dataTableColumns = 'data.frame' # the columns of the data table ), methods = list( #' constructor @@ -16,7 +19,19 @@ IrmsData <- setRefClass( init_irms_data = function() { "initialize irms data container" - plotOptions <<- list() + + # template for plot options + plotOptions <<- list( + masses = list() # example entry: mass46 = list(label = "Mass 46", color="black") + ) + + # template for dataTableColumn definitions + # data - name of the column header for in the data + # column - name of the column stored in the data table + # units - units of the data are in + # type - which mode it is (character, numeric, logical, Ratio, Abundance, Delta, etc.) + # show - whether to show this column in standard data table outputs + dataTableColumns <<- data.frame(data = character(), column = character(), units = character(), type = character(), show = logical(), stringsAsFactors = FALSE) }, #' @example setSettings(a=5, b='test', ...) @@ -35,11 +50,43 @@ IrmsData <- setRefClass( plotOptions <<- modifyList(plotOptions, options) }, + # DATA CHECKS ============================ + #' check internal consistency of data check_data = function(...) { + check_mass_data(...) + check_data_table(...) + }, + + check_mass_data = function(...) { + "checks the consistency of the raw mass data" + }, + + check_data_table = function(...) { + "checks the consistency of the table data" }, + # DATA RETRIEVAL ============== + + #' get data for masses + #' @param masses which masses to retrieve, all defined ones by default + #' @param melt whether to melt the data frame + get_mass_data = function(masses = names(.self$plotOptions$masses), melt = FALSE, ...) { + "get the mass trace data for specific masses, can be provided in \\code{melt = TRUE} long format + for easy use in ggplot style plotting" + stop("not implemented for this class") + }, + + get_data_table = function(...) { + "retrieve the data table" + stop("not implemented for this class") + }, + + # PLOTTING =================== + + #' plot data plot = function(...) { + "plot data with standard plot functions (fast) to standard output" stop("not implemented for this class") }, diff --git a/R/IrmsDualInletDataClass.R b/R/IrmsDualInletDataClass.R index eb6c67e..f23198a 100644 --- a/R/IrmsDualInletDataClass.R +++ b/R/IrmsDualInletDataClass.R @@ -9,5 +9,161 @@ IrmsDualInletData <- setRefClass( "IrmsDualInletData", contains = "IrmsData", fields = list (), - methods = list() + methods = list( + + #' initialize irms data container + init_irms_data = function(){ + callSuper() + + # default plot options + set_plot_options( + labels = list(xmasses = "Cycle", ymasses = "Signal [mV]") # default mass data plot labels + ) + + # if overwriting default in derived classes, make sure to define the cycle column in dataTableColumn definitions! + # (but it can be set to show = FALSE if desired) + # dataTableColumns <<- data.frame(data = "cycle", column = "cycle", units = "", type = "integer", show = TRUE, stringsAsFactors = FALSE) + }, + + # DATA CHECKS ============================ + + check_mass_data = function(...) { + # check if the masses defined in plotOptions actually exist + if (ncol(massData) == 0) + stop("No raw data is loaded. Make sure to run load() to load all data from the file.") + + missing <- setdiff( + names(.self$plotOptions$masses), + grep("mass\\d+", names(massData), value = T)) + + if ( length(missing) > 0 ) + stop("Not all masses appear to be recorded in this file, missing: ", paste(missing, collapse = ", ")) + + return(TRUE) + }, + + check_data_table = function(...) { + # checks the consistency of the data table and converts data types if necessary + # by default, checks all columns defined in dataTableColumns + + if (ncol(dataTable) == 0) + stop("No data table is loaded. Make sure to run load() to load all data from the file.") + + # check for existence of all columns + if (length(missing <- setdiff(dataTableColumns$column, names(dataTable))) > 0) { + # for the missing columns, try to find and convert the original data column names to the dataTable names (easier to access) + ptc_indices <- which(dataTableColumns$column %in% missing) # indices of missing columns in dataTableColumns + if (length(missing <- setdiff(dataTableColumns$data[ptc_indices], names(dataTable))) > 0) + stop("Some data columns ('", paste(missing, collapse = ", ") ,"') do not exist in the loaded dataTable.") + + # change original column names to new name + pt_cols <- sapply(dataTableColumns$data[ptc_indices], function(i) which(names(dataTable) == i), simplify = TRUE) + names(dataTable)[pt_cols] <<- dataTableColumns$column[ptc_indices] + } + + # bring data table columns into right order + dataTable <<- dataTable[dataTableColumns$column] + + # check for proper class and convert if necessary + if (any(types <- (sapply(dataTable, class, simplify=T) != dataTableColumns$type))) { + ptc_indices <- which(types) # indices of the columns to convert + + for (i in ptc_indices) { + value <- convert_data( + value = dataTable[[dataTableColumns$column[i]]], + data_type = dataTableColumns$type[i]) + dataTable[[dataTableColumns$column[i]]] <<- value + } + } + }, + + convert_data = function(value, data_type) { + "function converts data table entries to their appropriate data types - overwrite in derived classes for more specialized behaviour" + suppressWarnings( + try(switch( + data_type, + "integer" = as.integer(value), + "character" = as.character(value), + "numeric" = as.numeric(value), + "logical" = as.logical(value), + stop("data type not supported: ", data_type)), + TRUE)) + }, + + # DATA RETRIEVAL =========== + + get_mass_data = function(masses = names(.self$plotOptions$masses), melt = FALSE) { + check_mass_data() + + if (length(missing <- setdiff(masses, names(massData))) > 0) + stop("Some masses ('", paste(missing, collapse = ", ") ,"') do not exist in the loaded massData.") + + if (!melt) # wide format + return(massData[c("analysis", "cycle", masses)]) + else # long format + return(melt(massData[c("analysis", "cycle", masses)], + .(analysis, cycle), variable.name = "mass", value.name = "intensity")) + }, + + #' by default, returns all data table columns that are enabled with show = TRUE + #' @param summarize whether to show whole data table or just the summary + get_data_table = function(select = default_select(), summarize = FALSE) { + + default_select <- function() { + dataTableColumns$column[dataTableColumns$show] + } + + check_data_table() + + if (length(missing <- setdiff(select, names(dataTable))) > 0) + stop("Some data ('", paste(missing, collapse = ", ") ,"') do not exist in the loaded dataTable.") + + if (!summarize) + return(dataTable[select]) + + # summarize data table + select <- select[select != "cycle"] # exclude cycle form the summary (since it gets summarized) + summary <- ddply(melt(dataTable[select], id.vars = NULL, variable.name = "Variable"), .(Variable), + plyr:::summarize, + Mean = mean(value), + `Std. Devi.` = sd(value), + `Std. Error.` = `Std. Devi.`/sqrt(length(value))) + return(summary) + }, + + # PLOTTING =================== + + plot = function(masses = names(.self$plotOptions$masses), ...) { + stop("not implemented yet") + }, + + #' ggplot data + make_ggplot = function(masses = names(.self$plotOptions$masses), ...) { + library(ggplot2) + + plot.df <- get_mass_data(masses = masses, melt = T) # pass masses FIXME + plot.df <- merge(plot.df, data.frame( + mass = names(plotOptions$masses), + mass_label = sapply(plotOptions$masses, function(x) x$label)), by="mass") + x_breaks <- seq(min(plot.df$cycle), max(plot.df$cycle), by=1) + + p <- ggplot(plot.df, + aes(cycle, intensity, shape = analysis, linetype = analysis, fill = mass)) + + geom_line(colour = "black") + + geom_point(colour = "black") + + scale_x_continuous(breaks = x_breaks) + + scale_shape_manual("Type", values = c(21, 22)) + + scale_linetype_manual("Type", values = c(1, 2)) + + scale_fill_manual("Mass", breaks = names(plotOptions$masses), + labels = vapply(plotOptions$masses, function(x) x$label, FUN.VALUE=character(1)), + values = vapply(plotOptions$masses, function(x) x$color, FUN.VALUE=character(1)), + guide = "none") + + theme_bw() + theme(legend.position = "bottom") + + facet_wrap(~mass_label, scales = "free") + + labs(y = plotOptions$labels$ymasses) + + return(p) + } + + ) ) \ No newline at end of file diff --git a/R/IsodatClumpedCO2FileClass.R b/R/IsodatClumpedCO2FileClass.R new file mode 100644 index 0000000..177a20a --- /dev/null +++ b/R/IsodatClumpedCO2FileClass.R @@ -0,0 +1,35 @@ +#' @include IsodatDualInletFileClass.R +NULL + +#' Clumped dual inlet data class +#' +#' +#' @name IsodatClumpedCO2File +#' @exportClass IsodatClumpedCO2File +#' @seealso \link{IrmsDualInletData}, \link{BinaryFile}, \link{IsodatFile}, \link{IsodatDualInletFile} +IsodatClumpedCO2File <- setRefClass( + "IsodatClumpedCO2File", + contains = c("IsodatDualInletFile"), + fields = list (), + methods = list( + + #' initialize irms data container + init_irms_data = function(){ + callSuper() + + # specifically define the data table columns of CO2 dual inlet files + dataTableColumns <<- + data.frame( + data = c("cycle", "d 45CO2/44CO2 ", "d 46CO2/44CO2 ", + "d 13C/12C ", "d 18O/16O ", "d 17O/16O ", + "AT% 13C/12C ", "AT% 18O/16O "), + column = c("cycle", "d 45CO2/44CO2", "d 46CO2/44CO2", + "d13C", "d18O", "d17O", + "at% 13C", "at% 18O"), + units = c("", rep("permil", 5), "", ""), + type = c("integer", rep("numeric", 7)), + show = TRUE, stringsAsFactors = FALSE) + } + + ) +) \ No newline at end of file diff --git a/R/IsodatDualInletFileClass.R b/R/IsodatDualInletFileClass.R new file mode 100644 index 0000000..8c55475 --- /dev/null +++ b/R/IsodatDualInletFileClass.R @@ -0,0 +1,155 @@ +#' @include IsodatFileClass.R +#' @include IrmsDualInletDataClass.R +NULL + +#' Clumped dual inlet data class +#' +#' +#' @name IsodatDualInletFile +#' @exportClass IsodatDualInletFile +#' @seealso \link{BinaryFile}, \link{IsodatFile}, \link{IrmsDualInletData}, \link{IrmsData} +IsodatDualInletFile <- setRefClass( + "IsodatDualInletFile", + contains = c("IsodatFile", "IrmsDualInletData"), + fields = list (), + methods = list( + #' initialize + initialize = function(...) { + callSuper(...) + init_irms_data() + }, + + #' initialize irms data container + init_irms_data = function(){ + callSuper() + # overwrite in derived classes and set data table definitions properly! + # see IrmsDualInletDataClass for details on requirements and functionality + }, + + # READ DATA ========================= + + #' expand process function specifically for dual inlet type data + process = function(...) { + callSuper() + + # find recorded masses + masses <- find_key("Mass \\d+", + byte_min = find_key("CTraceInfo", occ = 1, fix = T)$byteEnd, + byte_max = find_key("CPlotRange", occ = 1, fix = T)$byteStart)$value + + if (length(masses) == 0) + stop("Error: no keys named 'Mass ..' found. Cannot identify recorded mass traces in this file.") + + # unless mass plot options are already manually defined (in init_irms_data), define them automatically here and assign colors + mass_names <- sub("Mass (\\d+)", "mass\\1", masses) + if (length(plotOptions$masses) == 0) { + # color blind friendly pallete (9 colors) + palette <- c("#000000", "#E69F00", "#56B4E9", "#009E73", "#D55E00", "#0072B2", "#CC79A7", "#999999", "#F0E442") + if (length(masses) > length(palette)) + stop("Currently only supporting up to ", length(palette), " automatically assigned different colors for masses but ", + "this file is recording data for ", length(masses), " different masses. Plesae define the plotOptions manually.") + + set_plot_options( + masses = setNames( + sapply(seq_along(masses), function(i) list(list(label = masses[i], color = palette[i]))), + mass_names) + ) + } + + # extract raw voltage data from the cycles + raw_data_keys <- find_key("^(Standard|Sample) \\w+$", + byte_min = find_key("CDualInletRawData", occ = 1, fix = T)$byteEnd, + byte_max = find_key("CTwoDoublesArrayData", occ = 1, fix = T)$byteStart) + + if (nrow(raw_data_keys) == 0) + stop("could not find raw data in this file") + + # extract cycle information + raw_data_keys <- mutate(raw_data_keys, + analysis = sub("^(Standard|Sample) (\\w+)$", "\\1", value), + cycle.0idx = sub("^(Standard|Sample) (\\w+)$", "\\2", value), # 0 based index, adjust in next line + cycle = ifelse(cycle.0idx == "Pre", 0, suppressWarnings(as.integer(cycle.0idx)) + 1L)) + n_cycles <- max(raw_data_keys$cycle) + + # read in all masses and cycles + massData <<- do.call(data.frame, + args = c(list(stringsAsFactors = FALSE, analysis = character(), cycle = integer()), + lapply(plotOptions$masses, function(i) numeric()))) + + for (i in 1:nrow(raw_data_keys)) { + move_to_key(raw_data_keys[i, ]) + has_intensity_block <- nrow(subset(keys, value == "CIntensityData" & byteStart > raw_data_keys[i, "byteStart"] & byteEnd < raw_data_keys[i, "byteEnd"] + 64)) > 0 + massData[i, ] <<- c(list(raw_data_keys[i, "analysis"], raw_data_keys[i, "cycle"]), + as.list(parse("double", length = length(mass_names), skip_first = if (has_intensity_block) 82 else 64))) + } + + # evaluated data / data table + # NOTE: this could (should ?) be calculated from the raw voltage data directly + eval_data_keys <- find_key("^(d |AT).+$", + byte_min = find_key("CDualInletEvaluatedData", occ = 1, fix = T)$byteEnd, + byte_max = find_key("Sequence Line Information", occ = 1, fix = T)$byteStart) + if (nrow(eval_data_keys) == 0) + stop("could not find evaluated data in this file") + + eval_data <- list(cycle = 1:n_cycles) + for (i in 1:nrow(eval_data_keys)) { + move_to_key(eval_data_keys[i,]) + gap_to_data <- switch( + substr(eval_data_keys[i, "value"], 1, 2), + `d ` = 54, `AT` = 50) + # these are evaluated data points for ALL cycles + eval_data[[eval_data_keys[i,"value"]]] <- parse("double", length = 2 * n_cycles, skip_first = gap_to_data)[c(FALSE, TRUE)] + } + dataTable <<- data.frame(eval_data, check.names = F) + + # unless dataTableColumns are already manually defined, define them here + if (nrow(dataTableColumns) == 0) { + dataTableColumns <<- + data.frame(data = names(dataTable), column = names(dataTable), + units = "", type = "numeric", show = TRUE, stringsAsFactors = FALSE) + } + + # grid infos + rawtable <- rawdata[subset(keys, value=="CMeasurmentInfos")$byteEnd:subset(keys, value=="CMeasurmentErrors")$byteStart] + dividers <- c(grepRaw("\xff\xfe\xff", rawtable, all=TRUE), length(rawtable)) + if (length(dividers) == 0) + stop("this file does not seem to have the expected hex code sequence FF FE FF as dividers in the grid info") + + for (i in 2:length(dividers)) { + # read ASCII data for each block + raw_ascii <- grepRaw("([\u0020-\u007e][^\u0020-\u007e])+", rawtable[(dividers[i-1]+4):dividers[i]], all=T, value = T) + x <- if (length(raw_ascii) > 0) rawToChar(raw_ascii[[1]][c(TRUE, FALSE)]) else "" + if (x == "CUserInfo") data[[paste0("Info_", sub("^(\\w+).*$", "\\1", value))]] <<- value # store value with first word as ID + else value <- x # keep value + } + + # sequence line information + rawtable <- rawdata[subset(keys, value=="Sequence Line Information")$byteEnd:subset(keys, value=="Visualisation Informations")$byteStart] + if (length(rawtable) < 10) + stop("this file does not seem to have a data block for the sequence line information") + + dividers <- grepRaw("\xff\xfe\xff", rawtable, all=TRUE) + if (length(dividers) == 0) + stop("this file does not seem to have the expected hex code sequence FF FE FF as dividers in the sequence line information") + + for (i in 2:length(dividers)) { + # read ASCII data for each block + raw_ascii <- grepRaw("([\u0020-\u007e][^\u0020-\u007e])+", rawtable[(dividers[i-1]+4):dividers[i]], all=T, value = T) + x <- if (length(raw_ascii) > 0) rawToChar(raw_ascii[[1]][c(TRUE, FALSE)]) else "" + if (i %% 2 == 1) data[[x]] <<- value # store key / value pair in data list + else value <- x # keep value for key (which comes AFTER its value) + } + + }, + + #' custom show function to display roughly what data we've got going + show = function() { + cat("\nShowing summary of", class(.self), "\n") + callSuper() + cat("\n\nMass data:\n") + print(get_mass_data()) + cat("\n\nData table:\n") + print(get_data_table(summarize = TRUE)) + } + ) +) \ No newline at end of file diff --git a/R/IsodatHydrogenContinuousFlowFileClass.R b/R/IsodatHydrogenContinuousFlowFileClass.R index 5753728..e7c75fb 100644 --- a/R/IsodatHydrogenContinuousFlowFileClass.R +++ b/R/IsodatHydrogenContinuousFlowFileClass.R @@ -115,10 +115,10 @@ IsodatHydrogenContinuousFlowFile <- setRefClass( # other information move_to_key("H3 Factor") parse("double", id = "H3factor", skip_first = 8) - data$GCprogram <<- find_key(".gcm$") - data$MSprogram <<- find_key(".met$") - data$Filename <<- find_key(".cf$") - data$ASprogram <<- find_key("Internal") + data$GCprogram <<- find_key(".gcm$")$value + data$MSprogram <<- find_key(".met$")$value + data$Filename <<- find_key(".cf$")$value + data$ASprogram <<- find_key("Internal")$value # reorganize data, move to IrmsDataClass structure if (readChromData) { diff --git a/R/isoread.R b/R/isoread.R index 88d2dd9..9add310 100644 --- a/R/isoread.R +++ b/R/isoread.R @@ -7,6 +7,7 @@ #' @docType package #' @title isoread package #' @author Sebastian Kopf +#' @author Max Lloyd NULL #' @include IsodatHydrogenContinuousFlowFileClass.R @@ -26,6 +27,8 @@ NULL #' @param ... parameters passed to the \code{load} and \code{process} functions of the IsodatFile objects #' @return List of file \code{type} specific objects. #' \itemize{ +#' \item{'DUAL'}{ = instance(s) of a basic \code{\link{IsodatDualInletFile}} which implements \code{\link{IrmsDualInletData}}}. +#' \item{'CO2_CLUMPED'}{ = instance(s) of the more specialized \code{\link{IsodatClumbedCO2File}} which extends \code{\link{IsodatDualInletFile}}}. #' \item{'H_CSIA'}{ = instance(s) of \code{\link{IsodatHydrogenContinuousFlowFile}} which implements \code{\link{IrmsContinuousFlowData}}}. #' } #' If file names start with a number, @@ -36,6 +39,8 @@ isoread <- function(files, type, load_chroms = T, ...) { typeClass <- switch( type, H_CSIA = 'IsodatHydrogenContinuousFlowFile', + DUAL = 'IsodatDualInletFile', + CO2_CLUMPED = 'IsodatClumpedCO2File', stop("not a currently supported file type: '", type, "'")) files <- as.list(files) diff --git a/R/zzz.R b/R/zzz.R index df00b05..e941bc1 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -1,9 +1,8 @@ #FIXME remove again (just a helper during development) +# automatically create a global instance of a test file on attachment of the package .onAttach <- function(libname, pkgname) { - #isoread("/Users/sk/Dropbox/VM Windows/6520__F8-5_5uL_isodat2.cf", readChromData = TRUE, type = "H_CSIA") ->> i + #i <<- suppressMessages(isoread(system.file("extdata", "dual_inlet_clumped_carbonate.did", package="isoread"), type = "CO2_CLUMPED")) + #i$load() } -# for auto-testing, just start R in separate console inside the package and -# run the following code: -# library(testthat) -# auto_test_package(pkg=".") \ No newline at end of file +# for auto-testing, just run 'make autotest' on a terminal in the isoread folder diff --git a/README.md b/README.md index b9cf77b..bc8b36e 100644 --- a/README.md +++ b/README.md @@ -5,30 +5,58 @@ R interface to IRMS (isotope ratio mass spectrometry) file formats typically use This package allows the reading and processing of stable isotope data directly from the data files and thus provides a tool for reproducible data reduction. This package is definitely still a work-in-progress, however the master branch will always be a functional version (get the 'dev' branch for the active development version) and I'll make an effort to keep it backwards compatible as it evolves. -The underlying object structure of the package is designed to allow expansion towards a number of different types of data (the uml diagram contains a rough visual sketch of the class hierarchy) but currently, the only supported format (the only one I have test data from and had time to implement) are files containing compound specific hydrogen isotope data but expansions will come over time. +Currently, **isoread** supports reading files containing compound specific hydrogen isotope data, as well as clumped carbonate dual inlet data. The underlying object structure of the package is designed to allow easy expansion towards a number of different types of data and both supported file types are dynamically implemented and should be easily expandable to other continuous flow and dual inlet isotope data files, so expansions will hopefully come over time. -##Installation +## How to use the isoread package + +### Installation Hadley Wickham's **devtools** package provides a super convenient way of installing ```R``` packages directly from GitHub. To install **devtools**, run the following from the R command line: ```coffee -install.packages('devtools', depen=T) # development tools +install.packages('devtools', depen=T) ``` - -Then simply install the latest version of **isoread** directly from GitHub by running the following code (if it is the first time you install the **isoread** package, all missing dependencies will be automatically installed as well -> **ggplot2, plyr, reshape2, stringr** as well as their respective dependencies, which might take a minute, except for the **isotopia** package which is not on CRAN yet - see code below): +Then simply install the latest version of **isoread** directly from GitHub by running the following code (if it is the first time you install the **isoread** package, all missing dependencies will be automatically installed as well + their respective dependencies, which might take a minute, except for the **isotopia** package which is not on CRAN yet and requires manual installation - see code below): ```coffee library(devtools) -install_github('isotopia', 'sebkopf') # not on CRAN yet -install_github('isoread', 'sebkopf') +install_github('sebkopf/isotopia') # not on CRAN yet +install_github('sebkopf/isoread') ``` -##Examples +### Examples + +The following examples can be run with the test data provided by the **isoread** package and illustrate the direct reading of isotope data from the binary data files. Please use the help files in R for details on functions and paramters (e.g. via ```?isoread``` - note: the object methods' help files are not supported by ```Roxygen``` yet but this is [currently being implemented](http://lists.r-forge.r-project.org/pipermail/roxygen-devel/2014-January/000456.html) so will come soon!). + +#### Continuous flow -The following example can be run with the test data provided by the **isoread** package and illustrates the direct reading of a compound-specific hydrogen isotope dataset from the binary data file. A summary of the retrieved data can be printed out via ```$show()``` and both ```$plot()``` and ```$make_ggplot()``` commands for the data set are already fully implemented and provide an easy quick way for visualization (of course you can access all the raw data in the object as well via ```$get_mass_data()``` and ```$get_ratio_data()``` and process it as needed). Please use the help files in R for details on functions and paramters (e.g. via ```?isoread``` - note: the object methods' help files are not supported by ```Roxygen``` yet but this is [currently being implemented](http://lists.r-forge.r-project.org/pipermail/roxygen-devel/2014-January/000456.html) so will come soon!). +The following example llustrates the direct reading of a compound-specific hydrogen isotope dataset from the binary data file. A summary of the retrieved data can be printed out via ```$show()``` and both ```$plot()``` (fast plotting of the chromatographic data) and ```$make_ggplot()``` (ggplot that is slower but easy to manipulate). Of course, you can access all the raw data in the object as well via ```$get_mass_data()``` and ```$get_ratio_data()``` and process it as needed). ```coffee library(isoread) -obj <- isoread(system.file("extdata", "6520__F8-5_5uL_isodat2.cf", package="isoread"), type = c("H_CSIA")) +obj <- isoread( + system.file("extdata", "6520__F8-5_5uL_isodat2.cf", package="isoread"), + type = c("H_CSIA")) obj$show() obj$plot() obj$make_ggplot() ``` + +For a more detailed introduction, **check out the [continuous flow intro](inst/doc/continuous_flow_intro.Rmd)** and the resulting [HTML output](https://rawgit.com/sebkopf/isoread/master/inst/doc/continuous_flow_intro.html)! + +#### Dual Inlet + +Thanks to a push from [Max Lloyd](https://github.com/maxmansaxman), **isoread** now has basic support for dual inlet isotope data and specifically supports reading clumped CO2 runs. The following example illustrates the direct reading of a clumped CO2 dual inlet dataset from the binary data file, and prints out a summary of the retrieved data via ```$show()``` and ```$make_ggplot()```. + +```coffee +library(isoread) +obj <- isoread( + system.file("extdata", "dual_inlet_clumped_carbonate.did", package="isoread"), + type = "CO2_CLUMPED") +obj$show() +obj$make_ggplot() +``` + +For a more detailed introduction, **check out the [dual inlet intro](inst/doc/dual_inlet_intro.Rmd)** and the resulting [HTML output](https://rawgit.com/sebkopf/isoread/master/inst/doc/dual_inlet_intro.html)! + +## Development + +If you have use cases for **isoread** that are not currently supported, please make use of the [Issue Tracker](https://github.com/sebkopf/isoread/issues) to collect feature ideas, expansion requests, and of course bug reports. If you are interested in helping with development, that's fantastic! Please fork the repository and branch off from the [dev branch](https://github.com/sebkopf/isoread/tree/dev) since it contains the most up-to-date development version of **isoread**. Make sure to write [```testthat``` tests](http://r-pkgs.had.co.nz/tests.html) for your work (stored in the tests/testthat directory). All tests can be run automatically and continuously during development to make it easier to spot any code problems on the go. The easiest way to run them is by running ```make autotest``` in the **isoread** directory from command line (it will test everything automatically in a completely separate R session). diff --git a/inst/doc/continuous_flow_intro.Rmd b/inst/doc/continuous_flow_intro.Rmd new file mode 100644 index 0000000..25ed929 --- /dev/null +++ b/inst/doc/continuous_flow_intro.Rmd @@ -0,0 +1,98 @@ +--- +title: "Continuous Flow Intro" +output: html_document +--- + +## Installation (not run) + +```{r, eval=FALSE} +library(devtools) +install_github('isoread', 'sebkopf') +``` + +## Reading a file + +Here, we read a simple isodat file that is provided as an example in the module. **isoread** takes all the information directly from the binary, which makes it easy to record each step of what is happening with the data. + +```{r load} +library(isoread) +file <- isoread( + system.file("extdata", "6520__F8-5_5uL_isodat2.cf", package="isoread"), + type = "H_CSIA") +``` + +## Chromatographic data + +The *file* variable now contains an isoread object with all the information from the binary file and we can take a look at the chromatographic data in the object, here we look at the first 10 lines (using the k-table or kable command from the knitr package for table output): + +```{r show-data, results='asis'} +library(knitr) +kable(head(file$get_mass_data(), n = 10)) +``` + +### Plot Chromatogram + +For convenience, **isoread** also implements several plotting functions based on standard ```plot``` as well as the ```ggplot``` module so we can have a look at the whole chromatograms: + +```{r ggplot, fig.width=10, fig.height=7} +file$make_ggplot() +``` + +Notice that **isoread** plots all masses and ratios by default and labels the peaks with their peak numbers (reference peaks are marked with *). The plotting functions are of course a lot more flexible and we can use isoread functionality to plot just a specific time window of the mass trace chromatogram, and switch the time units to minutes instead of seconds as illustrated below: + +```{r} +file$plot_masses(tlim = c(12.3, 12.6), tunits = "min") +``` + +## File information + +Since **isoread** has access to the original raw binary data file, it can extract other parameters stored with the data, here shown with the example of the H3factor registered as the most current during the analysis: + +```{r, results='asis'} +kable(file$get_info("H3factor")) +``` + +## Peak table + +The table of peaks detected by isodat during the analysis or added by the user later on are also directly accessible. The complete set of 29 columns is available through **isoread**, here a small subset of key components: + +```{r, results='asis'} +kable( +subset(file$get_peak_table(), select = c("Peak Nr.", "Status", + "Ref. Peak", "Component", "Rt", "Start", "End", "Ampl. 2", + "d 2H/1H"))) +``` + +Currently, none of the Components in this peak table are identified, but we can generate a mapping file that identifies which component comes out approximately at which retention time. A simple mapping table, which identifies peaks by retention time, could look like this (here only for 2 components): + +```{r, results='asis'} +map <- data.frame(Rt = c(940, 1135), Component = c("C16:0 FAME", "C18:0 FAME"), stringsAsFactors=F) +kable(map) +``` + +Typically, one would maintain this information for example in an excel file and load it directly from there. The map can then be applied to the peak table by **isoread**, which makes the identified peaks accessible by name: + +```{r, results='asis'} +file$map_peaks(map) +kable( +file$get_peak_by_name(c("C16:0 FAME", "C18:0 FAME"), + select = c("Peak Nr.", "Component", "Rt", "Start", "End", "Ampl. 2", "d 2H/1H"))) +``` + +Lastly, the delta value reported in column *d 2H/1H* is automatically loaded as a delta value object using [**isotopia**](http://sebkopf.github.io/isotopia/) and can be used accordingly with all the functionality from **isotopia**. For a simple example, conversion to a fractional abundance (and switch to percent notation): + +```{r} +library(isotopia) +d <- file$get_peak_by_name(c("C16:0 FAME", "C18:0 FAME"), select = "d 2H/1H") +print(d) +print(switch_notation(to_abundance(d), "percent")) +``` + +## Extensions + +Having this information available of course opens various possibilities for the implementation of useful features that are specific to the data. For example, an overview of how consistent the reference peaks in a run were is helpful for determining if one of them might be offset by an overlapping analyte or contaminant. This is implement in **isoread** by the plot_refs() functionality: + +```{r} +file$plot_refs() +``` + diff --git a/inst/doc/continuous_flow_intro.html b/inst/doc/continuous_flow_intro.html new file mode 100644 index 0000000..d0e43db --- /dev/null +++ b/inst/doc/continuous_flow_intro.html @@ -0,0 +1,553 @@ + + + + +
+ + + + + + + + +library(devtools)
+install_github('isoread', 'sebkopf', ref = "dev")
+Here, we read a simple isodat file that is provided as an example in the module. isoread takes all the information directly from the binary, which makes it easy to record each step of what is happening with the data.
+library(isoread)
+## Loading required package: plyr
+## Loading required package: reshape2
+## Loading required package: ggplot2
+## Loading required package: isotopia
+file <- isoread(
+ system.file("extdata", "6520__F8-5_5uL_isodat2.cf", package="isoread"),
+ type = "H_CSIA")
+## Reading file /Library/Frameworks/R.framework/Versions/3.1/Resources/library/isoread/extdata/6520__F8-5_5uL_isodat2.cf
+The file variable now contains an isoread object with all the information from the binary file and we can take a look at the chromatographic data in the object, here we look at the first 10 lines (using the k-table or kable command from the knitr package for table output):
+library(knitr)
+kable(head(file$get_mass_data(), n = 10))
+time | +mass2 | +mass3 | +time.s | +time.min | +mass2.offset | +mass3.offset | +
---|---|---|---|---|---|---|
0.209 | +194.6 | +60.02 | +0.209 | +0.0035 | +394.6 | +60.02 | +
0.418 | +194.5 | +60.05 | +0.418 | +0.0070 | +394.5 | +60.05 | +
0.627 | +194.5 | +60.21 | +0.627 | +0.0104 | +394.5 | +60.21 | +
0.836 | +194.6 | +59.92 | +0.836 | +0.0139 | +394.6 | +59.92 | +
1.045 | +194.6 | +59.72 | +1.045 | +0.0174 | +394.6 | +59.72 | +
1.254 | +194.5 | +59.70 | +1.254 | +0.0209 | +394.5 | +59.70 | +
1.463 | +194.5 | +59.59 | +1.463 | +0.0244 | +394.5 | +59.59 | +
1.672 | +194.5 | +59.72 | +1.672 | +0.0279 | +394.5 | +59.72 | +
1.881 | +194.5 | +59.74 | +1.881 | +0.0314 | +394.5 | +59.74 | +
2.090 | +194.5 | +59.74 | +2.090 | +0.0348 | +394.5 | +59.74 | +
For convenience, isoread also implements several plotting functions based on standard plot
as well as the ggplot
module so we can have a look at the whole chromatograms:
file$make_ggplot()
+
+Notice that isoread plots all masses and ratios by default and labels the peaks with their peak numbers (reference peaks are marked with *). The plotting functions are of course a lot more flexible and we can use isoread functionality to plot just a specific time window of the mass trace chromatogram, and switch the time units to minutes instead of seconds as illustrated below:
+file$plot_masses(tlim = c(12.3, 12.6), tunits = "min")
+
+Since isoread has access to the original raw binary data file, it can extract other parameters stored with the data, here shown with the example of the H3factor registered as the most current during the analysis:
+kable(file$get_info("H3factor"))
++ | Property | +Value | +
---|---|---|
11 | +H3factor | +2.79431047797221 | +
The table of peaks detected by isodat during the analysis or added by the user later on are also directly accessible. The complete set of 29 columns is available through isoread, here a small subset of key components:
+kable(
+subset(file$get_peak_table(), select = c("Peak Nr.", "Status",
+ "Ref. Peak", "Component", "Rt", "Start", "End", "Ampl. 2",
+ "d 2H/1H")))
+Peak Nr. | +Status | +Ref. Peak | +Component | +Rt | +Start | +End | +Ampl. 2 | +d 2H/1H | +
---|---|---|---|---|---|---|---|---|
1 | +Auto | +FALSE | +- | +286.3 | +283.4 | +293.0 | +3978 | +-160.9 | +
2 | +Auto | +FALSE | +- | +321.2 | +318.3 | +327.9 | +3979 | +-160.4 | +
3 | +Auto | +FALSE | +- | +612.0 | +606.3 | +634.9 | +4993 | +-154.2 | +
4 | +Auto | +TRUE | +- | +671.5 | +666.1 | +699.3 | +4906 | +-151.9 | +
5 | +Auto | +FALSE | +- | +747.8 | +740.7 | +768.1 | +5227 | +-218.1 | +
6 | +Auto | +FALSE | +- | +809.5 | +801.5 | +829.3 | +5044 | +-210.4 | +
7 | +Auto | +TRUE | +- | +860.7 | +855.4 | +889.5 | +4129 | +-151.9 | +
8 | +Auto | +FALSE | +- | +936.5 | +927.8 | +961.6 | +4534 | +-155.5 | +
9 | +Auto | +FALSE | +- | +1002.2 | +993.4 | +1023.1 | +4354 | +-198.1 | +
10 | +Auto | +TRUE | +- | +1055.0 | +1049.0 | +1086.0 | +4070 | +-151.9 | +
11 | +Auto | +FALSE | +- | +1135.9 | +1126.7 | +1154.3 | +4377 | +-189.5 | +
12 | +Auto | +FALSE | +- | +1201.3 | +1191.9 | +1223.1 | +4384 | +-207.9 | +
13 | +Auto | +TRUE | +- | +1249.4 | +1244.2 | +1283.1 | +4160 | +-151.9 | +
14 | +Auto | +FALSE | +- | +1333.6 | +1324.4 | +1356.2 | +4316 | +-168.1 | +
15 | +Auto | +FALSE | +- | +1395.3 | +1386.3 | +1416.8 | +3706 | +-193.3 | +
16 | +Auto | +TRUE | +- | +1459.4 | +1453.6 | +1490.2 | +4183 | +-151.9 | +
17 | +Auto | +FALSE | +- | +1608.7 | +1600.9 | +1636.5 | +4303 | +-154.3 | +
18 | +Auto | +FALSE | +- | +1739.7 | +1736.4 | +1746.2 | +3974 | +-160.1 | +
19 | +Auto | +FALSE | +- | +1779.4 | +1776.7 | +1786.1 | +3972 | +-160.6 | +
Currently, none of the Components in this peak table are identified, but we can generate a mapping file that identifies which component comes out approximately at which retention time. A simple mapping table, which identifies peaks by retention time, could look like this (here only for 2 components):
+map <- data.frame(Rt = c(940, 1135), Component = c("C16:0 FAME", "C18:0 FAME"), stringsAsFactors=F)
+kable(map)
+Rt | +Component | +
---|---|
940 | +C16:0 FAME | +
1135 | +C18:0 FAME | +
Typically, one would maintain this information for example in an excel file and load it directly from there. The map can then be applied to the peak table by isoread, which makes the identified peaks accessible by name:
+file$map_peaks(map)
+kable(
+file$get_peak_by_name(c("C16:0 FAME", "C18:0 FAME"),
+ select = c("Peak Nr.", "Component", "Rt", "Start", "End", "Ampl. 2", "d 2H/1H")))
++ | Peak Nr. | +Component | +Rt | +Start | +End | +Ampl. 2 | +d 2H/1H | +
---|---|---|---|---|---|---|---|
8 | +8 | +C16:0 FAME | +936.5 | +927.8 | +961.6 | +4534 | +-155.5 | +
11 | +11 | +C18:0 FAME | +1135.9 | +1126.7 | +1154.3 | +4377 | +-189.5 | +
Lastly, the delta value reported in column d 2H/1H is automatically loaded as a delta value object using isotopia and can be used accordingly with all the functionality from isotopia. For a simple example, conversion to a fractional abundance (and switch to percent notation):
+library(isotopia)
+d <- file$get_peak_by_name(c("C16:0 FAME", "C18:0 FAME"), select = "d 2H/1H")
+print(d)
+## An isotope value object of type 'Delta value': d2H [permil] vs. VSMOW
+## [1] -155.5 -189.5
+print(switch_notation(to_abundance(d), "percent"))
+## An isotope value object of type 'Abundance value': F 2H [%]
+## [1] 0.01315 0.01262
+Having this information available of course opens various possibilities for the implementation of useful features that are specific to the data. For example, an overview of how consistent the reference peaks in a run were is helpful for determining if one of them might be offset by an overlapping analyte or contaminant. This is implement in isoread by the plot_refs() functionality:
+file$plot_refs()
+
+library(devtools)
+install_github('isoread', 'sebkopf')
+library(isoread)
+## Loading required package: plyr
+## Loading required package: reshape2
+## Loading required package: ggplot2
+## Loading required package: isotopia
+file <- isoread(system.file("extdata", "dual_inlet_clumped_carbonate.did", package="isoread"), type = "CO2_CLUMPED")
+## Reading file /Library/Frameworks/R.framework/Versions/3.1/Resources/library/isoread/extdata/dual_inlet_clumped_carbonate.did
+library(knitr)
+kable(file$get_mass_data())
+analysis | +cycle | +mass44 | +mass45 | +mass46 | +mass47 | +mass48 | +mass49 | +
---|---|---|---|---|---|---|---|
Standard | +1 | +15941 | +18996 | +21954 | +2512 | +29.80 | +-181.0 | +
Standard | +2 | +15934 | +18987 | +21944 | +2511 | +29.82 | +-180.8 | +
Standard | +3 | +15917 | +18966 | +21920 | +2508 | +29.78 | +-180.5 | +
Standard | +4 | +15902 | +18949 | +21899 | +2506 | +29.76 | +-180.2 | +
Standard | +5 | +15896 | +18942 | +21891 | +2506 | +29.76 | +-180.3 | +
Standard | +6 | +15885 | +18929 | +21876 | +2504 | +29.73 | +-180.2 | +
Standard | +7 | +15876 | +18918 | +21864 | +2502 | +29.70 | +-180.0 | +
Sample | +1 | +15955 | +19123 | +22238 | +2559 | +31.09 | +-181.2 | +
Sample | +2 | +15946 | +19111 | +22225 | +2558 | +31.09 | +-181.0 | +
Sample | +3 | +15926 | +19088 | +22197 | +2554 | +31.07 | +-180.7 | +
Sample | +4 | +15911 | +19070 | +22176 | +2552 | +31.02 | +-180.5 | +
Sample | +5 | +15910 | +19068 | +22175 | +2552 | +31.03 | +-180.3 | +
Sample | +6 | +15913 | +19072 | +22178 | +2552 | +31.04 | +-180.5 | +
Sample | +7 | +15914 | +19073 | +22181 | +2553 | +31.06 | +-180.4 | +
Standard | +0 | +15946 | +19002 | +21961 | +2513 | +29.79 | +-181.3 | +
file$make_ggplot()
+
+file$make_ggplot(masses = c("mass44", "mass47"))
+
+The entire table of processed data.
+kable(file$get_data_table())
+cycle | +d 45CO2/44CO2 | +d 46CO2/44CO2 | +d13C | +d18O | +d17O | +at% 13C | +at% 18O | +
---|---|---|---|---|---|---|---|
1 | +3.329 | +37.33 | +2.193 | +37.37 | +6.202 | +1.108 | +0.2076 | +
2 | +3.321 | +37.31 | +2.185 | +37.35 | +6.193 | +1.108 | +0.2076 | +
3 | +3.326 | +37.32 | +2.191 | +37.35 | +6.196 | +1.108 | +0.2076 | +
4 | +3.320 | +37.32 | +2.184 | +37.35 | +6.196 | +1.108 | +0.2076 | +
5 | +3.319 | +37.33 | +2.182 | +37.37 | +6.202 | +1.108 | +0.2076 | +
6 | +3.318 | +37.32 | +2.182 | +37.36 | +6.198 | +1.108 | +0.2076 | +
7 | +3.322 | +37.32 | +2.186 | +37.35 | +6.196 | +1.108 | +0.2076 | +
kable(file$get_data_table(summarize = TRUE))
+Variable | +Mean | +Std. Devi. | +Std. Error. | +
---|---|---|---|
d 45CO2/44CO2 | +3.3220 | +0.0040 | +0.0015 | +
d 46CO2/44CO2 | +37.3212 | +0.0070 | +0.0026 | +
d13C | +2.1861 | +0.0043 | +0.0016 | +
d18O | +37.3570 | +0.0070 | +0.0026 | +
d17O | +6.1976 | +0.0035 | +0.0013 | +
at% 13C | +1.1080 | +0.0000 | +0.0000 | +
at% 18O | +0.2076 | +0.0000 | +0.0000 | +
kable(file$get_data_table(select = c("d13C", "d18O"), sum = T))
+Variable | +Mean | +Std. Devi. | +Std. Error. | +
---|---|---|---|
d13C | +2.186 | +0.0043 | +0.0016 | +
d18O | +37.357 | +0.0070 | +0.0026 | +
And whatever other information was pulled out of the file.
+kable(file$get_info())
+Property | +Value | +
---|---|
File location | +/Library/Frameworks/R.framework/Versions/3.1/Resources/library/isoread/extdata/dual_inlet_clumped_carbonate.did | +
Date | +2014-11-16 15:23:29 | +
Info_Peak | +Peak Center found at [61032] | +
Info_Background | +Background: 8.87 mV,11.31 mV,12.98 mV,6.40 mV,1.90 mV,5.88 mV (old253) | +
Info_PressAdjust | +PressAdjust: L: 15972.5 R: 15971.6 ( Manual Adjustment ) | +
Line | +158 | +
Peak Center | +1 | +
Pressadjust | +1 | +
Background | +1 | +
Identifier 1 | +CIT Carrara | +
Identifier 2 | +13 | +
Analysis | +49077 | +
Comment | ++ |
Preparation | ++ |
Post Script | ++ |
Method | +CO2_multiply_16V.met | +