This page documents the S4 generics and methods defined for objects inheriting of the Sets class. In the usage below, object and x represent an object of class inheriting from Sets, and value is an object of a class specified in the S4 method signature or as outlined in 'Accessors'.

relations(object)

relations(object) <- value

elements(object)

elementInfo(object)

elementInfo(object) <- value

sets(object)

setInfo(object)

setInfo(object) <- value

nElements(object)

nSets(object)

setLengths(object)

elementLengths(object)

# S4 method for Sets
relations(object)

# S4 method for Sets
relations(object) <- value

# S4 method for Sets
elementInfo(object)

# S4 method for Sets
elementInfo(object) <- value

# S4 method for Sets
setInfo(object)

# S4 method for Sets
setInfo(object) <- value

# S4 method for Sets
elements(object)

# S4 method for Sets
sets(object)

# S4 method for Sets
length(x)

# S4 method for Sets
nElements(object)

# S4 method for Sets
nSets(object)

# S4 method for Sets
setLengths(object)

# S4 method for Sets
elementLengths(object)

# S3 method for Sets
c(x, ...)

# S4 method for Sets,ANY,ANY,ANY
[(x, i, j, ..., drop = TRUE)

# S3 method for Sets
subset(x, ...)

# S4 method for Sets
duplicated(x, incomparables = FALSE, ...)

# S4 method for Sets
unique(x, incomparables = FALSE, ...)

union.Sets(x, y, ...)

as.DataFrame.Sets(object, ...)

# S3 method for Sets
as.data.frame(x, ...)

# S3 method for Sets
as.list(x, ...)

# S3 method for Sets
as.matrix(x, ...)

as.Sets.list(list, ...)

as.Sets.matrix(matrix, ...)

Arguments

object, x

An object of class inheriting from Sets.

value

An object of a class specified in the S4 method signature or as outlined in 'Accessors'.

...

Additional arguments passed to and from other methods.

i

index specifying elements to extract or replace.

j

Ignored.

drop

A logical scalar indicating whether to remove orphan elements and sets from the elementInfo and setInfo slots, respectively.

incomparables

Ignored.

y

An object of class inheriting from Sets.

list

A list of named character vectors. The names are taken as the set identifiers. The character vectors are taken as identifiers of elements that are member of each set.

matrix

A matrix. The matrix will be coerced to logical type and relations indicating TRUE will be stored in the Sets.

Accessors

relations(object) returns the relations slot. A Hits objets storing the integer index of elements (from) and sets (to) in the elementInfo and setInfo slots, respectively, and associated relation metadata (mcols).

elementInfo(object) returns the elementInfo slot. An IdVector objets storing the unique element identifiers (ids) and associated element metadata (mcols).

setInfo(object) returns the setInfo slot. An IdVector objets storing the unique set identifiers (ids) and associated set metadata (mcols).

elements(object) returns an IdVector element identifiers and associated metadata as ordered in relations(object)$element (i.e., of length equal to length(object)).

sets(object) returns an IdVector of set identifiers and associated metadata as ordered in relations(object)$set. (i.e., of length equal to length(object)).

Dimensions

length(x) returns the total count of relations.

nElements(object) returns the count of unique elements.

nSets(object) returns the count of unique sets.

setLengths(object) returns the count of relations per set.

elementLengths(object) returns the count of relations per element.

Combining

c(x, ...) combines its arguments

Subsetting

x[i, drop=TRUE] returns new Sets object of the same class as x made of the elements selected by i. i can be missing; an NA-free logical, numeric, or character vector or factor (as ordinary vector or Rle object); or an IntegerRanges object. The drop logical value controls whether the metadata of elements and sets orphaned during the subsetting should be removed from the elementInfo and setInfo slots, respectively.

subset(object, subset, ..., drop=TRUE) returns subsets of relations which meet conditions. The subset argument should be a logical expression referring to any of "element", "set", and any available relation metadata indicating elements or rows to keep: missing values are taken as false. The drop logical scalar controls whether elements and sets orphaned during the subsetting should be removed from the elementInfo and setInfo slots, respectively.

Duplication and uniqueness

duplicated(x) determines which relations of a Sets are duplicates of relations with smaller subscripts, and returns a logical vector indicating which relations are duplicates.

unique(x) returns a Sets like x but with duplicate relations removed.

union(x) returns a Sets composed of the union of relations in x and y.

Coercion from Sets

as(object, "DataFrame") and as.DataFrame(object) return a nested DataFrame including columns "element", "set", "relationData", "elementInfo", and "setInfo".

as(x, "data.frame") and as.data.frame(x) return a flattened data.frame including "element", "set", and columns in mcols(relations(x)) if any.

as(x, "list") and as.list(x) return a named list. Names are set identifiers, and values are character vectors of element identifiers.

as(x, "matrix") and as.matrix(x) return a matrix with elements as rows, sets as columns, and a logical value to indicate membership.

Coercion to Sets

as(list, "Sets") and as.Sets(object) return a Sets from a list of character vectors.

as(matrix, "Sets") and as.Sets(object) return a Sets from an incidence matrix.

See also

Examples

# Constructor ---- # Visually intuitive definition of sets sets <- list( set1=c("A", "B"), set2=c("B", "C", "D"), set3=c("E")) bs <- as(sets, "Sets") bs
#> Sets with 6 relations between 5 elements and 3 sets #> element set #> <character> <character> #> [1] A set1 #> [2] B set1 #> [3] B set2 #> [4] C set2 #> [5] D set2 #> [6] E set3 #> ----------- #> elementInfo: IdVector with 0 metadata #> setInfo: IdVector with 0 metadata
# Accessors ---- relations(bs)
#> Hits object with 6 hits and 0 metadata columns: #> from to #> <integer> <integer> #> [1] 1 1 #> [2] 2 1 #> [3] 2 2 #> [4] 3 2 #> [5] 4 2 #> [6] 5 3 #> ------- #> nLnode: 5 / nRnode: 3
bs1 <- bs mcols(relations(bs1))[["NEW"]] <- paste0("value", seq_len(length(bs1))) elementInfo(bs)
#> IdVector of length 5 with 5 unique identifiers #> Ids: A, B, C, D, ... #> Metadata: (0 columns)
bs1 <- bs mcols(elementInfo(bs1))[["NEW"]] <- paste0("value", seq_len(nElements(bs1))) setInfo(bs)
#> IdVector of length 3 with 3 unique identifiers #> Ids: set1, set2, set3 #> Metadata: (0 columns)
bs1 <- bs mcols(setInfo(bs1))[["NEW"]] <- paste0("value", seq_len(nSets(bs1))) elements(bs)
#> IdVector of length 6 with 5 unique identifiers #> Ids: A, B, B, C, ... #> Metadata: (0 columns)
ids(elements(bs))
#> [1] "A" "B" "B" "C" "D" "E"
mcols(elements(bs))
#> DataFrame with 6 rows and 0 columns
sets(bs)
#> IdVector of length 6 with 3 unique identifiers #> Ids: set1, set1, set2, set2, ... #> Metadata: (0 columns)
ids(sets(bs))
#> [1] "set1" "set1" "set2" "set2" "set2" "set3"
mcols(sets(bs))
#> DataFrame with 6 rows and 0 columns
# Dimensions ---- length(bs)
#> [1] 6
nElements(bs)
#> [1] 5
nSets(bs)
#> [1] 3
setLengths(bs)
#> set1 set2 set3 #> 2 3 1
elementLengths(bs)
#> A B C D E #> 1 2 1 1 1
# Combining ---- bs1 <- c(bs, bs) # Subsetting ---- bs1 <- bs[1:5] bs1 <- bs[1:5, , drop=FALSE] # keep metadata of orphan elements and sets bs1 <- subset(bs, set == "set1" | element == "E") bs1
#> Sets with 3 relations between 3 elements and 2 sets #> element set #> <character> <character> #> [1] A set1 #> [2] B set1 #> [3] E set3 #> ----------- #> elementInfo: IdVector with 0 metadata #> setInfo: IdVector with 0 metadata
# Duplication and uniqueness ---- bs1 <- bs relations(bs1) <- rep(relations(bs1), each=2) table(duplicated(bs1))
#> #> FALSE TRUE #> 6 6
unique(bs1)
#> Sets with 6 relations between 5 elements and 3 sets #> element set #> <character> <character> #> [1] A set1 #> [2] B set1 #> [3] B set2 #> [4] C set2 #> [5] D set2 #> [6] E set3 #> ----------- #> elementInfo: IdVector with 0 metadata #> setInfo: IdVector with 0 metadata
bs1 <- union(bs, bs) # Coercion from Sets ---- DF1 <- as(bs, "DataFrame") df1 <- as.data.frame(bs) l1 <- as(bs, "list") m1 <- as(bs, "matrix") bs1 <- bs mcols(relations(bs1))[["membership"]] <- runif(length(bs1)) fs <- as(bs1, "FuzzySets") # Fetch a sample of GO annotations library(org.Hs.eg.db) gs <- import(org.Hs.egGO)
#> 'select()' returned 1:1 mapping between keys and columns
#> Coercing evidence to factor
#> Coercing ontology to factor
bs1 <- as(gs, "Sets") gs1 <- as(bs1, "GOSets") # Coercion to Sets ---- # list bs1 <- as(list(set1=c("A", "B"), set2=c("B", "C")), "Sets") # matrix bs1 <- as(m1, "Sets")