graphAM-class {graph}R Documentation

Class "graphAM"

Description

A graph class where node and edge information is represented as an adjacency matrix. The adjacency matrix is square and element adjMat[i, j] is one if there is an edge from node i to node j and zero otherwise.

Details

The non-zero matrix values can be used to initialize an edge attribute. If this is desired, use the values argument in the call to new and provide a list with a single named element. The name determines the attributes and the value provides the default value for that attribute.

Objects from the Class

Objects can be created by calls of the form new("graphAM", adjMat, edgemode, values).

Slots

adjMat:
An adjacency "matrix" describing the graph structure. The colnames of the matrix will be used as node names for the graph if present.
edgemode:
A "character" vector specifying whether the graph is "directed" or "undirected".
edgeData:
Storage for edge attributes.
nodeData:
Storage for node attributes.

Extends

Class "graph", directly.

Methods

addEdge
signature(from = "character", to = "character", graph = "graphAM", weights = "missing"): ...
addNode
signature(object = "graphAM", nodes = "character"): ...
clearNode
signature(node = "character", object = "graphAM"): ...
coerce
signature(from = "graphAM", to = "graphNEL"): ...
coerce
signature(from = "graphAM", to = "matrix"): In converting to a matrix, if an edge attribute named "weight" is defined, the non-zero elements of the matrix will contain the corresponding attribute value. For more flexible matrix conversion, see toMatrix.
coerce
signature(from = "matrix", to = "graphAM"): This coerce method exists for symmetry. In most cases, creating a new graphAM instance using new gives one more control over the resulting graph.
edges
signature(object = "graphAM", which = "missing"): ...
edges
signature(object = "graphAM", which = "character"): ...
initialize
signature(.Object = "graphAM"): ...
inEdges
signature(node = "character", object = "graphNEL"): Return the incoming edges for the specified nodes. See inEdges.
isAdjacent
signature(object = "graphAM", from = "character", to = "character"): ...
nodes<-
signature(object = "graphAM", value = "character"): ...
nodes
signature(object = "graphAM"): ...
numEdges
signature(graph = "graphAM"): ...
numNodes
signature(object = "graphAM"): ...
removeEdge
signature(from = "character", to = "character", graph = "graphAM"): ...
removeNode
signature(node = "character", object = "graphAM"): ...

Author(s)

Seth Falcon

See Also

graph-class, graphNEL-class

Examples

mat <- rbind(c(0, 0, 1, 1),
             c(0, 0, 1, 1),
             c(1, 1, 0, 1),
             c(1, 1, 1, 0))
rownames(mat) <- colnames(mat) <- letters[1:4]
g1 <- new("graphAM", adjMat=mat)
stopifnot(identical(mat, as(g1, "matrix")), validObject(g1))

## now with weights:
mat[1,3] <- mat[3,1] <- 10
gw <- new("graphAM", adjMat=mat, values=list(weight=1))

## consistency check:
stopifnot(identical(mat, as(gw, "matrix")),
          validObject(gw),
          identical(gw, as(as(gw, "graphNEL"), "graphAM")))

[Package graph version 1.14.2 Index]