graphAM-class {graph} | R Documentation |
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.
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 can be created by calls of the form new("graphAM", adjMat, edgemode, values)
.
adjMat
:"matrix"
describing the
graph structure. The colnames
of the matrix will be used as
node names for the graph if present.edgemode
:"character"
vector specifying
whether the graph is "directed" or "undirected".edgeData
:nodeData
:
Class "graph"
, directly.
signature(from = "character", to = "character", graph = "graphAM", weights = "missing")
: ... signature(object = "graphAM", nodes = "character")
: ... signature(node = "character", object = "graphAM")
: ... signature(from = "graphAM", to = "graphNEL")
: ... 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
.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.signature(object = "graphAM", which = "missing")
: ... signature(object = "graphAM", which = "character")
: ... signature(.Object = "graphAM")
: ... signature(node = "character", object =
"graphNEL")
: Return the incoming edges for the specified
nodes. See inEdges
.signature(object = "graphAM", from = "character", to = "character")
: ... signature(object = "graphAM", value = "character")
: ... signature(object = "graphAM")
: ... signature(graph = "graphAM")
: ... signature(object = "graphAM")
: ... signature(from = "character", to = "character", graph = "graphAM")
: ... signature(node = "character", object = "graphAM")
: ... Seth Falcon
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")))