Merge branch 'master' into 13822-nm-delayed-daemon
[arvados.git] / sdk / R / R / Collection.R
index 29afadc02dab103a863af0b8bcb315b44c1d447e..e23da138329786cba49e3a8001479461dd30be77 100644 (file)
-source("./R/Arvados.R")
-source("./R/HttpParser.R")
+# Copyright (C) The Arvados Authors. All rights reserved.
+#
+# SPDX-License-Identifier: Apache-2.0
+
 source("./R/Subcollection.R")
 source("./R/ArvadosFile.R")
+source("./R/RESTService.R")
+source("./R/util.R")
 
-#' Collection Class
-#' 
-#' @details 
-#' Todo: Update description
 #' Collection
 #' 
-#' @param uuid Object ID
-#' @param etag Object version
-#' @param owner_uuid No description
-#' @param created_at No description
-#' @param modified_by_client_uuid No description
-#' @param modified_by_user_uuid No description
-#' @param modified_at No description
-#' @param portable_data_hash No description
-#' @param replication_desired No description
-#' @param replication_confirmed_at No description
-#' @param replication_confirmed No description
-#' @param updated_at No description
-#' @param manifest_text No description
-#' @param name No description
-#' @param description No description
-#' @param properties No description
-#' @param delete_at No description
-#' @param file_names No description
-#' @param trash_at No description
-#' @param is_trashed No description
+#' Collection class provides interface for working with Arvados collections.
 #' 
-#' @export Collection
+#' @section Usage:
+#' \preformatted{collection = Collection$new(arv, uuid)}
+#'
+#' @section Arguments:
+#' \describe{
+#'   \item{arv}{Arvados object.}
+#'   \item{uuid}{UUID of a collection.}
+#' }
+#' 
+#' @section Methods:
+#' \describe{
+#'   \item{add(content)}{Adds ArvadosFile or Subcollection specified by content to the collection.}
+#'   \item{create(fileNames, relativePath = "")}{Creates one or more ArvadosFiles and adds them to the collection at specified path.}
+#'   \item{remove(fileNames)}{Remove one or more files from the collection.}
+#'   \item{move(content, newLocation)}{Moves ArvadosFile or Subcollection to another location in the collection.}
+#'   \item{getFileListing()}{Returns collections file content as character vector.}
+#'   \item{get(relativePath)}{If relativePath is valid, returns ArvadosFile or Subcollection specified by relativePath, else returns NULL.}
+#' }
+#'
+#' @name Collection
+#' @examples
+#' \dontrun{
+#' arv <- Arvados$new("your Arvados token", "example.arvadosapi.com")
+#' collection <- Collection$new(arv, "uuid")
+#'
+#' newFile <- ArvadosFile$new("myFile")
+#' collection$add(newFile, "myFolder")
+#'
+#' createdFiles <- collection$create(c("main.cpp", lib.dll), "cpp/src/")
+#'
+#' collection$remove("location/to/my/file.cpp")
+#'
+#' collection$move("folder/file.cpp", "file.cpp")
+#'
+#' arvadosFile <- collection$get("location/to/my/file.cpp")
+#' arvadosSubcollection <- collection$get("location/to/my/directory/")
+#' }
+NULL
 
-#' @exportClass Collection
-Collection <- setRefClass(
+#' @export
+Collection <- R6::R6Class(
 
     "Collection",
 
-    fields = list(uuid                     = "ANY",
-                  items                    = "ANY",
-                  fileContent              = "ANY",
-                  etag                     = "ANY",
-                  owner_uuid               = "ANY",
-                  created_at               = "ANY",
-                  modified_by_client_uuid  = "ANY",
-                  modified_by_user_uuid    = "ANY",
-                  modified_at              = "ANY",
-                  portable_data_hash       = "ANY",
-                  replication_desired      = "ANY",
-                  replication_confirmed_at = "ANY",
-                  replication_confirmed    = "ANY",
-                  updated_at               = "ANY",
-                  manifest_text            = "ANY",
-                  name                     = "ANY",
-                  description              = "ANY",
-                  properties               = "ANY",
-                  delete_at                = "ANY",
-                  file_names               = "ANY",
-                  trash_at                 = "ANY",
-                  is_trashed               = "ANY",
-
-                  getCollectionContent = "function",
-                  get                  = "function"
-    ),
+    public = list(
 
-    methods = list(
+               uuid = NULL,
+        # api  = NULL,
 
-        initialize = function(api, uuid) 
+               initialize = function(api, uuid) 
         {
-            result <- api$collection_get(uuid)
-            
-            # Private members
-            uuid                     <<- result$uuid                               
-            etag                     <<- result$etag                               
-            owner_uuid               <<- result$owner_uuid                         
-            created_at               <<- result$created_at                         
-            modified_by_client_uuid  <<- result$modified_by_client_uuid            
-            modified_by_user_uuid    <<- result$modified_by_user_uuid              
-            modified_at              <<- result$modified_at                        
-            portable_data_hash       <<- result$portable_data_hash                 
-            replication_desired      <<- result$replication_desired                
-            replication_confirmed_at <<- result$replication_confirmed_at           
-            replication_confirmed    <<- result$replication_confirmed              
-            updated_at               <<- result$updated_at                         
-            manifest_text            <<- result$manifest_text                      
-            name                     <<- result$name                               
-            description              <<- result$description                        
-            properties               <<- result$properties                         
-            delete_at                <<- result$delete_at                          
-            file_names               <<- result$file_names                         
-            trash_at                 <<- result$trash_at                           
-            is_trashed               <<- result$is_trashed                         
-
-            # Public methods
-
-            getCollectionContent <<- function()
-            {
-                #TODO(Fudo): Use proper URL here.
-                uri <- URLencode(api$getWebDavHostName())
+            # self$api <- api
+            private$REST <- api$getRESTService()
+
+            self$uuid <- uuid
 
-                # fetch directory listing via curl and parse XML response
-                h <- curl::new_handle()
-                curl::handle_setopt(h, customrequest = "PROPFIND")
+            private$fileContent <- private$REST$getCollectionContent(uuid)
+            private$tree <- CollectionTree$new(private$fileContent, self)
+        },
 
-                #TODO(Fudo): Use proper token here.
-                curl::handle_setheaders(h, "Authorization" = paste("OAuth2", api$getWebDavToken()))
-                response <- curl::curl_fetch_memory(uri, h)
+        add = function(content, relativePath = "")
+        {
+            if(is.null(private$tree))
+                private$genereateCollectionTreeStructure()
 
-                HttpParser()$parseWebDAVResponse(response, uri)
+            if(relativePath == ""  ||
+               relativePath == "." ||
+               relativePath == "./")
+            {
+                subcollection <- private$tree$getTree()
+            }
+            else
+            {
+                relativePath <- trimFromEnd(relativePath, "/")
+                subcollection <- self$get(relativePath)
             }
 
-            get <<- function(pathToTheFile)
+            if(is.null(subcollection))
+                stop(paste("Subcollection", relativePath, "doesn't exist."))
+
+            if("ArvadosFile"   %in% class(content) ||
+               "Subcollection" %in% class(content))
             {
-                fileWithPath <- unlist(stringr::str_split(pathToTheFile, "/"))
-                fileWithPath <- fileWithPath[fileWithPath != ""]
+                if(content$getName() == "")
+                    stop("Content has invalid name.")
 
-                findFileIfExists <- function(name, node)
-                {
-                    matchPosition <- match(name, sapply(node$content, function(nodeInSubcollection) {nodeInSubcollection$name}), -1)
-                    if(matchPosition != -1)
-                    {
-                        return(node$content[[matchPosition]])
-                    }
-                    else
-                    {
-                        return(NULL)
-                    }
-                }
-                
-                nodeToCheck = .self$fileContent
-                for(fileNameIndex in 1:length(fileWithPath))
-                {
-                    nodeToCheck <- findFileIfExists(fileWithPath[fileNameIndex], nodeToCheck)
-                    if(is.null(nodeToCheck))
-                        stop("File or folder you asked for is not part of the collection.")
-                }
+                subcollection$add(content)
+                content
+            }
+            else
+            {
+                stop(paste0("Expected AravodsFile or Subcollection object, got ",
+                            paste0("(", paste0(class(content), collapse = ", "), ")"),
+                            "."))
+            }
+        },
 
-                nodeToCheck
+        create = function(fileNames, relativePath = "")
+        {
+            if(is.null(private$tree))
+                private$genereateCollectionTreeStructure()
+
+            if(relativePath == ""  ||
+               relativePath == "." ||
+               relativePath == "./")
+            {
+                subcollection <- private$tree$getTree()
+            }
+            else
+            {
+                relativePath  <- trimFromEnd(relativePath, "/") 
+                subcollection <- self$get(relativePath)
             }
 
+            if(is.null(subcollection))
+                stop(paste("Subcollection", relativePath, "doesn't exist."))
 
-            # Private methods
-            .createCollectionContentTree <- function(fileStructure)
+            if(is.character(fileNames))
             {
-                #TODO(Fudo): Refactor this.
-                #TODO(Fudo): Find a way to link children to parents. (R has no pointers or references).
-                treeBranches <- sapply(fileStructure, function(filePath)
+                arvadosFiles <- NULL
+                sapply(fileNames, function(fileName)
                 {
-                    fileWithPath <- unlist(stringr::str_split(filePath, "/"))
-                    file <- fileWithPath[length(fileWithPath), drop = T]
-
-                    if(file != "")
-                    {
-                        file <- ArvadosFile(file, api)
-                        file$relativePath <- filePath
-                    }
-                    else
-                    {
-                        file <- NULL
-                    }
-
-                    folders <- fileWithPath[-length(fileWithPath)]
-
-                    subcollections <- sapply(folders, function(folder)
-                    {
-                        folder <- Subcollection(folder)
-                        unname(folder)
-                    })
-
-                    if(!is.null(file))
-                        subcollections <- c(subcollections, file)
-
-                    if(length(subcollections) > 1)
-                    {
-                        for(subcollectionIndex in 1:(length(subcollections) - 1))
-                        {
-                            subcollections[[subcollectionIndex]]$relativePath <- paste(folders[1:(subcollectionIndex)], collapse = "/")
-                            subcollections[[subcollectionIndex]]$add(subcollections[[subcollectionIndex + 1]])
-                        }
-                    }
-                    subcollections[[1]]
+                    childWithSameName <- subcollection$get(fileName)
+                    if(!is.null(childWithSameName))
+                        stop("Destination already contains file with same name.")
+
+                    newFile <- ArvadosFile$new(fileName)
+                    subcollection$add(newFile)
+
+                    arvadosFiles <<- c(arvadosFiles, newFile)
                 })
 
-                root <- Subcollection(".")
+                if(length(arvadosFiles) == 1)
+                    return(arvadosFiles[[1]])
+                else
+                    return(arvadosFiles)
+            }
+            else 
+            {
+                stop(paste0("Expected character vector, got ",
+                            paste0("(", paste0(class(fileNames), collapse = ", "), ")"),
+                            "."))
+            }
+        },
 
-                addIfExists <- function(firstNode, secondNode)
-                {
-                    firstNodeContent <- sapply(firstNode$content, function(node) {node$name})
-                    if(length(firstNodeContent) == 0)
-                    {
-                        firstNode$add(secondNode)
-                        return()
-                    }
-
-                    matchPosition <- match(secondNode$name, firstNodeContent, -1)
-                    if(matchPosition != -1)
-                    {
-                        addIfExists(firstNode$content[[matchPosition]], secondNode$content[[1]])
-                    }
-                    else
-                    {
-                        firstNode$add(secondNode)
-                    }
-                }
-
-                sapply(treeBranches, function(branch)
+        remove = function(paths)
+        {
+            if(is.null(private$tree))
+                private$genereateCollectionTreeStructure()
+
+            if(is.character(paths))
+            {
+                sapply(paths, function(filePath)
                 {
-                    addIfExists(root, branch)
+                    filePath <- trimFromEnd(filePath, "/")
+                    file <- self$get(filePath)
+
+                    if(is.null(file))
+                        stop(paste("File", filePath, "doesn't exist."))
+
+                    parent <- file$getParent()
+
+                    if(is.null(parent))
+                        stop("You can't delete root folder.")
+
+                    parent$remove(file$getName())
                 })
 
-                root
+                "Content removed"
+            }
+            else 
+            {
+                stop(paste0("Expected character vector, got ",
+                            paste0("(", paste0(class(paths), collapse = ", "), ")"),
+                            "."))
             }
+        },
+
+        move = function(content, newLocation)
+        {
+            if(is.null(private$tree))
+                private$genereateCollectionTreeStructure()
+
+            content <- trimFromEnd(content, "/")
+
+            elementToMove <- self$get(content)
+
+            if(is.null(elementToMove))
+                stop("Content you want to move doesn't exist in the collection.")
+
+            elementToMove$move(newLocation)
+        },
+
+        getFileListing = function()
+        {
+            if(is.null(private$tree))
+                private$genereateCollectionTreeStructure()
+
+            content <- private$REST$getCollectionContent(self$uuid)
+            content[order(tolower(content))]
+        },
+
+        get = function(relativePath)
+        {
+            if(is.null(private$tree))
+                private$genereateCollectionTreeStructure()
 
-            #Todo(Fudo): This is dummy data. Real content will come from WebDAV server.
-            # testFileStructure <- c("math.h", "main.cpp", "emptyFolder/",
-                                   # "java/render.java", "java/test/observer.java",
-                                   # "java/test/observable.java",
-                                   # "csharp/this.cs", "csharp/is.cs",
-                                   # "csharp/dummy.cs", "csharp/file.cs")
-            items  <<- getCollectionContent()
-            fileContent  <<- .createCollectionContentTree(items)
+            private$tree$getElement(relativePath)
+        },
+
+               toJSON = function() 
+        {
+                       fields <- sapply(private$classFields, function(field)
+                       {
+                               self[[field]]
+                       }, USE.NAMES = TRUE)
+                       
+                       jsonlite::toJSON(list("collection" = 
+                     Filter(Negate(is.null), fields)), auto_unbox = TRUE)
+               },
+
+               isEmpty = function() {
+                       fields <- sapply(private$classFields,
+                                        function(field) self[[field]])
+
+                       if(any(sapply(fields, function(field) !is.null(field) && field != "")))
+                               FALSE
+                       else
+                               TRUE
+               },
+
+        getRESTService = function() private$REST,
+        setRESTService = function(newRESTService) private$REST <- newRESTService
+    ),
+
+    private = list(
+
+        REST        = NULL,
+        tree        = NULL,
+        fileContent = NULL,
+        classFields = NULL,
+
+        genereateCollectionTreeStructure = function()
+        {
+            if(is.null(self$uuid))
+                stop("Collection uuid is not defined.")
+
+            if(is.null(private$REST))
+                stop("REST service is not defined.")
+
+            private$fileContent <- private$REST$getCollectionContent(self$uuid)
+            private$tree <- CollectionTree$new(private$fileContent, self)
         }
-    )
+    ),
+
+    cloneable = FALSE
 )
+
+#' print.Collection
+#'
+#' Custom print function for Collection class
+#'
+#' @param x Instance of Collection class
+#' @param ... Optional arguments.
+#' @export 
+print.Collection = function(x, ...)
+{
+    cat(paste0("Type: ", "\"", "Arvados Collection", "\""), sep = "\n")
+    cat(paste0("uuid: ", "\"", x$uuid,               "\""), sep = "\n")
+}