Skip to content

Commit

Permalink
add csv writing.
Browse files Browse the repository at this point in the history
  • Loading branch information
wincowgerDEV committed Jan 4, 2024
1 parent 2abf6f5 commit c81fa83
Show file tree
Hide file tree
Showing 2 changed files with 31 additions and 6 deletions.
17 changes: 15 additions & 2 deletions R/io_spec.R
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@
#' write_spec(raman_hdpe, "raman_hdpe.yml")
#' write_spec(raman_hdpe, "raman_hdpe.json")
#' write_spec(raman_hdpe, "raman_hdpe.rds")
#' write_spec(raman_hdpe, "raman_hdpe.csv")
#'
#' # Convert an OpenSpecy object to a hyperSpec object
#' hyper <- as_hyperSpec(raman_hdpe)
Expand All @@ -61,7 +62,7 @@
#'
#' @importFrom yaml write_yaml read_yaml
#' @importFrom jsonlite write_json read_json
#' @importFrom data.table as.data.table
#' @importFrom data.table as.data.table fwrite
#'
#' @export
write_spec <- function(x, ...) {
Expand All @@ -88,7 +89,19 @@ write_spec.OpenSpecy <- function(x, file, method = NULL,
write_json(x, path = file, dataframe = "columns", digits = digits, ...)
} else if (grepl("\\.rds$", file, ignore.case = T)) {
saveRDS(x, file = file, ...)
} else {
}
else if (grepl("\\.csv$", file, ignore.case = T)){
wave_names <- round(x$wavenumber, 0)

spectra <- t(x$spectra)

colnames(spectra) <- wave_names

flat_specy <- cbind(spectra, x$metadata)

fwrite(flat_specy, file = file)
}
else {
stop("unknown file type: specify a method to write custom formats or ",
"provide one of the supported .yml, .json, or .rds formats as ",
"file extension", call. = F)
Expand Down
20 changes: 16 additions & 4 deletions R/read_ext.R
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@
#' \code{\link{read_zip}()} and \code{\link{read_any}()} for wrapper functions;
#' \code{\link[hyperSpec]{read.jdx}()}; \code{\link[hyperSpec]{read.spc}()}
#'
#' @importFrom data.table data.table as.data.table fread
#' @importFrom data.table data.table as.data.table fread transpose
#' @export
read_text <- function(file, colnames = NULL, method = "fread",
share = NULL,
Expand Down Expand Up @@ -91,9 +91,21 @@ read_text <- function(file, colnames = NULL, method = "fread",
"use 'header = FALSE' or an ",
"alternative read method",
call. = F)

os <- as_OpenSpecy(dt, colnames = colnames, metadata = metadata,
session_id = T)
if(sum(grepl("^[0-9]{1,}$",colnames(dt))) > 4){
wavenumbers <- colnames(dt)[grepl("^[0-9]{1,}$",colnames(dt))]

spectra <- transpose(dt[,..wavenumbers])

metadata_names <- colnames(dt)[!grepl("^[0-9]{1,}$",colnames(dt))]

metadata <- dt[,..metadata_names]

os <- as_OpenSpecy(as.numeric(wavenumbers), spectra = spectra, metadata = metadata)
}
else{
os <- as_OpenSpecy(dt, colnames = colnames, metadata = metadata,
session_id = T)
}

if (!is.null(share)) share_spec(os, file = file, share = share)

Expand Down

0 comments on commit c81fa83

Please sign in to comment.