Skip to content

Commit

Permalink
provenance, RDF
Browse files Browse the repository at this point in the history
  • Loading branch information
antaldaniel committed Dec 24, 2024
1 parent 03baa5e commit 5443fd7
Show file tree
Hide file tree
Showing 42 changed files with 1,076 additions and 360 deletions.
6 changes: 4 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Package: dataset
Title: Create Data Frames that are Easier to Exchange and Reuse
Version: 0.3.4
Date: 2024-12-23
Version: 0.3.4001
Date: 2024-12-24
DOI: 10.32614/CRAN.package.dataset
Language: en-US
Authors@R:
Expand Down Expand Up @@ -33,13 +33,15 @@ Imports:
labelled,
methods,
pillar,
RefManageR,
rlang,
tibble,
utils,
vctrs (>= 0.5.2)
RoxygenNote: 7.3.2
Suggests:
knitr,
rdflib,
rmarkdown,
spelling,
testthat (>= 3.0.0)
Expand Down
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,7 @@ export(dataset_title)
export(dataset_to_triples)
export(defined)
export(definition_attribute)
export(describe)
export(description)
export(dublincore)
export(geolocation)
Expand Down Expand Up @@ -97,6 +98,7 @@ export(xsd_convert)
import(methods)
import(pillar)
import(vctrs)
importFrom(RefManageR,BibEntry)
importFrom(assertthat,assert_that)
importFrom(cli,cat_line)
importFrom(haven,as_factor)
Expand Down
121 changes: 121 additions & 0 deletions R/agent.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,121 @@


#' @keywords internal
`agent<-` <- function(x, value) {

return_type <- NULL

if ("dataset_bibentry" %in% names(attributes(x))) {
dataset_bibentry <- get_bibentry(x)
return_type <- "dataset"
} else if (inherits(x, "dublincore")) {
dataset_bibentry <- x
return_type <- "dublincore"
} else if (inherits(x, "datacite")) {
dataset_bibentry <- x
return_type <- "datacite"
} else {
stop("Error: agent(x)<- x must be a dataset_df, a dublincore or a datacite object.")
}

assertthat::assert_that(all(inherits(value, "person")),
msg = "Error: agent(x) <- value: value must be a vector of utils::persons.")

creators <- ifelse(is.null(dataset_bibentry$author), ":tba", dataset_bibentry$author)
publishers <- ifelse(is.null(dataset_bibentry$publisher), ":unas", dataset_bibentry$publisher)
contributors <- ifelse(is.null(dataset_bibentry$contributor), ":unas", dataset_bibentry$contributor)

get_creator <- function(x) {
if (!is.null(x$role)) ifelse("cre" %in% x$role, TRUE, FALSE) else FALSE
}

get_author <- function(x) {
if (!is.null(x$role)) ifelse("aut" %in% x$role, TRUE, FALSE) else FALSE
}

get_publisher <- function(x) {
if (!is.null(x$role)) ifelse("pbl" %in% x$role, TRUE, FALSE) else FALSE
}

is_creator <- vapply(value, get_creator, logical(1))
is_author <- vapply(value, get_creator, logical(1))
is_publisher <- vapply(value, get_publisher, logical(1))


new_creators <- c(value[is_creator], value[is_author[!is_creator]])
new_publishers <- c(value[is_publisher])
new_contributors <- c(value[!value %in% c(creators, publishers)])

creators <- ifelse(length(new_creators)>0, new_creators, creators)
publishers <- ifelse(length(new_publishers)>0, new_publishers, publishers)
contributors <- ifelse(length(new_creators)>0, new_contributors, contributors)

dataset_bibentry$author <- ifelse(length(new_creators)>0, new_creators, dataset_bibentry[[1]]$author)
dataset_bibentry$contributor <- contributors
dataset_bibentry$publisher <- publishers

if ( return_type %in% c("datacite", "dublincore")) {
dataset_bibentry
} else if ( return_type == "dataset") {
attr(x, "dataset_bibentry") <- dataset_bibentry
invisible(x)
}
}

#' @keywords internal
agent <- function(x) {

if(inherits(x, "dataset_df")) {
dataset_bibentry <- get_bibentry(x)
} else if(inherits(x, "datacite")) {
dataset_bibentry <- x
creators <- ifelse(is.null(dataset_bibentry$author), ":tba", dataset_bibentry$author)
publishers <- ifelse(is.null(dataset_bibentry$publisher), ":unas", dataset_bibentry$publisher)
contributors <- ifelse(is.null(dataset_bibentry$contributor), ":unas", dataset_bibentry$contributor)

} else if (inherits(x, "dublincore")) {
dataset_bibentry <- x
creators <- ifelse(is.null(dataset_bibentry$author), ":tba", dataset_bibentry$author)
publishers <- ifelse(is.null(dataset_bibentry$publisher), ":unas", dataset_bibentry$publisher)
contributors <- ifelse(is.null(dataset_bibentry$contributor), ":unas", dataset_bibentry$contributor)
} else if ( all(inherits(x, "person"))) {
contributors <- x
publishers <- x
creators <- x
return_type <- "persons_vector"
} else {
stop("Error: agent(x)<- x must be a dataset_df, a vector of persons, a dublincore or datacite object.")
}

get_creator <- function(x) {
if (!is.null(x$role)) ifelse("cre" %in% x$role, TRUE, FALSE) else FALSE
}

get_author <- function(x) {
if (!is.null(x$role)) ifelse("aut" %in% x$role, TRUE, FALSE) else FALSE
}

get_publisher <- function(x) {
if (!is.null(x$role)) ifelse("pbl" %in% x$role, TRUE, FALSE) else FALSE
}

is_creator <- vapply(creators, get_creator, logical(1))
is_author <- vapply(creators, get_creator, logical(1))
is_publisher <- vapply(creators, get_publisher, logical(1))

new_creators <- c(creators[is_creator], creators[is_author[!is_creator]])
new_contributors <- c(contributors[!contributors %in% c(creators, publishers)])
new_publishers <- publishers[is_publisher]

creators <- if(length(new_creators)>0) creators <- new_creators
contributors <- if(length(new_contributors)>0) contributors <- new_contributors
publishers <- if(length(new_publishers)>0) publishers <- new_publishers



list(creators = creators,
contributors = contributors,
publishers = publishers)

}

164 changes: 164 additions & 0 deletions R/as_dublincore.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,164 @@
#' @rdname dublincore
#' @param type For \code{as_dublincore}, any of \code{"bibentry", "dataset_df", "list", "ntriples"}.
#' @param ... Optional parameters to add to a \code{dublincore} object.
#' \code{author=person("Jane", "Doe")} adds an author to the citation
#' object if \code{type="dataset"}.
#' @export
as_dublincore <- function(x, type = "bibentry", ...) {

citation_author <- person(NULL, NULL)

is_person <- function(p) ifelse (inherits(p, "person"), TRUE, FALSE)

arguments <- list(...)

if (!is.null(arguments$author)) {
if ( is_person(arguments$author)) {
citation_author <- arguments$author
} else {
stop("as_dublincore(x, ..., author = ): author must be created with utils::person().")
}
}

if (! type %in% c("bibentry", "list", "dataset_df", "ntriples")) {
warning_message <- "as_dublincore(ds, type=...) type cannot be "
warning(warning_message, type, ". Reverting to 'bibentry'.")
type <- 'bibentry'
}

dataset_bibentry <- get_bibentry(x)
dataset_title <- dataset_bibentry$title
dataset_creator <- dataset_bibentry$author

if (! is_person(dataset_creator)) {
stop('attr(x, "dataset_bibentry")$author is not a person object.')
}

if (!is.null(dataset_bibentry$year)) {
if(is.null(dataset_bibentry$dataset_date)) {
dataset_date <- as.character(dataset_bibentry$year)
} else {
dataset_date <- as.character(dataset_bibentry$date)
}
} else if (!is.null(dataset_bibentry$date)) {
dataset_date <- dataset_bibentry$date
} else {
dataset_date <- ":tba"
}

dataset_relation <- ifelse (is.null(dataset_bibentry$relation), ":unas", as.character(dataset_bibentry$relation))
dataset_identifier <- ifelse (is.null(dataset_bibentry$identifier), ":tba", as.character(dataset_bibentry$identifier))
dataset_version <- ifelse (is.null(dataset_bibentry$version), ":unas", as.character(dataset_bibentry$version))
dataset_description <- ifelse (is.null(dataset_bibentry$description), ":unas", as.character(dataset_bibentry$description))
dataset_language <- ifelse (is.null(dataset_bibentry$language), ":unas", as.character(dataset_bibentry$language))
dataset_format <- ifelse (is.null(dataset_bibentry$format), ":tba", as.character(dataset_bibentry$format))
dataset_rights <- ifelse (is.null(dataset_bibentry$rights), ":tba", as.character(dataset_bibentry$rights))
dataset_coverage <- ifelse (is.null(dataset_bibentry$coverage), ":unas", as.character(dataset_bibentry$coverage))
datasource <- ifelse (is.null(dataset_bibentry$datasource), ":unas", as.character(dataset_bibentry$datasource))
dataset_contributor <- ifelse (is.null(dataset_bibentry$contributor), "", as.character(dataset_bibentry$contributor))
dataset_subject <- ifelse (is.null(dataset_bibentry$subject), "", as.character(dataset_bibentry$subject))
dataset_publisher <- ifelse (is.null(dataset_bibentry$publisher), "", as.character(dataset_bibentry$publisher))

properties <- c(length(dataset_title),
length(as.character(dataset_creator)),
length(dataset_identifier),
length(dataset_publisher),
length(dataset_subject),
length("DCMITYPE:Dataset"),
length(dataset_contributor),
length(dataset_date),
length(dataset_language),
length(dataset_relation),
length(dataset_format),
length(dataset_rights),
length(datasource),
length(dataset_description),
length(dataset_coverage)
)

if (type == "bibentry") {
new_dublincore(title = dataset_title,
creator = dataset_creator,
identifier = dataset_identifier,
publisher = dataset_publisher,
subject = dataset_subject,
type = "DCMITYPE:Dataset",
contributor = dataset_contributor,
publication_date = dataset_date,
language = dataset_language,
relation = dataset_relation,
format = dataset_format,
rights = dataset_rights,
datasource = datasource,
description = dataset_description,
coverage = dataset_coverage)
} else if (type== "list") {
if (dataset_contributor == "") dataset_contributor <- NULL
if (dataset_subject == "") dataset_subject <- NULL

list(title=dataset_title,
creator=dataset_creator,
identifier = dataset_identifier,
publisher = dataset_publisher,
subject = dataset_subject,
type = "DCMITYPE:Dataset",
contributor = dataset_contributor,
date = dataset_date,
language = dataset_language,
relation = dataset_relation,
format = dataset_format,
rights = dataset_rights,
datasource = datasource,
description = dataset_description,
coverage = dataset_coverage)
} else if ( type == "dataset_df") {
assertthat::assert_that(
all(properties)==1, msg= "In as_dublincore() not all properties have a length 1 to export into datataset (data.frame)."
)
dataset_df(
data.frame(title = dataset_title,
creator = as.character(dataset_creator),
identifier = dataset_identifier,
publisher = dataset_publisher,
subject = dataset_subject,
type = "DCMITYPE:Dataset",
contributor = dataset_contributor,
date = dataset_date,
language = dataset_language,
relation = dataset_relation,
format = dataset_format,
rights = dataset_rights,
datasource = datasource,
description = dataset_description,
coverage = dataset_coverage),
reference = list(
title = paste0("The Dublin Core Metadata of `", dataset_bibentry$title, "'"),
author = citation_author,
year = substr(as.character(Sys.Date()),1,4)

))
} else if (type=="ntriples") {
dclist <- list(title=dataset_title,
creator=dataset_creator,
identifier = dataset_identifier,
publisher = dataset_publisher,
subject = dataset_subject,
type = "DCMITYPE:Dataset",
contributor = dataset_contributor,
date = dataset_date,
language = dataset_language,
relation = dataset_relation,
format = dataset_format,
rights = dataset_rights,
datasource = datasource,
description = dataset_description,
coverage = dataset_coverage)

if ( dataset_identifier == ":tba") {
dataset_id <- "http:/example.com/dataset_tba/"
} else {
dataset_id <- dataset_identifier
}
dublincore_to_triples(dclist=dclist, dataset_id=dataset_id)
}
}
Loading

0 comments on commit 5443fd7

Please sign in to comment.