1
2## ----------------------------------------------------------------------
3##
4##   IGraph R package
5##   Copyright (C) 2005-2014  Gabor Csardi <csardi.gabor@gmail.com>
6##   334 Harvard street, Cambridge, MA 02139 USA
7##
8##   This program is free software; you can redistribute it and/or modify
9##   it under the terms of the GNU General Public License as published by
10##   the Free Software Foundation; either version 2 of the License, or
11##   (at your option) any later version.
12##
13##   This program is distributed in the hope that it will be useful,
14##   but WITHOUT ANY WARRANTY; without even the implied warranty of
15##   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16##   GNU General Public License for more details.
17##
18##   You should have received a copy of the GNU General Public License
19##   along with this program; if not, write to the Free Software
20##   Foundation, Inc.,  51 Franklin Street, Fifth Floor, Boston, MA
21##   02110-1301 USA
22##
23## ----------------------------------------------------------------------
24
25###################################################################
26# Convert graphs to human readable forms
27###################################################################
28
29.get.attr.codes <- function(object) {
30  ga <- va <- ea <- ""
31  gal <- graph_attr_names(object)
32  if (length(gal) != 0) {
33    ga <- paste(sep="", gal, " (g/",
34                .Call(C_R_igraph_get_attr_mode, object, 2L),
35                ")")
36  }
37  val <- vertex_attr_names(object)
38  if (length(val) != 0) {
39    va <- paste(sep="", val, " (v/",
40                .Call(C_R_igraph_get_attr_mode, object, 3L),
41                ")")
42  }
43  eal <- edge_attr_names(object)
44  if (length(eal) != 0) {
45    ea <- paste(sep="", edge_attr_names(object), " (e/",
46                .Call(C_R_igraph_get_attr_mode, object, 4L),
47                ")")
48  }
49  c(ga, va, ea)
50}
51
52.print.header <- function(object) {
53
54  if (!is_igraph(object)) {
55    stop("Not a graph object")
56  }
57
58  title <- paste(sep="", "IGRAPH ", substr(graph_id(object), 1, 7), " ",
59                 c("U","D")[is_directed(object)+1],
60                 c("-","N")[is_named(object)+1],
61                 c("-","W")[is_weighted(object)+1],
62                 c("-","B")[is_bipartite(object)+1], " ",
63                 vcount(object), " ", ecount(object), " -- ")
64  w <- getOption("width")
65  if (nchar(title) < w && "name" %in% graph_attr_names(object)) {
66    title <- substring(paste(sep="", title,
67                             as.character(object$name)[1]), 1, w-1)
68  }
69  cat(title, "\n", sep="")
70
71  atxt <- .get.attr.codes(object)
72  atxt <- paste(atxt[atxt!=""], collapse=", ")
73  if (atxt != "") {
74    atxt <- strwrap(paste(sep="", "+ attr: ", atxt), prefix = "| ",
75                    initial = "")
76    cat(atxt, sep="\n")
77  }
78  1 + if (length(atxt) == 1 && atxt == "") 0 else length(atxt)
79}
80
81#' @importFrom utils capture.output
82
83.print.graph.attributes <- function(x, full, max.lines) {
84  list <- graph_attr_names(x)
85  if (length(list)!=0) {
86    cat("+ graph attributes:\n")
87    out <- capture.output({
88      lapply(list, function(n) {
89        cat(sep="", "+ ", n, ":\n")
90        indent_print(graph_attr(x, n), .indent = "  ")
91      })
92      invisible(NULL)
93    })
94    indent_print(out, sep = "\n", .indent = "| ", .printer = cat)
95    length(out) + 1
96  } else {
97    0
98  }
99}
100
101## IGRAPH U--- 10 10 -- Ring graph
102## + attr: name (g/c), mutual (g/l), circular (g/l)
103## + graph attributes:
104## | + name:
105## |   [1] "Ring graph"
106## | + mutual:
107## |   [1] FALSE
108## | + circular=
109## |   [1] TRUE
110## | + layout =
111## |            [,1]          [,2]
112## |    [1,]  0.000000  0.000000e+00
113## |    [2,]  1.000000  0.000000e+00
114## |    [3,]  0.809017  5.877853e-01
115## |    [4,]  0.309017  9.510565e-01
116## |    [5,] -0.309017  9.510565e-01
117## |    [6,] -0.809017  5.877853e-01
118## |    [7,] -1.000000  1.224647e-16
119## |    [8,] -0.809017 -5.877853e-01
120## |    [9,] -0.309017 -9.510565e-01
121## |   [10,]  0.309017 -9.510565e-01
122## |   [11,]  0.809017 -5.877853e-01
123## + edges:
124##  [1] 1-- 2 2-- 3 3-- 4 4-- 5 5-- 6 6-- 7 7-- 8 8-- 9 9--10 1--10
125
126.print.vertex.attributes <- function(x, full, max.lines) {
127  pf <- function(x) .print.vertex.attributes.old(x, full, max.lines)
128  if (length(vertex_attr_names(x))) cat("+ vertex attributes:\n")
129  indent_print(x, .indent = "| ", .printer = pf)
130}
131
132.print.vertex.attributes.old <- function(x, full, max.lines) {
133  vc <- vcount(x)
134  list <- vertex_attr_names(x)
135  if (length(list) != 0) {
136    mp <- getOption("max.print")
137    options(max.print=1000000000)
138    if (vc <= mp) {
139      omitted.vertices <- 0
140      ind <- as.numeric(V(x))
141    } else {
142      omitted.vertices <- vc-mp
143      ind <- seq(length=mp)
144    }
145    if (vc==0 ||
146        all(sapply(list, function(v)
147                   is.numeric(vertex_attr(x, v)) ||
148                   is.character(vertex_attr(x, v)) ||
149                   is.logical(vertex_attr(x, v))))) {
150      ## create a table
151      tab <- data.frame(v=paste(sep="", "[", ind, "]"), row.names="v")
152      for (i in list) {
153        tab[i] <- vertex_attr(x, i, ind)
154      }
155      print(tab)
156    } else {
157      for (i in ind) {
158        cat(sep="", "[[", i, "]]\n")
159        lapply(list, function(n) {
160          cat(sep="", "[[", i, "]][[", n, "]]\n")
161          print(vertex_attr(x, n, i))})
162      }
163    }
164    options(max.print=mp)
165    if (omitted.vertices != 0) {
166      cat(paste('[ reached getOption("max.print") -- omitted',
167                omitted.vertices, "vertices ]\n\n"))
168    }
169  }
170}
171
172.print.edges.edgelist <- function(x, edges = E(x), names) {
173  ec <- length(edges)
174  list <- edge_attr_names(x)
175  list <- list[list!="name"]
176  arrow <- ifelse(is_directed(x), "->", "--")
177  if (is_named(x)) {
178    cat("+ edges (vertex names) and their attributes:\n")
179  } else {
180    cat("+ edges and their attributes:\n")
181  }
182  if (names && ! "name" %in% vertex_attr_names(x)) {
183    names <- FALSE
184  }
185  if (names && "name" %in% vertex_attr_names(x) &&
186      !is.numeric(vertex_attr(x, "name")) &&
187      !is.character(vertex_attr(x, "name")) &&
188      !is.logical(vertex_attr(x, "name"))) {
189    warning("Can't print vertex names, complex `name' vertex attribute")
190    names <- FALSE
191  }
192
193  mp <- getOption("max.print")
194  if (mp >= ec) {
195    omitted.edges <- 0
196    el <- ends(x, edges, names=names)
197  } else {
198    omitted.edges <- ec-mp
199    el <- ends(x, ends[seq_len(mp)])
200    if (names) { el[] <- V(x)$name[el] }
201  }
202  ename <- if ("name" %in% edge_attr_names(x)) {
203    paste(sep="", "'", E(x)$name, "'")
204  } else {
205    seq(length=nrow(el))
206  }
207  if (ec==0 ||
208      all(sapply(list, function(v) is.numeric(edge_attr(x, v)) |
209                 is.character(edge_attr(x,v)) |
210                 is.logical(edge_attr(x, v))))) {
211    ## create a table
212    tab <- data.frame(row.names=paste(sep="", "[", ename, "]"))
213    if (is.numeric(el)) { w <- nchar(max(el)) } else { w <- max(nchar(el)) }
214    tab["edge"] <- paste(sep="", format(el[,1], width=w),
215                         arrow, format(el[,2], width=w))
216    for (i in list) {
217      tab[i] <- edge_attr(x, i)
218    }
219    print(tab)
220  } else {
221    i <- 1
222    apply(el, 1, function(v) {
223      cat(sep="", "[", ename[i], "] ", v[1], " ", arrow, " ", v[2]);
224      lapply(list, function(n) {
225        cat(sep="", "\n[[", i, "]][[", n, "]]\n")
226        print(edge_attr(x, n, i))})
227      cat("\n")
228      i <<- i+1
229    })
230  }
231  if (omitted.edges != 0) {
232    cat(paste('[ reached getOption("max.print") -- omitted', omitted.edges,
233              'edges ]\n\n'))
234  }
235}
236
237.print.edges.compressed <- function(x, edges = E(x), names, num = FALSE,
238                                      max.lines = igraph_opt("auto.print.lines")) {
239
240  len <- length(edges)
241  id <- graph_id(edges)
242
243  title <- "+" %+%
244    (if (num) " " %+% chr(len) %+% "/" %+%
245       (if (is.null(x)) "?" else chr(gsize(x))) else "") %+%
246    (if (len == 1) " edge" else " edges") %+%
247    (if (!is.na(id)) paste(" from", substr(id, 1, 7)) else " unknown") %+%
248    (if (is.null(x)) " (deleted)" else "") %+%
249    (if (is.null(attr(edges, "vnames"))) "" else " (vertex names)") %+%
250    ":\n"
251  cat(title)
252
253  if (!is.null(attr(edges, "single")) && attr(edges, "single") &&
254      !is.null(x)) {
255    ## Double bracket
256    ea <- edge_attr(x)
257    if (all(sapply(ea, is.atomic))) {
258      etail <- tail_of(x, edges)
259      ehead <- head_of(x, edges)
260      df <- data.frame(
261        stringsAsFactors = FALSE,
262        tail = as_ids(etail),
263        head = as_ids(ehead),
264        tid  = as.vector(etail),
265        hid  = as.vector(ehead)
266      )
267      if (length(ea)) {
268        ea <- do_call(data.frame, .args = ea, stringsAsFactors = FALSE)
269        df <- cbind(df, ea[as.vector(edges), , drop = FALSE])
270      }
271      print(df)
272
273    } else {
274      print(lapply(ea, "[", as.vector(edges)))
275    }
276
277  } else if (is.null(max.lines)) {
278    .print.edges.compressed.all(x, edges, names)
279
280  } else {
281    .print.edges.compressed.limit(x, edges, names, max.lines)
282  }
283}
284
285.print.edges.compressed.all <- function(x, edges, names) {
286
287  arrow <- c("--", "->")[is_directed(x)+1]
288
289  if (!is.null(x)) {
290    el <- ends(x, edges, names=names)
291    pr <- paste(sep="", format(el[,1]), arrow, format(el[,2]))
292    print(pr, quote=FALSE)
293  } else {
294    if (!is.null(attr(edges, "vnames"))) {
295      print(as.vector(attr(edges, "vnames")), quote = FALSE)
296    } else if (!is.null(names(edges))) {
297      print(names(edges), quote = FALSE)
298    } else {
299      print(as.vector(edges))
300    }
301  }
302
303}
304
305#' @importFrom utils capture.output
306
307.print.edges.compressed.limit <- function(x, edges, names, max.lines) {
308
309  if (!is.null(x)) {
310
311    arrow <- c("--", "->")[is_directed(x)+1]
312
313    can_max <- NA
314    el <- NA
315
316    fun <- function(q, no) {
317      if (q == "length") {
318        length(edges)
319      } else if (q == "min_width") {
320        5
321      } else if (q == "width") {
322        el <<- ends(x, edges[seq_len(no)], names = names)
323        cummax(nchar(el[,1])) + nchar(arrow) + cummax(nchar(el[,2])) + 1
324      } else if (q == "print") {
325        el <<- el[seq_len(no), , drop = FALSE]
326        out <- paste(sep="", format(el[,1]), arrow, format(el[,2]))
327        capture.output(print(out, quote = FALSE))
328      } else if (q == "max") {
329        can_max <<- no
330      } else if (q == "done") {
331        if (no["tried_items"] < length(edges) ||
332            no["printed_lines"] < no["tried_lines"]) {
333          cat("+ ... omitted several edges\n")
334        }
335      }
336    }
337
338    fun <- printer_callback(fun)
339    head_print(fun, max_lines = max.lines)
340  } else {
341    if (!is.null(attr(edges, "vnames"))) {
342      head_print(as.vector(attr(edges, "vnames")), quote = FALSE)
343    } else if (!is.null(names(edges))) {
344      head_print(names(edges), quote = FALSE)
345    } else {
346      head_print(as.vector(edges))
347    }
348  }
349}
350
351.print.edges.adjlist <- function(x) {
352  ## TODO: getOption("max.print")
353  cat("+ edges:\n")
354  vc <- vcount(x)
355  arrow <- c(" -- ", " -> ")[is_directed(x)+1]
356  al <- as_adj_list(x, mode="out")
357  w <- nchar(max(which(degree(x, mode="in") != 0)))
358  mpl <- trunc((getOption("width")-nchar(arrow)-nchar(vc)) / (w+1))
359  if (any(sapply(al, length) > mpl)) {
360    ## Wrapping needed
361    mw <- nchar(vcount(x))
362    sm <- paste(collapse="", rep(" ", mw+4))
363    alstr <- lapply(seq_along(al), function(x) {
364      len <- length(al[[x]])
365      fac <- rep(1:(len/mpl+1), each=mpl, length=len)
366      nei <- tapply(format(al[[x]], width=mw), fac, paste, collapse=" ")
367      mark <- paste(sep="", format(x, width=mw), arrow)
368      mark <- c(mark, rep(sm, max(0, length(nei)-1)))
369      paste(sep="", mark, nei)
370    })
371    cat(unlist(alstr), sep="\n")
372  } else {
373    alstr <- sapply(al, function(x) {
374      paste(format(x, width=w), collapse=" ")
375    })
376    mark <- paste(sep="", format(seq_len(vc)), arrow)
377    alstr <- paste(sep="", mark, alstr)
378    maxw <- max(nchar(alstr))
379    sep <- "   "
380    ncol <- trunc((getOption("width")-1+nchar(sep)) / (maxw+nchar(sep)))
381    if (ncol > 1) {
382      alstr <- format(alstr, width=maxw, justify="left")
383      fac <- rep(1:(vc/ncol+1), each=ncol, length=vc)
384      alstr <- tapply(alstr, fac, paste, collapse=sep)
385    }
386    cat(alstr, sep="\n")
387  }
388}
389
390.print.edges.adjlist.named <- function(x, edges = E(x)) {
391  ## TODO getOption("max.print")
392  cat("+ edges (vertex names):\n")
393
394  arrow <- c(" -- ", " -> ")[is_directed(x)+1]
395  vn <- V(x)$name
396
397  al <- as_adj_list(x, mode="out")
398  alstr <- sapply(al, function(x) { paste(collapse=", ", vn[x]) })
399  alstr <- paste(sep="", format(vn), arrow, alstr)
400  alstr <- strwrap(alstr, exdent=max(nchar(vn))+nchar(arrow))
401  cat(alstr, sep="\n")
402}
403
404#' @export
405
406print_all <- function(object, ...) {
407  print.igraph(object, full=TRUE, ...)
408}
409
410
411
412#' Print graphs to the terminal
413#'
414#' These functions attempt to print a graph to the terminal in a human readable
415#' form.
416#'
417#' \code{summary.igraph} prints the number of vertices, edges and whether the
418#' graph is directed.
419#'
420#' \code{print_all} prints the same information, and also lists the edges, and
421#' optionally graph, vertex and/or edge attributes.
422#'
423#' \code{print.igraph} behaves either as \code{summary.igraph} or
424#' \code{print_all} depending on the \code{full} argument. See also the
425#' \sQuote{print.full} igraph option and \code{\link{igraph_opt}}.
426#'
427#' The graph summary printed by \code{summary.igraph} (and \code{print.igraph}
428#' and \code{print_all}) consists one or more lines. The first line contains
429#' the basic properties of the graph, and the rest contains its attributes.
430#' Here is an example, a small star graph with weighted directed edges and named
431#' vertices: \preformatted{    IGRAPH badcafe DNW- 10 9 -- In-star
432#'     + attr: name (g/c), mode (g/c), center (g/n), name (v/c),
433#'       weight (e/n) }
434#' The first line always
435#' starts with \code{IGRAPH}, showing you that the object is an igraph graph.
436#' Then a seven character code is printed, this the first seven characters
437#' of the unique id of the graph. See \code{\link{graph_id}} for more.
438#' Then a four letter long code string is printed. The first letter
439#' distinguishes between directed (\sQuote{\code{D}}) and undirected
440#' (\sQuote{\code{U}}) graphs. The second letter is \sQuote{\code{N}} for named
441#' graphs, i.e. graphs with the \code{name} vertex attribute set. The third
442#' letter is \sQuote{\code{W}} for weighted graphs, i.e. graphs with the
443#' \code{weight} edge attribute set. The fourth letter is \sQuote{\code{B}} for
444#' bipartite graphs, i.e. for graphs with the \code{type} vertex attribute set.
445#'
446#' Then, after two dashes, the name of the graph is printed, if it has one,
447#' i.e. if the \code{name} graph attribute is set.
448#'
449#' From the second line, the attributes of the graph are listed, separated by a
450#' comma. After the attribute names, the kind of the attribute -- graph
451#' (\sQuote{\code{g}}), vertex (\sQuote{\code{v}}) or edge (\sQuote{\code{e}})
452#' -- is denoted, and the type of the attribute as well, character
453#' (\sQuote{\code{c}}), numeric (\sQuote{\code{n}}), logical
454#' (\sQuote{\code{l}}), or other (\sQuote{\code{x}}).
455#'
456#' As of igraph 0.4 \code{print_all} and \code{print.igraph} use the
457#' \code{max.print} option, see \code{\link[base]{options}} for details.
458#'
459#' As of igraph 1.1.1, the \code{str.igraph} function is defunct, use
460#' \code{print_all()}.
461#'
462#' @aliases print.igraph print_all summary.igraph str.igraph
463#' @param x The graph to print.
464#' @param full Logical scalar, whether to print the graph structure itself as
465#' well.
466#' @param graph.attributes Logical constant, whether to print graph attributes.
467#' @param vertex.attributes Logical constant, whether to print vertex
468#' attributes.
469#' @param edge.attributes Logical constant, whether to print edge attributes.
470#' @param names Logical constant, whether to print symbolic vertex names (ie.
471#' the \code{name} vertex attribute) or vertex ids.
472#' @param max.lines The maximum number of lines to use. The rest of the
473#' output will be truncated.
474#' @param object The graph of which the summary will be printed.
475#' @param \dots Additional agruments.
476#' @return All these functions return the graph invisibly.
477#' @author Gabor Csardi \email{csardi.gabor@@gmail.com}
478#' @method print igraph
479#' @export
480#' @export print.igraph
481#' @keywords graphs
482#' @examples
483#'
484#' g <- make_ring(10)
485#' g
486#' summary(g)
487#'
488print.igraph <- function(x, full=igraph_opt("print.full"),
489                graph.attributes=igraph_opt("print.graph.attributes"),
490                vertex.attributes=igraph_opt("print.vertex.attributes"),
491                edge.attributes=igraph_opt("print.edge.attributes"),
492                names=TRUE, max.lines = igraph_opt("auto.print.lines"), ...) {
493
494  if (!is_igraph(x)) {
495    stop("Not a graph object")
496  }
497
498  head_lines <- .print.header(x)
499  if (is.logical(full) && full) {
500    if (graph.attributes) {
501      head_lines <- head_lines + .print.graph.attributes(x, full, max.lines)
502    }
503    if (vertex.attributes) {
504      head_lines <- head_lines + .print.vertex.attributes(x, full, max.lines)
505    }
506    if (ecount(x)==0) {
507      ## Do nothing
508    } else if (edge.attributes && length(edge_attr_names(x)) != 0 ) {
509      .print.edges.edgelist(x, names = names)
510    } else if (median(degree(x, mode="out")) < 3) {
511      .print.edges.compressed(x, names = names, max.lines = NULL)
512    } else if (is_named(x)) {
513      .print.edges.adjlist.named(x)
514    } else {
515      .print.edges.adjlist(x)
516    }
517  } else if (full == "auto") {
518    .print.edges.compressed(x, names = names, max.lines =
519                              max.lines - head_lines)
520  }
521
522  invisible(x)
523}
524
525#' @rdname print.igraph
526#' @method summary igraph
527#' @export
528
529summary.igraph <- function(object, ...) {
530  .print.header(object)
531  invisible(object)
532}
533
534"
535####################################################################
536## Various designs for printing graphs
537
538## Summary
539
540IGRAPH UNW- 5 5 -- A ring
541Attr: name (g/c), name (v/c), weight (e/n)
542
543IGRAPH D-W- 100 200 -- Gnm random graph
544
545## Printing, edge list
546
547IGRAPH-UNW--V5-E5----------------------------------------- A ring -
548+ attributes: name (g), name (v), weight (e).
549+ edges:
550     edge  weight
551[1]' a--b       1
552[2]' b--c       2
553[3]' c--d      -1
554[4]' d--e     0.5
555[5]' a--e       1
556
557## Compressed edge list
558
559IGRAPH UNW- 5 10 -- A ring
560+ attributes: name (g/c), name (v/n), weight (e/n)
561+ edges:
562[1]' 1--2 2--3 3--4 4--5 1--5 2--5 5--1
563[8]' 1--4 4--2 1--3
564
565## This is good if vertices are named
566
567IGRAPH UNW- 10 18 -- Krackhardt kite
568+ attributes: name (g/c), name (v/c), weight (e/n)
569+ edges:
570Andre    -- [1] Beverly, Carol, Diane, Fernando
571Beverly  -- [1] Andre, Diane, Ed, Garth
572Carol    -- [1] Andre, Diane, Fernando
573Diane    -- [1] Andre, Beverly, Carol, Diane, Ed
574         -- [6] Garth
575Ed       -- [1] Beverly, Diane, Garth
576Fernando -- [1] Andre, Carol, Diane, Garth
577Garth    -- [1] Beverly, Diane, Ed, Fernando
578Heather  -- [1] Fernando, Garth
579Ike      -- [1] Heather, Jane
580Jane     -- [1] Ike
581
582IGRAPH UNW- 10 18 -- Krackhardt kite
583+ attributes: name (g/c), name (v/c), weight (e/n)
584+ edges:
585Andre    -- Beverly, Carol, Diane, Fernando
586Beverly  -- Andre, Diane, Ed, Garth
587Carol    -- Andre, Diane, Fernando
588Diane    -- Andre, Beverly, Carol, Diane, Ed, Garth
589Ed       -- Beverly, Diane, Garth
590Fernando -- Andre, Carol, Diane, Garth
591Garth    -- Beverly, Diane, Ed, Fernando
592Heather  -- Fernando, Garth
593Ike      -- Heather, Jane
594Jane     -- Ike
595
596## This is the good one if vertices are not named
597
598IGRAPH U--- 100 200 -- Gnm random graph
599+ edges:
600[  1] 28 46 89 90                 [  2] 47 69 72 89
601[  3] 29                          [  4] 17 20
602[  5] 11 40 42 51 78 89           [  6] 27 32 70 87 93
603[  7] 18 27 87                    [  8] 18 24 82
604[  9] 18 20 85 94                 [ 10] 24 70 77 91
605[ 11]  5 12 34 61 62              [ 12] 11 41 44 61 65 80
606...
607
608## Alternative designs, summary
609
610IGRAPH-UNW--V5-E5,---------------------------------------- A ring -
611+ attributes: name (g/c), name (v/c), weight (e/n)
612
613IGRAPH. |V|=5, |E|=5, undirected, named, weighted.
614Attributes: name (g/c), name (v/c), weight (e/n)
615
616IGRAPH: 'A ring'
617Graph attributes: |V|=5, |E|=5, undirected, name.
618Vertex attributes: name.
619Edge attributes: weight.
620
621## Alternative designs, printing
622
623IGRAPH-UNW--V5-E5----------------------------------------- A ring -
624'- attributes: name (g), name (v), weight (e).
625'         edge  weight
626[1] 'a' -- 'b'       1
627[2] 'b' -- 'c'       2
628[3] 'c' -- 'd'      -1
629[4] 'd' -- 'e'     0.5
630[5] 'a' -- 'e'       1
631
632IGRAPH-UNW--V-5-E-10-------------------------------------- A ring -
633|- attributes: name (g), name (v), weight (e).
634|- edges:
635[1] 'a'--'b'  'b'--'c'  'c'--'d'  'd'--'e'  'a'--'e'  'b'-'e'
636[7] 'e'--'a'  'a'--'d'  'd'--'b'  'a'--'c'
637
638
639IGRAPH-UNW--V-5-E-10-------------------------------------- A ring -
640+ attributes: name (g), name (v), weight (e).
641+ vertices:
642|     name
643| [1]    a
644| [2]    b
645| [3]    c
646| [4]    d
647| [5]    e
648+ edges:
649[1] 'a'--'b'  'b'--'c'  'c'--'d'  'd'--'e'  'a'--'e'  'b'-'e'
650[7] 'e'--'a'  'a'--'d'  'd'--'b'  'a'--'c'
651
652
653
654
655IGRAPH-UNW--V-5-E-10-------------------------------------- A ring -
656+ graph attributes: name
657+ vertex attributes: name
658+ edge attributes: weight
659+ vertices:
660|   name
661|1]    a
662|2]    b
663|3]    c
664|4]    d
665|5]    e
666+ edges:
667|1] a--b  b--c  c--d  d--e  a--e  b-e
668|7] e--a  a--d  d--b  a--c
669
670
671
672IGRAPH-UNW--V-5-E-10-------------------------------------- A ring -
673+ graph attributes:  name (c)
674+ vertex attributes: name (c)
675+ edge attributes:   weight (n)
676+ edges:
677[1] a--b  b--c  c--d  d--e  a--e  b-e
678[7] e--a  a--d  d--b  a--c
679
680
681IGRAPH-UNW--V-5-E-10-------------------------------------- A ring -
682+ attributes: name (g/c), name (v/c), weight (e/n)
683+ edges:
684[ 1] a--b b--c c--d d--e a--e b--e e--a a--d d--b
685[10] a--c
686
687IGRAPH-DNW--V-5-E-10-------------------------------------- A ring -
688+ attributes: name (g/c), name (v/n), weight (e/n)
689+ edges:
690[1]' 1->2 2->3 3->4 4->5 1->5 2->5 5->1
691[8]' 1->4 4->2 1->3
692
693
694IGRAPH-UNW--V-5-E-20-------------------------------------- A ring -
695+ attributes: name (g/c), name (v/c), weight (e/n)
696+ edges:
697[ 1] a-b b-c c-d d-e a-e b-e e-a a-d d-b a-c
698[11] a-b b-c c-d d-e a-e b-e e-a a-d d-b a-c
699
700
701IGRAPH-UNW--V-8-E-10-------------------------------------- A ring -
702+ attributes: name (g/c), name (v/c), weight (e/n)
703+ edges:
704[a] b c e f h
705[b] a c e
706[c] a b d
707[d] a b c h
708[e] a b d
709[f] a
710[g]
711[h] a d
712
713IGRAPH-UNW--V-10-E-18------------------------------------- A ring -
714+ attributes: name (g/c), name (v/c), weight (e/n)
715+ edges:
716[a] a--{b,c,e,f,h}  b--{a,c,e}  c--{a,b,d}  d--{a,b,c,h}
717[e] e--{a,b,d}      f--{a}      g--{}       h--{a,d}
718
719
720IGRAPH-UNW--V10-E18------------------------------Krackhardt kite--
721+ attributes: name (g/c), name (v/c), weight (e/n)
722+ edges:
723[   Andre][1] Beverly  Carol    Diane    Fernando
724[ Beverly][1] Andre    Diane    Ed       Garth
725[   Carol][1] Andre    Diane    Fernando
726[   Diane][1] Andre    Beverly  Carol    Diane    Ed
727[   Diane][6] Garth
728[      Ed][1] Beverly  Diane    Garth
729[Fernando][1] Andre    Carol    Diane    Garth
730[   Garth][1] Beverly  Diane    Ed       Fernando
731[ Heather][1] Fernando Garth
732[     Ike][1] Heather  Jane
733[    Jane][1] Ike
734
735IGRAPH-UNW--V10-E18-------------------------------Krackhardt kite--
736+ attributes: name (g/c), name (v/c), weight (e/n)
737+ edges:
738[   Andre][1] Beverly/1  Carol/3    Diane/3    Fernando/1
739[ Beverly][1] Andre/1    Diane/1    Ed/2       Garth/2
740[   Carol][1] Andre/2    Diane/2    Fernando/1
741[   Diane][1] Andre/5    Beverly/1  Carol/0.4  Diane/2
742[   Diane][5] Ed/1.5     Garth/2.5
743[      Ed][1] Beverly/-1 Diane/1.5  Garth/2
744[Fernando][1] Andre/1    Carol/2    Diane/1    Garth/1
745[   Garth][1] Beverly/2  Diane/3    Ed/1       Fernando/-1
746[ Heather][1] Fernando/3 Garth/1
747[     Ike][1] Heather/1  Jane/-1
748[    Jane][1] Ike/-2
749
750
751IGRAPH-UNW--V10-E18-------------------------------Krackhardt kite--
752+ attributes: name (g/c), name (v/c), weight (e/n)
753+ edges:
754[   Andre][1] Beverly (1)  Carol (3)    Diane (3)    Fernando (1)
755[ Beverly][1] Andre (1)    Diane (1)    Ed (2)       Garth (2)
756[   Carol][1] Andre (2)    Diane (2)    Fernando (1)
757[   Diane][1] Andre (5)    Beverly (1)  Carol (0.5)  Diane (2)
758[   Diane][5] Ed (1.5)     Garth (2.5)
759[      Ed][1] Beverly (-1) Diane (1.5)  Garth (2)
760[Fernando][1] Andre (1)    Carol (2)    Diane (1)    Garth (1)
761[   Garth][1] Beverly (2)  Diane (3)    Ed (1)       Fernando (-1)
762[ Heather][1] Fernando (3) Garth (1)
763[     Ike][1] Heather (1)  Jane (-1)
764[    Jane][1] Ike (-2)
765
766IGRAPH UNW- V10 E18 -- Krackhardt kite
767+ attr: name (g/c), name (v/c), weight (e/n)
768+ edges:
769[   Andre][1] Beverly (1)  Carol (3)    Diane (3)    Fernando (1)
770[ Beverly][1] Andre (1)    Diane (1)    Ed (2)       Garth (2)
771[   Carol][1] Andre (2)    Diane (2)    Fernando (1)
772[   Diane][1] Andre (5)    Beverly (1)  Carol (0.5)  Diane (2)
773[   Diane][5] Ed (1.5)     Garth (2.5)
774[      Ed][1] Beverly (-1) Diane (1.5)  Garth (2)
775[Fernando][1] Andre (1)    Carol (2)    Diane (1)    Garth (1)
776[   Garth][1] Beverly (2)  Diane (3)    Ed (1)       Fernando (-1)
777[ Heather][1] Fernando (3) Garth (1)
778[     Ike][1] Heather (1)  Jane (-1)
779[    Jane][1] Ike (-2)
780
781
782
783IGRAPH-U----V100-E200----------------------------Gnm random graph--
784+ edges:
785[  1] 28 46 89 90
786[  2] 47 69 72 89
787[  3] 29
788[  4] 17 20
789[  5] 11 40 42 51 78 89
790[  6] 27 32 70 87 93
791[  7] 18 27 87
792[  8] 18 24 82
793[  9] 18 20 85 94
794[ 10] 24 70 77 91
795[ 11]  5 12 34 61 62
796[ 12] 11 41 44 61 65 80
797...
798
799IGRAPH-U----100-200------------------------------Gnm random graph--
800+ edges:
801[  1] 28 46 89 90                 [  2] 47 69 72 89
802[  3] 29                          [  4] 17 20
803[  5] 11 40 42 51 78 89           [  6] 27 32 70 87 93
804[  7] 18 27 87                    [  8] 18 24 82
805[  9] 18 20 85 94                 [ 10] 24 70 77 91
806[ 11]  5 12 34 61 62              [ 12] 11 41 44 61 65 80
807...
808
809
810
811"
812