21700: Install Bundler system-wide in Rails postinst
[arvados.git] / sdk / R / R / Subcollection.R
1 # Copyright (C) The Arvados Authors. All rights reserved.
2 #
3 # SPDX-License-Identifier: Apache-2.0
4
5 #' R6 Class Representing a Subcollection
6 #'
7 #' @description
8 #' Subcollection class represents a folder inside Arvados collection.
9 #' It is essentially a composite of arvadosFiles and other subcollections.
10
11 #' @export
12 Subcollection <- R6::R6Class(
13
14     "Subcollection",
15
16     public = list(
17
18         #' @description
19         #' Initialize new enviroment.
20         #' @param name Name of the new enviroment.
21         #' @return A new `Subcollection` object.
22         initialize = function(name)
23         {
24             private$name <- name
25         },
26
27         #' @description
28         #' Returns name of the file.
29         getName = function() private$name,
30
31         #' @description
32         #' Returns Subcollection's path relative to the root.
33         getRelativePath = function()
34         {
35             relativePath <- c(private$name)
36             parent <- private$parent
37
38             while(!is.null(parent))
39             {
40                 relativePath <- c(parent$getName(), relativePath)
41                 parent <- parent$getParent()
42             }
43
44             relativePath <- relativePath[relativePath != ""]
45             paste0(relativePath, collapse = "/")
46         },
47
48         #' @description
49         #' Adds ArvadosFile or Subcollection specified by content to the Subcollection.
50         #' @param content Content to be added.
51         add = function(content)
52         {
53             if("ArvadosFile"   %in% class(content) ||
54                "Subcollection" %in% class(content))
55             {
56                 if(!is.null(content$getCollection()))
57                     stop("Content already belongs to a collection.")
58
59                 if(content$getName() == "")
60                     stop("Content has invalid name.")
61
62                 childWithSameName <- self$get(content$getName())
63
64                 if(!is.null(childWithSameName))
65                     stop(paste("Subcollection already contains ArvadosFile",
66                                "or Subcollection with same name."))
67
68                 if(!is.null(private$collection))
69                 {
70                     if(self$getRelativePath() != "")
71                         contentPath <- paste0(self$getRelativePath(),
72                                               "/", content$getFileListing())
73                     else
74                         contentPath <- content$getFileListing()
75
76                     REST <- private$collection$getRESTService()
77                     REST$create(contentPath, private$collection$uuid)
78                     content$setCollection(private$collection)
79                 }
80
81                 private$children <- c(private$children, content)
82                 content$setParent(self)
83
84                 "Content added successfully."
85             }
86             else
87             {
88                 stop(paste0("Expected AravodsFile or Subcollection object, got ",
89                             paste0("(", paste0(class(content), collapse = ", "), ")"),
90                             "."))
91             }
92         },
93
94         #' @description
95         #' Removes ArvadosFile or Subcollection specified by name from the Subcollection.
96         #' @param name Name of the file to be removed.
97         remove = function(name)
98         {
99             if(is.character(name))
100             {
101                 child <- self$get(name)
102
103                 if(is.null(child))
104                     stop(paste("Subcollection doesn't contains ArvadosFile",
105                                "or Subcollection with specified name."))
106
107                 if(!is.null(private$collection))
108                 {
109                     REST <- private$collection$getRESTService()
110                     REST$delete(child$getRelativePath(), private$collection$uuid)
111
112                     child$setCollection(NULL)
113                 }
114
115                 private$removeChild(name)
116                 child$setParent(NULL)
117
118                 "Content removed"
119             }
120             else
121             {
122                 stop(paste0("Expected character, got ",
123                             paste0("(", paste0(class(name), collapse = ", "), ")"),
124                             "."))
125             }
126         },
127
128         #' @description
129         #' Returns Subcollections file content as character vector.
130         #' @param fullPath Checking if the path to file exists.
131         getFileListing = function(fullPath = TRUE)
132         {
133             content <- private$getContentAsCharVector(fullPath)
134             content[order(tolower(content))]
135         },
136
137         #' @description
138         #' Returns subcollections content size in bytes.
139         getSizeInBytes = function()
140         {
141             if(is.null(private$collection))
142                 return(0)
143
144             REST <- private$collection$getRESTService()
145
146             fileSizes <- REST$getResourceSize(paste0(self$getRelativePath(), "/"),
147                                               private$collection$uuid)
148             return(sum(fileSizes))
149         },
150
151         #' @description
152         #' Moves Subcollection to a new location inside collection.
153         #' @param destination Path to move the file.
154         move = function(destination)
155         {
156             if(is.null(private$collection))
157                 stop("Subcollection doesn't belong to any collection.")
158
159             destination <- trimFromEnd(destination, "/")
160             nameAndPath <- splitToPathAndName(destination)
161
162             newParent <- private$collection$get(nameAndPath$path)
163
164             if(is.null(newParent))
165                 stop("Unable to get destination subcollection.")
166
167             childWithSameName <- newParent$get(nameAndPath$name)
168
169             if(!is.null(childWithSameName))
170                 stop("Destination already contains content with same name.")
171
172             REST <- private$collection$getRESTService()
173             REST$move(self$getRelativePath(),
174                       paste0(newParent$getRelativePath(), "/", nameAndPath$name),
175                       private$collection$uuid)
176
177             private$dettachFromCurrentParent()
178             private$attachToNewParent(self, newParent)
179
180             private$parent <- newParent
181             private$name <- nameAndPath$name
182
183             self
184         },
185
186         #' @description
187         #' Copies Subcollection to a new location inside collection.
188         #' @param destination Path to copy the file.
189         copy = function(destination)
190         {
191             if(is.null(private$collection))
192                 stop("Subcollection doesn't belong to any collection.")
193
194             destination <- trimFromEnd(destination, "/")
195             nameAndPath <- splitToPathAndName(destination)
196
197             newParent <- private$collection$get(nameAndPath$path)
198
199             if(is.null(newParent) || !("Subcollection" %in% class(newParent)))
200                 stop("Unable to get destination subcollection.")
201
202             childWithSameName <- newParent$get(nameAndPath$name)
203
204             if(!is.null(childWithSameName))
205                 stop("Destination already contains content with same name.")
206
207             REST <- private$collection$getRESTService()
208             REST$copy(self$getRelativePath(),
209                       paste0(newParent$getRelativePath(), "/", nameAndPath$name),
210                       private$collection$uuid)
211
212             newContent <- self$duplicate(nameAndPath$name)
213             newContent$setCollection(self$getCollection(), setRecursively = TRUE)
214             newContent$setParent(newParent)
215             private$attachToNewParent(newContent, newParent)
216
217             newContent
218         },
219
220         #' @description
221         #' Duplicate Subcollection and gives it a new name.
222         #' @param newName New name for duplicated file.
223         duplicate = function(newName = NULL)
224         {
225             name <- if(!is.null(newName)) newName else private$name
226             root <- Subcollection$new(name)
227             for(child in private$children)
228                 root$add(child$duplicate())
229
230             root
231         },
232
233         #' @description
234         #' If name is valid, returns ArvadosFile or Subcollection specified by relativePath, else returns NULL.
235         #' @param name Name of the file.
236         get = function(name)
237         {
238             for(child in private$children)
239             {
240                 if(child$getName() == name)
241                     return(child)
242             }
243
244             return(NULL)
245         },
246
247         #' @description
248         #' Returns files in Subcollection.
249         getFirst = function()
250         {
251             if(length(private$children) == 0)
252                 return(NULL)
253
254             private$children[[1]]
255         },
256
257         #' @description
258         #' Sets Collection by its UUID.
259         setCollection = function(collection, setRecursively = TRUE)
260         {
261             private$collection = collection
262
263             if(setRecursively)
264             {
265                 for(child in private$children)
266                     child$setCollection(collection)
267             }
268         },
269
270         #' @description
271         #' Returns Collection of Subcollection.
272         getCollection = function() private$collection,
273
274         #' @description
275         #' Returns Collection UUID.
276         getParent = function() private$parent,
277
278         #' @description
279         #' Sets new Collection.
280         setParent = function(newParent) private$parent <- newParent
281     ),
282
283     private = list(
284
285         name       = NULL,
286         children   = NULL,
287         parent     = NULL,
288         collection = NULL,
289
290         removeChild = function(name)
291         {
292             numberOfChildren = length(private$children)
293             if(numberOfChildren > 0)
294             {
295                 for(childIndex in 1:numberOfChildren)
296                 {
297                     if(private$children[[childIndex]]$getName() == name)
298                     {
299                         private$children = private$children[-childIndex]
300                         return()
301                     }
302                 }
303             }
304         },
305
306         attachToNewParent = function(content, newParent)
307         {
308             # We temporary set parents collection to NULL. This will ensure that
309             # add method doesn't post this subcollection to REST.
310             # We also need to set content's collection to NULL because
311             # add method throws exception if we try to add content that already
312             # belongs to a collection.
313             parentsCollection <- newParent$getCollection()
314             content$setCollection(NULL, setRecursively = FALSE)
315             newParent$setCollection(NULL, setRecursively = FALSE)
316             newParent$add(content)
317             content$setCollection(parentsCollection, setRecursively = FALSE)
318             newParent$setCollection(parentsCollection, setRecursively = FALSE)
319         },
320
321         dettachFromCurrentParent = function()
322         {
323             # We temporary set parents collection to NULL. This will ensure that
324             # remove method doesn't remove this subcollection from REST.
325             parent <- private$parent
326             parentsCollection <- parent$getCollection()
327             parent$setCollection(NULL, setRecursively = FALSE)
328             parent$remove(private$name)
329             parent$setCollection(parentsCollection, setRecursively = FALSE)
330         },
331
332         getContentAsCharVector = function(fullPath = TRUE)
333         {
334             content <- NULL
335
336             if(fullPath)
337             {
338                 for(child in private$children)
339                     content <- c(content, child$getFileListing())
340
341                 if(private$name != "")
342                     content <- unlist(paste0(private$name, "/", content))
343             }
344             else
345             {
346                 for(child in private$children)
347                     content <- c(content, child$getName())
348             }
349
350             content
351         }
352     ),
353
354     cloneable = FALSE
355 )
356
357 #' print.Subcollection
358 #'
359 #' Custom print function for Subcollection class
360 #'
361 #' @param x Instance of Subcollection class
362 #' @param ... Optional arguments.
363 #' @export
364 print.Subcollection = function(x, ...)
365 {
366     collection   <- NULL
367     relativePath <- x$getRelativePath()
368
369     if(!is.null(x$getCollection()))
370     {
371         collection <- x$getCollection()$uuid
372
373         if(!x$getName() == "")
374             relativePath <- paste0("/", relativePath)
375     }
376
377     cat(paste0("Type:          ", "\"", "Arvados Subcollection", "\""), sep = "\n")
378     cat(paste0("Name:          ", "\"", x$getName(),             "\""), sep = "\n")
379     cat(paste0("Relative path: ", "\"", relativePath,            "\""), sep = "\n")
380     cat(paste0("Collection:    ", "\"", collection,              "\""), sep = "\n")
381 }