Author: Martin Morgan (mtmorgan@fredhutch.org)
Date: 7 September, 2015
Back to Workshop Outline

The material in this document requires R version 3.2 and Bioconductor version 3.1

stopifnot(
    getRversion() >= '3.2' && getRversion() < '3.3',
    BiocInstaller::biocVersion() >= "3.1"
)

Bioconductor 'infrastructure' for sequence analysis

Classes, methods, and packages

This section focuses on classes, methods, and packages, with the goal being to learn to navigate the help system and interactive discovery facilities.

Motivation

Sequence analysis is specialized

Additional considerations

Solution: use well-defined classes to represent complex data; methods operate on the classes to perform useful functions. Classes and methods are placed together and distributed as packages so that we can all benefit from the hard work and tested code of others.

Core packages

                   VariantAnnotation
                           |
                           v
                    GenomicFeatures
                           |
                           v
                       BSgenome
                           |
                           v
                      rtracklayer
                           |
                           v
                    GenomicAlignments
                      |           |
                      v           v
     SummarizedExperiment   Rsamtools  ShortRead
                  |         |      |      |
                  v         v      v      v
                GenomicRanges     Biostrings
                        |          |
                        v          v
               GenomeInfoDb   (XVector)
                        |     |
                        v     v
                        IRanges
                           |
                           v 
                      (S4Vectors)

Core classes

Case study: IRanges and GRanges

The IRanges package defines an important class for specifying integer ranges, e.g.,

library(IRanges)
ir <- IRanges(start=c(10, 20, 30), width=5)
ir
## IRanges of length 3
##     start end width
## [1]    10  14     5
## [2]    20  24     5
## [3]    30  34     5

There are many interesting operations to be performed on ranges, e.g, flank() identifies adjacent ranges

flank(ir, 3)
## IRanges of length 3
##     start end width
## [1]     7   9     3
## [2]    17  19     3
## [3]    27  29     3

The IRanges class is part of a class hierarchy. To see this, ask R for the class of ir, and for the class definition of the IRanges class

class(ir)
## [1] "IRanges"
## attr(,"package")
## [1] "IRanges"
getClass(class(ir))
## Class "IRanges" [package "IRanges"]
## 
## Slots:
##                                                                                       
## Name:            start           width           NAMES     elementType elementMetadata
## Class:         integer         integer characterORNULL       character DataTableORNULL
##                       
## Name:         metadata
## Class:            list
## 
## Extends: 
## Class "Ranges", directly
## Class "IntegerList", by class "Ranges", distance 2
## Class "RangesORmissing", by class "Ranges", distance 2
## Class "AtomicList", by class "Ranges", distance 3
## Class "List", by class "Ranges", distance 4
## Class "Vector", by class "Ranges", distance 5
## Class "Annotated", by class "Ranges", distance 6
## 
## Known Subclasses: "NormalIRanges"

Notice that IRanges extends the Ranges class. Now try entering ?flank (?"flank,<tab>" if not using _RStudio, where <tab> means to press the tab key to ask for tab completion). You can see that there are help pages for flank operating on several different classes. Select the completion

?"flank,Ranges-method" 

and verify that you're at the page that describes the method relevant to an IRanges instance. Explore other range-based operations.

The GenomicRanges package extends the notion of ranges to include features relevant to application of ranges in sequence analysis, particularly the ability to associate a range with a sequence name (e.g., chromosome) and a strand. Create a GRanges instance based on our IRanges instance, as follows

library(GenomicRanges)
gr <- GRanges(c("chr1", "chr1", "chr2"), ir, strand=c("+", "-", "+"))
gr
## GRanges object with 3 ranges and 0 metadata columns:
##       seqnames    ranges strand
##          <Rle> <IRanges>  <Rle>
##   [1]     chr1  [10, 14]      +
##   [2]     chr1  [20, 24]      -
##   [3]     chr2  [30, 34]      +
##   -------
##   seqinfo: 2 sequences from an unspecified genome; no seqlengths

The notion of flanking sequence has a more nuanced meaning in biology. In particular we might expect that flanking sequence on the + strand would precede the range, but on the minus strand would follow it. Verify that flank applied to a GRanges object has this behavior.

flank(gr, 3)
## GRanges object with 3 ranges and 0 metadata columns:
##       seqnames    ranges strand
##          <Rle> <IRanges>  <Rle>
##   [1]     chr1  [ 7,  9]      +
##   [2]     chr1  [25, 27]      -
##   [3]     chr2  [27, 29]      +
##   -------
##   seqinfo: 2 sequences from an unspecified genome; no seqlengths

Discover what classes GRanges extends, find the help page documenting the behavior of flank when applied to a GRanges object, and verify that the help page documents the behavior we just observed.

class(gr)
## [1] "GRanges"
## attr(,"package")
## [1] "GenomicRanges"
getClass(class(gr))
## Class "GRanges" [package "GenomicRanges"]
## 
## Slots:
##                                                                                       
## Name:         seqnames          ranges          strand elementMetadata         seqinfo
## Class:             Rle         IRanges             Rle       DataFrame         Seqinfo
##                       
## Name:         metadata
## Class:            list
## 
## Extends: 
## Class "GenomicRanges", directly
## Class "Vector", by class "GenomicRanges", distance 2
## Class "GenomicRangesORmissing", by class "GenomicRanges", distance 2
## Class "GenomicRangesORGRangesList", by class "GenomicRanges", distance 2
## Class "GenomicRangesORGenomicRangesList", by class "GenomicRanges", distance 2
## Class "RangedDataORGenomicRanges", by class "GenomicRanges", distance 2
## Class "Annotated", by class "GenomicRanges", distance 3
?"flank,GenomicRanges-method"

Notice that the available flank() methods have been augmented by the methods defined in the GenomicRanges package.

It seems like there might be a number of helpful methods available for working with genomic ranges; we can discover some of these from the command line, indicating that the methods should be on the current search() path

methods(class="GRanges")
##   [1] !=                  $                   $<-                 %in%               
##   [5] <                   <=                  ==                  >                  
##   [9] >=                  BamViews            GenomicFiles        NROW               
##  [13] Ops                 ROWNAMES            ScanBamParam        ScanBcfParam       
##  [17] [                   [<-                 aggregate           anyNA              
##  [21] append              as.character        as.complex          as.data.frame      
##  [25] as.env              as.integer          as.list             as.logical         
##  [29] as.numeric          as.raw              bamWhich<-          blocks             
##  [33] browseGenome        c                   chrom               chrom<-            
##  [37] coerce              coerce<-            compare             countOverlaps      
##  [41] coverage            disjoin             disjointBins        distance           
##  [45] distanceToNearest   duplicated          elementMetadata     elementMetadata<-  
##  [49] end                 end<-               eval                export             
##  [53] extractROWS         extractUpstreamSeqs findOverlaps        flank              
##  [57] follow              gaps                getPromoterSeq      granges            
##  [61] head                high2low            intersect           isDisjoint         
##  [65] length              liftOver            mapCoords           mapFromTranscripts 
##  [69] mapToTranscripts    match               mcols               mcols<-            
##  [73] metadata            metadata<-          mstack              names              
##  [77] names<-             narrow              nearest             order              
##  [81] overlapsAny         pack                parallelSlotNames   parallelVectorNames
##  [85] pgap                pintersect          pmapCoords          pmapFromTranscripts
##  [89] pmapToTranscripts   precede             promoters           psetdiff           
##  [93] punion              range               ranges              ranges<-           
##  [97] rank                reduce              reduceByFile        reduceByRange      
## [101] relist              relistToClass       rename              rep                
## [105] rep.int             replaceROWS         resize              restrict           
## [109] rev                 rowRanges<-         scanFa              scanTabix          
## [113] score               score<-             seqinfo             seqinfo<-          
## [117] seqlevelsInUse      seqnames            seqnames<-          setdiff            
## [121] shift               shiftApply          show                showAsCell         
## [125] sort                split               split<-             start              
## [129] start<-             strand              strand<-            subset             
## [133] subsetByOverlaps    summarizeOverlaps   table               tail               
## [137] tapply              tile                trim                union              
## [141] unique              update              updateObject        values             
## [145] values<-            width               width<-             window             
## [149] window<-            with                xtfrm              
## see '?methods' for accessing help and source code

Use help() to list the help pages in the GenomicRanges package, and vignettes() to view and access available vignettes; these are also available in the Rstudio 'Help' tab.

help(package="GenomicRanges")
vignette(package="GenomicRanges")
vignette(package="GenomicRanges", "GenomicRangesHOWTOs")

GenomicRanges

The GRanges and GRangesList classes

Aside: 'TxDb' packages provide an R representation of gene models

library(TxDb.Hsapiens.UCSC.hg19.knownGene)
txdb <- TxDb.Hsapiens.UCSC.hg19.knownGene

exons(): GRanges

exons(txdb)
## GRanges object with 289969 ranges and 1 metadata column:
##            seqnames               ranges strand   |   exon_id
##               <Rle>            <IRanges>  <Rle>   | <integer>
##        [1]     chr1       [11874, 12227]      +   |         1
##        [2]     chr1       [12595, 12721]      +   |         2
##        [3]     chr1       [12613, 12721]      +   |         3
##        [4]     chr1       [12646, 12697]      +   |         4
##        [5]     chr1       [13221, 14409]      +   |         5
##        ...      ...                  ...    ... ...       ...
##   [289965]     chrY [27607404, 27607432]      -   |    277746
##   [289966]     chrY [27635919, 27635954]      -   |    277747
##   [289967]     chrY [59358329, 59359508]      -   |    277748
##   [289968]     chrY [59360007, 59360115]      -   |    277749
##   [289969]     chrY [59360501, 59360854]      -   |    277750
##   -------
##   seqinfo: 93 sequences (1 circular) from hg19 genome

Alt Genomic Ranges

exonsBy(): GRangesList

exonsBy(txdb, "tx")
## GRangesList object of length 82960:
## $1 
## GRanges object with 3 ranges and 3 metadata columns:
##       seqnames         ranges strand |   exon_id   exon_name exon_rank
##          <Rle>      <IRanges>  <Rle> | <integer> <character> <integer>
##   [1]     chr1 [11874, 12227]      + |         1        <NA>         1
##   [2]     chr1 [12613, 12721]      + |         3        <NA>         2
##   [3]     chr1 [13221, 14409]      + |         5        <NA>         3
## 
## $2 
## GRanges object with 3 ranges and 3 metadata columns:
##       seqnames         ranges strand | exon_id exon_name exon_rank
##   [1]     chr1 [11874, 12227]      + |       1      <NA>         1
##   [2]     chr1 [12595, 12721]      + |       2      <NA>         2
##   [3]     chr1 [13403, 14409]      + |       6      <NA>         3
## 
## $3 
## GRanges object with 3 ranges and 3 metadata columns:
##       seqnames         ranges strand | exon_id exon_name exon_rank
##   [1]     chr1 [11874, 12227]      + |       1      <NA>         1
##   [2]     chr1 [12646, 12697]      + |       4      <NA>         2
##   [3]     chr1 [13221, 14409]      + |       5      <NA>         3
## 
## ...
## <82957 more elements>
## -------
## seqinfo: 93 sequences (1 circular) from hg19 genome

Alt Genomic Ranges List

GRanges / GRangesList are incredibly useful

Algebra of genomic ranges

Many biologically interesting questions represent operations on ranges

GRanges Algebra

Alt Ranges Algebra

Biostrings (DNA or amino acid sequences)

Classes

Methods –

Related packages

Example

GenomicAlignments (Aligned reads)

Classes – GenomicRanges-like behaivor

Methods

Example

VariantAnnotation (Called variants)

Classes – GenomicRanges-like behavior

Functions and methods

Example

Related packages

Reference

rtracklayer (Genome annotations)

SummarizedExperiment

Alt SummarizedExperiment

Functions and methods

Input & representation of standard file formats

BAM files of aligned reads – GenomicAlignments

Recall: overall workflow

  1. Experimental design
  2. Wet-lab preparation
  3. High-throughput sequencing
  4. Alignment
  5. Summary
  6. Statistical analysis
  7. Comprehension

BAM files of aligned reads

GenomicAlignments

Other formats and packages

Alt Files and the Bioconductor packages that input them

Large data – BiocParallel, GenomicFiles

Restriction

Iteration

Iterative programming model

Parallel evaluation