Skip to content

Commit

Permalink
add input_matrix() and output_matrix() function, now it can work on J…
Browse files Browse the repository at this point in the history
…SON directlh, and app and app will use this method to quickly access json list instead of slowly convert it to Tool or Flow object, so it's #1 faster than old method #2 more stable to customized fields.
  • Loading branch information
tengfei committed Jan 10, 2017
1 parent 8ff4c68 commit 2ec7c84
Show file tree
Hide file tree
Showing 5 changed files with 302 additions and 14 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -114,6 +114,7 @@ export(gender)
export(getTaskHook)
export(get_cwl_class)
export(input)
export(input_matrix)
export(investigation)
export(is_commandlinetool)
export(is_workflow)
Expand All @@ -126,6 +127,7 @@ export(misc_get_uploader)
export(misc_make_metadata)
export(misc_upload_cli)
export(output)
export(output_matrix)
export(paired_end)
export(platform)
export(platform_unit_id)
Expand Down
233 changes: 233 additions & 0 deletions R/api-utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -873,3 +873,236 @@ deType <- function(x) {
}
res
}

#' get input/output matrix out of json cwl file directly
#'
#' an efficient way to access json file, no need to convert a json into a Tool or Flow object before access, directly
#' operate on a list parsed from json file. Compare to \code{convert_app}, it's much faster.
#'
#' @param from a json file path
#' @param new.order a vector of column orders by default for input it's
#' "id", "label", "type", "required", "prefix", "fileTypes"; For output it's
#' "id", "label", "type", "fileTypes"
#' @param required logical value, show requried input node only or not.
#' @export input_matrix
#' @rdname input_output_matrix
#' @examples
#' tool.in = system.file("extdata/app", "tool_unpack_fastq.json", package = "sevenbridges")
#' flow.in = system.file("extdata/app", "flow_star.json", package = "sevenbridges")
#' input_matrix(tool.in)
#' input_matrix(tool.in, required = TRUE)
#' input_matrix(flow.in)
#' input_matrix(flow.in, c("id", "type"))
#' input_matrix(flow.in, required = TRUE)
input_matrix = function(from,
new.order = c("id", "label", "type", "required", "prefix", "fileTypes"),
required = NULL){

if(is.character(from) && file.exists(from)){
## json cwl file
obj <- fromJSON(from, FALSE)
}else{
## parsed list
obj <- from
}

in.lst = obj$inputs
lst = lapply(in.lst, function(x){
ib = x$inputBinding
res = c(x[!names(x) %in% c("inputBinding",
"sbg:category",
"required",
"sbg:fileTypes",
"type", "fileTypes",
"sbg:stageInput")],
list(

required = sevenbridges:::is_required(x),
type = sevenbridges:::make_type(x$type),
category = x[["sbg:category"]],
fileTypes = x[["sbg:fileTypes"]],
stageInput = x[["sbg:stageInput"]]),
ib)

res[sapply(res, is.null)] <- "null"
res = do.call(data.frame, res)
.fullnames = names(res)

.names.sbg = sort(.fullnames[grep("^sbg", .fullnames)])
.names.other = sort(setdiff(.fullnames, .names.sbg))
.names.priority = c("id", "type", "required", "fileTypes", "label")
.names.p2 = sort(setdiff(.names.other, .names.priority))
new.order = c(.names.priority, .names.p2, .names.sbg)

res[, new.order]
})

res = suppressWarnings(do.call("bind_rows", lst))


# reorder for File File...
idx = res$type %in% c("File", "File...")
res1 = res[idx, ]
res2 = res[!idx, ]
res = rbind(res1, res2)

# required or not

if (!is.null(required)) {
stopifnot(is.logical(required))
res = res[res$required == required, ]
if (!nrow(res)) {
return(NULL)
}
}

if (!is.null(new.order)) {
new.order = intersect(new.order, names(res))
res[, new.order]
} else {
res
}
}

#' @rdname input_output_matrix
#' @export output_matrix
#' @examples
#' tool.in = system.file("extdata/app", "tool_unpack_fastq.json", package = "sevenbridges")
#' flow.in = system.file("extdata/app", "flow_star.json", package = "sevenbridges")
#' output_matrix(tool.in)
#' output_matrix(flow.in)
output_matrix = function(from, new.order = c("id", "label", "type", "fileTypes")){

if(is.character(from) && file.exists(from)){
## json cwl file
obj <- fromJSON(from, FALSE)
}else{
## parsed list
obj <- from
}

.c = obj$class
out.lst = obj$outputs
switch(.c,
"CommandLineTool" = {
lst = lapply(out.lst, function(x){

o.b <- x$outputBinding
# glob
if (length(o.b$glob) == 1 && is.character(o.b$glob)) {
res.glob <- o.b$glob
} else {
res.glob <- o.b$glob$script
}
# load Contents
if (length(o.b$loadContents)) {
res.load <- o.b$loadContetns
} else {
res.load <- NULL
}
#
if (length(o.b$outputEval)) {
if (length(o.b$outputEval) == 1 &&
is.character(o.b$outputEval)){
res.eval <- o.b$outputEval
} else {
res.eval <- o.b$outputEval$script
}
} else {
res.eval <- NULL
}
ob <- list(glob = res.glob,
loadContents = res.load,
outputEval = res.eval,
inheritMetadataFrom = x$`sbg:inheritMetadataFrom`,
metadata = x$`sbg:metadata`,
secondaryFiles = x$seconaryFiles)

res = c(x[!names(x) %in% c("sbg:fileTypes",
"outputBinding",
"type",
"fileTypes",
"sbg:inheritMetadataFrom",
"sbg:metadata")],
list(type = sevenbridges:::make_type(x$type),

fileTypes = x[["sbg:fileTypes"]]), ob)

res[sapply(res, is.null)] <- "null"

res = do.call(data.frame, res)
.fullnames = names(res)

.names.sbg = sort(.fullnames[grep("^sbg", .fullnames)])
.names.other = sort(setdiff(.fullnames, .names.sbg))
.names.priority = c("id", "label", "type")
.names.p2 = sort(setdiff(.names.other, .names.priority))
new.order = c(.names.priority, .names.p2, .names.sbg)

res[, new.order]
})

res = suppressWarnings(do.call("bind_rows", lst))
# reorder for File File...
idx = res$type %in% c("File", "File...")
res1 = res[idx, ]
res2 = res[!idx, ]
res = rbind(res1, res2)

# new order
if (!is.null(new.order)) {
new.order = intersect(new.order, names(res))
res[, new.order]
} else {
res
}
},
"Workflow" = {
lst = lapply(out.lst, function(x){
res = c(x[!names(x) %in% c("sbg:fileTypes",
"type",
"fileTypes",
"sbg:inheritMetadataFrom",
"sbg:metadata")],
list(type = sevenbridges:::make_type(x$type),

fileTypes = x[["sbg:fileTypes"]]))


res[sapply(res, is.null)] <- "null"
res = do.call(data.frame, res)
.fullnames = names(res)

.names.sbg = sort(.fullnames[grep("^sbg", .fullnames)])
.names.other = sort(setdiff(.fullnames, .names.sbg))
.names.priority = c("id", "label", "type")
.names.p2 = sort(setdiff(.names.other, .names.priority))
new.order = c(.names.priority, .names.p2, .names.sbg)

res[, new.order]
})
res = suppressWarnings(do.call("bind_rows", lst))
# reorder for File File...
idx = res$type %in% c("File", "File...")
res1 = res[idx, ]
res2 = res[!idx, ]
res = rbind(res1, res2)
# new order
if ("link_to" %in% new.order || is.null(new.order)) {
lm = link_map()
res$link_to = sapply(res$id, function(i) {
paste0(as.character(lm[which(lm$id == i), "source"]), collapse = " | ")
})
}

if (!is.null(new.order)) {
new.order = intersect(new.order, names(res))
res[, new.order]
} else {
res
}


})

}
21 changes: 11 additions & 10 deletions R/class-app.R
Original file line number Diff line number Diff line change
Expand Up @@ -84,24 +84,19 @@ App <- setRefClass("App", contains = "Item",
if (is.null(raw)) {
message("get cwl raw file")
cwl()
raw_obj <<- convert_app(.self)
}
if (is.null(raw_obj)) {
raw_obj <<- convert_app(.self)

}
raw_obj$input_matrix(...)
sevenbridges:::input_matrix(raw, ...)

},

output_matrix = function(...) {
if (is.null(raw)) {
message("get cwl raw file")
cwl()
raw_obj <<- convert_app(.self)
}
if (is.null(raw_obj)) {
raw_obj <<- convert_app(.self)

}
raw_obj$output_matrix(...)
sevenbridges:::output_matrix(raw, ...)
},

input_type = function(...) {
Expand Down Expand Up @@ -608,3 +603,9 @@ get_steplist_item = function(input) {
ss = obj$steps
do.call(SBGStepList, lapply(ss, get_step_item))
}






39 changes: 39 additions & 0 deletions man/input_output_matrix.Rd

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

21 changes: 17 additions & 4 deletions vignettes/api.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -455,14 +455,15 @@ To draft a new task, you need to specify the following:

You can always check the App details on the visual interface for task input requirements. To find the required inputs with R, you need to get an `App` object first.



```{r}
app <- a$app(id = "tengfei/api-testing-2/newcopyofstar")
# get input matrix
app$input_matrix()
app$input_matrix(c("id", "label", "type"))
# get required node only
app$input_matrix(c("id", "label", "type"), required = TRUE)
# get required input names and types only
app$get_required()
```

Conversely, you can load the app from a CWL JSON and convert it into an R object first, as shown below.
Expand All @@ -474,8 +475,20 @@ app <- convert_app(f1)
app$input_matrix()
app$input_matrix(c("id", "label", "type"))
app$input_matrix(c("id", "label", "type"), required = TRUE)
# get required input names and types only
app$get_required()
```

Note `input_matrix` and `output_matrix` are useful accessor for Tool, Flow, App object as shown below in App example, you can directly call these two function on a JSON file as well.

```{r}
tool.in = system.file("extdata/app", "tool_unpack_fastq.json", package = "sevenbridges")
flow.in = system.file("extdata/app", "flow_star.json", package = "sevenbridges")
input_matrix(tool.in)
input_matrix(tool.in, required = TRUE)
input_matrix(flow.in)
input_matrix(flow.in, c("id", "type"))
input_matrix(flow.in, required = TRUE)
output_matrix(tool.in)
output_matrix(flow.in)
```

In the response body, locate the names of the required inputs. Note that task inputs need to match the expected data type and name. In the above example, we see two required fields:
Expand Down

0 comments on commit 2ec7c84

Please sign in to comment.