Skip to content

Commit

Permalink
Merge branch 'develop' into dk
Browse files Browse the repository at this point in the history
  • Loading branch information
dankelley committed May 15, 2018
2 parents b1d8b27 + 0363911 commit 645fcf6
Show file tree
Hide file tree
Showing 8 changed files with 79 additions and 17 deletions.
50 changes: 37 additions & 13 deletions R/accessors.R
Original file line number Diff line number Diff line change
Expand Up @@ -64,9 +64,15 @@ oceDeleteData <- function(object, name)
#' three possible forms (see \dQuote{Details}).
#' @param originalName Optional character string giving an 'original' name (e.g.
#' as stored in the header of a data file).
#' @param note A note to be stored in the processing log. If an empty string
#' (the default) then an entry will be constructed from the function call. If
#' \code{NULL}, then no entry will be added to the processing log.
#' @param note Either empty (the default), a character string, or \code{NULL},
#' to control additions made to the processing log of the return value. If
#' \code{note=""} then the an entry is created based on deparsing the function call.
#' If \code{note} is a non-empty string, then that string gets added added
#' to the processing log. Finally, if \code{note=NULL}, then nothing is
#' added to the processing log. This last form is useful in cases where
#' \code{oceSetData} is to be called many times in succession, resulting
#' in an overly verbose processing log; in such cases, it might help
#' to add a note by e.g. \code{processingLog(a) <- "QC (memo dek-2018-01/31)"}
#'
#' @examples
#' data(ctd)
Expand All @@ -81,13 +87,9 @@ oceSetData <- function(object, name, value, unit, originalName, note="")
if (!inherits(object, "oce"))
stop("oceSetData() only works for oce objects")
object@data[[name]] <- value
if (nchar(note) > 0)
object@processingLog <- processingLogAppend(object@processingLog, note)
else if (!is.null(note))
object@processingLog <- processingLogAppend(object@processingLog, paste(deparse(match.call()), sep="", collapse=""))
if (!missing(unit)) {
if (!("units" %in% names(object@metadata))) # some objects might not have units yet
object@metadata$units <- list()
if (!("units" %in% names(object@metadata))) # some objects might not have units yet
object@metadata$units <- list()
if (is.list(unit)) {
## message("case 1")
if (is.null(names(unit)))
Expand Down Expand Up @@ -134,6 +136,14 @@ oceSetData <- function(object, name, value, unit, originalName, note="")
object@metadata$dataNamesOriginal[[name]] <- originalName
}
}
if (!is.null(note)) {
if (nchar(note) > 0)
object@processingLog <- processingLogAppend(object@processingLog, note)
else
object@processingLog <- processingLogAppend(object@processingLog,
paste(deparse(match.call()),
sep="", collapse=""))
}
object
}

Expand Down Expand Up @@ -177,14 +187,28 @@ oceDeleteMetadata <- function(object, name)
#' @param object an \code{oce} object
#' @param name String indicating the name of the item to be set.
#' @param value Value for the item.
#' @param note A note to be stored in the processing log.
#' @param note Either empty (the default), a character string, or \code{NULL},
#' to control additions made to the processing log of the return value. If
#' \code{note=""} then the an entry is created based on deparsing the function call.
#' If \code{note} is a non-empty string, then that string gets added added
#' to the processing log. Finally, if \code{note=NULL}, then nothing is
#' added to the processing log. This last form is useful in cases where
#' \code{oceSetData} is to be called many times in succession, resulting
#' in an overly verbose processing log; in such cases, it might help
#' to add a note by e.g. \code{processingLog(a) <- "QC (memo dek-2018-01/31)"}
#'
oceSetMetadata <- function(object, name, value, note="")
{
if (!inherits(object, "oce"))
stop("oceSetData() only works for oce objects")
object@metadata[[name]] <- value
object@processingLog <- processingLogAppend(object@processingLog, paste(deparse(match.call()), sep="", collapse=""))
if (nchar(note) > 0)
object@processingLog <- processingLogAppend(object@processingLog, note)
if (!is.null(note)) {
if (nchar(note) > 0)
object@processingLog <- processingLogAppend(object@processingLog, note)
else
object@processingLog <- processingLogAppend(object@processingLog,
paste(deparse(match.call()),
sep="", collapse=""))
}
object
}
4 changes: 4 additions & 0 deletions R/processingLog.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
#' processingLogShow(ctd)
#' processingLog(ctd) <- "test"
#' processingLogShow(ctd)
#' @family things related to processing logs
"processingLog<-" <- function(x, value)
{
if (inherits(x, "oce")) {
Expand All @@ -31,6 +32,7 @@
#' @param h either the \code{processingLog} slot of an object, or
#' an \code{oce} object from which the processingLog will be extracted
#' @param value A string indicating the text of the log entry.
#' @family things related to processing logs
processingLogAppend <- function(h, value="")
{
if (inherits(h, "oce"))
Expand All @@ -56,13 +58,15 @@ processingLogAppend <- function(h, value="")
#' @return A \code{\link{list}} containing \code{time}, which is
#' the \code{\link{Sys.time}} at the moment the function is called and
#' \code{value}, a string that is set to the argument of the same name.
#' @family things related to processing logs
processingLogItem <- function(value="")
{
list(time=c(Sys.time()), value=value)
}

#' Show the processing log of an \code{oce} object
#' @param x An \code{oce} object.
#' @family things related to processing logs
processingLogShow <- function(x)
{
cat("* Processing Log\n")
Expand Down
12 changes: 9 additions & 3 deletions man/oceSetData.Rd

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

10 changes: 9 additions & 1 deletion man/oceSetMetadata.Rd

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

5 changes: 5 additions & 0 deletions man/processingLog-set.Rd

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

5 changes: 5 additions & 0 deletions man/processingLogAppend.Rd

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

5 changes: 5 additions & 0 deletions man/processingLogItem.Rd

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

5 changes: 5 additions & 0 deletions man/processingLogShow.Rd

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

0 comments on commit 645fcf6

Please sign in to comment.