Skip to content

Commit

Permalink
change misleading source() to datasource()
Browse files Browse the repository at this point in the history
  • Loading branch information
antaldaniel committed Nov 29, 2023
1 parent 435dc85 commit 10c4d82
Show file tree
Hide file tree
Showing 3 changed files with 76 additions and 15 deletions.
58 changes: 58 additions & 0 deletions R/datasource.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
#' @title Get/set the Source of the object.
#' @description Get/set the optional \code{Source} property as an attribute to an
#' R object. Do not confuse with the base R \code{source()} function.
#' @details The \code{Source} is a related resource from which the described resource is
#' derived. See \href{https://purl.org/dc/elements/1.1/source}{dct:source}. In Datacite,
#' the source is described by a \code{relatedIdentifierType} with the property
#' \code{relationType="isDerivedFrom"}.
#' @param value The \code{Source} as a character string of lengths one.
#' @inheritParams dublincore
#' @return The \code{Source} attribute as a character of length 1 is added to \code{x}.
#' @examples
#' datasource(iris_dataset) <- "https://doi.org/10.1111/j.1469-1809.1936.tb02137.x"
#' datasource(iris_dataset)
#' @family Reference metadata functions
#' @export
datasource <- function(x) {

assertthat::assert_that(is.dataset(x),
msg = "datasource(x) must be a dataset object created with dataset() or as_dataset().")
DataBibentry <- dataset_bibentry(x)
DataBibentry$source

}

#' @rdname dataset_source
#' @export
`datasource<-` <- function(x, overwrite = TRUE, value) {

assertthat::assert_that(is.dataset(x),
msg = "datasource(x): x must be a dataset object created with dataset() or as_dataset().")

DataBibentry <- invisible(dataset_bibentry(x))

if ( is.null(value) ) {
DataBibentry$source <- ":unas"
attr(x, "DataBibentry") <- DataBibentry
return(invisible(x))
}

if (length(value)>1) {
stop("source(x) <- value: value must be of length 1.")
}

is_unas <- DataBibentry$source == ":unas"

if (is.null(DataBibentry$source)) {
DataBibentry$source <- value
} else if (is_unas) {
DataBibentry$source <- value
}else if ( overwrite ) {
DataBibentry$source <- value
} else {
message ("The dataset has already a source: ", DataBibentry$source )
}

attr(x, "DataBibentry") <- DataBibentry
invisible(x)
}
22 changes: 7 additions & 15 deletions man/dataset_source.Rd → man/datasource.Rd

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

11 changes: 11 additions & 0 deletions tests/testthat/test-datasource.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
datasource(x=iris_dataset) <- NULL

test_that("datasource() initializes :unas unassigned value", {
expect_equal(datasource(iris_dataset), ":unas")
})

datasource(iris_dataset) <- "https://doi.org/10.1111/j.1469-1809.1936.tb02137.x"

test_that("dataset_source() <- assignment works", {
expect_equal(datasource(iris_dataset), "https://doi.org/10.1111/j.1469-1809.1936.tb02137.x")
})

0 comments on commit 10c4d82

Please sign in to comment.