Skip to content

Commit

Permalink
add better spa file reading, fix duplicate metadata name issue, add test
Browse files Browse the repository at this point in the history
  • Loading branch information
wincowgerDEV committed Nov 24, 2024
1 parent ab372be commit 3aed982
Show file tree
Hide file tree
Showing 3 changed files with 63 additions and 31 deletions.
17 changes: 16 additions & 1 deletion R/as_OpenSpecy.R
Original file line number Diff line number Diff line change
Expand Up @@ -322,7 +322,22 @@ as_OpenSpecy.default <- function(x, spectra,
stop("inconsistent input for 'metadata'", call. = F)
}
}


if(any(duplicated(names(obj$metadata)))){
message("Duplicate column names found, adding a unique numeric ID to the end.")
nms <- names(obj$metadata)
# Identify all names that are duplicated
dups <- duplicated(nms) | duplicated(nms, fromLast = TRUE)
# Initialize a vector to hold the counts
counts <- rep(NA, length(nms))
# For duplicated names, generate sequence numbers starting from 0
counts[dups] <- ave(seq_along(nms)[dups], nms[dups], FUN = function(x) seq_along(x) - 0)
# Create new names by appending counts to duplicated names
new_nms <- nms
new_nms[dups] <- paste0(nms[dups], "_", counts[dups] - 1)
# Update the names in os$metadata
names(obj$metadata) <- new_nms
}
return(obj)
}

Expand Down
67 changes: 37 additions & 30 deletions R/read_ext.R
Original file line number Diff line number Diff line change
Expand Up @@ -204,36 +204,43 @@ read_spa <- function(file,
if (!grepl("\\.spa$", ignore.case = T, file))
stop("file type should be 'spa'", call. = F)

trb <- file.path(file) |> file(open = "rb", ...)

seek(trb, 576, origin = "start")
spr <- readBin(trb, "numeric", n = 2, size = 4)

if (!all(spr >= 0 & spr <= 15000 & spr[1] > spr[2]))
stop("unknown spectral range", call. = F)

# Read the start offset
seek(trb, 386, origin = "start")
startOffset <- readBin(trb, "int", n = 1, size = 2)
# Read the length
seek(trb, 390, origin = "start")
readLength <- readBin(trb, "int", n = 1, size = 2)

# seek to the start
seek(trb, startOffset, origin = "start")

# we'll read four byte chunks
floatCount <- readLength / 4

# read all our floats
floatData <- c(readBin(trb, "double", floatCount, size = 4))

close(trb)

x <- seq(spr[1], spr[2], length = length(floatData))
y <- floatData

os <- as_OpenSpecy(x, data.table(intensity = y), metadata = metadata,
# Read a *.spa file
# Returns:
# A list containing Spectra, Wavelengths (nm), and Titles
# Converted to r from https://github.com/lerkoah/spa-on-python/blob/master/LoadSpectrum.py
con <- file(file, "rb", ...) # Open the file in binary mode
on.exit(close(con)) # Ensure the file is closed

seek(con, where = 564, rw = "r")
Spectrum_Pts <- readBin(con, integer(), size = 4, n = 1, endian = "little")

seek(con, where = 30, rw = "r")
SpectraTitlesRaw <- readBin(con, raw(), n = 255)
SpectraTitles <- rawToChar(SpectraTitlesRaw[SpectraTitlesRaw != as.raw(0)])

seek(con, where = 576, rw = "r")
Max_Wavenum <- readBin(con, numeric(), size = 4, n = 1, endian = "little")
Min_Wavenum <- readBin(con, numeric(), size = 4, n = 1, endian = "little")

# Generate wavenumbers
Wavenumbers <- rev(seq(Min_Wavenum, Max_Wavenum, length.out = Spectrum_Pts))

seek(con, where = 288, rw = "r")

Flag <- 0
while (Flag != 3) {
Flag <- readBin(con, integer(), size = 2, n = 1, endian = "little")
}

DataPosition <- readBin(con, integer(), size = 2, n = 1, endian = "little")
seek(con, where = DataPosition, rw = "r")

Spectra <- readBin(con, numeric(), size = 4, n = Spectrum_Pts, endian = "little")

# Return the results
metadata$title <- SpectraTitles

os <- as_OpenSpecy(Wavenumbers, data.table(intensity = Spectra), metadata,
session_id = T)

return(os)
Expand Down
10 changes: 10 additions & 0 deletions tests/testthat/test-as_OpenSpecy.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,16 @@ test_that("as_OpenSpecy() handles errors correctly", {
intensity = df$intensity)) |>
expect_error()

as_OpenSpecy(df, metadata = list(file_name = "test",
file_name = "test",
fun_val = "t",
check = "c",
check = "a",
check = "a")) |>
check_OpenSpecy() |>
expect_true() |>
expect_message()

as_OpenSpecy(data.frame(x = df$wavenumber, abs = df$intensity)) |>
expect_message()
as_OpenSpecy(data.frame(wav = df$wavenumber, y = df$intensity)) |>
Expand Down

0 comments on commit 3aed982

Please sign in to comment.