Hervé Pagès
June 2016
methods
package.> sessionInfo()
...
attached base packages:
[1] stats graphics grDevices utils datasets
[6] methods base
The syntax
not:
like in other OO programming languages.
The central concepts
The result
> ls('package:methods')
[1] "addNextMethod" "allGenerics"
[3] "allNames" "Arith"
[5] "as" "as<-"
[7] "asMethodDefinition" "assignClassDef"
...
[211] "testVirtual" "traceOff"
[213] "traceOn" "tryNew"
[215] "unRematchDefinition" "validObject"
[217] "validSlotNames"
ChemmineOB
, 98 in flowCore
, 79 in IRanges
, 68 in rsbml
, 61 in ShortRead
, 58 in Biostrings
, 51 in rtracklayer
, 50 in oligoClasses
, 45 in flowUtils
, and 40 in BaseSpaceR
.From a dataset
## A graphNEL graph with directed edges
## Number of Nodes = 50
## Number of Edges = 59
From using an object constructor function
## IRanges object with 2 ranges and 0 metadata columns:
## start end width
## <integer> <integer> <integer>
## [1] 101 110 10
## [2] 25 80 56
From a coercion
## 2 x 4 Matrix of class "dgeMatrix"
## [,1] [,2] [,3] [,4]
## [1,] 3 1 -1 -3
## [2,] 2 0 -2 -4
From using a specialized high-level constructor
TxDb object:
# Db type: TxDb
# Supporting package: GenomicFeatures
# Data source: UCSC
# Genome: sacCer2
# Organism: Saccharomyces cerevisiae
# Taxonomy ID: 4932
# UCSC Table: ensGene
# UCSC Track: Ensembl Genes
...
From using a high-level I/O function
library(ShortRead)
path_to_my_data <- system.file(
package="ShortRead",
"extdata", "Data", "C1-36Firecrest", "Bustard", "GERALD")
lane1 <- readFastq(path_to_my_data, pattern="s_1_sequence.txt")
lane1
## class: ShortReadQ
## length: 256 reads; width: 36 cycles
Inside another object
## DNAStringSet object of length 256:
## width seq
## [1] 36 GGACTTTGTAGGATACCCTCGCTTTCCTTCTCCTGT
## [2] 36 GATTTCTTACCTATTAGTGGTTGAACAGCATCGGAC
## [3] 36 GCGGTGGTCTATAGTGTTATTAATATCAATTTGGGT
## [4] 36 GTTACCATGATGTTATTTCTTCATTTGGAGGTAAAA
## [5] 36 GTATGTTTCTCCTGCTTATCACCTTCTTGAAGGCTT
## ... ... ...
## [252] 36 GTTTAGATATGAGTCACATTTTGTTCATGGTAGAGT
## [253] 36 GTTTTACAGACACCTAAAGCTACATCGTCAACGTTA
## [254] 36 GATGAACTAAGTCAACCTCAGCACTAACCTTGCGAG
## [255] 36 GTTTGGTTCGCTTTGAGTCTTCTTCGGTTCCGACTA
## [256] 36 GCAATCTGCCGACCACTCGCGATTCAATCATGACTT
Low-level: getters and setters
## [1] 10 56
## IRanges object with 2 ranges and 0 metadata columns:
## start end width
## <integer> <integer> <integer>
## [1] 101 105 5
## [2] 25 75 51
High-level: plenty of specialized methods
## [1] "ShortReadQQA"
## attr(,"package")
## [1] "ShortRead"
class?graphNEL
or equivalently ?
graphNEL-class`` for accessing the man page of a class?qa
for accessing the man page of a generic functionshowMethods()
can be useful:## Function: qa (package ShortRead)
## dirPath="ShortReadQ"
## dirPath="SolexaPath"
## dirPath="character"
## dirPath="list"
?
qa,ShortReadQ-method`` to access the man page for a particular method (might be the same man page as for the generic)??qa
will search the man pages of all the installed packages and return the list of man pages that contain the string qa
class()
and showClass()
## [1] "ShortReadQ"
## attr(,"package")
## [1] "ShortRead"
## Class "ShortReadQ" [package "ShortRead"]
##
## Slots:
##
## Name: quality sread id
## Class: QualityScore DNAStringSet BStringSet
##
## Extends:
## Class "ShortRead", directly
## Class ".ShortReadBase", by class "ShortRead", distance 2
##
## Known Subclasses: "AlignedRead"
str()
for compact display of the content of an objectshowMethods()
to discover methodsselectMethod()
to see the codeClass definition
setClass("SNPLocations",
slots=c(
genome="character", # a single string
snpid="character", # a character vector of length N
chrom="character", # a character vector of length N
pos="integer" # an integer vector of length N
)
)
Constructor
Defining the length
method
## [1] 2
Defining the slot getters
setGeneric("genome", function(x) standardGeneric("genome"))
setMethod("genome", "SNPLocations", function(x) x@genome)
setGeneric("snpid", function(x) standardGeneric("snpid"))
setMethod("snpid", "SNPLocations", function(x) x@snpid)
setGeneric("chrom", function(x) standardGeneric("chrom"))
setMethod("chrom", "SNPLocations", function(x) x@chrom)
setGeneric("pos", function(x) standardGeneric("pos"))
setMethod("pos", "SNPLocations", function(x) x@pos)
## [1] "hg19"
## [1] "rs0001" "rs0002"
Defining the show
method
setMethod("show", "SNPLocations",
function(object)
cat(class(object), "instance with", length(object),
"SNPs on genome", genome(object), "\n")
)
## SNPLocations instance with 2 SNPs on genome hg19
Defining the validity method
setValidity("SNPLocations",
function(object) {
if (!is.character(genome(object)) ||
length(genome(object)) != 1 || is.na(genome(object)))
return("'genome' slot must be a single string")
slot_lengths <- c(length(snpid(object)),
length(chrom(object)),
length(pos(object)))
if (length(unique(slot_lengths)) != 1)
return("lengths of slots 'snpid', 'chrom' and 'pos' differ")
TRUE
}
)
## Error in validObject(snplocs): invalid class "SNPLocations" object: lengths of slots 'snpid', 'chrom' and 'pos' differ
Defining slot setters
setGeneric("chrom<-", function(x, value) standardGeneric("chrom<-"))
setReplaceMethod("chrom", "SNPLocations",
function(x, value) {x@chrom <- value; validObject(x); x})
## Error in validObject(x): invalid class "SNPLocations" object: lengths of slots 'snpid', 'chrom' and 'pos' differ
Defining a coercion method
setAs("SNPLocations", "data.frame",
function(from)
data.frame(snpid=snpid(from), chrom=chrom(from), pos=pos(from))
)
## snpid chrom pos
## 1 rs0001 A 224033
## 2 rs0002 B 1266886
setClass("AnnotatedSNPs",
contains="SNPLocations",
slots=c(
geneid="character" # a character vector of length N
)
)
## Class "AnnotatedSNPs" [in ".GlobalEnv"]
##
## Slots:
##
## Name: geneid genome snpid chrom pos
## Class: character character character character integer
##
## Extends: "SNPLocations"
snps <- AnnotatedSNPs("hg19",
c("rs0001", "rs0002"),
c("chr1", "chrX"),
c(224033L, 1266886L),
c("AAU1", "SXW-23"))
## AnnotatedSNPs instance with 2 SNPs on genome hg19
## snpid chrom pos
## 1 rs0001 chr1 224033
## 2 rs0002 chrX 1266886
## [1] TRUE
## [1] TRUE
## [1] "AnnotatedSNPs"
## attr(,"package")
## [1] ".GlobalEnv"
show
method for AnnotatedSNPs objects. callNextMethod
can be used in that context to call the method defined for the parent class from within the method for the child class.## SNPLocations instance with 2 SNPs on genome hg19
setValidity("AnnotatedSNPs",
function(object) {
if (length(object@geneid) != length(object))
return("'geneid' slot must have the length of the object")
TRUE
}
)
Other important S4 features
?setClassUnion
)Resources
methods
package: ?setClass
, ?showMethods
, ?selectMethod
, ?getMethod
, ?is
, ?setValidity
, ?as
SummarizedExperiment
package.