Skip to content

Commit

Permalink
Template to Component
Browse files Browse the repository at this point in the history
  • Loading branch information
anngvu committed Aug 15, 2024
1 parent 109f7e6 commit 27bfeca
Show file tree
Hide file tree
Showing 2 changed files with 31 additions and 11 deletions.
6 changes: 6 additions & 0 deletions R/nextflow_annotation_utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -333,9 +333,11 @@ annotate_aligned_reads <- function(metadata,
verbose = TRUE) {

outputFrom <- attr(metadata, "outputFrom")
template <- sub("bts:", "", attr(metadata, "template"))
if(verbose) message("Running annotate_aligned_reads for ", outputFrom)

format_as <- annotation_rule(outputFrom, "format_as")
metadata[, Component := template]
metadata[, fileFormat := format_as(Filename)]
metadata[, dataType := "AlignedReads"]
metadata[, dataSubtype := "processed"]
Expand Down Expand Up @@ -369,13 +371,15 @@ annotate_quantified_expression <- function(metadata,
verbose = TRUE) {

outputFrom <- attr(metadata, "outputFrom")
template <- sub("bts:", "", attr(metadata, "template"))
if(verbose) message("Running annotate_quantified_expression for ", outputFrom)

format_as <- annotation_rule(outputFrom, "format_as")
expression_unit <- switch(outputFrom,
"STAR and Salmon" = "TPM",
"featureCounts" = "Counts")

metadata[, Component := template]
metadata[, fileFormat := format_as(Filename)]
metadata[, dataType := "geneExpression"]
metadata[, dataSubtype := "processed"]
Expand All @@ -402,6 +406,7 @@ annotate_called_variants <- function(metadata,
verbose = TRUE) {

outputFrom <- attr(metadata, "outputFrom")
template <- sub("bts:", "", attr(metadata, "template"))
if(verbose) message("Running annotate_called_variants for ", outputFrom)

# vcfs can be annotated type, workflow stops at Variant Calling bc we run a custom nf-vcf2maf
Expand All @@ -422,6 +427,7 @@ annotate_called_variants <- function(metadata,
}

format_as <- annotation_rule(outputFrom, "format_as")
metadata[, Component := template]
metadata[, fileFormat := format_as(Filename)]
metadata[, dataType := data_type_assign(Filename, fileFormat), by = entityId]
metadata[, dataSubtype := "processed"]
Expand Down
36 changes: 25 additions & 11 deletions R/provenance.R
Original file line number Diff line number Diff line change
@@ -1,18 +1,18 @@
#' Add activity to entity
#'
#'
#' Util for adding activity info to a file entity.
#' See also https://help.synapse.org/docs/Provenance.1972470373.html
#'
#'
#' @param entity Synapse entity id.
#' @param act_name Name of activity.
#' @param act_executed Reference to the the activity executed (URL preferred).
#' @param used_inputs Vector of inputs for this act, e.g. syn ids, links to other data sources, etc.
#' @export
add_activity <- function(entity,
add_activity <- function(entity,
act_name,
act_executed,
used_inputs) {

act <- synapseclient$Activity(name = act_name,
executed = act_executed,
used = used_inputs)
Expand All @@ -21,22 +21,22 @@ add_activity <- function(entity,
}

#' Add activity to multiple entities
#'
#' Wrapper provenance function that does a little more work to
#'
#' Wrapper provenance function that does a little more work to
#' expand many-to-many mappings to create records of entity, activity, and input.
#'
#' @param entities Vector or list of entities.
#'
#' @param entities Vector or list of entities.
#' @param act_name Vector or list of activity name.
#' @param act_executed Vector or list of reference activity executed.
#' @param used_inputs Vector or list of inputs for each entity.
#' @import data.table
#' @export
add_activity_batch <- function(entities,
add_activity_batch <- function(entities,
act_name,
act_executed,
used_inputs
) {

stopifnot(lengths(list(entities, act_name, act_executed, used_inputs)) > 0)
if(is.list(entities)) {
if(length(used_inputs) > 1) used_inputs <- rep(used_inputs, lengths(entities))
Expand All @@ -56,4 +56,18 @@ delete_provenance <- function(entities) {
for(i in entities) {
.syn$deleteProvenance(entity)
}
}
}

### Validate manifest

Manifests can be inspected and validated using schematic before submission.
To do so, it has to be written to a .csv first.

```{r rnaseq-meta-validate, eval=FALSE}

manifest_1 <- meta$manifests$`STAR and Salmon`
template <- sub("bts:", "", attr(manifest_1, "template"))
fwrite(manifest_1, "manifest_1.csv")
manifest_validate(data_type = template, file_name = "manifest_1.csv")

```

0 comments on commit 27bfeca

Please sign in to comment.