Skip to content

Commit

Permalink
try an odf flag-detection scheme BUT
Browse files Browse the repository at this point in the history
I think the IML and BIO schemes might differ.  I commented-out my
attempt because it broke the ODF file I use in tests ... but that file
lacks the QQQQ info. In fact, *all* the files I have lack QQQQ info.

dankelley#1808
  • Loading branch information
dankelley committed Apr 20, 2021
1 parent b7424d8 commit effc2b6
Show file tree
Hide file tree
Showing 3 changed files with 30 additions and 8 deletions.
13 changes: 13 additions & 0 deletions 1808a.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
library(oce)
source("R/oce.R")
source("R/odf.R")
source("R/ctd.R")
source("R/ctd.odf.R")
file <- "CTD_1994038_147_1_DN.ODF"
if (!file.exists(file)) {
dir <- "https://raw.githubusercontent.com/cioos-siooc/cioos-siooc_data_transform/odf_transform/projects/odf_transform/sample_data/test_files"
download.file(paste0(dir, "/", file), file)
}
d <- read.ctd.odf(file, debug=3)
message("are these ok for flag names? ", paste(names(d@metadata$flags), collapse=","))

2 changes: 1 addition & 1 deletion R/ctd.odf.R
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@
read.ctd.odf <- function(file, columns=NULL, station=NULL, missingValue, deploymentType="unknown",
monitor=FALSE, exclude=NULL, debug=getOption("oceDebug"), processingLog, ...)
{
oceDebug(debug, "read.ctd.odf(\"", file, "\", ...) {\n", sep="", unindent=1)
oceDebug(debug, "read.ctd.odf(\"", file, "\", ...) {\n", sep="", unindent=1, style="bold")
if (!is.null(columns)) warning("'columns' is ignored by read.ctd.odf() at present")
odf <- read.odf(file=file, columns=columns, exclude=exclude, debug=debug-1)
res <- as.ctd(odf, debug=debug-1)
Expand Down
23 changes: 16 additions & 7 deletions R/odf.R
Original file line number Diff line number Diff line change
Expand Up @@ -972,7 +972,7 @@ read.odf <- function(file, columns=NULL, header="list", exclude=NULL, debug=getO
stop("can only handle one file at a time (the length of 'file' is ", length(file), ", not 1)")
if (is.character(file) && 0 == file.info(file)$size)
stop("the file named '", file, "' is empty, and so cannot be read")
oceDebug(debug, "read.odf(\"", file, "\", exclude=", if (is.null(exclude)) "NULL" else "'", exclude, "', ...) {\n", unindent=1, sep="")
oceDebug(debug, "read.odf(\"", file, "\", exclude=", if (is.null(exclude)) "NULL" else "'", exclude, "', ...) {\n", unindent=1, sep="", style="bold")
if (!is.null(header)) {
if (!is.character(header))
stop("the header argument must be NULL, \"character\", or \"list\"")
Expand Down Expand Up @@ -1110,6 +1110,7 @@ read.odf <- function(file, columns=NULL, header="list", exclude=NULL, debug=getO
ODForiginalNames <- NULL
ODFnames <- NULL
ODFunits <- NULL
flagTranslationTable <- list()
for (l in linePARAMETER_HEADER) {
## message("\nl=", l)
lstart <- l + 1
Expand All @@ -1131,14 +1132,18 @@ read.odf <- function(file, columns=NULL, header="list", exclude=NULL, debug=getO
stop("cannot handle two CODE lines in a PARAMETER_HEADER block starting at line ", lstart-1)
## message("lines[", lstart+iCODE-1, "] is \"", lines[lstart+iCODE-1], "\"")
CODE <- gsub("^\\s*(WMO_)?CODE\\s*=\\s*'?([^',]*)'?,?\\s*$", "\\2", lines[lstart+iCODE-1])
## message(" CODE = \"", CODE, "\"")
if (length(grep("QQQQ", CODE))) {
oceDebug(debug, "CODE \"", CODE, "\" at line ", lstart+iCODE-1, "\n", sep="")
if (grepl("QQQQ", CODE)) {
iNAME <- grep("^\\s*NAME\\s*=\\s*'", lines[lstart:lend])
if (length(iNAME) == 1) {
## Sample input line: " NAME= 'Quality Flag for Parameter: TEMP_01',"
## Sample input lines (two leading spaces):
## NAME= 'Quality Flag for Parameter: TEMP_01',
## NAME= 'Quality flag: Sea Temperature (IPTS-68)',
## NAME <- paste(gsub("^.*:\\s*'?(.*)([_0-9]*)'?.*$", "\\1", lines[lstart+iNAME-1]), "Flag", sep="")
NAME <- paste(gsub(".*:[ ]*([A-Z0-9_]*).*", "\\1", lines[lstart+iNAME-1]), "Flag", sep="")
oceDebug(debug, "quality-control code '", lines[lstart+iNAME-1], "' yielded NAME='", NAME, "'")
#?IML? NAME <- gsub("^.*:[ ]*(.*)',[ ]*$","\\1", lines[lstart+iNAME-1])
oceDebug(debug, " \"", lines[lstart+iNAME-1], "\" -> flag name \"", NAME, "\"\n", sep="")
flagTranslationTable[CODE] <- NAME
} else {
stop("cannot link flag to variable name in a PARAMETER_HEADER block starting at line ", lstart-1)
}
Expand Down Expand Up @@ -1245,6 +1250,9 @@ read.odf <- function(file, columns=NULL, header="list", exclude=NULL, debug=getO
##> oceDebug(debug, "ODFnames: ", paste(ODFnames, collapse=" "), "\n")
##> ODFnames <- gsub("_1$", "", ODFnames)
##> oceDebug(debug, "ODFnames: ", paste(ODFnames, collapse=" "), "\n")
oceDebug(debug, "next is flagTranslationTable:\n")
if (debug > 0)
print(flagTranslationTable)

namesUnits <- ODFNames2oceNames(ODFnames, ODFunits, PARAMETER_HEADER=NULL, columns=columns, debug=debug-1)
## check for missing units, and warn if pressure and/or temperature lack units
Expand All @@ -1255,7 +1263,7 @@ read.odf <- function(file, columns=NULL, header="list", exclude=NULL, debug=getO
}

##names <- ODFName2oceName(ODFnames, PARAMETER_HEADER=NULL, columns=columns, debug=debug-1)
oceDebug(debug, "oce names:", paste(namesUnits$names, collapse=" "), "\n")
oceDebug(debug, "oce names: c(\"", paste(namesUnits$names, collapse="\",\""), ")\n", sep="")

res@metadata$depthOffBottom <- findInHeader("DEPTH_OFF_BOTTOM", lines, returnOnlyFirst=TRUE, numeric=TRUE)
res@metadata$initialLatitude <- findInHeader("INITIAL_LATITUDE", lines, returnOnlyFirst=TRUE, numeric=TRUE)
Expand Down Expand Up @@ -1424,7 +1432,8 @@ read.odf <- function(file, columns=NULL, header="list", exclude=NULL, debug=getO
for (name in names(data)) {
bad <- data[[name]] == NAvalueList[[name]]
data[[name]][bad] <- NA
oceDebug(debug, "set ", sum(bad), " values in '", name, "' to NA, because they matched the NULL_VALUE (", NAvalueList[[name]], ")\n", sep="")
if (sum(bad) > 0)
oceDebug(debug, "set ", sum(bad), " values in '", name, "' to NA, because they matched the NULL_VALUE (", NAvalueList[[name]], ")\n", sep="")
}
}
##. if (length(NAvalue) > 0 && !is.na(NAvalue)) {
Expand Down

0 comments on commit effc2b6

Please sign in to comment.