Skip to content

Commit

Permalink
#387 zenodo entity handler
Browse files Browse the repository at this point in the history
  • Loading branch information
eblondel committed May 19, 2024
1 parent 33ca3fa commit 8246d08
Showing 1 changed file with 27 additions and 24 deletions.
51 changes: 27 additions & 24 deletions inst/metadata/entity/entity_handler_zenodo.R
Original file line number Diff line number Diff line change
Expand Up @@ -65,30 +65,30 @@ handle_entities_zenodo <- function(handler, source, config, handle = TRUE){

entities <- lapply(1:length(results), function(i){
result <- results[[i]]
config$logger.info(sprintf("Creating entity (%s out of %s) from Zenodo deposit/record with DOI '%s'", i, length(results), result$doi))
config$logger.info(sprintf("Creating entity (%s out of %s) from Zenodo deposit/record with DOI '%s'", i, length(results), result$metadata$doi))

#create entity
entity <- geoflow::geoflow_entity$new()
#entity Identifier
entity$setIdentifier("doi", result$doi)
entity$setIdentifier("doi", result$metadata$doi)
#semantic identifier
identifiers = result$metadata$related_identifiers[sapply(result$metadata$related_identifiers, function(x){x$scheme == "urn" && x$relation == "isIdenticalTo"})]
if(length(identifiers)>0){
identifier = identifiers[[1]]$identifier
entity$setIdentifier("id", substr(identifier, 5,nchar(identifier)))
}else{
entity$setIdentifier("id", gsub("/", "_", result$doi))
entity$setIdentifier("id", gsub("/", "_", result$metadata$doi))
}

#entity Date
if(!is.null(result$created)) entity$addDate(dateType = "creation", date = str_to_posix(result$created))
if(!is.null(result$modified)) entity$addDate(dateType = "lastUpdate", date = str_to_posix(result$modified))
if(!is.null(result$modified)) entity$addDate(dateType = "lastUpdate", date = str_to_posix(result$updated))
if(!is.null(result$metadata$publication_date)) entity$addDate(dateType = "publication", date = str_to_posix(result$metadata$publication_date))
if(!is.null(result$metadata$embargo_date)) entity$addDate(dateType = "embargo", date = str_to_posix(result$metadata$embargo_date))
if(isTRUE(result$access$embargo$active) & !is.null(result$access$embargo$until)) entity$addDate(dateType = "embargo", date = str_to_posix(result$access$embargo$until))

#entity common metadata
#entity Type
entity$setType(key = "generic", result$metadata$upload_type)
entity$setType(key = "generic", result$metadata$resource_type$id)
#entity Title
entity$setTitle("title", result$metadata$title)
#entity Description
Expand All @@ -97,38 +97,41 @@ handle_entities_zenodo <- function(handler, source, config, handle = TRUE){
subj <- geoflow::geoflow_subject$new()
subj$setKey("theme")
subj$setName("General")
for(kwd in result$metadata$keywords){
subj$addKeyword(kwd)
}
for(sbj in result$metadata$subjects){
subj$addKeyword(sbj$term, uri = sbj$identifier)
subj$addKeyword(sbj$subject)
}
entity$addSubject(subj)

#entity Contacts/roles
#creator(s)
creators <- result$metadata$creators
for(creator in creators){
creatorNames <- unlist(strsplit(creator$name, ", "))
if(length(creators)>0) for(creator in creators){
creator_poo = creator$person_or_org
creatorNames <- unlist(strsplit(creator_poo$name, ", "))
creator_c <- geoflow::geoflow_contact$new()
creator_c$setFirstName(creatorNames[2])
creator_c$setLastName(creatorNames[1])
if(!is.null(creator$affiliation)) creator_c$setOrganizationName(creator$affiliation)
if(!is.null(creator$orcid)) creator_c$setIdentifier("orcid", creator$orcid)
if(!is.null(creator$gnd)) creator_c$setIdentifier("gnd", creator$gnd)
if(!is.null(creator_poo$affiliations)) creator_c$setOrganizationName(creator_poo$affiliations[[1]]$id)
ids = creator_poo$identifiers
names(ids) = sapply(ids, function(x){x$scheme})
if(!is.null(ids$orcid)) creator_c$setIdentifier("orcid", ids$orcid$identifier)
if(!is.null(ids$gnd)) creator_c$setIdentifier("gnd", ids$gnd$identifier)
creator_c$setRole("creator")
entity$addContact(creator_c)
}
#contributor(s)
contribs <- result$metadata$contributors
for(contrib in contribs){
contribNames <- unlist(strsplit(contrib$name, ", "))
contrib_poo = contrib$person_or_org
contribNames <- unlist(strsplit(contrib_poo$name, ", "))
contrib_c <- geoflow::geoflow_contact$new()
contrib_c$setFirstName(contribNames[2])
contrib_c$setLastName(contribNames[1])
if(!is.null(contrib$affiliation)) contrib_c$setOrganizationName(contrib$affiliation)
if(!is.null(contrib$orcid)) contrib_c$setIdentifier("orcid", contrib$orcid)
if(!is.null(contrib$gnd)) contrib_c$setIdentifier("gnd", contrib$gnd)
if(!is.null(contrib_poo$affiliations)) contrib_c$setOrganizationName(contrib_poo$affiliations[[1]]$id)
ids = contrib_poo$identifiers
names(ids) = sapply(ids, function(x){x$scheme})
if(!is.null(ids$orcid)) contrib_c$setIdentifier("orcid", ids$orcid$identifier)
if(!is.null(ids$gnd)) contrib_c$setIdentifier("gnd", ids$gnd$identifier)
contrib_c$setRole("contributor")
entity$addContact(contrib_c)
}
Expand All @@ -138,7 +141,7 @@ handle_entities_zenodo <- function(handler, source, config, handle = TRUE){
for(reference in result$metadata$references){
ref_rel = geoflow_relation$new()
ref_rel$setKey("ref")
ref_rel$setName(reference)
ref_rel$setName(reference$reference)
entity$addRelation(ref_rel)
}
}
Expand All @@ -156,13 +159,13 @@ handle_entities_zenodo <- function(handler, source, config, handle = TRUE){
rights <- geoflow::geoflow_right$new()
if(!is.null(result$metadata$license)) {
rights$setKey("license")
rights$setValues(result$metadata$license)
rights$setValues(result$metadata$rights[[1]]$id)
entity$addRight(rights)
}
if(result$metadata$access_right != "open"){
if(result$access$files != "public"){
access_rights = geoflow::geoflow_right$new()
access_rights$setKey("accessRight")
access_rights$setValues(result$metadata$access_right)
access_rights$setValues(result$access$files)
entity$addRight(access_rights)
}

Expand All @@ -176,7 +179,7 @@ handle_entities_zenodo <- function(handler, source, config, handle = TRUE){
data$source <- lapply(1:length(result$files), function(i){
z_file <- result$files[[i]]
z_filename <- z_file$filename
attr(z_filename, "uri") <- result$doi
attr(z_filename, "uri") <- result$metadata$doi
return(z_filename)
})
data$upload <- TRUE
Expand Down

0 comments on commit 8246d08

Please sign in to comment.