Skip to content

Commit

Permalink
Resolve CRAN check problems
Browse files Browse the repository at this point in the history
  • Loading branch information
gothub committed Jun 19, 2018
1 parent f20238b commit 84c9ccf
Show file tree
Hide file tree
Showing 5 changed files with 20 additions and 4 deletions.
6 changes: 4 additions & 2 deletions R/CNode.R
Original file line number Diff line number Diff line change
Expand Up @@ -240,11 +240,12 @@ setMethod("getFormat", signature("CNode"), function(x, formatId) {

#' @rdname getChecksum
#' @export
#' @examples
#' @examples \dontrun{
#' pid <- "doi:10.5063/F1QN64NZ"
#' cn <- CNode()
#' pid <- "doi:10.5063/F1QN64NZ"
#' chksum <- getChecksum(cn, pid)
#' }
setMethod("getChecksum", signature("CNode"), function(x, pid, ...) {
url <- paste(x@endpoint, "checksum", URLencode(pid, reserved=T), sep="/")
response <- GET(url, user_agent(get_user_agent()))
Expand Down Expand Up @@ -480,11 +481,12 @@ setMethod("getObject", signature("CNode"), function(x, pid) {
#' @import datapack
#' @export
#' @rdname getSystemMetadata
#' @examples
#' @examples \dontrun{
#' library(dataone)
#' cn <- CNode()
#' pid <- "aceasdata.3.2"
#' sysmeta <- getSystemMetadata(cn, pid)
#' }
setMethod("getSystemMetadata", signature("CNode"), function(x, pid) {
stopifnot(is.character(pid))
# TODO: need to properly URL-escape the PID
Expand Down
6 changes: 4 additions & 2 deletions R/D1Node.R
Original file line number Diff line number Diff line change
Expand Up @@ -228,12 +228,13 @@ setGeneric("getObject", function(x, ...) {
#' @return character the checksum value, with the checksum algorithm as the attribute "algorithm"
#' @seealso \code{\link{D1Node-class}{D1Node}}{ class description.}
#' @export
#' @examples
#' @examples \dontrun{
#' library(dataone)
#' cn <- CNode()
#' mn <- getMNode(cn, "urn:node:KNB")
#' pid <- "doi:10.5063/F1QN64NZ"
#' chksum <- getChecksum(mn, pid)
#' }
setGeneric("getChecksum", function(x, ...) {
standardGeneric("getChecksum")
})
Expand Down Expand Up @@ -320,12 +321,13 @@ setMethod("getQueryEngineDescription", signature("D1Node"), function(x, queryEng
#' @return SystemMetadata for the object
#' @import datapack
#' @export
#' @examples
#' @examples \dontrun{
#' library(dataone)
#' cn <- CNode()
#' mn <- getMNode(cn, "urn:node:KNB")
#' pid <- "doi:10.5063/F1QN64NZ"
#' sysmeta <- getSystemMetadata(mn, pid)
#' }
setGeneric("getSystemMetadata", function(x, ...) {
standardGeneric("getSystemMetadata")
})
Expand Down
4 changes: 4 additions & 0 deletions man/getChecksum.Rd

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

4 changes: 4 additions & 0 deletions man/getSystemMetadata.Rd

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

4 changes: 4 additions & 0 deletions tests/testthat/test.CNode.R
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,10 @@ test_that("CNode getObject()", {
#cn <- CNode("PROD")
pid <- "aceasdata.3.2"
obj <- getObject(cnProd, pid)
if(is.null(obj) || class(obj) != "raw") {
skip_on_cra()
skip(sprintf("Unable to retrieve pid %s from production CN, skipping test\n", pid))
}
xml <- xmlParseDoc(rawToChar(obj), asText=TRUE)
cname <- class(xml)[1]
expect_match(cname, "XML")
Expand Down

0 comments on commit 84c9ccf

Please sign in to comment.