Contents

1 Overview

Developers can also create “alabaster applications”, which customize the machinery of the alabaster framework for specific needs. Customizations typically involve:

We provide a number of hooks inside alabaster.base to enable applications to apply these customizations over the defaults.

2 Creating a new retrieval mechanism

The acquireMetadata() and acquireFile() generic, which describe how the metadata and file artifacts should be acquired. For example, applications can write new methods that query APIs for this content rather than reading it from the filesystem.

library(alabaster.base)
setClass("RemoteDownloadHandler", slots=c(host="character", id="character"))

setMethod("acquireFile", "RemoteDownloadHandler", function(project, path) {
    # Download a file here, possibly with some application-specific caching.
    demo.url <- paste0(project@host, "/projects/", project@id, "/file", path)
    target <- tempfile()
    download.file(demo.url, target)
    target
})

setMethod("acquireMetadata", "RemoteDownloadHandler", function(project, path) {
    # Pull down JSON metadata, possibly with some application-specific caching.
    demo.url <- paste0(project@host, "/projects/", project@id, "/file", path)
    target <- tempfile()
    download.file(demo.url, target)
    jsonlite::fromJSON(target, simplifyVector=FALSE)
})

We can then construct an instance of a RemoteDownloadHandler;

proj <- new("RemoteDownloadHandler", host="https://my.institute.org/downloads", id="PROJECT_ID")

And use it in loadObject(), which will use the new methods for all internal acquireMetadata() and acquireFile() calls. This will instruct loadObject() to download remote content on demand.

# Demonstration only.
meta <- acquireMetadata(proj, "some/file/path.csv")
obj <- loadObject(meta, proj)

3 Creating new schemas

Applications can define their own schemas with custom metadata requirements or data structures. See here for more details. Once created, the application-specific schemas should be stored in the inst/schemas directory of the application’s R package.

4 Overriding the staging method

The .altStageObject() setter allows applications to replace stageObject() with an alternative staging generic. This can be used to perform additional tasks during staging of some or all classes, e.g., add more metadata. For example, we could force all saving operations to include the author in the metadata for non-child objects:

setGeneric("appStageObject", function(x, dir, path, child=FALSE, ...) 
    standardGeneric("appStageObject"))
## [1] "appStageObject"
setMethod("appStageObject", "ANY", function(x, dir, path, child=FALSE, ...) {
    meta <- stageObject(x, dir, path, child=child, ...)

    # Creating a fallback that adds authorship to all non-child objects. 
    if (!child) {
        meta$authors <- I(Sys.info()[["user"]])
    }

    # Pointing writeMetadata to the application package storing the schemas.
    attr(meta[["$schema"]], "package") <- "APPLICATION_NAME_HERE"

    meta 
})

Application developers will typically create another wrapper function that runs the setter before attempting to stage an object. This is more convenient for the end-users of that application, who do not have to remember what to set:

appSave <- function(x, dir, path, child=FALSE) {
    olds <- altStageObjectFunction(appStageObject)
    on.exit(altStageObjectFunction(olds))

    meta <- appStageObject(x, dir, path, child=child)
    written <- writeMetadata(meta, dir) 

    written$path
}

Of course, it is possible to customize the staging of specific classes by simply defining a new method for the new generic:

setMethod("appStageObject", "DFrame", function(x, dir, path, child=FALSE, ...) {
    # Extracting details from the metadata.
    clinical.trial.id <- metadata(x)$trial_id
    treatment <- metadata(x)$treatment
    study.design <- metadata(x)$study

    # Calling the ANY method, which eventually just calls stageObject...
    meta <- callNextMethod()

    # Adding some metadata for data frames, assuming these properties are
    # listed in the schema.
    meta[["clinical_trail_details"]] <- list(
        trial_id = trail.id,
        treatment = treatment,
        design = study.design
    )

    meta
})

5 Overriding the loading method

Similarly, the .altLoadObject() setter allows applications to set an alternative loading function to replace loadObject(). This is necessary if .altStageObject() is used to define a staging override that points to a different set of schemas; in which case, the loading method must also be overridden to look at those schemas to obtain appropriate restoration method (in the _attributes.restore.R property). The loading method may also attach various bits and pieces of global metadata that we might have stored, e.g. authorship.

# Memorize schema look-up in the R session, to avoid having to repeatedly query
# the R package directory on the file system at every loadObject request.
memory <- new.env()
memory$cache <- list()

appLoadObject <- function(info, project, ...) {
    # customLoadObjectHelper is a helper function that handles loading with
    # different schema location and memory store.
    output <- customLoadObjectHelper(info, project, ..., 
        .locations="APPLCATION_NAME_HERE",
        .memory=memory
    )

    if ("authors" %in% names(info) && is(output, "Annotated")) {
        metadata(output)$authors <- info$authors
    }

    output
}

Application developers will typically create another wrapper function that runs the setter before attempting to load an object. This wrapper may also create the application-specific *Handler class that will be used to override acquireFile and acquireMetadata.

appLoad <- function(project, path) {
    oldl <- altLoadObjectFunction(appLoadObject)
    on.exit(altLoadObjectFunction(oldl))
    info <- acquireMetadata(project, path)
    appLoadObject(info, project, child=child)
}

Note that altLoadObject() will override the loading for all objects. For overrides of specific objects, application developers can simply modify the _attributes.restore.R in the corresponding schema to point to a different function.

Session information

sessionInfo()
## R version 4.3.2 (2023-10-31)
## Platform: x86_64-pc-linux-gnu (64-bit)
## Running under: Ubuntu 22.04.3 LTS
## 
## Matrix products: default
## BLAS:   /home/biocbuild/bbs-3.18-bioc/R/lib/libRblas.so 
## LAPACK: /usr/lib/x86_64-linux-gnu/lapack/liblapack.so.3.10.0
## 
## locale:
##  [1] LC_CTYPE=en_US.UTF-8       LC_NUMERIC=C              
##  [3] LC_TIME=en_GB              LC_COLLATE=C              
##  [5] LC_MONETARY=en_US.UTF-8    LC_MESSAGES=en_US.UTF-8   
##  [7] LC_PAPER=en_US.UTF-8       LC_NAME=C                 
##  [9] LC_ADDRESS=C               LC_TELEPHONE=C            
## [11] LC_MEASUREMENT=en_US.UTF-8 LC_IDENTIFICATION=C       
## 
## time zone: America/New_York
## tzcode source: system (glibc)
## 
## attached base packages:
## [1] stats     graphics  grDevices utils     datasets  methods   base     
## 
## other attached packages:
## [1] alabaster.base_1.2.1 BiocStyle_2.30.0    
## 
## loaded via a namespace (and not attached):
##  [1] cli_3.6.1               knitr_1.45              rlang_1.1.2            
##  [4] xfun_0.41               jsonlite_1.8.7          S4Vectors_0.40.1       
##  [7] htmltools_0.5.7         sass_0.4.7              stats4_4.3.2           
## [10] rmarkdown_2.25          evaluate_0.23           jquerylib_0.1.4        
## [13] fastmap_1.1.1           yaml_2.3.7              alabaster.schemas_1.2.0
## [16] Rhdf5lib_1.24.0         bookdown_0.36           BiocManager_1.30.22    
## [19] compiler_4.3.2          Rcpp_1.0.11             rhdf5filters_1.14.1    
## [22] rhdf5_2.46.0            digest_0.6.33           R6_2.5.1               
## [25] bslib_0.5.1             tools_4.3.2             BiocGenerics_0.48.1    
## [28] cachem_1.0.8