20660: Tweaks to eliminate check warnings
[arvados.git] / sdk / R / R / autoGenAPI.R
index 849875204d6f224052ce3fca2a5f6d766c30a2c4..fbf58c2f51744173335709d35b517037a92d62ef 100644 (file)
@@ -1,10 +1,18 @@
+# Copyright (C) The Arvados Authors. All rights reserved.
+#
+# SPDX-License-Identifier: Apache-2.0
+
 getAPIDocument <- function(){
-    url <- "https://4xphq.arvadosapi.com/discovery/v1/apis/arvados/v1/rest"
+    url <- "https://jutro.arvadosapi.com/discovery/v1/apis/arvados/v1/rest"
     serverResponse <- httr::RETRY("GET", url = url)
 
     httr::content(serverResponse, as = "parsed", type = "application/json")
 }
 
+#' generateAPI
+#'
+#' Autogenerate classes to interact with Arvados from the Arvados discovery document.
+#'
 #' @export
 generateAPI <- function()
 {
@@ -13,30 +21,39 @@ generateAPI <- function()
     discoveryDocument <- getAPIDocument()
 
     methodResources <- discoveryDocument$resources
+
+    # Don't emit deprecated APIs
+    methodResources <- methodResources[!(names(methodResources) %in% c("jobs", "job_tasks", "pipeline_templates", "pipeline_instances",
+                           "keep_disks", "nodes", "humans", "traits", "specimens"))]
     resourceNames   <- names(methodResources)
 
-    doc <- generateMethodsDocumentation(methodResources, resourceNames)
-    arvadosAPIHeader <- generateAPIClassHeader()
-    arvadosProjectMethods <- generateProjectMethods()
-    arvadosClassMethods <- generateClassContent(methodResources, resourceNames)
-    arvadosAPIFooter <- generateAPIClassFooter()
+    methodDoc <- genMethodsDoc(methodResources, resourceNames)
+    classDoc <- genAPIClassDoc(methodResources, resourceNames)
+    arvadosAPIHeader <- genAPIClassHeader()
+    arvadosProjectMethods <- genProjectMethods()
+    arvadosClassMethods <- genClassContent(methodResources, resourceNames)
+    arvadosAPIFooter <- genAPIClassFooter()
 
-    arvadosClass <- c(doc,
+    arvadosClass <- c(methodDoc,
+                      classDoc,
                       arvadosAPIHeader,
                       arvadosProjectMethods,
                       arvadosClassMethods,
                       arvadosAPIFooter)
 
     fileConn <- file("./R/Arvados.R", "w")
+    writeLines(c(
+    "# Copyright (C) The Arvados Authors. All rights reserved.",
+    "#",
+    "# SPDX-License-Identifier: Apache-2.0", ""), fileConn)
     writeLines(unlist(arvadosClass), fileConn)
     close(fileConn)
     NULL
 }
 
-generateAPIClassHeader <- function()
+genAPIClassHeader <- function()
 {
-    c("#' @export",
-      "Arvados <- R6::R6Class(",
+    c("Arvados <- R6::R6Class(",
       "",
       "\t\"Arvados\",",
       "",
@@ -68,7 +85,7 @@ generateAPIClassHeader <- function()
       "\t\t},\n")
 }
 
-generateProjectMethods <- function()
+genProjectMethods <- function()
 {
     c("\t\tprojects.get = function(uuid)",
       "\t\t{",
@@ -104,7 +121,7 @@ generateProjectMethods <- function()
       "")
 }
 
-generateClassContent <- function(methodResources, resourceNames)
+genClassContent <- function(methodResources, resourceNames)
 {
     arvadosMethods <- Map(function(resource, resourceName)
     {
@@ -130,7 +147,7 @@ generateClassContent <- function(methodResources, resourceNames)
     arvadosMethods
 }
 
-generateAPIClassFooter <- function()
+genAPIClassFooter <- function()
 {
     c("\t\tgetHostName = function() private$host,",
       "\t\tgetToken = function() private$token,",
@@ -247,7 +264,7 @@ getRequestURL <- function(methodMetaData)
 
 getRequestHeaders <- function()
 {
-    c("headers <- list(Authorization = paste(\"OAuth2\", private$token), ",
+    c("headers <- list(Authorization = paste(\"Bearer\", private$token), ",
       "                \"Content-Type\" = \"application/json\")")
 }
 
@@ -314,7 +331,7 @@ getReturnObject <- function()
 
 #NOTE: Arvados class documentation:
 
-generateMethodsDocumentation <- function(methodResources, resourceNames)
+genMethodsDoc <- function(methodResources, resourceNames)
 {
     methodsDoc <- unlist(unname(Map(function(resource, resourceName)
     {
@@ -329,18 +346,80 @@ generateMethodsDocumentation <- function(methodResources, resourceNames)
                return(NULL)
 
             methodName <- paste0(resourceName, ".", methodName)
-            getMethodDocumentation(methodName, methodMetaData)
+            getMethodDoc(methodName, methodMetaData)
 
         }, resource$methods, methodNames)
 
         unlist(unname(methodDoc))
 
     }, methodResources, resourceNames)))
-    
-    methodsDoc
+
+    projectDoc <- genProjectMethodsDoc()
+
+    c(methodsDoc, projectDoc)
+}
+
+genAPIClassDoc <- function(methodResources, resourceNames)
+{
+    c("#' Arvados",
+      "#'",
+      "#' Arvados class gives users ability to access Arvados REST API.",
+      "#'" ,
+      "#' @section Usage:",
+      "#' \\preformatted{arv = Arvados$new(authToken = NULL, hostName = NULL, numRetries = 0)}",
+      "#'",
+      "#' @section Arguments:",
+      "#' \\describe{",
+      "#' \t\\item{authToken}{Authentification token. If not specified ARVADOS_API_TOKEN environment variable will be used.}",
+      "#' \t\\item{hostName}{Host name. If not specified ARVADOS_API_HOST environment variable will be used.}",
+      "#' \t\\item{numRetries}{Number which specifies how many times to retry failed service requests.}",
+      "#' }",
+      "#'",
+      "#' @section Methods:",
+      "#' \\describe{",
+      getAPIClassMethodList(methodResources, resourceNames),
+      "#' }",
+      "#'",
+      "#' @name Arvados",
+      "#' @examples",
+      "#' \\dontrun{",
+      "#' arv <- Arvados$new(\"your Arvados token\", \"example.arvadosapi.com\")",
+      "#'",
+      "#' collection <- arv$collections.get(\"uuid\")",
+      "#'",
+      "#' collectionList <- arv$collections.list(list(list(\"name\", \"like\", \"Test%\")))",
+      "#' collectionList <- listAll(arv$collections.list, list(list(\"name\", \"like\", \"Test%\")))",
+      "#'",
+      "#' deletedCollection <- arv$collections.delete(\"uuid\")",
+      "#'",
+      "#' updatedCollection <- arv$collections.update(list(name = \"New name\", description = \"New description\"),",
+      "#'                                             \"uuid\")",
+      "#'",
+      "#' createdCollection <- arv$collections.create(list(name = \"Example\",",
+      "#'                                                  description = \"This is a test collection\"))",
+      "#' }",
+      "NULL",
+      "",
+      "#' @export")
+}
+
+getAPIClassMethodList <- function(methodResources, resourceNames)
+{
+    methodList <- unlist(unname(Map(function(resource, resourceName)
+    {
+        methodNames <- names(resource$methods)
+        paste0(resourceName,
+               ".",
+               methodNames[!(methodNames %in% c("index", "show", "destroy"))])
+
+    }, methodResources, resourceNames)))
+
+    hardcodedMethods <- c("projects.create", "projects.get",
+                          "projects.list", "projects.update", "projects.delete")
+    paste0("#' \t\\item{}{\\code{\\link{", sort(c(methodList, hardcodedMethods)), "}}}")
 }
 
-getMethodDocumentation <- function(methodName, methodMetaData)
+getMethodDoc <- function(methodName, methodMetaData)
 {
     name        <- paste("#' @name", methodName)
     usage       <- getMethodUsage(methodName, methodMetaData)
@@ -348,7 +427,9 @@ getMethodDocumentation <- function(methodName, methodMetaData)
     params      <- getMethodDescription(methodMetaData)
     returnValue <- paste("#' @return", methodMetaData$response[["$ref"]], "object.")
 
-    c(description,
+    c(paste("#'", methodName),
+      "#' ",
+      description,
       "#' ",
       usage,
       params,
@@ -378,7 +459,7 @@ getMethodDescription <- function(methodMetaData)
                                  className <- sapply(prop, function(ref) ref)
                                  objectName <- paste0(tolower(substr(className, 1, 1)),
                                                       substr(className, 2, nchar(className)))
-                                 paste("#' @param", objectName, className, "object.") 
+                                 paste("#' @param", objectName, className, "object.")
                              })))
     }
 
@@ -388,12 +469,81 @@ getMethodDescription <- function(methodMetaData)
     {
         arg <- methodMetaData$parameters[[argName]]
         argDescription <- arg$description
-        paste("#' @param", argName, argDescription) 
+        paste("#' @param", argName, argDescription)
     })))
 
     c(requestDoc, argsDoc)
 }
 
+genProjectMethodsDoc <- function()
+{
+    #TODO: Manually update this documentation to reflect changes in discovery document.
+    c("#' project.get",
+    "#' ",
+    "#' projects.get is equivalent to groups.get method.",
+    "#' ",
+    "#' @usage arv$projects.get(uuid)",
+    "#' @param uuid The UUID of the Group in question.",
+    "#' @return Group object.",
+    "#' @name projects.get",
+    "NULL",
+    "",
+    "#' project.create",
+    "#' ",
+    "#' projects.create wrapps groups.create method by setting group_class attribute to \"project\".",
+    "#' ",
+    "#' @usage arv$projects.create(group, ensure_unique_name = \"false\")",
+    "#' @param group Group object.",
+    "#' @param ensure_unique_name Adjust name to ensure uniqueness instead of returning an error on (owner_uuid, name) collision.",
+    "#' @return Group object.",
+    "#' @name projects.create",
+    "NULL",
+    "",
+    "#' project.update",
+    "#' ",
+    "#' projects.update wrapps groups.update method by setting group_class attribute to \"project\".",
+    "#' ",
+    "#' @usage arv$projects.update(group, uuid)",
+    "#' @param group Group object.",
+    "#' @param uuid The UUID of the Group in question.",
+    "#' @return Group object.",
+    "#' @name projects.update",
+    "NULL",
+    "",
+    "#' project.delete",
+    "#' ",
+    "#' projects.delete is equivalent to groups.delete method.",
+    "#' ",
+    "#' @usage arv$project.delete(uuid)",
+    "#' @param uuid The UUID of the Group in question.",
+    "#' @return Group object.",
+    "#' @name projects.delete",
+    "NULL",
+    "",
+    "#' project.list",
+    "#' ",
+    "#' projects.list wrapps groups.list method by setting group_class attribute to \"project\".",
+    "#' ",
+    "#' @usage arv$projects.list(filters = NULL,",
+    "#'        where = NULL, order = NULL, distinct = NULL,",
+    "#'        limit = \"100\", offset = \"0\", count = \"exact\",",
+    "#'        include_trash = NULL, uuid = NULL, recursive = NULL)",
+    "#' @param filters ",
+    "#' @param where ",
+    "#' @param order ",
+    "#' @param distinct ",
+    "#' @param limit ",
+    "#' @param offset ",
+    "#' @param count ",
+    "#' @param include_trash Include items whose is_trashed attribute is true.",
+    "#' @param uuid ",
+    "#' @param recursive Include contents from child groups recursively.",
+    "#' @return Group object.",
+    "#' @name projects.list",
+    "NULL",
+    "")
+}
+
 #NOTE: Utility functions:
 
 # This function is used to split very long lines of code into smaller chunks.
@@ -403,7 +553,7 @@ formatArgs <- function(prependAtStart, prependToEachSplit,
 {
     if(length(args) > 1)
     {
-        args[1:(length(args) - 1)] <- paste0(args[1:(length(args) - 1)], ",") 
+        args[1:(length(args) - 1)] <- paste0(args[1:(length(args) - 1)], ",")
     }
 
     args[1] <- paste0(prependAtStart, args[1])
@@ -426,12 +576,12 @@ formatArgs <- function(prependAtStart, prependToEachSplit,
 
         argLines <- c(argLines, line)
     }
-    
+
     argLines <- unlist(argLines)
     argLinesLen <- length(argLines)
 
     if(argLinesLen > 1)
-        argLines[2:argLinesLen] <- paste0(prependToEachSplit, argLines[2:argLinesLen]) 
+        argLines[2:argLinesLen] <- paste0(prependToEachSplit, argLines[2:argLinesLen])
 
     argLines
 }