Skip to content

Commit

Permalink
docs: update docs, added explanatory comments to internal fncs
Browse files Browse the repository at this point in the history
  • Loading branch information
ethanbass committed Dec 24, 2023
1 parent 1c18870 commit 7885ccf
Show file tree
Hide file tree
Showing 12 changed files with 85 additions and 36 deletions.
13 changes: 7 additions & 6 deletions R/call_openchrom.R
Original file line number Diff line number Diff line change
Expand Up @@ -34,12 +34,12 @@
#' @param return_paths Logical. If TRUE, the function will return a character
#' vector of paths to the newly created files.
#' @param verbose Logical. Whether to print output from OpenChrom to the console.
#' @return If \code{return_paths} is \code{FALSE}, the function will return a list of
#' chromatograms (if an appropriate parser is available in chromConverter). The
#' chromatograms will be returned in \code{matrix} or \code{data.frame} format
#' according to the value of {data_class}. If \code{return_paths} is \code{TRUE},
#' the function will return a character vector of paths to the newly created
#' files.
#' @return If \code{return_paths} is \code{FALSE}, the function will return a
#' list of chromatograms (if an appropriate parser is available to import the
#' files into R). The chromatograms will be returned in \code{matrix} or
#' \code{data.frame} format according to the value of {format_out}. If
#' \code{return_paths} is \code{TRUE}, the function will return a character
#' vector of paths to the newly created files.
#' @section Side effects: Chromatograms will be exported in the format specified
#' by \code{export_format} in the folder specified by \code{path_out}.
#' @author Ethan Bass
Expand Down Expand Up @@ -98,6 +98,7 @@ call_openchrom <- function(files, path_out = NULL, format_in,
}

#' Writes OpenChrom XML batch file
#' This function is called internally by \code{call_openchrom}.
#' @import xml2
#' @import magrittr
#' @param files Paths to files for conversion
Expand Down
9 changes: 9 additions & 0 deletions R/call_rainbow.R
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,9 @@ call_rainbow <- function(file,
xx
}

#' Extract data with rainbow
#' This function is called internally by \code{call_rainbow}.
#' @author Ethan Bass
#' @noRd
extract_rb_data <- function(xx, format_out = "matrix",
data_format = c("wide", "long"),
Expand All @@ -111,13 +114,17 @@ extract_rb_data <- function(xx, format_out = "matrix",
data
}

#' Extract 'rainbow' element names.
#' This function is called internally by \code{call_rainbow}.
#' @noRd
extract_rb_names <- function(xx){
sapply(xx, function(xxx){
xxx$name
})
}

#' Assign 'rainbow' read
#' This function is called internally by \code{call_rainbow}.
#' @noRd
assign_rb_read <- function(){
pos <- 1
Expand All @@ -126,6 +133,8 @@ assign_rb_read <- function(){
assign("rb_parse_agilent", reticulate::import("rainbow.agilent"), envir = envir)
}

#' Check 'rainbow' configuration
#' This function is called internally by \code{call_rainbow}.
#' @noRd
check_rb_configuration <- function(){
assign_rb_read()
Expand Down
10 changes: 7 additions & 3 deletions R/read_chemstation_ch.R
Original file line number Diff line number Diff line change
Expand Up @@ -163,16 +163,18 @@ get_chemstation_dir_name <- function(path){
grep("\\.D|\\.d$", sp, ignore.case = TRUE, value = TRUE)
}

#' Get number of characters for Agilent segment
#' @noRd
get_nchar <- function(f){
as.numeric(readBin(f, what = "raw", n = 1))
}

#' Decode double delta array
#' @noRd
#' @note This function was adapted from the
#' \href{https://github.com/chemplexity/chromatography}{Chromatography Toolbox}
#' ((c) James Dillon 2014).
#' @noRd

decode_double_delta <- function(file, offset) {

seek(file, 0, 'end')
Expand Down Expand Up @@ -208,10 +210,11 @@ decode_double_delta <- function(file, offset) {
}

#' Decode double array
#' @noRd
#' @note This function was adapted from the
#' \href{https://github.com/chemplexity/chromatography}{Chromatography Toolbox}
#' ((c) James Dillon 2014).
#' @noRd

decode_double_array_4byte <- function(file, offset) {
seek(file, 0, 'end')
fsize <- seek(file, NA, "current")
Expand All @@ -238,10 +241,11 @@ decode_double_array_8byte <- function(file, offset) {
}

#' Decode delta array
#' @noRd
#' @note This function was adapted from the
#' \href{https://github.com/chemplexity/chromatography}{Chromatography Toolbox}
#' ((c) James Dillon 2014).
#' @noRd

decode_delta <- function(file, offset) {
seek(file, 0, 'end')
fsize <- seek(file, NA, "current")
Expand Down
1 change: 1 addition & 0 deletions R/read_chemstation_report.R
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,7 @@ convert_chemstation_peaklist <- function(table, data_format =
}

#' Remove blank lines
#' This function is called internally by \code{read_chemstation_reports}.
#' @noRd
remove_blank_lines <- function(x){
x[which(x != "")]
Expand Down
1 change: 1 addition & 0 deletions R/read_mdf.R
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,7 @@ read_mdf <- function(file, format_out = c("matrix","data.frame"),
}

#' Extract MDF metadata
#' This function is called internally by \code{read_mdf}.
#' @author Ethan Bass
#' @noRd
extract_mdf_metadata <- function(x){
Expand Down
18 changes: 17 additions & 1 deletion R/read_shimadzu_ascii.R
Original file line number Diff line number Diff line change
Expand Up @@ -143,6 +143,9 @@ read_shimadzu <- function(file, what = "chromatogram",
xx
}

#' Convert list of mass spectra to data.frame
#' This function is called internally by \code{read_shimadzu}.
#' @author Ethan Bass
#' @noRd
ms_list_to_dataframe <- function(x){
if (!is.null(names(x))){
Expand All @@ -156,7 +159,10 @@ ms_list_to_dataframe <- function(x){
}
as.data.frame(do.call(rbind, ms))
}
#' Read Shimadzu Metadata

#' Read 'Shimadzu' Metadata
#' This function is called internally by \code{read_shimadzu}.
#' @author Ethan Bass
#' @noRd
read_shimadzu_metadata <- function(x, met = NULL, sep){

Expand All @@ -181,6 +187,8 @@ read_shimadzu_metadata <- function(x, met = NULL, sep){
}

#' Read Shimadzu Chromatogram
#' This function is called internally by \code{read_shimadzu}.
#' @author Ethan Bass
#' @noRd
read_shimadzu_chromatogram <- function(file, x, chrom.idx, sep, data_format,
read_metadata, format_out){
Expand Down Expand Up @@ -221,6 +229,8 @@ read_shimadzu_chromatogram <- function(file, x, chrom.idx, sep, data_format,
}

#' Read Shimadzu DAD Array
#' This function is called internally by \code{read_shimadzu}.
#' @author Ethan Bass
#' @noRd
read_shimadzu_dad <- function(file, x, chrom.idx, sep, data_format,
read_metadata, format_out){
Expand Down Expand Up @@ -258,6 +268,8 @@ read_shimadzu_dad <- function(file, x, chrom.idx, sep, data_format,
}

#' Read Shimadzu Peak Table
#' This function is called internally by \code{read_shimadzu}.
#' @author Ethan Bass
#' @noRd
read_shimadzu_peaktable <- function(file, x, idx, sep, format_in, format_out){
nrows <- as.numeric(strsplit(x = x[idx + 1], split = sep)[[1]][2])
Expand All @@ -283,6 +295,8 @@ read_shimadzu_peaktable <- function(file, x, idx, sep, format_in, format_out){
}

#' Read Shimadzu MS Spectrum
#' This function is called internally by \code{read_shimadzu}.
#' @author Ethan Bass
#' @noRd
read_shimadzu_spectrum <- function(file, x, idx, sep){
nrows <- as.numeric(strsplit(x = x[idx + 1], split = sep)[[1]][2])
Expand All @@ -295,6 +309,8 @@ read_shimadzu_spectrum <- function(file, x, idx, sep){
}

#' Extract Header from Shimadzu ASCII Files
#' This function is called internally by \code{read_shimadzu}.
#' @author Ethan Bass
#' @noRd
extract_shimadzu_header <- function(x, chrom.idx, sep){
index <- chrom.idx + 1
Expand Down
43 changes: 26 additions & 17 deletions R/read_shimadzu_lcd.R
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,10 @@
#' @param data_format Either \code{wide} (default) or \code{long}.
#' @param read_metadata Logical. Whether to attach metadata.
#' @author Ethan Bass
#' @return A 3D chromatogram from the PDA stream in \code{matrix} or
#' \code{data.frame} format, according to the value of \code{format_out}.
#' The chromatograms will be returned in \code{wide} or \code{long} format
#' according to the value of \code{data_format}.
#' @note This parser is experimental and may still
#' need some work. It is not yet able to interpret much metadata from the files.
#' @export
Expand Down Expand Up @@ -75,6 +79,7 @@ read_shimadzu_lcd <- function(path, format_out = c("matrix", "data.frame"),
}

#' Read Shimadzu "Method" stream
#' This function is called internally by \code{read_shimadzu_lcd}.
#' @author Ethan Bass
#' @noRd
read_sz_method <- function(path){
Expand Down Expand Up @@ -110,6 +115,7 @@ read_sz_method <- function(path){
}

#' Infer times from 'Shimadzu' Method stream
#' This function is called internally by \code{read_shimadzu_lcd}.
#' @author Ethan Bass
#' @noRd
get_sz_times <- function(sz_method, nval){
Expand Down Expand Up @@ -151,6 +157,7 @@ read_shimadzu_raw <- function(path, n_lambdas = NULL){
}

#' Export OLE stream
#' This function is called internally by \code{read_shimadzu_lcd}.
#' Use olefile to export te specified stream.
#' @param file Path to ole file.
#' @author Ethan Bass
Expand Down Expand Up @@ -183,7 +190,25 @@ export_stream <- function(path_in, stream, path_out, remove_null_bytes = FALSE,
}
}

#' Extract wavelengths from Shimadzu LCD
#' This function is called internally by \code{read_shimadzu_lcd}.
#' @author Ethan Bass
#' @noRd
read_shimadzu_wavelengths <- function(path){
path_wavtab <- export_stream(path, stream = c("PDA 3D Raw Data", "Wavelength Table"))
f <- file(path_wavtab, "rb")
on.exit(close(f))
n_lambda <- readBin(f, what="integer", size = 4)
count <- 1
# lambdas <- numeric(n_lambda)
lambdas <- sapply(seq_len(n_lambda), function(i){
readBin(f, what="integer", size = 4)/100
})
lambdas
}

#' Read 'Shimadzu' LCD data block
#' This function is called internally by \code{read_shimadzu_lcd}.
#' @author Ethan Bass
#' @noRd
decode_shimadzu_block <- function(file) {
Expand Down Expand Up @@ -236,6 +261,7 @@ decode_shimadzu_block <- function(file) {
}

#' Return twos complement from binary string
#' This function is called internally by \code{read_shimadzu_lcd}.
#' @noRd
twos_complement <- function(bin, exp){
if (missing(exp)){
Expand Down Expand Up @@ -277,20 +303,3 @@ integer_to_binary <- function(x, n) {
# Return
x
}

#' Extract wavelengths from Shimadzu LCD
#' @author Ethan Bass
#' @noRd
read_shimadzu_wavelengths <- function(path){
path_wavtab <- export_stream(path, stream = c("PDA 3D Raw Data", "Wavelength Table"))
f <- file(path_wavtab, "rb")
on.exit(close(f))
n_lambda <- readBin(f, what="integer", size = 4)
count <- 1
# lambdas <- numeric(n_lambda)
lambdas <- sapply(seq_len(n_lambda), function(i){
readBin(f, what="integer", size = 4)/100
})
lambdas
}

1 change: 1 addition & 0 deletions R/read_thermoraw.R
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,7 @@ read_thermoraw <- function(path_in, path_out = NULL,
#' @return No return value.
#' @author Ethan Bass
#' @noRd

configure_thermo_parser <- function(reconfigure = FALSE, check = FALSE){
if (.Platform$OS.type == "windows"){
path_parser <- readLines(system.file("shell/path_parser.txt", package = 'chromConverter'))
Expand Down
3 changes: 1 addition & 2 deletions R/reshape_chroms.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@

#' Reshapes list of chromatograms from wide to long format
#' @name reshape_chroms
#' @param x A list of chromatographic matrices in wide format.
Expand Down Expand Up @@ -92,7 +91,7 @@ reshape_chrom_long <- function(x, lambdas, format_out = NULL, names_to = "lambda
data
}


#' Reshapes a single chromatogram from long to wide format
#' @noRd
reshape_chrom_wide <- function(x, lambdas, lambda_var = "lambda", time_var="rt",
value_var = "int", drop){
Expand Down
12 changes: 6 additions & 6 deletions man/call_openchrom.Rd

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

6 changes: 6 additions & 0 deletions man/read_shimadzu_lcd.Rd

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

4 changes: 3 additions & 1 deletion man/write_openchrom_batchfile.Rd

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

0 comments on commit 7885ccf

Please sign in to comment.