diff --git a/DESCRIPTION b/DESCRIPTION index 39079df..9df55c0 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: venndir Title: Directional Venn diagrams -Version: 0.0.38.900 +Version: 0.0.39.900 Authors@R: c( person(given="James M.", family="Ward", @@ -15,12 +15,12 @@ Imports: jamba(>= 0.0.101.900), colorjam(>= 0.0.26.900), pracma, polyclip, - vwline, polylabelr, gridtext, gridBase, data.table, gridExtra, + gridGeometry, methods Suggests: eulerr, @@ -28,6 +28,7 @@ Suggests: knitr, rmarkdown, testthat (>= 2.1.0), + vwline, vdiffr License: MIT Encoding: UTF-8 diff --git a/NAMESPACE b/NAMESPACE index a8d3a91..caa7243 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -4,7 +4,6 @@ S3method(plot,JamPolygon) export(add_orientation_JamPolygon) export(area_JamPolygon) export(bbox_JamPolygon) -export(bbox_polygon_list) export(buffer_JamPolygon) export(check_JamPolygon) export(check_Venndir) @@ -15,23 +14,18 @@ export(diff_degrees) export(display_angles) export(draw_gridtext_groups) export(eulerr_to_JamPolygon) -export(eulerr_to_polygon_list) export(expand_range) export(farthest_point_JamPolygon) export(find_venn_overlaps_JamPolygon) -export(get_largest_polygon_list) export(get_venn_polygon_shapes) -export(get_venn_shapes) export(has_point_in_JamPolygon) export(im2list) export(im_value2list) export(intersect_JamPolygon) -export(intersect_polygon_list) export(label_fill_JamPolygon) export(label_outside_JamPolygon) export(label_segment_JamPolygon) export(labelr_JamPolygon) -export(labelr_polygon_list) export(list2im_opt) export(list2im_value) export(make_color_contrast) @@ -41,25 +35,19 @@ export(match_list) export(mean_degree_arc) export(mean_degrees) export(minus_JamPolygon) -export(minus_polygon_list) export(nearest_point_JamPolygon) -export(nudge_polygon_coords) -export(nudge_polygon_list) +export(nudge_JamPolygon) export(nudge_venndir_label) export(overlaplist2setlist) -export(plot_polygon_list) export(point_in_JamPolygon) export(polyclip_to_JamPolygon) -export(polygon_areas) export(polygon_circles) export(polygon_ellipses) -export(polygon_list_labelr) -export(polygon_list_to_xy_list) export(print_color_df) +export(rbind2.JamPolygon) export(render_venndir) export(reposition_venn_gridtext_labels) export(rescale_coordinates) -export(rescale_polygon_list) export(sample_JamPolygon) export(shrink_df) export(signed_counts2setlist) @@ -72,15 +60,15 @@ export(three_point_angle) export(to_basic.GeomRichText) export(to_basic.GeomTextBox) export(union_JamPolygon) -export(union_polygon_list) export(update_JamPolygon) export(venn_meme) export(venndir) export(venndir_label_style) export(venndir_legender) export(venndir_to_df) -export(xy_list_to_polygon_list) exportMethods("[") exportMethods(plot) +exportMethods(rbind2) +exportMethods(setlist) import(data.table) importFrom(methods,as) diff --git a/NEWS.md b/NEWS.md index c5f393d..3f0511f 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,122 @@ +# venndir 0.0.39.900 + +## changes to existing functions + +* `render_venndir()` + + * Signed output now uses `":"` instead of `": "` between the directional + arrow and the count, for example `"^^:20"` instead of `"^^: 20"`. + Somehow the whitespace calculation is inconsistent, causing some + labels to be wider than others with `gridtext::richtext_grob()`, + with much wider whitespace than anticipated. + The effect was inconsistent even on the same machine, between RStudio + and R console, and differed across other machines also. + Workarounds include choosing different fonts, apparently some provide + more reliable whitespace calculations. + The change only occurs during rendering when `grobs` are created. + The underlying `Venndir` data is not changed. + +* `plot.JamPolygon()`, affecting `venndir()` and `render_venndir()` + + * Now renders borders using `gridGeometry` thanks to suggestion from + pmur002. Borders are more consistent, without small visual artifacts. + * Added `"outerborder"` as a formal border type. + * All three types of borders can be rendered, in order: outer, inner, border + + * "outerborder" - begins at the outer edge of the boundary + * "border" - is centered on the boundary itself + * "innerborder" - begins at the inner edge of the boundary + * when `border` is not drawn, either the innerborder or outerborder + are drawn on the border itself to prevent a tiny artifact gap + between the innerborder and outerborder. + +* `venndir()` + + * The `Venndir` object now uses `outerborder` instead of `border`, + and sets `border` to `NA`. + * New argument `lwd` controls default border line width. + * `unicode` (silent argument passed to `curate_venn_labels()` controls + the Unicode character with up/down arrows, disagreement, etc. + You can supply `unicode=2` for alternate symbols, though they are + font-dependent, R-dependent, and terminal-dependent. All things must + work well together (apparently). Use `unicode=FALSE` for simple text. + * New default `poly_alpha=0.6` makes background less intense. + * Now calls `make_color_contrast()` properly without forcing saturation, + previously caused blue to become cyan instead of light blue. + +* `sample_JamPolygon()` changed `n_ratio=1` after testing and disliking +the previous `n_ratio=4`. +* `venndir_to_df()` gained some new features: + + * new argument `df_format` with three formats: + + * `"hits"` - essentially a hit matrix with 1, 0, -1 indicating direction + * `"items"` - each column of a data.frame contains items for a Venn + overlap. + * `"wide"` - intended as an RMarkdown summary - it uses grouped rows + to display items in each Venn overlap. Not sure it works very well. + + * argument `return_type`: + + * `"data.frame"` (default) - returns a data.frame + * `"kable"` - returns a colorized `kable` table for RMarkdown HTML + +* `textvenn()` + + * now returns column `"color"` mainly used for `venndir_to_df()` + * calls `colorjam::col_linear_xf()` for better colorization of counts + when `color_by_counts=TRUE`. + +* `get_venn_polygon_shapes()` + + * Changed default `return_type="JamPolygon"` since transition to JamPolygon, + removed the option for `"polygon_list"`. + +* `polygon_circles()`, `polygon_ellipses()` both now return `JamPolygon`. + +## new functions + +* `nudge_JamPolygon()` - simple function to adjust `JamPolygon` polygons + + +## added generic functions + +* Cleaned up some generic function logic, probably more to do. +* `Venndir` objects + + * `plot()` + * `length()` + +* `rbind2.JamPolygon()` + + * This function was enhanced to be able to combine multiple `JamPolygon` + objects either in a single `list`, multiple `list`, and will now + retain all colnames across all `JamPolygon` objects. + +## removed deprecated functions, mostly related to polygon_list data format + +The polygon_list format loosely conformed to `polyclip` data input/output, +but had several exceptions that motivated me to use `JamPolygon`: simple +polygons encoded as list, complex polygons encoded as nested list; +solid polygon encoded as clockwise points, holes encoded counterclockwise. + +* `bbox_polygon_list()` +* `get_largest_polygon_list()` +* `intersect_polygon_list()` +* `labelr_polygon_list()` +* `minus_polygon_list()` +* `plot_polygon_list()` +* `polygon_list_labelr()` +* `rescale_polygon_list()` +* `union_polygon_list()` +* `get_venn_shapes()` +* `eulerr_to_polygon_list()` +* `polygon_areas()` +* `nudge_polygon_coords()` +* `nudge_polygon_list()` +* `polygon_list_to_xy_list()` +* `xy_list_to_polygon_list()` + # venndir 0.0.38.900 ## changes to existing functions diff --git a/R/JamPolygon.R b/R/JamPolygon.R index 2f299dd..326c068 100644 --- a/R/JamPolygon.R +++ b/R/JamPolygon.R @@ -53,10 +53,11 @@ check_JamPolygon <- function #' JamPolygon class #' -#' JamPolygon class +#' JamPolygon class contains one slot `"polygons"` which is a `data.frame` +#' with one polygon per row. An individual polygon can #' #' @family JamPolygon - +#' #' @examples #' df <- data.frame(name=c("polygon1", "polygon2"), #' x=I(list( @@ -82,6 +83,10 @@ setClass("JamPolygon", validity=check_JamPolygon ); +#' Subset JamPolygon object +#' +#' @docType methods +#' @rdname JamPolygon-methods #' @export setMethod("[", signature=c(x="JamPolygon", @@ -120,16 +125,6 @@ if (!isGeneric("plot")) { #' #' Plot JamPolygon object #' -#' Todo: -#' * Consider re-factoring so that inner/outer borders are rendered -#' in proper order, immediately after each polygon is drawn. -#' This change means the polygons can no longer be rendered in -#' vectorized fashion, since each polygon should have the opportunity -#' to overlap existing polygons and their borders. -#' * Implement method to render inner and outer borders where defined. -#' Currently only the outer border is rendered. -#' * Consider disabling the thin black border by default. -#' #' @returns `JamPolygon` object, invisibly. #' #' @family JamPolygon @@ -173,6 +168,8 @@ if (!isGeneric("plot")) { #' jpz <- add_orientation_JamPolygon(jpz); #' plot(jpz); #' +#' @docType methods +#' @rdname JamPolygon-methods #' @export setMethod("plot", signature=c(x="JamPolygon", y="missing"), @@ -257,6 +254,23 @@ setMethod("plot", #' jpx <- new("JamPolygon", polygons=dfx); #' plot(jpx); #' +#' # if you want to add to the plot, you must capture output +#' # to use the viewport +#' jpxout <- plot(jpx); +#' vp <- attr(jpxout, "viewport"); +#' adjx <- attr(jpxout, "adjx"); +#' adjy <- attr(jpxout, "adjy"); +#' grid::grid.path(x=adjx(c(4, 5, 5, 4) + 0.5), +#' y=adjy(c(3, 3, 4, 4)), +#' vp=vp, +#' gp=grid::gpar(fill="purple", col="red1", lwd=2), +#' default.units="snpc") +#' grid::grid.text(x=adjx(5), y=adjy(3.5), +#' label="new grob", +#' vp=vp, +#' gp=grid::gpar(col="yellow", fontsize=20), +#' default.units="snpc") +#' #' dfz <- data.frame(name=c("polygon1", "polygon2", "polygon3"), #' x=I(list( #' list(c(1, 4, 4, 1), @@ -277,8 +291,13 @@ setMethod("plot", #' fill=c("gold", "firebrick", "dodgerblue")); #' jpz <- new("JamPolygon", polygons=dfz); #' jpz@polygons[, c("label_x", "label_y")] <- as.data.frame(labelr_JamPolygon(jpz)) -#' jpz@polygons$border <- c("orange", "gold", "purple"); -#' jpz@polygons$border.lwd <- c(3, 4, 5); +#' jpz@polygons$outerborder <- c("orange", "gold", "purple"); +#' jpz@polygons$outerborder.lwd <- 0; +#' jpz@polygons$outerborder.lwd <- c(3, 4, 5); +#' jpz@polygons$innerborder <- c("orange4", "gold3", "purple4"); +#' jpz@polygons$innerborder.lwd <- c(3, 4, 5); +#' jpz@polygons$border.lwd <- 1; +#' jpz@polygons$border.lty <- 2; #' #jpz <- add_orientation_JamPolygon(jpz); #' plot(jpz); #' @@ -329,6 +348,8 @@ setMethod("plot", #' `grid::grid.draw()` for each graphical object. #' When `do_draw=FALSE`, it also forces `do_newpage=FALSE`, #' `do_viewport=FALSE`, and `do_pop_viewport=FALSE`. +#' @param do_experimental `logical` indicating whether to use experimental +#' rendering with `gridGeometry` as potential replacement for `vwline`. #' @param verbose `logical` indicating whether to print verbose output. #' @param debug `logical` (default FALSE) indicating whether to enable #' debug operations. When `debug=TRUE` it is also passed to `grid` @@ -336,6 +357,7 @@ setMethod("plot", #' calculations in the graphical output. #' @param ... additional arguments are recognized to customize plot features. #' +#' #' @export plot.JamPolygon <- function (x, @@ -355,6 +377,7 @@ plot.JamPolygon <- function do_viewport=TRUE, do_pop_viewport=TRUE, do_draw=TRUE, + do_experimental=TRUE, verbose=FALSE, debug=FALSE, ...) @@ -374,8 +397,9 @@ plot.JamPolygon <- function flip_sign <- head(flip_sign, 1); flip_sign <- ifelse(flip_sign >= 0, 1, -1); } - if (flip_sign < 0) { - jamba::printDebug("Handling flip_sign:", flip_sign); + if (flip_sign < 0 && TRUE %in% verbose) { + jamba::printDebug("plot.JamPolygon(): ", + "Handling flip_sign:", flip_sign); } } # grid options @@ -412,11 +436,15 @@ plot.JamPolygon <- function do_pop_viewport <- head(as.logical(do_pop_viewport), 1); } # render_vectorized: whether to draw polygons altogether, then borders later + render_vectorized <- FALSE; if (length(render_vectorized) == 0 || FALSE %in% render_vectorized) { render_vectorized <- FALSE; } else { render_vectorized <- head(as.logical(render_vectorized), 1); - jamba::printDebug("Overriding render_vectorized:", render_vectorized); + if (TRUE %in% verbose) { + jamba::printDebug("plot.JamPolygon(): ", + "Overriding render_vectorized:", render_vectorized); + } } # linejoin: the inner/outer border method if (length(mitrelimit) == 0) { @@ -443,6 +471,9 @@ plot.JamPolygon <- function # - for now we assume all are defined via colnames(jp@polygons) opt_args <- c("fill", "label", + "outerborder", + "outerborder.lwd", + "outerborder.lty", "border", "border.lwd", "border.lty", @@ -469,6 +500,9 @@ plot.JamPolygon <- function # fill in some default values where missing if (!"border.lwd" %in% colnames(x@polygons)) { x@polygons$border.lwd <- 1; + } else { + x@polygons$border.lwd <- jamba::rmNA(x@polygons$border.lwd, + naValue=0) } if (!"border.lty" %in% colnames(x@polygons)) { x@polygons$border.lty <- 1; @@ -486,6 +520,22 @@ plot.JamPolygon <- function # assemble tall format for coordinates df <- x@polygons; + + ## Reverse orientation of points where warranted + # (Experimental) + if (any(unlist(df$orientation) %in% c(1, -1))) { + for (i in seq_len(nrow(df))) { + idirs <- df$orientation[[i]]; + for (ipart in seq_along(idirs)) { + idir <- idirs[[ipart]]; + if (-1 %in% idir) { + # reverse the orientation for convenience later on + df$x[[i]][[ipart]] <- rev(df$x[[i]][[ipart]]); + df$y[[i]][[ipart]] <- rev(df$y[[i]][[ipart]]); + } + } + } + } # JamPolygon_to_grid_coords() row_lengths <- lapply(df$x, function(i){ if (is.list(i)) { @@ -516,7 +566,8 @@ plot.JamPolygon <- function yrange <- range(coords_df$y, na.rm=TRUE); } if (verbose) { - jamba::printDebug("xrange:", xrange, ", yrange:", yrange); + jamba::printDebug("plot.JamPolygon(): ", + "xrange:", xrange, ", yrange:", yrange); } ymid <- mean(yrange); yspan <- diff(yrange); @@ -615,11 +666,186 @@ plot.JamPolygon <- function # and draw only the border on the appropriate side # # iterate each row + if (debug) { + jamba::printDebug("df:");print(df);# debug + } for (irow in seq_len(length(x))) { irowname <- rownames(x@polygons)[irow]; # jamba::printDebug("irow:", irow, ", irowname:", irowname);# debug # render each polygon - if (FALSE %in% render_vectorized) { + if (TRUE %in% do_experimental) { + if (verbose) { + jamba::printDebug("Rendering polygon with gridGeometry: ", irow); + } + # first create the polygon path grob + use_coords_df <- subset(coords_df, pathId %in% irow); + if (nrow(use_coords_df) == 0 || all(is.na(use_coords_df$x))) { + next; + } + # jamba::printDebug("use_coords_df:");print(use_coords_df);# debug + + bc <- df[["border"]][[irow]]; + bw <- jamba::rmNA(naValue=0, + df[["border.lwd"]][[irow]]) + bt <- jamba::rmNA(naValue=0, + df[["border.lty"]][[irow]]); + # jamba::printDebug("bc:", bc, ", bw:", bw, ", bt:", bt);# debug + fc <- df$fill[[irow]]; + has_border <- (length(bc) > 0 && + length(bw) > 0 && + !any(bc %in% c(NA, "")) && + all(!is.na(bw) & bw > 0)); + # jamba::printDebug("df[irow,]:");print(df[irow, , drop=FALSE]);# debug + # jamba::printDebug("irow: ", irow, ", fc:", fc, ", bc:", bc, ", bw:", bw);jamba::printDebugI(fc);# debug + if (length(bt) == 0) { + bt <- 1; + } + if (length(bc) == 0 || any(bc %in% c(NA, "")) || + length(bw) == 0 || any(bw %in% c(NA) | bw <= 0)) { + bw <- 1; + bc <- NA; + } + shrunken <- NULL; + obc <- df[["outerborder"]][[irow]]; + obw <- jamba::rmNA(naValue=0, + df[["outerborder.lwd"]][[irow]] / 2); + obt <- jamba::rmNA(naValue=0, + df[["outerborder.lwd"]][[irow]]); + has_outer <- (length(obc) > 0 && + length(obw) > 0 && + !any(obc %in% c(NA, "")) && + all(obw > 0)); + ibc <- df[["innerborder"]][[irow]]; + ibw <- jamba::rmNA(naValue=0, + df[["innerborder.lwd"]][[irow]] / 2); + ibt <- jamba::rmNA(naValue=0, + df[["innerborder.lwd"]][[irow]]); + # jamba::printDebug("bw:", bw, ", ibw:", ibw, ", obw:", obw);# debug + has_inner <- (length(ibc) > 0 && + length(ibw) > 0 && + !any(ibc %in% c(NA, "")) && + all(ibw > 0)); + if (debug) { + jamba::printDebug("ibc:", ibc, ", ibw:", ibw, ", ibt:", ibt, ", has_inner:", has_inner);# debug + } + if (!has_border) { + if (has_inner) { + bw <- 0.5; + bc <- ibc; + } else if (has_outer) { + bw <- 0.5; + bc <- obc; + } + } + + if (has_inner) { + grobname <- paste0(irowname, ":", "pathGrob"); + path_grob <- grid::pathGrob( + rule="evenodd", + x=adjx(use_coords_df$x), + y=adjy(use_coords_df$y), + pathId=use_coords_df$pathId, + id=use_coords_df$id, + name=grobname, + vp=use_vp, + gp=grid::gpar( + fill=NA, + lwd=bw, + lty=bt, + col=bc)) + # col=bc)) + } else { + grobname <- paste0(irowname, ":", "pathGrob"); + path_grob <- grid::pathGrob( + rule="evenodd", + x=adjx(use_coords_df$x), + y=adjy(use_coords_df$y), + pathId=use_coords_df$pathId, + id=use_coords_df$id, + name=grobname, + vp=use_vp, + gp=grid::gpar( + fill=fc, + lwd=bw, + lty=bt, + col=bc)) + # col=bc)) + } + # check for inner border + # - if so, shrink polygon, use difference as inner border + if (has_inner) { + # jamba::printDebug("ibc:", ibc, ", ibw:", ibw, ", ibt:", ibt, fgText=ibc);# debug + shrunken_grob <- gridGeometry::polyoffsetGrob( + A=path_grob, + rule="evenodd", + delta=grid::unit(-(ibw), "mm"), + name=paste0(grobname, ":inner"), + gp=grid::gpar( + fill=fc, + lwd=bw, + lty=bt, + col=NA)); + # add the shrunken path_grob + if (TRUE %in% do_draw) { + grid::grid.draw(shrunken_grob) + } + grob_list <- c(grob_list, + setNames(list(shrunken_grob), paste0(grobname, ":inner:0"))); + innerborder_grob <- gridGeometry::polyclipGrob( + A=path_grob, + B=shrunken_grob, + op="minus", + name=paste0(grobname, ":inner:1"), + gp=grid::gpar( + col=NA, + fill=ibc)) + # add the innerborder_grob + if (TRUE %in% do_draw) { + grid::grid.draw(innerborder_grob) + } + grob_list <- c(grob_list, + setNames(list(innerborder_grob), paste0(grobname, ":inner:1"))); + } + if (length(obc) > 0 && + length(obw) > 0 && + !any(obc %in% c(NA, "")) && + all(obw > 0)) { + # jamba::printDebug("obc:", obc, ", obw:", obw, ", obt:", obt, fgText=obc);# debug + expanded_grob <- gridGeometry::polyoffsetGrob( + A=path_grob, + rule="evenodd", + delta=grid::unit(obw, "mm"), + name=paste0(grobname, ":outer:0"), + gp=grid::gpar( + fill="#FF0000", + col=NA)) + outerborder_grob <- gridGeometry::polyclipGrob( + A=expanded_grob, + B=path_grob, + op="minus", + name=paste0(grobname, ":outer:1"), + gp=grid::gpar( + col=NA, + fill=obc)) + # add the outerborder_grob + if (TRUE %in% do_draw) { + grid::grid.draw(outerborder_grob) + } + grob_list <- c(grob_list, + setNames(list(outerborder_grob), paste0(grobname, ":outer:1"))); + } + # add the original path_grob + if (TRUE %in% do_draw) { + grid::grid.draw(path_grob) + } + grob_list <- c(grob_list, + setNames(list(path_grob), paste0(grobname))); + # check for outer border + # - if so, expand polygon, use difference as outer border + # check for border (drawn last?) + # - if so render only the edge with no color fill + # assemble gTree? + } else if (FALSE %in% render_vectorized) { if (verbose) { jamba::printDebug("Rendering polygon: ", irow); } @@ -660,124 +886,126 @@ plot.JamPolygon <- function ######################################## # render inner and outer borders - for (border_type in c("inner", "outer")) { - if ("outer" %in% border_type) { - use_border <- x@polygons$border[[irow]]; - osign <- 1; - } else { - use_border <- x@polygons$innerborder[[irow]]; - osign <- -1; - } - ## confirm use_border is a color - if (length(use_border) == 0 || - any(is.na(use_border)) || - !jamba::isColor(use_border)) { - # skip rows with no border color - # next; - use_border <- "#FFFFFF00"; - } - if (verbose) { - jamba::printDebug("Rendering ", border_type, " border: ", - use_border, fgText=list("darkorange", use_border)); - } - use_x <- x@polygons$x[[irow]]; - use_y <- x@polygons$y[[irow]]; - if (!is.list(use_x)) { - use_x <- list(use_x); - use_y <- list(use_y); - } - # iterate each polygon part - for (ipart in seq_along(use_x)) { - part_x <- use_x[[ipart]]; - part_y <- use_y[[ipart]]; - part_x <- c(tail(part_x, 1), part_x, head(part_x, 0)); - part_y <- c(tail(part_y, 1), part_y, head(part_y, 0)); - npts <- length(part_x); - if (npts == 0) { - next; - } - part_orientation <- x@polygons$orientation[[irow]][[ipart]]; - if ("inner" %in% border_type) { - lwd_pts <- jamba::rmNULL(x@polygons$innerborder.lwd[[irow]], - nullValue=2); - lty_pts <- jamba::rmNULL(x@polygons$innerborder.lty[[irow]], - nullValue=1); + if (FALSE %in% do_experimental) { + for (border_type in c("inner", "outer")) { + if ("outer" %in% border_type) { + use_border <- x@polygons$border[[irow]]; + osign <- 1; } else { - lwd_pts <- jamba::rmNULL(x@polygons$border.lwd[[irow]], - nullValue=2); - lty_pts <- jamba::rmNULL(x@polygons$border.lty[[irow]], - nullValue=1); + use_border <- x@polygons$innerborder[[irow]]; + osign <- -1; } - # define line width at each point - if (any(lwd_pts <= 0)) { - lwd_pts[lwd_pts <= 0] <- 0.01; + ## confirm use_border is a color + if (length(use_border) == 0 || + any(is.na(use_border)) || + !jamba::isColor(use_border)) { + # skip rows with no border color + # next; + use_border <- "#FFFFFF00"; } - use_w <- vwline::widthSpec(list( - right=grid::unit(rep( - lwd_pts * ((osign * part_orientation) > 0), - # lwd_pts * (part_orientation != 0), - npts), "pt"), - left=grid::unit(rep( - lwd_pts * ((osign * part_orientation) < 0), - npts), "pt"))); - grobname <- paste0(irowname, ":vwlineGrob:", - border_type, ":", ipart); # rowname:grob:type:num - ## render the border - vwline_grob <- vwline::vwlineGrob( - x=adjx(part_x), - y=adjy(part_y), - w=use_w, - open=FALSE, - stepWidth=TRUE, - mitrelimit=mitrelimit, - linejoin=linejoin, - lineend="butt", - debug=debug, - name=grobname, - # vp=use_vp, - gp=grid::gpar( - fill=use_border, - col=NA, - lwd=1)) - ## update the viewport manually - vwline_grob$vp <- use_vp; - if (TRUE %in% do_draw) { - grid::grid.draw(vwline_grob); + if (verbose) { + jamba::printDebug("Rendering ", border_type, " border: ", + use_border, fgText=list("darkorange", use_border)); } - grob_list <- c(grob_list, - setNames(list(vwline_grob), grobname)); - - if (TRUE %in% render_thin_border) { - # consider whether to draw a thin border as below - # grobname <- paste0("border.", irow, ".", border_type, ".", ipart);# old style - grobname <- paste0(irowname, ":pathGrob:", - "border", ":", ipart); # rowname:grob:border:num - path_grob2 <- grid::pathGrob(x=adjx(part_x), + use_x <- x@polygons$x[[irow]]; + use_y <- x@polygons$y[[irow]]; + if (!is.list(use_x)) { + use_x <- list(use_x); + use_y <- list(use_y); + } + # iterate each polygon part + for (ipart in seq_along(use_x)) { + part_x <- use_x[[ipart]]; + part_y <- use_y[[ipart]]; + part_x <- c(tail(part_x, 1), part_x, head(part_x, 0)); + part_y <- c(tail(part_y, 1), part_y, head(part_y, 0)); + npts <- length(part_x); + if (npts == 0) { + next; + } + part_orientation <- x@polygons$orientation[[irow]][[ipart]]; + if ("inner" %in% border_type) { + lwd_pts <- jamba::rmNULL(x@polygons$innerborder.lwd[[irow]], + nullValue=2); + lty_pts <- jamba::rmNULL(x@polygons$innerborder.lty[[irow]], + nullValue=1); + } else { + lwd_pts <- jamba::rmNULL(x@polygons$border.lwd[[irow]], + nullValue=2); + lty_pts <- jamba::rmNULL(x@polygons$border.lty[[irow]], + nullValue=1); + } + # define line width at each point + if (any(lwd_pts <= 0)) { + lwd_pts[lwd_pts <= 0] <- 0.01; + } + use_w <- vwline::widthSpec(list( + right=grid::unit(rep( + lwd_pts * ((osign * part_orientation) > 0), + # lwd_pts * (part_orientation != 0), + npts), "pt"), + left=grid::unit(rep( + lwd_pts * ((osign * part_orientation) < 0), + npts), "pt"))); + grobname <- paste0(irowname, ":vwlineGrob:", + border_type, ":", ipart); # rowname:grob:type:num + ## render the border + vwline_grob <- vwline::vwlineGrob( + x=adjx(part_x), y=adjy(part_y), - rule="evenodd", - pathId=rep(1, length(part_x)), - id=rep(1, length(part_x)), + w=use_w, + open=FALSE, + stepWidth=TRUE, + mitrelimit=mitrelimit, + linejoin=linejoin, + lineend="butt", + debug=debug, name=grobname, - vp=use_vp, + # vp=use_vp, gp=grid::gpar( - fill=NA, - col="#00000022", - lty=lty_pts, - lwd=0.25)); + fill=use_border, + col=NA, + lwd=1)) + ## update the viewport manually + vwline_grob$vp <- use_vp; if (TRUE %in% do_draw) { - grid::grid.draw(path_grob2); + grid::grid.draw(vwline_grob); } grob_list <- c(grob_list, - setNames(list(path_grob2), grobname)); - } - - if (FALSE) { - # for debug only, print "1" at first point in polygon - grid::grid.text( - x=head(adjx(part_x), 1), - y=head(adjy(part_y), 1), - label="1", - gp=grid::gpar(fontsize=8, color="black")) + setNames(list(vwline_grob), grobname)); + + if (TRUE %in% render_thin_border) { + # consider whether to draw a thin border as below + # grobname <- paste0("border.", irow, ".", border_type, ".", ipart);# old style + grobname <- paste0(irowname, ":pathGrob:", + "border", ":", ipart); # rowname:grob:border:num + path_grob2 <- grid::pathGrob(x=adjx(part_x), + y=adjy(part_y), + rule="evenodd", + pathId=rep(1, length(part_x)), + id=rep(1, length(part_x)), + name=grobname, + vp=use_vp, + gp=grid::gpar( + fill=NA, + col="#00000022", + lty=lty_pts, + lwd=0.25)); + if (TRUE %in% do_draw) { + grid::grid.draw(path_grob2); + } + grob_list <- c(grob_list, + setNames(list(path_grob2), grobname)); + } + + if (FALSE) { + # for debug only, print "1" at first point in polygon + grid::grid.text( + x=head(adjx(part_x), 1), + y=head(adjy(part_y), 1), + label="1", + gp=grid::gpar(fontsize=8, color="black")) + } } } } @@ -796,6 +1024,10 @@ plot.JamPolygon <- function } } } + # Debug print grob_list + # if (TRUE %in% do_experimental) { + # jamba::printDebug("sdim(grob_list):");print(jamba::sdim(grob_list));# debug + # } # optionally print labels # Todo: Determine whether labels should be rendered "per polygon" @@ -880,28 +1112,132 @@ plot.JamPolygon <- function # Todo: # - Enhance rbind2 to keep all columns and not only keep the shared columns. # Useful and important to keep things like fill/border color. -setMethod("rbind2", - signature=c(x="JamPolygon", y="JamPolygon"), - definition=function(x, y, ...) { - if (!all(colnames(x@polygons) == colnames(y@polygons))) { - use_colnames <- intersect(colnames(x@polygons), - colnames(y@polygons)); - new_polygons <- rbind(x@polygons[, use_colnames, drop=FALSE], - y@polygons[, use_colnames, drop=FALSE]); + +#' Combine multiple JamPolygon objects +#' +#' Combine multiple JamPolygon objects, given two JamPolygon or multiple +#' objects in a list. +#' +#' This function is intended to support input as `rbind2(list(JamPolygons))` +#' or `do.call(rbind2.JamPolygon, list(JamPolygons))` with any +#' combination of one or more `JamPolygon` objects. +#' +#' @family JamPolygon +#' +#' @docType methods +#' @rdname JamPolygon-methods +#' +#' @param x,y `JamPolygon` object +#' @param ... additional `JamPolygon` objects if present +#' @export +rbind2.JamPolygon <- function +(x, + y, + ...) +{ + # convert everything to a list of dots + dots <- list(...); + if (!missing(y)) { + if (is.list(y)) { + dots <- c(y, dots); } else { - new_polygons <- rbind(x@polygons, y@polygons); + dots <- c(list(y), dots); } - dots <- list(...); - for (i in seq_along(dots)) { - if (!all(colnames(new_polygons) == colnames(dots[[i]]@polygons))) { - new_polygons <- rbind(new_polygons[, use_colnames, drop=FALSE], - dots[[i]]@polygons[, use_colnames, drop=FALSE]); + y <- NULL; + } + if (!missing(x)) { + if (is.list(x)) { + dots <- c(x, dots); + } else { + dots <- c(list(x), dots); + } + x <- NULL; + } + use_dots <- sapply(dots, function(i){ + # ("JamPolygon" %in% class(i)) + inherits(i, "JamPolygon") + }) + if (!any(use_dots)) { + return(NULL) + } + use_dots <- which(use_dots) + # Option to keep columns already in all JamPolygon objects + if (FALSE) { + use_colnames <- Reduce("intersect", + lapply(dots[use_dots], function(i){ + colnames(i@polygons)})) + } else { + # Option to keep every column across all JamPolygon objects + use_colnames <- Reduce("union", + lapply(dots[use_dots], function(i){ + colnames(i@polygons)})) + } + # jamba::printDebug("use_colnames: ", use_colnames);# debug + + new_polygons <- dots[[head(use_dots, 1)]]@polygons; + new_names <- names(dots[use_dots]); + new_names[new_names %in% c("", NA)] <- "new"; + new_names <- jamba::makeNames(new_names, + renameFirst=FALSE); + + if (any(use_dots)) { + for (i in tail(use_dots, -1)) { + match1 <- match(use_colnames, colnames(new_polygons)); + match2 <- match(use_colnames, colnames(dots[[i]]@polygons)); + df1 <- as.data.frame(check.names=FALSE, + row.names=jamba::makeNames(new_polygons$name, + renameFirst=FALSE), + jamba::rmNULL(nullValue=NA, + as.list(new_polygons)[match1])); + colnames(df1) <- use_colnames; + df2list <- jamba::rmNULL(nullValue=NA, + as.list(dots[[i]]@polygons)[match2]); + names(df2list) <- use_colnames; + if ("name" %in% use_colnames) { + df2 <- as.data.frame(check.names=FALSE, + row.names=jamba::makeNames(df2list$name, + renameFirst=FALSE), + df2list); + # jamba::printDebug("df2:");print(df2);# debug } else { - new_polygons <- rbind(new_polygons, dots[[i]]@polygons); + df2 <- as.data.frame(check.names=FALSE, + row.names=as.character(seq_along(df2list[[1]])), + df2list); } + # if ("name" %in% colnames(df2)) { + # rownames(df2) <- df2[, "name"]; + # } + colnames(df2) <- use_colnames; + new_polygons <- rbind(df1, df2); } - x@polygons <- new_polygons; - x; + } + x <- new("JamPolygon", polygons=new_polygons); + # ensure names are unique + names(x) <- jamba::makeNames(names(x), + renameFirst=FALSE) + rownames(x@polygons) <- names(x); + + # one step of validation to make sure certain columns are not empty + # if ("label" %in% colnames(x@polygons)) { + # na_label <- is.na(x@polygons$label); + # if (any(na_label)) { + # x@polygons$label[na_label] <- x@polygons$label[na_label] + # } + # } + + # jamba::printDebug("x:");print(x);# debug + return(x) +} + +#' Combine multiple JamPolygon objects +#' +#' @docType methods +#' @rdname JamPolygon-methods +#' @export +setMethod("rbind2", + signature=c(x="JamPolygon", y="ANY"), + definition=function(x, y, ...) { + rbind2.JamPolygon(x, y, ...) } ) @@ -918,6 +1254,8 @@ setMethod("names<-", signature=c(x="JamPolygon"), definition=function(x, value) { x@polygons$name <- value; + # keep rownames in sync with names + rownames(x@polygons) <- value; check_JamPolygon(x) x } @@ -937,12 +1275,12 @@ setMethod("nrow", ) # length() -length.JamPolygon <- function -(x) -{ - # - nrow(x@polygons) -} +# length.JamPolygon <- function +# (x) +# { +# # +# nrow(x@polygons) +# } if (!isGeneric("length")) { # setGeneric("length", function(x) standardGeneric("length")) setGeneric("length") @@ -1670,6 +2008,8 @@ update_JamPolygon <- function #' #' @family JamPolygon #' +#' @param A output from `polyclip` functions. +#' #' @examples #' df <- data.frame(name=c("polygon1", "polygon2"), #' x=I(list( @@ -1794,7 +2134,7 @@ sample_JamPolygon <- function n=100, xyratio=1.1, spread=TRUE, - n_ratio=5, + n_ratio=1, pattern=c("offset", "rectangle"), buffer=0, @@ -1980,17 +2320,47 @@ sample_JamPolygon <- function #' #' @family JamPolygon #' +#' @returns `JamPolygon` with one polygon, although the polygon could +#' contain multiple disconnected parts. +#' #' @param jp `JamPolygon` with one or more polygons. When multiple polygons #' are provided, they are combined with `union_JamPolygon()` so that #' one overall buffer can be provided. #' @param buffer `numeric` buffer, where negative values cause the polygon #' to be reduced in size. +#' @param steps `numeric` number of steps, default 200, used to +#' determine relative unit sizes when `relative=TRUE` (which is default). +#' @param relative `logical` default `TRUE`, indicating whether to resize +#' polygons using relative dimensions. Relative units are defined by +#' the minimum negative buffer that results in non-zero area, where +#' relative unit -1 would result in zero area. +#' @param verbose `logical` indicating whether to print verbose output. +#' @param ... additional arguments are ignored. +#' +#' @examples +#' DEdf <- data.frame(check.names=FALSE, +#' name=c("D", "E"), +#' x=I(list( +#' c(-3, 3, 3, 0, -3), +#' c(-4, 2, 2, -4))), +#' y=I(list( +#' c(-3, -3, 1.5, 4, 1.5), +#' c(-2, -2, 4, 4))), +#' fill=c("#FFD70055", "#B2222255")) +#' jp <- new("JamPolygon", polygons=DEdf) +#' plot(jp) +#' +#' jp2 <- nudge_JamPolygon(jp, nudge=list(D=c(10, 0))); +#' jp_jp2 <- rbind2(jp2, buffer_JamPolygon(jp2)); +#' plot(jp_jp2, +#' border.lty=c(1, 1, 2), +#' fill=c(NA, NA, "gold")); #' #' @export buffer_JamPolygon <- function (jp, buffer=-0.5, - steps=50, + steps=200, relative=TRUE, verbose=FALSE, ...) @@ -2046,7 +2416,6 @@ buffer_JamPolygon <- function # buffer_polygon_list <- polyclip::polyoffset( poly_list[[k]], - # union_polygon_list(polygon_list), buffer, jointype="round") if (length(jamba::rmNA(unlist(buffer_polygon_list))) == 0) { @@ -2058,10 +2427,10 @@ buffer_JamPolygon <- function # relative size bbox_jp <- bbox_JamPolygon(jp); bbox_max <- max(apply(bbox_jp, 1, diff)) - if (relative) { + if (TRUE %in% relative) { buffer_seq <- tail(seq(from=bbox_max, to=0, - length.out=100), -1) + length.out=steps), -1) # jamba::printDebug("buffer_seq:", round(digits=2, buffer_seq)); # iterate buffer widths to determine complete removal @@ -2074,22 +2443,6 @@ buffer_JamPolygon <- function next; } break; - # buffer_polygon_list2 <- polyclip::polyoffset( - # poly_list[[1]], - # # union_polygon_list(polygon_list), - # # -max_buffer, - # -0.05, - # jointype="round") - # new_jp2 <- polyclip_to_JamPolygon(buffer_polygon_list2); - if (FALSE) { - plot(do.call(rbind2, list(jp, new_jp, new_jp2)), - border=c("grey", "gold", "blue"), border.lwd=c(1, 3, 3), - fill=c("firebrick", NA, "red1")) - } - if (length(buffer_polygon_list) > 0 && - sum(polygon_areas(buffer_polygon_list, simplify=TRUE)) > 0) { - break; - } } buffer <- buffer * max_buffer; if (verbose) { diff --git a/R/Venndir-class.R b/R/Venndir-class.R index f5279fa..5eceddc 100644 --- a/R/Venndir-class.R +++ b/R/Venndir-class.R @@ -121,6 +121,55 @@ setClass("Venndir", validity=check_Venndir ); + +#' Plot JamPolygon object +#' +#' Plot JamPolygon object +#' +#' @returns `Venndir` object, invisibly. +#' +#' @docType methods +#' @rdname `Venndir-methods` +#' +#' @export +setMethod("plot", + signature=c(x="Venndir", y="ANY"), + definition=function(x, y, ...) { + if (missing(y)) { + y <- 0; + } + render_venndir(x, ...) + }) + # Todo: # * print(), summary() functions -# * plot function as wrapper to render_venndir() + +setMethod("length", + signature=c(x="Venndir"), + definition=function(x) { + length(x@setlist); + } +) + +# if (!isGeneric("setlist")) { +setGeneric("setlist", function(x) standardGeneric("setlist")) +# } + +#' Extract setlist from a Venndir object +#' +#' @param x `Venndir` object +#' @docType methods +#' @rdname `Venndir-method` +#' @export +setMethod("setlist", + signature(x="Venndir"), + function(x) { + x@setlist + }) + +setMethod("names", + signature=c(x="Venndir"), + definition=function(x) { + names(x@setlist); + } +) diff --git a/R/venndir-base-polyclip.R b/R/venndir-base-polyclip.R index 3ec928e..2d13343 100644 --- a/R/venndir-base-polyclip.R +++ b/R/venndir-base-polyclip.R @@ -71,7 +71,7 @@ #' #' The default `c(1, 1, 0.8)` defines the signed count label slightly #' smaller than other labels. -#' @param poly_alpha `numeric` (default 0.8) value between 0 and 1, for +#' @param poly_alpha `numeric` (default 0.6) value between 0 and 1, for #' alpha transparency of the polygon fill color. #' This value is ignored when `alpha_by_counts=TRUE`. #' * `poly_alpha=1` is completely opaque (no transparency) @@ -241,7 +241,7 @@ venndir <- function # show_set=c("main", "all", "none"), show_label=NA, display_counts=TRUE, - poly_alpha=0.8, + poly_alpha=0.6, alpha_by_counts=FALSE, label_style=c("basic", "fill", @@ -269,6 +269,7 @@ venndir <- function verbose=FALSE, debug=0, circle_nudge=NULL, + lwd=1, rotate_degrees=0, ...) { @@ -451,7 +452,6 @@ venndir <- function rotate_degrees=rotate_degrees, return_type="JamPolygon", ...); - rownames(venn_jp@polygons) <- paste0(names(venn_jp), "|set"); } # Assign other attributes for consistency later on @@ -461,17 +461,29 @@ venndir <- function function(xi) character(0))); venn_jp@polygons$venn_color <- set_colors[venn_jp@polygons$venn_name]; border_dark_factor <- 1.1; - venn_jp@polygons$border <- jamba::makeColorDarker( - darkFactor=border_dark_factor, - set_colors[venn_jp@polygons$venn_name]); - venn_jp@polygons$border.lwd <- 4; + + venn_jp@polygons$outerborder <- jamba::alpha2col( + alpha=poly_alpha, + jamba::makeColorDarker( + darkFactor=border_dark_factor, + set_colors[venn_jp@polygons$venn_name])); + venn_jp@polygons$outerborder.lwd <- lwd; + + venn_jp@polygons$border <- jamba::alpha2col( + alpha=poly_alpha, + jamba::makeColorDarker( + darkFactor=border_dark_factor, + set_colors[venn_jp@polygons$venn_name])); + venn_jp@polygons$border.lwd <- lwd/2; + + venn_jp@polygons$innerborder <- NA; + venn_jp@polygons$innerborder.lwd <- 0; + venn_jp@polygons$fill <- NA; venn_jp@polygons$label <- venn_jp@polygons$venn_name; venn_jp@polygons$label_x <- NA; venn_jp@polygons$label_y <- NA; venn_jp@polygons$type <- "set"; - venn_jp@polygons$innerborder <- NA; - venn_jp@polygons$innerborder.lwd <- 0; # convert to venn overlap polygons @@ -489,6 +501,10 @@ venndir <- function ...); # rownames(venn_jpol@polygons) <- names(venn_jpol); venn_jp@polygons$type <- "set"; + # update JamPolygon names to indicate full set + names(venn_jp) <- paste0(names(venn_jp), "|set"); + rownames(venn_jp@polygons) <- names(venn_jp); + venn_jpol@polygons$type <- "overlap"; # jamba::printDebug("venndir(): ", "venn_jpol:");print(venn_jpol);# debug @@ -615,9 +631,6 @@ venndir <- function venn_jps@polygons$hjust[jamba::rmNA(whichset)] <- sapply(ploxy, function(ixy){ ixy["label", "adjy"] }); - # jamba::printDebug("venn_jps[whichset, ]@polygons:");print(venn_jps[whichset, ]@polygons);# debug - # jamba::printDebug("venn_jps@polygons:");print(venn_jps@polygons);# debug - # stop("Stopped after outside labels.");# debug } # show_set: whether to display each overlap label @@ -745,26 +758,34 @@ venndir <- function 0); # define inner border - venn_jps@polygons$innerborder.lwd <- 2; + venn_jps@polygons$innerborder.lwd <- lwd; # venn_jps@polygons$innerborder.lty <- 1; border_dark_factor <- 1.1; border_s_factor <- 1.2; venn_jps@polygons$innerborder <- ifelse(vset, - jamba::makeColorDarker( - jamba::unalpha(venn_jps@polygons$venn_color), - darkFactor=border_dark_factor, - sFactor=border_s_factor), + jamba::alpha2col(alpha=1, + jamba::makeColorDarker( + jamba::unalpha(venn_jps@polygons$venn_color), + darkFactor=border_dark_factor, + sFactor=border_s_factor)), NA); # define outer border - venn_jps@polygons$border.lwd <- 2; - # venn_jps@polygons$border.lty <- 1; - venn_jps@polygons$border <- ifelse(vset, + venn_jps@polygons$border.lwd <- lwd/2; + # option to re-use outer border as border + # venn_jps@polygons$border <- ifelse(vset, + # NA, + # venn_jps@polygons$outerborder); + venn_jps@polygons$border <- NA; + # venn_jps@polygons$border.lty <- 3; + venn_jps@polygons$outerborder.lwd <- lwd; + venn_jps@polygons$outerborder <- ifelse(vset, NA, - jamba::makeColorDarker( - jamba::unalpha(venn_jps@polygons$venn_color), - darkFactor=border_dark_factor, - sFactor=border_s_factor)) + jamba::alpha2col(alpha=1, + jamba::makeColorDarker( + jamba::unalpha(venn_jps@polygons$venn_color), + darkFactor=border_dark_factor, + sFactor=border_s_factor))) # define label font size venn_jps@polygons$fontsize <- 14 * head(font_cex, 1); diff --git a/R/venndir-curate.R b/R/venndir-curate.R index dc71b7e..f9609a6 100644 --- a/R/venndir-curate.R +++ b/R/venndir-curate.R @@ -97,29 +97,34 @@ curate_venn_labels <- function curate_list <- list( c("-1", "\u2193", "dodgerblue3"), c("1", "\u2191", "firebrick"), - c("concordant|agreement", "\u21F6", "dodgerblue3"), - #c("[ ]*mixed", "\u2193\u2191", "grey45")); - #c("[ ]*mixed", "\u21C6", "grey45")); - c("mixed", "\u2194", "grey45")); + c("concordant|agreement", "\u2714", "dodgerblue3"), # check mark + c("mixed", "\u2716", "grey45")); # X mark + # c("mixed", "\u2928", "grey45")); # up/down diagonal cross arrows - not supported widely + # c("concordant|agreement", "\u2016", "dodgerblue3"), # double bar || + # c("mixed", "\u2717", "grey45")); # X to go with check mark + # c("[ ]*mixed", "\u21C6", "grey45")); # left-right equilibrium arrows + # c("mixed", "\u2194", "grey45")); # left-right single arrow (small) + # c("mixed", "X", "grey45")); # uppercase X } else if (1 %in% unicode) { curate_list <- list( c("-1", "\u2193", "dodgerblue3"), c("1", "\u2191", "firebrick"), c("0", "-", ""), - c("concordant|agreement", "=", "dodgerblue3"), - c("mixed", "X", "grey45")); + c("concordant|agreement", "\u2016", "dodgerblue3"), # double bar || + c("mixed", "X", "grey45")); # uppercase X + # c("mixed", "\u58", "grey45")); # broken bar | + # c("mixed", "\u00A6", "grey45")); # broken bar | + # c("concordant|agreement", "\u2714", "dodgerblue3"), # check mark + # c("mixed", "\u2715", "grey45")); # X mark + # c("concordant|agreement", "=", "dodgerblue3"), # equal sign + # c("mixed", "X", "grey45")); #c("mixed", "\u21C6", "grey45")); } else { - curate_list <- list( - c("[ ]*-1", "v", "dodgerblue3"), - c("[ ]*1", "^", "firebrick"), # somehow ^ is not supported - c("[ ]*concordant|agreement", ">>>", "dodgerblue3"), - c("[ ]*mixed", ">|<", "grey45")); curate_list <- list( c("-1", "v", "dodgerblue3"), c("1", "^", "firebrick"), c("0", "-", ""), - c("concordant|agreement", ">>>", "dodgerblue3"), + c("concordant|agreement", "=", "dodgerblue3"), c("mixed", "X", "grey45")); } curate_df <- data.frame(check.names=FALSE, diff --git a/R/venndir-label-fill-jp.R b/R/venndir-label-fill-jp.R index a4b82cc..6f80e6a 100644 --- a/R/venndir-label-fill-jp.R +++ b/R/venndir-label-fill-jp.R @@ -58,12 +58,15 @@ #' jp3 <- new("JamPolygon", polygons=df3); #' plot(jp3); #' -#' label_fill_JamPolygon(jp3[1,], labels=1:20) -#' test_x <- jp3[1,]@polygons$x[[1]]; -#' test_y <- jp3[1,]@polygons$y[[1]]; -#' P <- list(x=c(3.5, 4.5), y=c(3.5, 4.5)) -#' A <- lapply(seq_along(test_x), function(i){ -#' list(x=test_x[[i]], y=test_y[[i]])}) +#' lfj <- label_fill_JamPolygon(jp3[1,], labels=1:20) +#' plot(lfj$items_df[, c("x", "y")], cex=0) +#' text(lfj$items_df[, c("x", "y")], labels=lfj$items_df$text) +#' +#' #test_x <- jp3[1,]@polygons$x[[1]]; +#' #test_y <- jp3[1,]@polygons$y[[1]]; +#' #P <- list(x=c(3.5, 4.5), y=c(3.5, 4.5)) +#' #A <- lapply(seq_along(test_x), function(i){ +#' # list(x=test_x[[i]], y=test_y[[i]])}) #' #' @export label_fill_JamPolygon <- function diff --git a/R/venndir-labels.R b/R/venndir-labels.R index 061ea46..25facb1 100644 --- a/R/venndir-labels.R +++ b/R/venndir-labels.R @@ -104,6 +104,7 @@ draw_gridtext_groups <- function ## Experimental realign strategy if (TRUE %in% realign && length(groupdf) > 0) { # check if main count label exists + # jamba::printDebug("use_groupdf:");print(use_groupdf);# debug is_main_count <- (grepl("count", use_groupdf$type) & grepl("main", use_groupdf$counttype)); is_signed_count <- (grepl("count", use_groupdf$type) & @@ -134,6 +135,7 @@ draw_gridtext_groups <- function # all_g_labels_cns <- grid::childNames(g_labels); # jamba::printDebug("all_g_labels_cns:");print(data.frame(all_g_labels_cns));# debug g_labels_cns <- use_groupdf$childName; + # jamba::printDebug("g_labels_cns:");print(g_labels_cns);# debug use_vp <- NULL; gdfbasename <- head(gdf[korig, "gdf_group"], 1); ## signed counts diff --git a/R/venndir-poly-conversions.R b/R/venndir-poly-conversions.R deleted file mode 100644 index 0f189b7..0000000 --- a/R/venndir-poly-conversions.R +++ /dev/null @@ -1,110 +0,0 @@ - - -#' Convert polygon list of x,y coordinate into a list by x and y -#' -#' Convert polygon list of x,y coordinate into a list by x and y -#' -#' Input is a list of polygons, where each polygon contains a `list` -#' with elements `"x"` and `"y"`. Output is a list of `"x"` and `"y"` -#' split by each polygon. -#' -#' @returns `list` with elements `"x"` and `"y"` which each contain a -#' `list` with length `length(x)`. -#' -#' @family venndir polygons -#' -#' @param x `list` of polygons -#' * each polygon should contain a `list` with elements `"x"` and `"y"`. -#' * each polygon can contain multiple component polygons as a -#' nested list, in which case this function is called iteratively -#' so that the component `"x"` and `"y"` are returned as equivalent -#' nested `list` objects. -#' * In all cases, `names(output$x)` and `names(output$y)` should equal -#' `names(x)`. -#' @param flatten `logical` indicating whether all polygons should be -#' flattened to the same level, without nested polygons. -#' @param ... additional arguments are ignored. -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' jamba::ssdim(polygon_list) -#' jamba::ssdim(polygon_list_to_xy_list(polygon_list)) -#' -#' jamba::ssdim(polygon_list_to_xy_list(list(AB=polygon_list))) -#' -#' @export -polygon_list_to_xy_list <- function -(x, - flatten=FALSE, - ...) -{ - # - # if (!all(c("x", "y") %in% names(x[[1]]))) { - # stop("input must be a list containing \"x\" and \"y\"") - # } - list_y <- lapply(x, function(ix){ - if (is.list(ix) && !all(c("x", "y") %in% names(ix))) { - polygon_list_to_xy_list(ix)$y - } else { - ix$y - } - }) - list_x <- lapply(x, function(ix){ - if (is.list(ix) && !all(c("x", "y") %in% names(ix))) { - polygon_list_to_xy_list(ix)$x - } else { - ix$x - } - }) - - # if input contains nested polygons (e.g. holes) - # they must be unlisted to flatten them - if (TRUE %in% flatten) { - if (is.list(list_y[[1]])) { - list_y <- unlist(list_y, recursive=FALSE); - } - if (is.list(list_x[[1]])) { - list_x <- unlist(list_x, recursive=FALSE); - } - } - return(list( - x=list_x, - y=list_y)) -} - - -#' Convert coordinate list of x and y into polygon list of x,y coordinates -#' -#' @family venndir polygons -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' xy_list <- polygon_list_to_xy_list(polygon_list) -#' polygon_list2 <- xy_list_to_polygon_list(xy_list) -#' identical(polygon_list, polygon_list2) -#' -#' @export -xy_list_to_polygon_list <- function -(x, - ...) -{ - # - if (!all(c("x", "y") %in% names(x))) { - stop("input must be a list containing \"x\" and \"y\"") - } - xy_seq <- jamba::nameVector(seq_along(x$x), names(x$x)); - polygon_list <- lapply(xy_seq, function(i){ - if (is.list(x$x[[i]])) { - xy_list_to_polygon_list(x=list(x=x$x[[i]], y=x$y[[i]])) - } else { - list(x=x$x[[i]], y=x$y[[i]]) - } - }) - return(polygon_list); -} - - diff --git a/R/venndir-polyclip.R b/R/venndir-polyclip.R index 3ae162b..202e3ef 100644 --- a/R/venndir-polyclip.R +++ b/R/venndir-polyclip.R @@ -1,41 +1,4 @@ -#' Convert euler output to polygons -#' -#' Convert euler output to polygons -#' -#' This function takes the output from `eulerr::euler()` and -#' converts it to polygons in `list` format. -#' -#' @return `list` polygon object with one polygon -#' for each Euler circle or ellipse. -#' -#' @family venndir polygons -#' -#' @param x output from `eulerr::euler()` -#' -#' @returns `list` with polygons for each unique set defined by `names(x)`, -#' where each list contains `numeric` vectors named `"x"` and `"y"`. -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' -#' polygon_areas(polygon_list) -#' -#' @export -eulerr_to_polygon_list <- function -(x) -{ - # x <- va - ellipses1 <- simple_ellipse(h=x$ellipses$h, - k=x$ellipses$k, - a=x$ellipses$a, - b=x$ellipses$b, - phi=x$ellipses$phi); - names(ellipses1) <- rownames(x$ellipses); - return(ellipses1); -} #' Simple ellipse function #' @@ -151,10 +114,10 @@ eulerr_to_JamPolygon <- function #' plot(jp1) #' #' xo <- find_venn_overlaps_JamPolygon(jp=jp1, venn_counts=test_counts) -#' xo@polygons$border <- jamba::makeColorDarker(darkFactor=1.2, +#' xo@polygons$outerborder <- jamba::makeColorDarker(darkFactor=1.2, #' xo@polygons$venn_color) -#' xo@polygons$border.lwd <- 2; -#' plot(xo, flip_sign=-1); +#' xo@polygons$outerborder.lwd <- 4; +#' plot(xo); #' #' @export # find_venn_polygon_list_overlaps <- function @@ -235,7 +198,6 @@ find_venn_overlaps_JamPolygon <- function } ## calculate venn overlap polygons - #vennCoords <- lapply(1:nrow(el1), function(j){ venn_poly_coords <- lapply(seq_len(nrow(el1)), function(j){ i <- el1[j,]; if (verbose) { @@ -289,7 +251,6 @@ find_venn_overlaps_JamPolygon <- function # print(jp[whichYes, ]);# debug } ellYes <- intersect_JamPolygon(jp[whichYes, ]); - # ellYes <- intersect_polygon_list(polygon_list[whichYes]); } if (length(ellYes) == 0) { ellUse <- list(); @@ -318,8 +279,10 @@ find_venn_overlaps_JamPolygon <- function ellUse@polygons$venn_color <- venn_color; ellUse@polygons$border <- NA; ellUse@polygons$border.lwd <- 1; + ellUse@polygons$outerborder <- NA; + ellUse@polygons$outerborder.lwd <- 1; ellUse@polygons$innerborder <- border; - ellUse@polygons$innerborder.lwd <- 3; + ellUse@polygons$innerborder.lwd <- 1; ellUse@polygons$fill <- venn_color; # attr(ellUse, "venn_name") <- poly_name; # attr(ellUse, "venn_count") <- venn_poly_count; @@ -333,15 +296,13 @@ find_venn_overlaps_JamPolygon <- function # jamba::printDebug("ellUse:");print(ellUse);# debug ellUse; }) - # jamba::printDebug("venn_poly_coords (before rbind2):");print(venn_poly_coords);# debug - # return(venn_poly_coords); - venn_poly_coords <- do.call(rbind2, venn_poly_coords); + # venn_poly_coords <- do.call(rbind2, venn_poly_coords); + # jamba::printDebug("venn_poly_coords:");print(venn_poly_coords);# debug + venn_poly_coords <- rbind2.JamPolygon(venn_poly_coords); # Note venn_poly_coords is JamPolygon - # jamba::printDebug("venn_poly_coords (after rbind2):");print(venn_poly_coords);# debug venn_poly_coords@polygons$name <- rownames(el1); rownames(venn_poly_coords@polygons) <- names(venn_poly_coords); - # names(venn_poly_coords) <- rownames(el1); - + venn_poly_colors <- venn_poly_coords@polygons$venn_color; # venn_poly_counts <- venn_poly_coords@polygons$venn_count; venn_poly_items <- venn_poly_coords@polygons$venn_items; @@ -353,98 +314,19 @@ find_venn_overlaps_JamPolygon <- function "vennUse:", vennUse, ", vennMissing:", vennMissing); } - # OMIT since JamPolygon already contains data.frame - # new data.frame format - # venn_xy_coords <- polygon_list_to_xy_list(venn_poly_coords); - # if (verbose > 1) { - # jamba::printDebug("ssdim(venn_poly_coords):");print(jamba::ssdim(venn_poly_coords));# debug - # jamba::printDebug("ssdim(venn_xy_coords):");print(jamba::ssdim(venn_xy_coords));# debug - # } - # return(invisible(venn_poly_coords)); - + venn_poly_coords@polygons$label <- names(venn_poly_coords); - # venn_pcdf <- data.frame(check.names=FALSE, - # stringsAsFactors=FALSE, - # label=names(venn_poly_coords[vennUse]), - # x=I(venn_xy_coords$x[vennUse]), - # y=I(venn_xy_coords$y[vennUse]), - # venn_poly_coords=I(venn_poly_coords[vennUse]), - # color=venn_poly_colors[vennUse], - # venn_counts=venn_poly_counts[vennUse], - # venn_color=venn_poly_colors[vennUse]) - # Define label position for each polygon label_xy <- labelr_JamPolygon(venn_poly_coords); venn_poly_coords@polygons[, c("label_x", "label_y")] <- as.data.frame( label_xy); - # venn_pcdf[, c("x_label", "y_label")] <- jamba::rbindList( - # polygon_list_labelr(venn_pcdf$venn_poly_coords)); - - # Port this function: sp_polylabelr(i) - # which calls polylabelr::poi(x, y) on each polygon + return(invisible(venn_poly_coords)); } -#' Intersect one or more polygons -#' -#' Intersect one or more polygons -#' -#' This function takes a `list` of polygons and iteratively -#' calls `polyclip::polyclip(A, B, op="intersect")` to produce the intersect -#' across one or more polygons, which otherwise only works with two -#' polygons. -#' -#' @return object `list` of polygons -#' -#' @family venndir polygons -#' -#' @param polygon_list `list` object that contains one or more polygons. -#' @param ... additional arguments are ignored. -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' -#' circle_intersect <- intersect_polygon_list(polygon_list); -#' jamba::ssdim(circle_intersect) -#' circle_colors <- colorjam::rainbowJam(2); -#' plot_polygon_list(polygon_list, col=circle_colors, main="intersect") -#' plot_polygon_list(circle_intersect, col="#FFDD0088", border="red", lwd=3, add=TRUE) -#' -#' @export -intersect_polygon_list <- function -(polygon_list, - new_name=NULL, - ...) -{ - # Purpose is to use polyclip::polyclip(A, B, op="intersect") - # on two or more polygons - if (all(c("x", "y") %in% names(polygon_list))) { - # convert xy_list to polygon_list - polygon_list <- xy_list_to_polygon_list(polygon_list); - } - if (length(polygon_list) <= 1) { - return(polygon_list); - } - output_polygon <- polygon_list[1]; - - for (i in 2:length(polygon_list)) { - output_polygon <- polyclip::polyclip( - A=output_polygon, - B=polygon_list[i], - op="intersect"); - } - if (length(new_name) == 1) { - names(output_polygon) <- new_name; - } else { - names(output_polygon) <- head(names(polygon_list), 1); - } - return(output_polygon); -} #' Intersect one or more JamPolygon objects #' @@ -756,443 +638,9 @@ minus_JamPolygon <- function } -#' Union one or more polygons -#' -#' Union one or more polygons -#' -#' This function takes a `list` of polygons and iteratively -#' calls `polyclip::polyclip(A, B, op="union")` to produce a union -#' across one or more polygons, which otherwise only works with two -#' polygons. -#' -#' @return object `list` of polygons -#' -#' @family venndir polygons -#' -#' @param polygon_list `list` object that contains one or more polygons. -#' @param ... additional arguments are ignored. -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' -#' circle_union <- union_polygon_list(polygon_list); -#' jamba::ssdim(circle_union) -#' circle_colors <- colorjam::rainbowJam(2); -#' plot_polygon_list(polygon_list, col=circle_colors, main="union") -#' plot_polygon_list(circle_union, col="#FFDD0088", border="red", lwd=3, add=TRUE) -#' -#' counts2 <- c(A=1, B=2, `A&B`=3, C=4) -#' x2 <- eulerr::euler(counts2) -#' polygon_list2 <- eulerr_to_polygon_list(x2) -#' plot_polygon_list(polygon_list2) -#' -#' @export -union_polygon_list <- function -(polygon_list, - ...) -{ - # Purpose is to use polyclip::polyclip(A, B, op="union") - # on two or more polygons - if (all(c("x", "y") %in% names(polygon_list))) { - # convert xy_list to polygon_list - polygon_list <- xy_list_to_polygon_list(polygon_list); - } - if (length(polygon_list) <= 1) { - return(polygon_list); - } - output_polygon <- polygon_list[1]; - - for (i in 2:length(polygon_list)) { - output_polygon <- polyclip::polyclip( - A=output_polygon, - B=polygon_list[i], - op="union"); - } - names(output_polygon) <- head(names(polygon_list), 1); - return(output_polygon); -} - - -#' Subtract one or more polygons -#' -#' Subtract one or more polygons -#' -#' This function takes a `list` of polygons and iteratively -#' calls `polyclip::polyclip(A, B, op="minus")` to produce a union -#' across one or more polygons, which otherwise only works with two -#' polygons. -#' -#' @return object `list` of polygons -#' -#' @family venndir polygons -#' -#' @param polygon_list `list` object that contains one or more polygons. -#' @param new_name `character` string with optional new name for the -#' output polygon. -#' @param ... additional arguments are ignored. -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3) -#' counts <- c(A=1, B=2, `A&B`=3, C=5, `B&C`=2, `A&C`=2, `A&B&C`=1) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' -#' circle_minus <- minus_polygon_list(polygon_list); -#' circle_colors <- colorjam::rainbowJam(length(polygon_list), alpha=0.5); -#' plot_polygon_list(polygon_list, col=circle_colors, main="minus") -#' plot_polygon_list(circle_minus, col="#FFDD0088", border="red", lwd=3, add=TRUE) -#' -#' circle_minus2 <- minus_polygon_list(polygon_list[c(2,1,3)]); -#' plot_polygon_list(circle_minus2, col="#FFDD0088", border="blue", lwd=3, add=TRUE) -#' @export -minus_polygon_list <- function -(polygon_list, - new_name=NULL, - ...) -{ - # Purpose is to use polyclip::polyclip(A, B, op="minus") - # on two or more polygons - if (all(c("x", "y") %in% names(polygon_list))) { - # convert xy_list to polygon_list - polygon_list <- xy_list_to_polygon_list(polygon_list); - } - if (length(polygon_list) <= 1) { - return(polygon_list); - } - output_polygon <- polygon_list[1]; - - for (i in 2:length(polygon_list)) { - output_polygon <- polyclip::polyclip( - A=output_polygon, - B=polygon_list[i], - op="minus"); - } - if (length(output_polygon) > 1) { - output_polygon <- list(output_polygon); - } - if (length(new_name) == 1) { - names(output_polygon) <- new_name; - } else { - names(output_polygon) <- head(names(polygon_list), 1); - } - return(output_polygon); -} - -#' Plot polygon_list using base R -#' -#' Plot polygon_list using base R -#' -#' @family venndir polygons -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3, C=5, `B&C`=2, `A&C`=2, `A&B&C`=1) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' plot_polygon_list(polygon_list, -#' col=colorjam::rainbowJam(length(polygon_list), alpha=0.5)) -#' -#' polygon_list2 <- list(A=polygon_list$A, BC=polygon_list[c("B", "C")]) -#' plot_polygon_list(polygon_list2, -#' col=colorjam::rainbowJam(length(polygon_list2), alpha=0.5)) -#' -#' @export -plot_polygon_list <- function -(polygon_list, - col=NULL, - border="black", - lwd=1, - add=FALSE, - asp=1, - bty="n", - xaxt="n", - yaxt="n", - xlab="", - ylab="", - xlim=NULL, - ylim=NULL, - rule=c("evenodd", "none"), - ...) -{ - # rule - rule <- match.arg(rule); - - # - if (all(c("x", "y") %in% names(polygon_list))) { - # input is xy_list format - xy_list <- polygon_list; - polygon_list <- xy_list_to_polygon_list(xy_list); - } else { - # input is polygon_list - xy_list <- polygon_list_to_xy_list(polygon_list); - } - if (FALSE %in% add) { - xy_ranges <- bbox_polygon_list(polygon_list); - if (length(xlim) == 0) { - xlim <- xy_ranges$x - } - if (length(ylim) == 0) { - ylim <- xy_ranges$y - } - plot(NULL, - xlim=xlim, - ylim=ylim, - asp=asp, - bty=bty, - xaxt=xaxt, - yaxt=yaxt, - xlab=xlab, - ylab=ylab, - ...) - } - if (length(col) >= 1) { - col <- rep(col, - length.out=length(polygon_list)); - } - if (length(border) >= 1) { - border <- rep(border, - length.out=length(polygon_list)); - } - for (i in seq_along(polygon_list)) { - if (is.list(polygon_list[[i]]) && - !all(c("x", "y") %in% names(polygon_list[[i]]))) { - # option 1: plot each polygon component independently - if ("none" %in% rule) { - jamba::printDebug("polygon_list[[i]] as nested polygon, rule='none':");print(polygon_list[[i]]); - plot_polygon_list( - polygon_list=polygon_list[[i]], - col=col[[i]], - border=border[[i]], - lwd=lwd, - add=TRUE, - ...) - } - # option 2: graphics::polypath(x, y, rule="evenodd") to allow holes - # - convert polygon_list to xy_list then to coord_list - if ("evenodd" %in% rule) { - if (length(polygon_list[[i]]) == 1) { - # single polygon, no need for fancy polypath() - coord_list <- list( - x=polygon_list[[i]][[1]]$x, - y=polygon_list[[i]][[1]]$y); - } else { - coord_list <- list( - x=head(unname(unlist( - lapply(polygon_list[[i]], function(i){c(i$x, NA)}))), -1), - y=head(unname(unlist( - lapply(polygon_list[[i]], function(i){c(i$y, NA)}))), -1)); - } - # use_xy_list <- polygon_list_to_xy_list(polygon_list[[i]]) - # coord_list <- xy_list_to_coord_list(use_xy_list) - # jamba::printDebug("coord_list:");print(coord_list);# debug - polypath(x=coord_list$x, - y=coord_list$y, - rule=rule, - col=col[[i]], - border=border[[i]], - lwd=lwd, - ...) - } - } else { - polygon( - x=polygon_list[[i]], - col=col[[i]], - border=border[[i]], - lwd=lwd, - ...) - } - } -} - - -#' Bounding box for polygon list -#' -#' Bounding box for polygon list -#' -#' @family venndir polygons -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3, C=5, `B&C`=2, `A&C`=2, `A&B&C`=1) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' bbox_polygon_list(polygon_list) -#' -#' @export -bbox_polygon_list <- function -(polygon_list, - ...) -{ - # - if (all(c("x", "y") %in% names(polygon_list))) { - # input is xy_list format - xy_list <- polygon_list; - polygon_list <- xy_list_to_polygon_list(xy_list); - } else { - # input is polygon_list - xy_list <- polygon_list_to_xy_list(polygon_list); - } - range_x <- range(unlist(xy_list$x), na.rm=TRUE); - range_y <- range(unlist(xy_list$y), na.rm=TRUE); - return(list(x=range_x, y=range_y)) -} - -#' Calculate polygon label positions using Pole of Inaccessibility -#' -#' Calculate polygon label positions using Pole of Inaccessibility, otherwise -#' known as the Visual Center. -#' -#' This function is a wrapper for `polylabelr::poi()` except that it -#' is applied to a `list` of polygons individually. -#' -#' When any one polygon is composed of two smaller polygon components, -#' as encoded with a nested list of coordinates, -#' first the polygons are combined using `union_polygon_list()`. -#' If the result is a single polygon, that is used to define the -#' label position. If the result is multiple separate polygon -#' components, the largest polygon component is used to find the label. -#' -#' @param polygon_list `list` containing elements `"x"` and `"y"` each -#' with `numeric` vectors, or `list` of `numeric` vectors. -#' @param add_labels `logical` indicating whether to plot the labels -#' using `text()` -#' @param ... additional arguments are passed to `text()` when -#' `add_labels=TRUE` -#' -#' @family venndir polygons -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3, C=5, `B&C`=2, `A&C`=2, `A&B&C`=1) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' -#' # default is to label each polygon in its center -#' plot_polygon_list(polygon_list, -#' col=colorjam::rainbowJam(length(polygon_list), alpha=0.5)) -#' labelr_polygon_list(polygon_list, add_labels=TRUE) -#' -#' # create unique polygons for each label -#' A_only <- minus_polygon_list(polygon_list, new_name="A_only"); -#' B_only <- minus_polygon_list(polygon_list[c(2,1,3)], new_name="B_only"); -#' C_only <- minus_polygon_list(polygon_list[c(3,1,2)], new_name="C_only"); -#' -#' plot_polygon_list(polygon_list, -#' col=colorjam::rainbowJam(length(polygon_list), alpha=0.5)) -#' ABC_only <- c(A_only, B_only, C_only); -#' polygon_list_labelr(ABC_only, add_labels=TRUE) -#' -#' # label ABC intersection -#' ABC_int <- intersect_polygon_list(polygon_list[c(1,2,3)], new_name="ABC"); -#' plot_polygon_list(ABC_int, add=TRUE, col="gold") -#' polygon_list_labelr(ABC_int, add_labels=TRUE) -#' -#' # label AB intersection -#' AB_only <- minus_polygon_list( -#' c(intersect_polygon_list(polygon_list[c(1,2)], new_name="BC_only"), -#' polygon_list[3])) -#' plot_polygon_list(AB_only, add=TRUE, col="darkviolet") -#' polygon_list_labelr(AB_only, add_labels=TRUE, col="white") -#' -#' # label BC intersection -#' BC_only <- minus_polygon_list( -#' c(intersect_polygon_list(polygon_list[c(2,3)], new_name="BC_only"), -#' polygon_list[1])) -#' plot_polygon_list(BC_only, add=TRUE, col="skyblue") -#' polygon_list_labelr(BC_only, add_labels=TRUE) -#' -#' @export -labelr_polygon_list <- function -(polygon_list, - add_labels=FALSE, - ...) -{ - # - if (all(c("x", "y") %in% names(polygon_list))) { - # input is xy_list format - xy_list <- polygon_list; - polygon_list <- xy_list_to_polygon_list(xy_list); - } else { - # input is polygon_list - xy_list <- polygon_list_to_xy_list(polygon_list); - } - - polygon_seq <- jamba::nameVector(seq_along(polygon_list), - names(polygon_list)); - xy_coords <- jamba::rbindList(lapply(polygon_seq, function(i){ - if (is.list(polygon_list[[i]]) && - !all(c("x", "y") %in% names(polygon_list[[i]]))) { - # jamba::printDebug("i: ", i, ", list(xy_list)") - union_poly <- union_polygon_list(polygon_list[[i]]) - if (length(union_poly) > 1) { - union_poly <- get_largest_polygon_list(union_poly_areas)[[1]]; - } - polylabelr::poi(union_poly) - } else { - # jamba::printDebug("i: ", i, ", xy_list") - polylabelr::poi(polygon_list[[i]]) - } - })) - if (TRUE %in% add_labels) { - text(x=xy_coords[, "x"], - y=xy_coords[, "y"], - labels=rownames(xy_coords), - ...) - } -} -#' Largest polygon in a polygon list -#' -#' Largest polygon in a polygon list -#' -#' This function returns the largest polygon in a polygon list, -#' intended when there are multiple polygons contained in one object. -#' -#' If two polygons have identical area, the first -#' polygon is returned. -#' -#' ## Todo: -#' -#' * Verify correct output when polygon(s) have holes. -#' -#' @family venndir polygons -#' -#' @returns `list` with polygon coordinates `"x"` and `"y"` -#' -#' @param polygon_list `list` with `"x"` and `"y"` elements with -#' polygon coordinates. -#' @param ... additional arguments are ignored. -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3, C=4) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' largest_poly <- get_largest_polygon_list(polygon_list) -#' plot_polygon_list(polygon_list, col=colorjam::rainbowJam(3, alpha=0.5)) -#' plot_polygon_list(largest_poly, add=TRUE, border="red", lwd=3) -#' -#' -#' @export -get_largest_polygon_list <- function -(polygon_list, - ...) -{ - # - if (all(c("x", "y") %in% names(polygon_list))) { - # input is xy_list format - xy_list <- polygon_list; - polygon_list <- xy_list_to_polygon_list(xy_list); - } else { - # input is polygon_list - xy_list <- polygon_list_to_xy_list(polygon_list); - } - - # Subset multi-polygon entries to use the largest polygon - poly_areas <- polygon_areas(polygon_list, simplify=TRUE) - polygon_list <- polygon_list[which.max(poly_areas)] - return(polygon_list); -} #' Make polygon_list circles @@ -1201,9 +649,9 @@ get_largest_polygon_list <- function #' #' This function creates one or more circles as polygon_list `list` objects. #' -#' @family venndir polygons +#' @family JamPolygon #' -#' @return object `list` with a number of circles encoded as polygons. +#' @returns `JamPolygon` object #' #' @param xcenter,ycenter `numeric` vector that defines the x and y #' coordinate position of the center of each circle. @@ -1217,9 +665,8 @@ get_largest_polygon_list <- function #' @param ... additional arguments are ignored. #' #' @examples -#' polygon_list <- polygon_circles(c(3, 2), c(2, 3)) -#' plot_polygon_list(polygon_list) -#' points(x=c(3, 2), y=c(2, 3), pch=c("1", "2"), add=TRUE); +#' circle_jp <- polygon_circles(c(3, 2), c(2, 3)) +#' plot(circle_jp, fill=c("red", "gold")) #' #' @export polygon_circles <- function @@ -1253,7 +700,12 @@ polygon_circles <- function x=xvals * radius[i] + xcenter[i], y=yvals * radius[i] + ycenter[i]) }) - return(polygon_list); + cjp <- rbind2.JamPolygon(lapply(polygon_list, function(i){ + polyclip_to_JamPolygon(A=list(i), ...) + })) + names(cjp) <- setnames; + rownames(cjp@polygons) <- setnames; + return(cjp); } @@ -1264,9 +716,9 @@ polygon_circles <- function #' #' This function creates one or more ellipses as polygon_list `list` objects. #' -#' @family venndir polygons +#' @family JamPolygon #' -#' @return object `list` with a number of circles encoded as polygons. +#' @returns `JamPolygon` object #' #' @param xcenter,ycenter `numeric` vector that defines the x and y #' coordinate position of the center of each ellipse. @@ -1284,11 +736,10 @@ polygon_circles <- function #' @param ... additional arguments are ignored. #' #' @examples -#' polygon_list <- polygon_ellipses(c(3, 2), c(2, 3), +#' ejp <- polygon_ellipses(c(3, 2), c(2, 3), #' xradius=c(1, 4), #' yradius=c(5, 2)) -#' plot_polygon_list(polygon_list, col=c("#FF000077", "#FFDD0077")); -#' points(x=c(3, 2), y=c(2, 3), pch=c("1", "2"), add=TRUE); +#' plot(ejp, fill=c("#FF000077", "#FFDD0077")) #' #' @export polygon_ellipses <- function @@ -1334,421 +785,136 @@ polygon_ellipses <- function polygon_list <- lapply(x_seq, function(i){ i_xvals <- (xvals * xradius[i]); i_yvals <- (yvals * yradius[i]); - e_xvals <- (i_xvals * cos(rotation_rad[i]) + i_yvals * sin(rotation_rad[i])); - e_yvals <- (i_yvals * cos(rotation_rad[i]) - i_xvals * sin(rotation_rad[i])); + e_xvals <- (i_xvals * cos(rotation_rad[i]) + + i_yvals * sin(rotation_rad[i])); + e_yvals <- (i_yvals * cos(rotation_rad[i]) - + i_xvals * sin(rotation_rad[i])); list( x=e_xvals + xcenter[i], y=e_yvals + ycenter[i]) }) - return(polygon_list); + cjp <- rbind2.JamPolygon(lapply(polygon_list, function(i){ + polyclip_to_JamPolygon(A=list(i), ...) + })) + names(cjp) <- setnames; + rownames(cjp@polygons) <- setnames; + return(cjp); } -#' Nudge polygon_list +#' Nudge JamPolygon coordinates #' -#' Nudge polygon_list +#' Nudge JamPolygon coordinates #' -#' This helper function is intended to take `list` polygon_list coordinates -#' and "nudge" (move by adding a scalar value to each coordinate) -#' only a subset of polygons identified by name. -#' -#' @family venndir polygons +#' Polygon coordinates within a `JamPolygon` object are nudged by name +#' or polygon number, such that all parts of each polygon are adjusted +#' together. For multi-part polygons, and/or polygons with internal holes, +#' all parts are moved the identical amount. #' -#' @return object `list` polygon_list object with `"x"` and `"y"` elements. +#' @family JamPolygon #' -#' @param polygon_list `list` object with `"x"` and `"y"` elements. -#' @param nudge `list` whose names are found in `names(polygon_list)`, -#' and whose values are `x` and `y` coordinates to be moved. -#' @param rotate_degrees `numeric` value in degrees (0, 360) to -#' rotate the `polygon_list` object and all contained polygons. -#' (Not yet implemented.) -#' @param ... additional arguments are ignored. +#' @param jp `JamPolygon` object +#' @param nudge `list` whose names match `names(jp)`, containing `numeric` +#' vector with names `"x"` and `"y"`. For example: +#' `nudge=list(polyname1=c(x=1, y=0))` +#' @param ... additional arguments are ignored #' #' @examples -#' D <- list( -#' x=c(-3, 3, 3, 0, -3), -#' y=c(-3, -3, 1.5, 4, 1.5)) -#' E <- list( -#' x=c(-3, 3, 3, -3), -#' y=c(-3, -3, 3, 3)) -#' DElist <- list(D=D, E=E, DE=list(D=D, E=E)) -#' nudge <- list(D=c(x=0, y=10), E=c(x=0, y=-10), DE=c(x=10, y=0)) -#' new_polygon_list <- nudge_polygon_list(polygon_list=DElist, -#' nudge=nudge) -#' poly_colors <- colorjam::rainbowJam(3, alpha=0.5); -#' plot_polygon_list(DElist, col=poly_colors) -#' plot_polygon_list(new_polygon_list, col=poly_colors) -#' -#' polygon_list <- polygon_ellipses(c(3, 2), c(2, 3), -#' xradius=c(1, 4), -#' yradius=c(5, 2)) -#' plot_polygon_list(polygon_list, -#' col=c("#FF000077", "#FFDD0000"), -#' xlim=c(-2, 9)); -#' polygon_list2 <- nudge_polygon_list(polygon_list, -#' nudge=list(`2`=c(x=3, y=-2)) -#' ) -#' plot_polygon_list(polygon_list2, -#' col=c("#FF000077", "#FFDD0077"), -#' add=TRUE, -#' xlim=c(-2, 9)); -#' -#' plot_polygon_list(polygon_list[2], border="blue", lty="dotted", lwd=3, add=TRUE); -#' plot_polygon_list(polygon_list2[2], border="blue", lty="dotted", lwd=3, add=TRUE); -#' arrows(x0=2, x1=5, y0=3, y1=1) +#' DEdf <- data.frame(check.names=FALSE, +#' name=c("D", "E"), +#' x=I(list( +#' c(-3, 3, 3, 0, -3), +#' c(-4, 2, 2, -4))), +#' y=I(list( +#' c(-3, -3, 1.5, 4, 1.5), +#' c(-2, -2, 4, 4))), +#' fill=c("#FFD70055", "#B2222255")) +#' DEjp <- new("JamPolygon", polygons=DEdf) +#' plot(DEjp) +#' nudge <- list(D=c(7, 1), E=c(-1, -1)); +#' DEjp_nudged <- nudge_JamPolygon(DEjp, nudge=nudge) +#' plot(DEjp_nudged) +#' +#' plot(rbind2(DEjp, DEjp_nudged), +#' fill=c("#FFD70055", "#B2222255", "gold", "firebrick"), +#' label=c("D_old", "E_old", "D_new", "E_new"), +#' border.lty=c(2, 2, 1, 1)) #' #' @export -nudge_polygon_list <- function -(polygon_list=NULL, +nudge_JamPolygon <- function +(jp, nudge=NULL, + verbose=FALSE, ...) { # - if (length(polygon_list) == 0) { - return(polygon_list); - } - if (all(c("x", "y") %in% names(polygon_list) && length(polygon_list) == 2)) { - # input is xy_list format - xy_list <- polygon_list; - polygon_list <- xy_list_to_polygon_list(xy_list); - } else { - # input is polygon_list - xy_list <- polygon_list_to_xy_list(polygon_list); - } - - # Optionally nudge the polygon coordinates - polygon_names <- names(polygon_list); - - ## shift by coordinates - if (length(nudge) > 0 && - is.list(nudge) && - any(names(nudge) %in% polygon_names)) { - use_nudge <- nudge[names(nudge) %in% polygon_names]; - for (i in seq_along(use_nudge)) { - iname <- names(use_nudge)[i]; - j <- match(iname, polygon_names); - i_nudge <- nudge[[i]]; - polygon_list[[j]] <- nudge_polygon_coords( - polygon=polygon_list[[j]], - nudge=nudge[[i]]) - } + if (length(jp) == 0) { + return(jp) } - - return(invisible(polygon_list)); -} - -#' Nudge polygon coordinates -#' -#' Nudge polygon coordinates -#' -#' This function differs from `nudge_polygon_list()` in that all polygons -#' are nudged the exact same amount. If there are nested polygons, they -#' are iteratively all nudged the same. -#' -#' @family venndir polygons -#' -#' @examples -#' D <- list( -#' x=c(-3, 3, 3, 0, -3), -#' y=c(-3, -3, 1.5, 4, 1.5)) -#' E <- list( -#' x=c(-3, 3, 3, -3), -#' y=c(-3, -3, 3, 3)) -#' DElist <- list(D=D, E=E, DE=list(D=D, E=E)) -#' nudge <- c(x=10, y=-10) -#' new_polygon_list <- nudge_polygon_coords(polygon_list=DElist, nudge=nudge) -#' plot_polygon_list(new_polygon_list) -#' -#' @export -nudge_polygon_coords <- function -(polygon_list, - nudge, - ...) -{ - # - if (length(nudge) == 1) { - nudge <- unname(rep(nudge, length.out=2)) + if (length(nudge) == 0) { + return(jp) } if (length(names(nudge)) == 0) { - names(nudge) <- c("x", "y") - } - if (is.list(polygon_list) && - all(c("x", "y") %in% names(polygon_list))) { - # simple list with "x","y" - polygon_list$x <- polygon_list$x + nudge["x"]; - polygon_list$y <- polygon_list$y + nudge["y"]; + stop("There must be names(nudge).") + } + if (length(names(nudge)) == 0 && !any(names(nudge) %in% names(jp))) { + # check for numeric names + nudge_names <- as.integer(names(nudge)); + use_nudge <- (!is.na(nudge_names) & + nudge_names == as.numeric(names(nudge)) & + nudge_names %in% seq_along(jp)) + if (!all(use_nudge)) { + stop("names(nudge) must match names(jp) or seq_along(jp)") + } + nudge_names <- names(jp)[nudge_names] } else { - # nested list - polygon_list <- lapply(polygon_list, function(ipolygon_list){ - nudge_polygon_coords(polygon_list=ipolygon_list, - nudge=nudge, - ...) - }) + nudge_names <- intersect(names(nudge), names(jp)) } - return(polygon_list); -} - - -#' Rescale a polygon_list object -#' -#' Rescale a polygon_list object -#' -#' This function simply applies `rescale_coordinates()` to an -#' `list` polygon_list object. -#' -#' @family venndir polygons -#' -#' @return object `list` polygon_list -#' -#' @inheritParams rescale_coordinates -#' -#' @param polygon_list `list` object -#' @param share_center `logical` indicating whether all polygons -#' should share the same center, where `share_center=TRUE` will -#' adjust everything collectively, and `share_center=FALSE` will -#' adjust each polygon independently relative to its own center -#' coordinate. -#' -#' @examples -#' polygon_list <- polygon_ellipses(c(3, 2), c(2, 3), -#' xradius=c(1, 4), -#' yradius=c(5, 2)) -#' polygon_list1 <- intersect_polygon_list(polygon_list); -#' polygon_list2 <- minus_polygon_list(polygon_list[1:2]); -#' polygon_list3 <- minus_polygon_list(polygon_list[2:1]); -#' polygon_list123 <- c(polygon_list1, -#' polygon_list2, -#' polygon_list3); -#' -#' polygon_list123a <- rescale_polygon_list(polygon_list123, -#' scale=c(1.5, 1.5), -#' share_center=TRUE); -#' polygon_list123b <- rescale_polygon_list(polygon_list123, -#' scale=c(1.5, 1.5)); -#' col3 <- c("#FF000077", "#FFDD0077", "#0000DD77"); -#' par("mfrow"=c(2, 2)); -#' plot_polygon_list(polygon_list123, -#' col=col3, -#' main="original polygons", -#' xlim=c(-10, 15), ylim=c(-5, 10)); -#' axis(1, las=2); axis(2, las=2); -#' plot_polygon_list(polygon_list123a, -#' col=col3, -#' main="share_center=TRUE", -#' xlim=c(-10, 15), ylim=c(-5, 10)); -#' axis(1, las=2); axis(2, las=2); -#' plot_polygon_list(polygon_list123[1:2], -#' col=col3[1:2], -#' main="share_center=FALSE\nrescaling only the blue polygon", -#' xlim=c(-10, 15), ylim=c(-5, 10)); -#' axis(1, las=2); axis(2, las=2); -#' plot_polygon_list(polygon_list123b[3], -#' col=col3[3], -#' add=TRUE); -#' plot_polygon_list(polygon_list123[2:3], -#' col=col3[2:3], -#' main="share_center=FALSE\nrescaling only the red polygon", -#' xlim=c(-10, 15), ylim=c(-5, 10)); -#' axis(1, las=2); axis(2, las=2); -#' plot_polygon_list(polygon_list123b[1], -#' col=col3[1], -#' add=TRUE); -#' par("mfrow"=c(1, 1)); -#' -#' {par("mfrow"=c(2, 2)); -#' plot_polygon_list(polygon_list123, col=col3, -#' xlim=c(-4, 8), ylim=c(-4, 8)) -#' title(main="Original polygons", line=0); -#' plot_polygon_list(rescale_polygon_list(polygon_list123, rotate_degrees=c(`11`=45, `12`=-10)), col=col3, -#' xlim=c(-4, 8), ylim=c(-4, 8)) -#' title(sub="yellow +45 degrees\nblue -10 degrees", line=0, -#' main="share_polygon_center=TRUE (default)") -#' plot_polygon_list(rescale_polygon_list(polygon_list123, rotate_degrees=c(`11`=45, `12`=-10), share_polygon_center=FALSE), col=col3, -#' xlim=c(-4, 8), ylim=c(-4, 8)) -#' title(sub="yellow +45 degrees\nblue -10 degrees", line=0, -#' main="share_polygon_center=FALSE\n(each polygon uses its center)") -#' plot_polygon_list(rescale_polygon_list(polygon_list123, rotate_degrees=c(`11`=45, `12`=-10), share_center=TRUE), col=col3, -#' xlim=c(-4, 8), ylim=c(-4, 8)) -#' title(sub="yellow +45 degrees\nblue -10 degrees", line=0, -#' main="share_center=TRUE\n(all polygons share one global center)") -#' par("mfrow"=c(1, 1));} -#' -#' -#' @export -rescale_polygon_list <- function -(polygon_list, - rotate_degrees=0, - scale=c(1, 1), - shift=c(0, 0), - center=NULL, - share_center=FALSE, - share_polygon_center=TRUE, - ...) -{ - ## SpatialPolygons - if (length(center) == 0) { - if (share_center) { - center <- sapply(bbox_polygon_list(polygon_list), mean); - center <- rep(list(center), - length.out=length(polygon_list)) - names(center) <- names(polygon_list); - } else if (share_polygon_center) { - center <- lapply(polygon_list, function(i){ - sapply(bbox_polygon_list(i), mean) + + # custom function to apply nudge to nested numeric list + apply_nudge <- function(i, offset) { + if (is.list(i)) { + lapply(i, function(j){ + apply_nudge(j, offset) }) - share_center <- TRUE; + } else { + i + offset } } - if (is.atomic(center)) { - center <- rep(list(center), - length.out=length(polygon_list)) - names(center) <- names(polygon_list); - } - if (is.atomic(scale)) { - scale <- rep(list(scale), - length.out=length(polygon_list)) - names(scale) <- names(polygon_list); - } - if (is.atomic(shift)) { - shift <- rep(list(shift), - length.out=length(polygon_list)) - names(shift) <- names(polygon_list); - } - if (is.atomic(rotate_degrees)) { - rotate_degrees <- rep(rotate_degrees, - length.out=length(polygon_list)) - names(rotate_degrees) <- names(polygon_list); - } - - poly_seq <- jamba::nameVector(seq_along(polygon_list), - names(polygon_list)); - polygon_list <- lapply(poly_seq, function(i){ - if (is.list(polygon_list[[i]]) && - all(c("x", "y") %in% names(polygon_list[[i]]))) { - xym <- rescale_coordinates(x=do.call(cbind, polygon_list[[i]]), - scale=scale[[i]], - rotate_degrees=rotate_degrees[[i]], - shift=shift[[i]], - center=center[[i]], - ...) - list(x=xym[, "x"], - y=xym[, "y"]) + for (nudge_name in nudge_names) { + n <- match(nudge_name, names(jp)); + if (all(c("x", "y") %in% names(nudge[[nudge_name]]))) { + nudge_x <- nudge[[nudge_name]][["x"]]; + nudge_y <- nudge[[nudge_name]][["y"]]; } else { - rescale_polygon_list(polygon_list=polygon_list[[i]], - scale=scale[[i]], - rotate_degrees=rotate_degrees[[i]], - shift=shift[[i]], - center=center[[i]], - ...) + nudge_x <- nudge[[nudge_name]][[1]]; + nudge_y <- nudge[[nudge_name]][[2]]; } - }) - - return(polygon_list); -} - - -#' Simple wrapper to polylabelr::poi() for polygon_list -#' -#' @family venndir polygons -#' -#' @returns `matrix` with nrow `length(polygon_list)` with x,y coordinates -#' representing the visual center of each polygon in the list. -#' -#' @param polygon_list `list` object -#' -#' @examples -#' counts <- c(A=1, B=2, `A&B`=3, C=5, `B&C`=2, `A&C`=2, `A&B&C`=1) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' -#' # default is to label each polygon in its center -#' plot_polygon_list(polygon_list, -#' col=colorjam::rainbowJam(length(polygon_list), alpha=0.5)) -#' polygon_list_labelr(polygon_list, add_labels=TRUE) -#' -#' # create unique polygons for each label -#' A_only <- minus_polygon_list(polygon_list, new_name="A_only"); -#' B_only <- minus_polygon_list(polygon_list[c(2,1,3)], new_name="B_only"); -#' C_only <- minus_polygon_list(polygon_list[c(3,1,2)], new_name="C_only"); -#' -#' plot_polygon_list(polygon_list, -#' col=colorjam::rainbowJam(length(polygon_list), alpha=0.5)) -#' ABC_only <- c(A_only, B_only, C_only); -#' polygon_list_labelr(ABC_only, add_labels=TRUE) -#' -#' # label ABC intersection -#' ABC_int <- intersect_polygon_list(polygon_list[c(1,2,3)], new_name="ABC"); -#' plot_polygon_list(ABC_int, add=TRUE, col="gold") -#' polygon_list_labelr(ABC_int, add_labels=TRUE) -#' -#' # label AB intersection -#' AB_only <- minus_polygon_list( -#' c(intersect_polygon_list(polygon_list[c(1,2)], new_name="BC_only"), -#' polygon_list[3])) -#' plot_polygon_list(AB_only, add=TRUE, col="darkviolet") -#' polygon_list_labelr(AB_only, add_labels=TRUE, col="white") -#' -#' # label BC intersection -#' BC_only <- minus_polygon_list( -#' c(intersect_polygon_list(polygon_list[c(2,3)], new_name="BC_only"), -#' polygon_list[1])) -#' plot_polygon_list(BC_only, add=TRUE, col="skyblue") -#' polygon_list_labelr(BC_only, add_labels=TRUE) -#' -#' # test with fully overlapping polygon (to create a hole) -#' counts <- c(A=5, B=0, C=3, `A&B`=1) -#' x <- eulerr::euler(counts) -#' polygon_list <- eulerr_to_polygon_list(x) -#' plot_polygon_list(polygon_list[1:3], col=c("red")) -#' A_only <- minus_polygon_list(polygon_list[c(1, 2, 3)], new_name="A_only"); -#' plot_polygon_list(A_only, col="gold", add=TRUE) -#' polygon_list_labelr(A_only, add_labels=TRUE) -#' -#' polygon_list_labelr(c(A_only, polygon_list[2:3]), add_labels=TRUE) -#' @export -polygon_list_labelr <- function -(polygon_list, - precision=1, - add_labels=FALSE, - ...) -{ - # validate input - if (all(c("x", "y") %in% names(polygon_list))) { - # input is xy_list format - xy_list <- polygon_list; - polygon_list <- xy_list_to_polygon_list(xy_list); - } else { - # input is polygon_list - xy_list <- polygon_list_to_xy_list(polygon_list); - } - - # iterate each polygon - label_xy_list <- lapply(polygon_list, function(ixy){ - if (is.list(ixy) && !all(c("x", "y") %in% names(ixy))) { - ixy <- get_largest_polygon_list(ixy)[[1]]; + if (verbose) { + jamba::printDebug("nudge_JamPolygon(): ", + "applying nudge (", c(nudge_x, nudge_y), ") ", + "to '", nudge_name, "'"); + } + if (!all(nudge_x %in% c(NA, 0))) { + old_x <- jp@polygons$x[n]; + new_x <- apply_nudge(jp[nudge_name, ]@polygons$x, offset=nudge_x) + jp@polygons$x[n] <- new_x; + } else { + new_x <- jp[nudge_name, ]@polygons$x; + } + if (!all(nudge_y %in% c(NA, 0))) { + old_y <- jp@polygons$y[n]; + new_y <- apply_nudge(jp[nudge_name, ]@polygons$y, offset=nudge_y) + jp@polygons$y[n] <- new_y; + } else { + new_y <- jp[nudge_name, ]@polygons$y; } - ixy <- do.call(cbind, ixy); - # Todo: fallback plan using mean x- and y-ranges? - polylabelr::poi(ixy, - precision=precision) - }) - # assemble into a matrix - label_xy_dist <- jamba::rbindList(label_xy_list, - newColnames=c("x", "y", "dist")) - xy_coords <- label_xy_dist[, c("x", "y"), drop=FALSE]; - - # optionally plot labels - if (TRUE %in% add_labels) { - text(x=xy_coords[, "x"], - y=xy_coords[, "y"], - labels=rownames(xy_coords), - ...) } - - - return(xy_coords); + return(jp); } + + #' Define label positions for JamPolygon using polylabelr::poi() #' #' Define label positions for JamPolygon using polylabelr::poi() diff --git a/R/venndir-polygon-areas.R b/R/venndir-polygon-areas.R deleted file mode 100644 index d6feb72..0000000 --- a/R/venndir-polygon-areas.R +++ /dev/null @@ -1,126 +0,0 @@ - - -#' Polygon area for simple or list of polygons -#' -#' Polygon area for simple or list of polygons -#' -#' @param x `numeric` input in one of the following formats: -#' * `numeric` vector of coordinates for single polygon input, which -#' also requires `y` is supplied as `numeric` vector with equal length. -#' * `list` of `numeric` vectors representing multiple polygons, -#' which also requires `y` is supplied as equivalent `list`. -#' * `list` of polygons, each polygon contains elements `"x"` and `"y"`. -#' * `list` of polygons, each polygon contains a `list` of polygon -#' component parts which each contain elements `"x"` and `"y"`. -#' @param y `numeric` vector or `list` of numeric vectors, compatible -#' with `x`, or `NULL` when `x` contains both coordinates. -#' @param simplify `logical` indicating whether area should be summed -#' for each polygon, potentially containing nested component polygons. -#' * `simplify=TRUE` returns `numeric` vector with one total area -#' per polygon. -#' * `simplify=FALSE` returns a `list` of `numeric` areas, using nested -#' list to indicate component polygons. -#' * Note that this step does not manipulate the polygons in any way, -#' for example it does not call union over component polygons, therefore -#' the component polygons may overlap. -#' @param verbose `logical` indicating whether to print verbose output. -#' @param ... additional arguments are ignored. -#' -#' @family venndir polygons -#' -#' @returns `numeric` vector with polygon area for each individual polygon -#' in the input `x`,`y`. -#' * When `x` is a `list` that contains `"x"` and `"y"` elements, those -#' elements are used. -#' * When `x` and `y` both contain a `list` of `numeric` vectors, each -#' vector is considered coordinates of a polygon, and the area is returned -#' for each polygon. -#' * When `x` and `y` are `numeric` vectors, it is considered a single -#' polygon, and thus one area is returned. -#' -#' @examples -#' D <- list( -#' x=c(-3, 3, 3, 0, -3), -#' y=c(-3, -3, 1.5, 4, 1.5)) -#' polygon_areas(D) -#' -#' E <- list( -#' x=c(-3, 3, 3, -3), -#' y=c(-3, -3, 3, 3)) -#' polygon_areas(E) -#' -#' DElist <- list( -#' x=list( -#' D=c(-3, 3, 3, 0, -3), -#' E=c(-3, 3, 3, -3)), -#' y=list( -#' D=c(-3, -3, 1.5, 4, 1.5), -#' E=c(-3, -3, 3, 3))) -#' polygon_areas(DElist) -#' -#' # list of polygons -#' poly_list <- list(D=D, E=E) -#' polygon_areas(poly_list) -#' -#' # list of nested polygons -#' polygon_areas(list(DE=poly_list, D=D, E=E)) -#' -#' polygon_areas(list(DE=poly_list, D=D, E=E), simplify=TRUE) -#' -#' @export -polygon_areas <- function -(x, - y=NULL, - simplify=FALSE, - verbose=FALSE, - ...) -{ - # simple wrapper around pracma::polyarea() - if (is.list(x) && length(y) == 0) { - if (all(c("x", "y") %in% names(x))) { - if (verbose) { - jamba::printDebug("polygon_areas(): ", - "using \"x\" and \"y\" from input list ", "x") - } - y <- x[["y"]]; - x <- x[["x"]]; - } else { - if (verbose) { - jamba::printDebug("polygon_areas(): ", - "splitting list ", "x ", - "into component lists of \"x\" and \"y\"") - } - xy_list <- polygon_list_to_xy_list(x); - x <- xy_list$x; - y <- xy_list$y; - } - } - if (is.atomic(x)) { - if (length(y) == 0) { - stop("x is atomic, y is empty. y must also be supplied.") - } - if (!is.atomic(y)) { - stop("x is atomic, y is not atomic. y must also be atomic.") - } - parea <- abs(pracma::polyarea( - x=x, - y=y)) - return(parea); - } - pareas <- lapply(seq_along(x), function(i){ - if (is.list(x[[i]])) { - polygon_areas(x=x[[i]], - y=y[[i]], - simplify=simplify) - } else { - abs(pracma::polyarea( - x=x[[i]], - y=y[[i]])) - } - }) - names(pareas) <- names(x); - if (TRUE %in% simplify) { - pareas <- sapply(pareas, sum) - } - return(pareas) -} diff --git a/R/venndir-render-jp.R b/R/venndir-render-jp.R index 1e9bb95..13640d6 100644 --- a/R/venndir-render-jp.R +++ b/R/venndir-render-jp.R @@ -155,7 +155,12 @@ render_venndir <- function # jamba::printDebug("show_items: ", show_items);# debug # show_items <- head(show_items, 1); item_style <- match.arg(item_style); - + + # validate other args + if (length(expand_fraction) == 0) { + expand_fraction <- 0; + } + # Apply label_style # - only if label_style is something other than "custom" # OR @@ -491,6 +496,8 @@ render_venndir <- function sc2 <- gsub("^$", "#00000000", jamba::rmNA(sc1)); sc2a <- jamba::col2alpha(sc2); sc2 <- sc2[sc2a > 0]; + sc2 <- jamba::alpha2col(alpha=(1 + jamba::col2alpha(sc2))/2, + sc2); head(sc2, 1) }); segment_df <- data.frame( @@ -501,8 +508,8 @@ render_venndir <- function group=rep(venn_jp@polygons$label[test_xy$sp_index[has_segment]], each=2), color=rep(seg_colors, each=2), lwd=rep(jamba::rmNULL( - venn_jp@polygons$border.lwd[test_xy$sp_index[has_segment]], - nullValue=1), each=2), + venn_jp@polygons$innerborder.lwd[test_xy$sp_index[has_segment]], + nullValue=2), each=2), point_order=c(1, 2) ); # jamba::printDebug("segment_df:");print(segment_df);# debug @@ -793,12 +800,18 @@ render_venndir <- function gdf$final_fill <- colorjam::blend_colors(todo_color_list); # adjust label color to contrast with the polygon fill color - new_label_col <- make_color_contrast(x=gdf$label_col, - L_threshold=63, - y=gdf$final_fill) - # y=omatch_fill) + if (TRUE) { + # assume signed labels were already adjusted, but not main labels + # Todo: adjust them all, consistently, in venndir_label_style() + new_label_col <- ifelse(gdf$type %in% "main", + make_color_contrast(x=gdf$label_col, + # L_threshold=63, + y=gdf$final_fill, + ...), + gdf$label_col); + gdf$label_col <- new_label_col; + } ## update all labels - gdf$label_col <- new_label_col; # jamba::printDebug("gdf:");print(gdf);# debug } @@ -885,6 +898,9 @@ render_venndir <- function gp=grid::gpar( col=itemlabels_df$color, fontsize=itemlabels_df$fontsize), + r=grid::unit(c(0, 0, 0, 0), "pt"), + padding=grid::unit(c(0, 0, 0, 0), "pt"), + margin=grid::unit(c(0, 0, 0, 0), "pt"), vp=jp_viewport, hjust=0.5, vjust=0.5); @@ -930,7 +946,10 @@ render_venndir <- function ## Push viewport in case that helps grob size estimates # grid::pushViewport(jp_viewport); g_labels_list <- lapply(gdf_list, function(igdf){ - # jamba::printDebug("igdf");print(igdf);# debug + ## 0.0.39.900 - fix for inconsistent whitespace width + ## - seems to occur only with ": " and on certain output devices + igdf$text <- gsub(": ", ":", igdf$text); + # jamba::printDebug("igdf$text");print(igdf$text);# debug g_labels <- gridtext::richtext_grob( text=igdf$text, x=adjx(igdf$x), diff --git a/R/venndir-shapes.R b/R/venndir-shapes.R index 3b5fce3..22f894e 100644 --- a/R/venndir-shapes.R +++ b/R/venndir-shapes.R @@ -1,126 +1,4 @@ -#' Get Venn shapes -#' -#' Get Venn shapes -#' -#' This function takes a Venn overlap counts and creates -#' corresponding circles or ellipses that represent -#' either a Venn diagram, or proportional Venn (Euler) -#' diagram. -#' -#' For non-proportional Venn diagrams, this function accepts -#' up to 5 sets, although the 5-way Venn diagram is not -#' visually intuitive. -#' -#' For proportional Euler diagrams, this function simply passes -#' the count vector to `eulerr::euler()` and returns the output. -#' That function accepts more sets, however not all overlaps may -#' be represented in the output. -#' -#' @family venndir utility -#' -#' @param counts `integer` vector whose names represent set overlaps, -#' where set names are separated by `sep` delimiter. -#' @param proportional `logical` indicating whether to create proportional -#' circles, where `proportional=FALSE` creates standard Venn diagram, -#' and `proportional=TRUE` creates a Euler diagram. -#' @param sep `character` delimiter used to separate set names in -#' `names(counts)`. -#' @param circles_only `logical` indicating whether to force Venn -#' 4-way diagram to use only circles; or passed to `eulerr::euler()` -#' to force it to return circles instead of allowing ellipse shapes. -#' @param circle_nudge `list` of `numeric` vectors each length 2, whose -#' names match set names derived from `counts`. For example if -#' `counts=c(set_A=5, set_B=10, "setA&set_B"=3)`, then to nudge -#' the `set_A` circle, use `circle_nudge=list(set_A=c(1, 0))`. -#' This argument is intended to allow manipulation of specific -#' circle or ellipse positions for aesthetic effects. Particularly -#' for proportional Euler diagrams, sometimes the algorithm places -#' circles in non-ideal locations -#' @param rotate_degrees `numeric` value indicating rotation in degrees -#' for the entire set of shapes. This argument is intended to -#' change the overall orientation, for example so that certain -#' sets are at the top. -#' @param ... additional arguments are ignored. -#' -#' @export -get_venn_shapes <- function -(counts, - proportional=FALSE, - sep="&", - circles_only=FALSE, - circle_nudge=NULL, - rotate_degrees=0, - ...) -{ - # - setnames <- unique(unlist(strsplit(names(counts), - fixed=TRUE, - split=sep))); - n <- length(setnames); - - if (!proportional) { - if (n < 1 || n > 5) { - stop("get_venn_shapes() for non-proportional Venn circles requires 1, 2, 3, 4, or 5 sets."); - } - if (n == 1) { - xcenter <- c(5); - ycenter <- c(5); - radius <- c(2); - venn_polygon_list <- polygon_circles(xcenter, ycenter, setnames, radius); - venn_sp <- sp_circles(xcenter, ycenter, setnames, radius); - } else if (n == 2) { - xcenter <- c(4, 6); - ycenter <- c(5, 5); - radius <- c(2, 2); - venn_sp <- sp_circles(xcenter, ycenter, setnames, radius); - } else if (n == 3) { - xcenter <- c(4, 6, 5); - ycenter <- c(6, 6, 4); - radius <- c(2, 2, 2); - venn_sp <- sp_circles(xcenter, ycenter, setnames, radius); - } else if (n == 4 && circles_only) { - #symbols(x=c(4, 5.5, 4, 5.5), y = c(6, 6, 4.5, 4.5), circles=c(2, 2, 2, 2), - xcenter <- c(4, 5.5, 4, 5.5); - ycenter <- c(6, 6, 4.5, 4.5); - radius <- c(2, 2, 2, 2); - venn_sp <- sp_circles(xcenter, ycenter, setnames, radius); - } else if (n == 4) { - xcenter <- c(3.4, 4.95+0.035, 5.30-0.035, 6.85); - ycenter <- c(3.6, 4.5, 4.5, 3.6); - xradius <- c(2, 2, 2, 2); - yradius <- c(4, 4, 4, 4); - rotation_degrees <- 39.2 * c(-1, -1, 1, 1); - venn_sp <- sp_ellipses(xcenter, ycenter, setnames, xradius, yradius, - rotation_degrees); - } else if (n == 5) { - xcenter <- c(4.83, 6.25, 6.10, 4.48, 3.70); - ycenter <- c(6.20, 5.40, 3.50, 3.15, 4.80); - xradius <- c(1.43, 1.7, 1.55, 1.55, 1.7); - yradius <- c(4.11, 3.6, 3.9, 3.92, 3.6); - rotation_degrees <- c(0, 66, 150, 210, 293.5); - venn_sp <- sp_ellipses(xcenter, ycenter, setnames, xradius, yradius, - rotation_degrees); - - } - } else if (suppressPackageStartupMessages(require(eulerr))) { - eu <- eulerr::euler(counts, ...); - # test for any identical circles/ellipses, potential methods: - # * test identical polygons, after rounding coordinates - # * test identical coordinate ranges, bbox(sp), after rounding - #test_repeat_polygons() - venn_sp <- eulerr2polys(eu); - } else { - stop("Proportional diagrams require the eulerr package."); - } - if (length(circle_nudge) > 0) { - venn_sp <- nudge_sp(sp=venn_sp, - sp_nudge=circle_nudge, - rotate_degrees=rotate_degrees); - } - return(invisible(venn_sp)); -} - #' Get Venn shapes as polygon_list #' @@ -173,17 +51,13 @@ get_venn_shapes <- function #' counts <- c(A=1, B=2, `A&B`=3, C=4) #' venn_colors <- colorjam::rainbowJam(3, alpha=0.5); #' -#' venn_polygon_list <- get_venn_polygon_shapes(counts) -#' plot_polygon_list(venn_polygon_list, col=venn_colors) +#' vjp <- get_venn_polygon_shapes(counts, return_type="JamPolygon") +#' plot(vjp, fill=venn_colors) #' -#' venn_polygon_list <- get_venn_polygon_shapes(counts, proportional=TRUE) -#' plot_polygon_list(venn_polygon_list, col=venn_colors) -#' -#' # TODO: examples showing circle_nudge, rotate_degrees -#' jpdf <- get_venn_polygon_shapes(counts, return_type="JamPolygon") -#' -#' counts4 <- c(A=1, B=2, `A&B`=3, C=4, `C&D`=2, D=3, `A&C`=2, `A&D`=1, `A&B&C&D`=3) -#' jpdf <- get_venn_polygon_shapes(counts4, return_type="JamPolygon") +#' vjp <- get_venn_polygon_shapes(counts, +#' return_type="JamPolygon", +#' proportional=TRUE) +#' plot(vjp, fill=venn_colors) #' #' @export get_venn_polygon_shapes <- function @@ -193,8 +67,7 @@ get_venn_polygon_shapes <- function circles_only=FALSE, circle_nudge=NULL, rotate_degrees=0, - return_type=c("polygon_list", - "JamPolygon"), + return_type=c("JamPolygon"), ...) { # validate return_type @@ -213,70 +86,87 @@ get_venn_polygon_shapes <- function xcenter <- c(5); ycenter <- c(5); radius <- c(2); - venn_polygon_list <- polygon_circles(xcenter, ycenter, setnames, radius); + venn_jp <- polygon_circles(xcenter=xcenter, + ycenter=ycenter, + setnames=setnames, + radius=radius, + ...); } else if (n == 2) { xcenter <- c(4, 6); ycenter <- c(5, 5); radius <- c(2, 2); - venn_polygon_list <- polygon_circles(xcenter, ycenter, setnames, radius); + venn_jp <- polygon_circles(xcenter=xcenter, + ycenter=ycenter, + setnames=setnames, + radius=radius, + ...); } else if (n == 3) { xcenter <- c(4, 6, 5); ycenter <- c(6, 6, 4); radius <- c(2, 2, 2); - venn_polygon_list <- polygon_circles(xcenter, ycenter, setnames, radius); + venn_jp <- polygon_circles(xcenter=xcenter, + ycenter=ycenter, + setnames=setnames, + radius=radius, + ...); } else if (n == 4 && circles_only) { #symbols(x=c(4, 5.5, 4, 5.5), y = c(6, 6, 4.5, 4.5), circles=c(2, 2, 2, 2), xcenter <- c(4, 5.5, 4, 5.5); ycenter <- c(6, 6, 4.5, 4.5); radius <- c(2, 2, 2, 2); - venn_polygon_list <- polygon_circles(xcenter, ycenter, setnames, radius); + venn_jp <- polygon_circles(xcenter=xcenter, + ycenter=ycenter, + setnames=setnames, + radius=radius, + ...); } else if (n == 4) { xcenter <- c(3.4, 4.95+0.035, 5.30-0.035, 6.85); ycenter <- c(3.6, 4.5, 4.5, 3.6); xradius <- c(2, 2, 2, 2); yradius <- c(4, 4, 4, 4); rotation_degrees <- 39.2 * c(-1, -1, 1, 1); - venn_polygon_list <- polygon_ellipses(xcenter, ycenter, setnames, - xradius, yradius, - rotation_degrees); + venn_jp <- polygon_ellipses(xcenter=xcenter, + ycenter=ycenter, + setnames=setnames, + xradius=xradius, + yradius=yradius, + rotation_degrees=rotation_degrees, + ...); } else if (n == 5) { xcenter <- c(4.83, 6.25, 6.10, 4.48, 3.70); ycenter <- c(6.20, 5.40, 3.50, 3.15, 4.80); xradius <- c(1.43, 1.7, 1.55, 1.55, 1.7); yradius <- c(4.11, 3.6, 3.9, 3.92, 3.6); rotation_degrees <- c(0, 66, 150, 210, 293.5); - venn_polygon_list <- polygon_ellipses(xcenter, ycenter, setnames, - xradius, yradius, - rotation_degrees); - + venn_jp <- polygon_ellipses(xcenter=xcenter, + ycenter=ycenter, + setnames=setnames, + xradius=xradius, + yradius=yradius, + rotation_degrees=rotation_degrees, + ...); } } else if (jamba::check_pkg_installed("eulerr")) { - eu <- eulerr::euler(counts, ...); + eu <- eulerr::euler(counts, + ...); # test for any identical circles/ellipses, potential methods: # * test identical polygons, after rounding coordinates # * test identical coordinate ranges, bbox(sp), after rounding #test_repeat_polygons() - venn_polygon_list <- eulerr_to_polygon_list(eu); + venn_jp <- eulerr_to_JamPolygon(eu) } else { stop("Proportional diagrams require the eulerr package."); } - if (length(circle_nudge) > 0) { + if (length(circle_nudge) > 0 || + (length(rotate_degrees) > 0 && any(rotate_degrees != 0))) { # jamba::printDebug("get_venn_polygon_shapes(): ", "before circle_nudge:");print(venn_polygon_list);# debug # jamba::printDebug("get_venn_polygon_shapes(): ", "circle_nudge:");print(circle_nudge);# debug - venn_polygon_list <- nudge_polygon_list( - polygon_list=venn_polygon_list, + venn_jp <- nudge_JamPolygon(jp=venn_jp, nudge=circle_nudge, - rotate_degrees=rotate_degrees) - # jamba::printDebug("get_venn_polygon_shapes(): ", "after circle_nudge:");print(venn_polygon_list);# debug - } else if (any(rotate_degrees != 0)) { - venn_polygon_list <- nudge_polygon_list( - polygon_list=venn_polygon_list, - nudge=NULL, - rotate_degrees=rotate_degrees) - } - if ("polygon_list" %in% return_type) { - return(invisible(venn_polygon_list)); + rotate_degrees=NULL, + ...) } + return(venn_jp); # JamPolygon df <- data.frame(name=names(venn_polygon_list), x=I(lapply(venn_polygon_list, function(i){i$x})), diff --git a/R/venndir-textvenn.R b/R/venndir-textvenn.R index 8c9b7c0..6fdf097 100644 --- a/R/venndir-textvenn.R +++ b/R/venndir-textvenn.R @@ -144,13 +144,18 @@ textvenn <- function # matrix for label colors header_colors <- c(vCol, vCol12); + names(header_colors) <- unique(sv$sets); + if (!"color" %in% colnames(sv)) { + sv$color <- header_colors[sv$sets] + } if (color_by_counts) { - count_colors <- colorjam::vals2colorLevels(sqrt(nCounts), - divergent=FALSE, - col="Reds", - trimRamp=c(8, 1), - lens=2, - baseline=0); + count_color_fn <- colorjam::col_linear_xf( + x=max(sqrt(nCounts)), + floor=max(c(0, min(sqrt(nCounts) - 1))), + lens=0, + ...); + count_colors <- count_color_fn(sqrt(nCounts)); + # k <- sqrt(1:10*10);jamba::showColors(jamba::nameVector(colorjam::col_linear_xf(x=max(k), floor=min(k - 1), lens=0, colramp="Reds")(k), k^2)) } else { if (inverse_counts) { count_colors <- header_colors; @@ -178,12 +183,12 @@ textvenn <- function ## signed counts if (any(lengths(gCounts) > 1)) { if (color_by_counts) { - gcount_colors <- colorjam::vals2colorLevels(sqrt(unlist(gCounts)), - divergent=FALSE, - col="Reds", - trimRamp=c(8, 1), - lens=2, - baseline=0); + count_color_fn <- colorjam::col_linear_xf( + x=max(sqrt(unlist(gCounts))), + floor=max(c(0, min(sqrt(unlist(gCounts)) - 1))), + lens=0, + ...); + gcount_colors <- count_color_fn(sqrt(unlist(gCounts))) } else { if (inverse_counts) { gcount_colors <- rep(header_colors, lengths(gCounts)); @@ -266,13 +271,17 @@ textvenn <- function # matrix for label colors header_colors <- c(vCol, vCol12, vCol13, vCol23, vCol123); + names(header_colors) <- unique(sv$sets); + if (!"color" %in% colnames(sv)) { + sv$color <- header_colors[sv$sets] + } if (color_by_counts) { - count_colors <- colorjam::vals2colorLevels(sqrt(nCounts), - divergent=FALSE, - col="Reds", - trimRamp=c(8, 1), - lens=2, - baseline=0); + count_color_fn <- colorjam::col_linear_xf( + x=max(sqrt(nCounts)), + floor=max(c(0, min(sqrt(nCounts) - 1))), + lens=0, + ...); + count_colors <- count_color_fn(sqrt(nCounts)); } else { if (inverse_counts) { count_colors <- header_colors; @@ -296,12 +305,18 @@ textvenn <- function ## signed counts if (any(lengths(gCounts) > 1)) { if (color_by_counts) { - gcount_colors <- colorjam::vals2colorLevels(sqrt(unlist(gCounts)), - divergent=FALSE, - col="Reds", - trimRamp=c(8, 1), - lens=2, - baseline=0); + count_color_fn <- colorjam::col_linear_xf( + x=max(sqrt(unlist(gCounts))), + floor=max(c(0, min(sqrt(unlist(gCounts)) - 1))), + lens=0, + ...); + gcount_colors <- count_color_fn(sqrt(unlist(gCounts))) + # gcount_colors2 <- colorjam::vals2colorLevels(sqrt(unlist(gCounts)), + # divergent=FALSE, + # col="Reds", + # trimRamp=c(8, 1), + # lens=2, + # baseline=0); } else { if (inverse_counts) { gcount_colors <- rep(header_colors, lengths(gCounts)); diff --git a/R/venndir-to-df.R b/R/venndir-to-df.R index c18148a..d211dfc 100644 --- a/R/venndir-to-df.R +++ b/R/venndir-to-df.R @@ -26,175 +26,329 @@ #' @param ... additional arguments are ignored. #' #' @examples -#' setlist <- venndir::make_venn_test(100, 3); +#' setlist <- venndir::make_venn_test(100, 3, do_signed=TRUE); #' venndir_out <- venndir::venndir(setlist, overlap_type="each") -#' kdf <- venndir_to_df(venndir_out) -#' kdf +#' df <- venndir_to_df(venndir_out) +#' head(df, 10) #' -#' kdf <- venndir_to_df(venndir_out, return_type="data.frame") +#' kdf <- venndir_to_df(venndir_out, return_type="kable") #' kdf #' +#' df2 <- venndir_to_df(venndir_out, df_format="items") +#' head(df2, 10) +#' +#' kdf2 <- venndir_to_df(venndir_out, df_format="items", return_type="kable") +#' kdf2 +#' +#' df3 <- venndir_to_df(venndir_out, df_format="wide", return_type="data.frame") +#' df3 +#' +#' kdf3 <- venndir_to_df(venndir_out, df_format="wide", return_type="kable") +#' kdf3 +#' #' @export venndir_to_df <- function (venndir_out, - return_type=c("kable", - "data.frame"), + df_format=c( + "hits", + "items", + "wide"), + return_type=c("data.frame", + "kable"), trim_blanks=TRUE, wrap_width=80, colorize_headers=TRUE, set_colors=NULL, + item_type="gene", + add_counts=TRUE, + verbose=FALSE, ...) { # validate arguments + df_format <- match.arg(df_format); return_type <- match.arg(return_type); - # label_df - if (!"Venndir" %in% class(venndir_out) && "vo" %in% names(venndir_out)) { - venndir_out <- venndir_out$vo; + + # validate input + if ("list" %in% class(venndir_out)) { + if ("vo" %in% names(venndir_out)) { + venndir_out <- venndir_out$vo; + } else { + stop("list input must contain Venndir object in 'vo'.") + } + } + if ("data.frame" %in% class(venndir_out)) { + if (!"items" %in% colnames(venndir_out)) { + stop("data.frame input must contain 'items' column."); + } + # assume output is from textvenn() + # label_df <- venndir_out; + if (!"overlap_sign" %in% colnames(venndir_out)) { + venndir_out[, "overlap_sign"] <- rownames(venndir_out); + } + label_df <- venndir_out; + vennlist <- venndir_out$items; + names(vennlist) <- rownames(venndir_out); + } else if ("Venndir" %in% class(venndir_out)) { + label_df <- venndir_out@label_df; + vennlist <- label_df$items; + names(vennlist) <- label_df$overlap_sign; + vennlist <- vennlist[grepl("[|]", names(vennlist))]; + } else { + stop(paste0("Input must be Venndir, ", + "or data.frame output from textvenn() or signed_overlaps()")) } - label_df <- venndir_out@label_df; - # encode factor to help sort properly - label_df$overlap_set <- factor(label_df$overlap_set, - levels=unique(label_df$overlap_set)) - label_df <- jamba::mixedSortDF(label_df, - byCols=c("overlap_set", "text")) - # spdf + # Define missing set_colors if (length(set_colors) == 0) { - set_colors <- jamba::nameVector( - subset(venndir_out@jps@polygons, - type %in% "overlap")[, c("venn_color", "label")]); + if ("Venndir" %in% class(venndir_out)) { + set_colors <- jamba::nameVector( + subset(venndir_out@jps@polygons, + type %in% "overlap")[, c("venn_color", "label")]); + } else if ("color" %in% colnames(label_df)) { + set_colors <- jamba::nameVector(renameFirst=FALSE, + unique(label_df[, c("color", "sets")])); + } } - # label text color - text_color <- farver::raise_channel( - farver::cap_channel( - label_df$color, - space="hcl", - channel="l", - value=45), - space="hcl", - channel="c", - value=70) - - # display_colnames - display_colnames <- c("overlap_set", - "text", - "overlap_sign", - "items"); - df <- label_df[, display_colnames, drop=FALSE]; - - # wrap item labels - item_label <- jamba::cPasteSU(lapply(df$items, c), sep=", ") - item_labels <- lapply(item_label, function(i){ - strwrap(i, - width=wrap_width) - }) - row_seq <- rep(seq_len(nrow(df)), - lengths(item_labels)); - dftall <- df[row_seq, , drop=FALSE] - dftall$items <- unname(unlist(item_labels)); - dftall$text_color <- rep(text_color, - lengths(item_labels)); - # dftall - - if (TRUE %in% trim_blanks) { - blank_lines <- (nchar(dftall$overlap_sign) > 0 & - nchar(dftall$items) == 0) - if (any(blank_lines)) { - dftall <- subset(dftall, !blank_lines); + ## Hits format produces an incidence matrix of hits + if ("hits" %in% df_format) { + vln <- rep(names(vennlist), + lengths(vennlist)); + vlv <- jamba::rbindList(lapply(strsplit(gsub("^.+[|]", "", vln), " "), as.numeric)) + rownames(vlv) <- unname(unlist(vennlist)) + colnames(vlv) <- strsplit(gsub("[|].+", "", + head(unique(jamba::unvigrep("[|].*0", vln)), 1)), "&")[[1]] + vlvdf <- data.frame(check.names=FALSE, + item=rownames(vlv), + vlv); + colnames(vlvdf)[1] <- head(item_type, 1); + if ("kable" %in% return_type) { + kvlvdf <- jamba::kable_coloring(vlvdf, + format.args=list(trim=TRUE, big.mark=","), + format="html", + row.names=FALSE, + colorSub=c(set_colors, + `-1`="dodgerblue", + `1`="firebrick3"), + ...) + return(kvlvdf); + } + if ("data.frame" %in% return_type) { + return(vlvdf); } } - # repair set names with "
" - if (any(grepl("|\n", ignore.case=TRUE, dftall$overlap_set))) { - dftall$overlap_set <- gsub("[ ]+", " ", - gsub("|\n", " ", - ignore.case=TRUE, - dftall$overlap_set)) - names(set_colors) <- gsub("[ ]+", " ", - gsub("|\n", " ", - ignore.case=TRUE, - names(set_colors))) - } - if (any(grepl("|\n", ignore.case=TRUE, dftall$overlap_sign))) { - dftall$overlap_sign <- gsub("[ ]+", " ", - gsub("|\n", " ", - ignore.case=TRUE, - dftall$overlap_sign)) + # Items format produces a table with items in each Venn overlap by column + if ("items" %in% df_format) { + vln <- names(vennlist); + if (any(grepl("[|].*-1", vln))) { + # goal: remove directionality for this purpose + while(any(grepl("[|].*-1", vln))) { + vln <- gsub("([|].*)-1", "\\11", vln); + } + vln <- factor(vln, levels=unique(vln)) + vennlist <- split(unname(unlist(vennlist)), rep(vln, lengths(vennlist))) + # jamba::printDebug("sdim(vennlist):");print(jamba::sdim(vennlist));# debug + } + if (!length(vennlist) %in% c(3, 7)) { + stop("This function only supports 2-way Venn without direction.") + } + # + if (length(vennlist) == 3) { + # 2-way Venn + vennorder <- c(1, 3, 2) + } else if (length(vennlist) == 7) { + # 3-way Venn + vennorder <- c(1, 4, 2, 6, 3, 5, 7); + } + vl <- vennlist[vennorder]; + vdf <- data.frame(do.call(cbind, lapply(vl, function(i){ + x <- rep("", max(lengths(vennlist))); + x[seq_along(i)] <- i; + x + }))) + colnames(vdf) <- gsub("[|].+", "", names(vl)); + # Optionally append the number of items to each header + if (TRUE %in% add_counts) { + vcts <- sapply(vdf, function(i){ + sum(!i %in% "") + }) + fromcols <- colnames(vdf); + tocols <- paste0(fromcols, + " (", vcts, + " ", item_type, + ifelse(vcts == 1, "", "s"), + ")") + colnames(vdf) <- tocols; + k <- intersect(fromcols, names(set_colors)); + if (length(k) > 0) { + ks <- set_colors[k]; + names(ks) <- tocols[match(k, fromcols)] + set_colors[names(ks)] <- ks; + } + } + if ("kable" %in% return_type) { + kvdf <- jamba::kable_coloring(vdf, + format.args=list(trim=TRUE, big.mark=","), + format="html", + row.names=FALSE, + colorSub=c(set_colors, + `-1`="dodgerblue", + `1`="firebrick3"), + ...) + return(kvdf); + } + return(vdf) } - if ("data.frame" %in% return_type) { - return(dftall[, 1:4]) - } + ## Wide format, perhaps suitable for RMarkdown + if ("wide" %in% df_format) { + # label_df + if (!"Venndir" %in% class(venndir_out) && "vo" %in% names(venndir_out)) { + venndir_out <- venndir_out$vo; + } + label_df <- venndir_out@label_df; + # encode factor to help sort properly + label_df$overlap_set <- factor(label_df$overlap_set, + levels=unique(label_df$overlap_set)) + label_df <- jamba::mixedSortDF(label_df, + byCols=c("overlap_set", "text")) - # split by set, then subset by set/direction - kdftall <- jamba::kable_coloring( - dftall[, "items", drop=FALSE], - col.names=NULL, - row.names=FALSE); - kdftall <- kableExtra::column_spec(kdftall, - column=1, - color=jamba::unalpha(dftall$text_color)) - for (igroup in as.character(unique(dftall$overlap_set))) { - from_to <- which(dftall$overlap_set %in% igroup); - bg_color <- set_colors[igroup]; - fg_color <- jamba::setTextContrastColor(bg_color); - kdftall <- kableExtra::pack_rows( - kdftall, - group_label=igroup, - hline_before=TRUE, - label_row_css=paste0( - "background-color: ", bg_color, ";", - "color: ", fg_color, ";"), - color=fg_color, background=bg_color, - start_row=min(from_to), end_row=max(from_to)) - } - row_group <- unname(jamba::pasteByRow(sep="!!!", - dftall[, c("overlap_set", "text"), drop=FALSE])) - for (igroup in unique(row_group)) { - from_to <- which(row_group %in% igroup); - igroup1 <- gsub("!!!.+", "", igroup) - igroups <- strsplit(igroup, "!!!")[[1]] - bg_color <- set_colors[igroup1]; - fg_color <- jamba::setTextContrastColor(bg_color); - kdftall <- kableExtra::group_rows( - kdftall, - group_label=gsub("!!!", " ", igroup), - hline_before=TRUE, - label_row_css=paste("border-bottom: 1px solid;", - "border-bottom-color: #000;", - "color:", fg_color, ";", - "background-color:", bg_color, ";", - "text-indent: 1.2em;"), - color=fg_color, background=bg_color, - start_row=min(from_to), end_row=max(from_to)) + # label text color + text_color <- farver::raise_channel( + farver::cap_channel( + label_df$color, + space="hcl", + channel="l", + value=45), + space="hcl", + channel="c", + value=70) + + # display_colnames + display_colnames <- c("overlap_set", + "text", + "overlap_sign", + "items"); + df <- label_df[, display_colnames, drop=FALSE]; + + # wrap item labels + item_label <- jamba::cPasteSU(lapply(df$items, c), sep=", ") + item_labels <- lapply(item_label, function(i){ + strwrap(i, + width=wrap_width) + }) + row_seq <- rep(seq_len(nrow(df)), + lengths(item_labels)); + dftall <- df[row_seq, , drop=FALSE] + dftall$items <- unname(unlist(item_labels)); + dftall$text_color <- rep(text_color, + lengths(item_labels)); + # dftall + + if (TRUE %in% trim_blanks) { + blank_lines <- (nchar(dftall$overlap_sign) > 0 & + nchar(dftall$items) == 0) + if (any(blank_lines)) { + dftall <- subset(dftall, !blank_lines); + } + } + + # repair set names with "
" + if (any(grepl("|\n", ignore.case=TRUE, dftall$overlap_set))) { + dftall$overlap_set <- gsub("[ ]+", " ", + gsub("|\n", " ", + ignore.case=TRUE, + dftall$overlap_set)) + names(set_colors) <- gsub("[ ]+", " ", + gsub("|\n", " ", + ignore.case=TRUE, + names(set_colors))) + } + if (any(grepl("|\n", ignore.case=TRUE, dftall$overlap_sign))) { + dftall$overlap_sign <- gsub("[ ]+", " ", + gsub("|\n", " ", + ignore.case=TRUE, + dftall$overlap_sign)) + } + + if ("data.frame" %in% return_type) { + return(dftall[, 1:4]) + } + + # split by set, then subset by set/direction + kdftall <- jamba::kable_coloring( + dftall[, "items", drop=FALSE], + format.args=list(trim=TRUE, big.mark=","), + format="html", + col.names=NULL, + row.names=FALSE); + kdftall <- kableExtra::column_spec(kdftall, + column=1, + color=jamba::unalpha(dftall$text_color)) + for (igroup in as.character(unique(dftall$overlap_set))) { + from_to <- which(dftall$overlap_set %in% igroup); + bg_color <- set_colors[igroup]; + fg_color <- jamba::setTextContrastColor(bg_color); + kdftall <- kableExtra::pack_rows( + kdftall, + group_label=igroup, + hline_before=TRUE, + label_row_css=paste0( + "background-color: ", bg_color, ";", + "color: ", fg_color, ";"), + color=fg_color, background=bg_color, + start_row=min(from_to), end_row=max(from_to)) + } + row_group <- unname(jamba::pasteByRow(sep="!!!", + dftall[, c("overlap_set", "text"), drop=FALSE])) + for (igroup in unique(row_group)) { + from_to <- which(row_group %in% igroup); + igroup1 <- gsub("!!!.+", "", igroup) + igroups <- strsplit(igroup, "!!!")[[1]] + bg_color <- set_colors[igroup1]; + fg_color <- jamba::setTextContrastColor(bg_color); + kdftall <- kableExtra::group_rows( + kdftall, + group_label=gsub("!!!", " ", igroup), + hline_before=TRUE, + label_row_css=paste("border-bottom: 1px solid;", + "border-bottom-color: #000;", + "color:", fg_color, ";", + "background-color:", bg_color, ";", + "text-indent: 1.2em;"), + color=fg_color, background=bg_color, + start_row=min(from_to), end_row=max(from_to)) + } + return(kdftall); } - return(kdftall); - # alternative method that only splits by set/direction - kdftall <- jamba::kable_coloring( - dftall[, -1, drop=FALSE], - row.names=FALSE); - row_group <- unname(jamba::pasteByRow(sep="!!!", - dftall[, c("overlap_set", "text"), drop=FALSE])) - for (igroup in unique(row_group)) { - from_to <- which(row_group %in% igroup); - igroup1 <- gsub("!!!.+", "", igroup) - igroups <- strsplit(igroup, "!!!")[[1]] - bg_color <- set_colors[igroup1]; - fg_color <- jamba::setTextContrastColor(bg_color); - kdftall <- kableExtra::group_rows( - kdftall, - group_label=gsub("!!!", " ", igroup), - hline_before=TRUE, - label_row_css=paste("border-bottom: 1px solid;", - "border-bottom-color: #000;", - "color:", fg_color, ";", - "background-color:", bg_color, ";", - "text-indent: 1.2em;"), - color=fg_color, background=bg_color, - indent=TRUE, - start_row=min(from_to), end_row=max(from_to)) + if (FALSE) { + # alternative method that only splits by set/direction + kdftall <- jamba::kable_coloring( + dftall[, -1, drop=FALSE], + row.names=FALSE); + row_group <- unname(jamba::pasteByRow(sep="!!!", + dftall[, c("overlap_set", "text"), drop=FALSE])) + for (igroup in unique(row_group)) { + from_to <- which(row_group %in% igroup); + igroup1 <- gsub("!!!.+", "", igroup) + igroups <- strsplit(igroup, "!!!")[[1]] + bg_color <- set_colors[igroup1]; + fg_color <- jamba::setTextContrastColor(bg_color); + kdftall <- kableExtra::group_rows( + kdftall, + group_label=gsub("!!!", " ", igroup), + hline_before=TRUE, + label_row_css=paste("border-bottom: 1px solid;", + "border-bottom-color: #000;", + "color:", fg_color, ";", + "background-color:", bg_color, ";", + "text-indent: 1.2em;"), + color=fg_color, background=bg_color, + indent=TRUE, + start_row=min(from_to), end_row=max(from_to)) + } } # label_row_css=paste0( # "background-color: ", bg_color, ";", diff --git a/README.md b/README.md index 005c0bb..5dcd6c3 100644 --- a/README.md +++ b/README.md @@ -370,9 +370,6 @@ textvenn(setlist, overlap_type="concordance", unicode=FALSE) #> #> C ^: 30 #> 71 v: 41 -``` - -``` r # Revert options # options("jam.htmlOut"=FALSE, "jam.comment"=TRUE) @@ -407,8 +404,6 @@ vn <- venndir(setlist_o, - #> ## (17:42:03) 18Jul2024: warning_label exists - The argument `circle_nudge` lets you nudge (move) a Venn circle given x,y coordinates. Provide a `list` named by the set you want to move, with a `numeric` vector for the `x,y` coordinates direction. diff --git a/TODO.md b/TODO.md index a56ebc9..5c9a1a1 100644 --- a/TODO.md +++ b/TODO.md @@ -1,5 +1,87 @@ # TODO for venndir +## 28aug2024 + +* Hide single-set signed labels with concordance and agreement +* Add generic convenience functions + + * `im()`, `im_value()` for `Venndir` objects: return incidence matrix, + or signed-incidence matrix. + * `setlist()` - accessor for `setlist` + * `label_df()` - accessor for `label_df` + * `overlaps()` or `get_overlaps()` - some accessors for set overlaps + +* `nudge_JamPolygon()` - extend with `scale`, `rotation`. +* Consider `item_style` with similar presets as `label_style`. + + * Use case is to allow shading/border for item labels, + `venndir()` and `venn_meme()`. + +* Consider adding validation for `Venndir` + + * Probably only necessary when editing `jps` and `label_df`, which may be rare + * Check that `label_df` and `jps` are compatible + +* Consider `signed_overlaps()` S4 object? + + * Currently returns `data.frame` - usable but due to the fixed formatting. + Could be useful to "lock it down" to add validation checks, + and to provide convenience functions. + * Probably not worth the effort yet. + +## 22aug2024 + +* Enhance `venndir_to_df()` + + * Add two additional formats: + + 1. Venn item format, one column for each overlap, with list of items + in each column. This is "user-convenient" and easy way to find a list + of items without having to filter the table. + 2. Hit format, with item rows, and one column for each `setlist` entry, + with values `-1` or `1` indicating presence of that item. + This format is programmatically easier to use, but requires some + filtering of the table to find particular overlaps. + + * Consider changing `return_type="data.frame"`, with `"kable"` optional. + +## 20aug2024 + +* Convert from `vwline` to `gridGeometry`, per pmur002 (author of both) + + * Initial testing confirms it should work. + * Polygon offset is explained in detail here: + https://www.stat.auckland.ac.nz/~paul/Reports/Geometry/offset/offset.html + * gridGeometry explained here: + https://www.stat.auckland.ac.nz/~paul/Reports/Geometry/gridgeometry/gridgeometry.html + * Useful functions: `polyoffsetGrob()` - use `rule="evenodd"` + +* Consider formally recognizing three types of border: + + * `outerborder` - only appears outside the polygon boundary + * `innerborder` - only appears inside the polygon boundary + * `border` - appears exactly on the polygon boundary, default `NA` + * each use suffix parameters: `.lwd`, `.lty` + * requires changing `venndir()` to use `outerborder` and not `border`. + +* Consider customizable `digits` for percent overlap label. +* `textvenn()` quality of life + + * Accept optional input data in `...` for convenience + * Add option to display percent overlap + * Consider using something like `show_labels` + +* Consider adding example test cases: + + * Venn diagram labeled by gene symbol. + Cho et al 2019, https://doi.org/10.1073/pnas.1919528117 + Figure 5A: Venn diagram showing +/-rapamycin ER-mito proteome. + Genes are also colorized and highlighted, it might be too much + as a visual, but is possible to replicate. + It shows item labels outside the Venn diagram which may + be useful `venndir` feature in future. + + ## 01aug2024 * Consider adding argument `title` or `main` to add a title to the figure. diff --git a/docs/404.html b/docs/404.html index 7d1512c..8f86944 100644 --- a/docs/404.html +++ b/docs/404.html @@ -32,7 +32,7 @@ venndir - 0.0.38.900 + 0.0.39.900 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index 2386091..33757e6 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -17,7 +17,7 @@ venndir - 0.0.38.900 + 0.0.39.900 diff --git a/docs/LICENSE.html b/docs/LICENSE.html index 6c9591f..3c0aece 100644 --- a/docs/LICENSE.html +++ b/docs/LICENSE.html @@ -17,7 +17,7 @@ venndir - 0.0.38.900 + 0.0.39.900 diff --git a/docs/TODO.html b/docs/TODO.html index fcc6ffb..03349d5 100644 --- a/docs/TODO.html +++ b/docs/TODO.html @@ -17,7 +17,7 @@ venndir - 0.0.38.900 + 0.0.39.900 @@ -58,6 +58,88 @@

TODO for venndir

+
+

28aug2024

+
  • Hide single-set signed labels with concordance and agreement

  • +
  • +

    Add generic convenience functions

    +
    • +im(), im_value() for Venndir objects: return incidence matrix, or signed-incidence matrix.
    • +
    • +setlist() - accessor for setlist +
    • +
    • +label_df() - accessor for label_df +
    • +
    • +overlaps() or get_overlaps() - some accessors for set overlaps
    • +
  • +
  • nudge_JamPolygon() - extend with scale, rotation.

  • +
  • +

    Consider item_style with similar presets as label_style.

    +
  • +
  • +

    Consider adding validation for Venndir

    +
    • Probably only necessary when editing jps and label_df, which may be rare
    • +
    • Check that label_df and jps are compatible
    • +
  • +
  • +

    Consider signed_overlaps() S4 object?

    +
    • Currently returns data.frame - usable but due to the fixed formatting. Could be useful to “lock it down” to add validation checks, and to provide convenience functions.
    • +
    • Probably not worth the effort yet.
    • +
  • +
+
+

22aug2024

+
  • +

    Enhance venndir_to_df()

    +
    • +

      Add two additional formats:

      +
      1. Venn item format, one column for each overlap, with list of items in each column. This is “user-convenient” and easy way to find a list of items without having to filter the table.
      2. +
      3. Hit format, with item rows, and one column for each setlist entry, with values -1 or 1 indicating presence of that item. This format is programmatically easier to use, but requires some filtering of the table to find particular overlaps.
      4. +
    • +
    • Consider changing return_type="data.frame", with "kable" optional.

    • +
  • +
+
+

20aug2024

+
  • +

    Convert from vwline to gridGeometry, per pmur002 (author of both)

    +
  • +
  • +

    Consider formally recognizing three types of border:

    +
    • +outerborder - only appears outside the polygon boundary
    • +
    • +innerborder - only appears inside the polygon boundary
    • +
    • +border - appears exactly on the polygon boundary, default NA +
    • +
    • each use suffix parameters: .lwd, .lty +
    • +
    • requires changing venndir() to use outerborder and not border.
    • +
  • +
  • Consider customizable digits for percent overlap label.

  • +
  • +

    textvenn() quality of life

    +
    • Accept optional input data in ... for convenience
    • +
    • Add option to display percent overlap
    • +
    • Consider using something like show_labels +
    • +
  • +
  • +

    Consider adding example test cases:

    +
    • Venn diagram labeled by gene symbol. Cho et al 2019, https://doi.org/10.1073/pnas.1919528117 Figure 5A: Venn diagram showing +/-rapamycin ER-mito proteome. Genes are also colorized and highlighted, it might be too much as a visual, but is possible to replicate. It shows item labels outside the Venn diagram which may be useful venndir feature in future.
    • +
  • +

01aug2024

  • @@ -715,7 +797,7 @@

    02may2023get_venn_shapes() -> venndir_attender() +get_venn_shapes() -> venndir_attender()

  • curate_venn_labels() -> venndir_amender() diff --git a/docs/articles/index.html b/docs/articles/index.html index d3169f8..ed5234e 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -17,7 +17,7 @@ venndir - 0.0.38.900 + 0.0.39.900
diff --git a/docs/articles/venndir_gene_expression.html b/docs/articles/venndir_gene_expression.html index 8d5ce42..1e8cc83 100644 --- a/docs/articles/venndir_gene_expression.html +++ b/docs/articles/venndir_gene_expression.html @@ -33,7 +33,7 @@ venndir - 0.0.37.900 + 0.0.39.900
diff --git a/docs/articles/venndir_gene_expression_files/figure-html/generic_1-1.png b/docs/articles/venndir_gene_expression_files/figure-html/generic_1-1.png index ab64330..ae89bc6 100644 Binary files a/docs/articles/venndir_gene_expression_files/figure-html/generic_1-1.png and b/docs/articles/venndir_gene_expression_files/figure-html/generic_1-1.png differ diff --git a/docs/articles/venndir_gene_expression_files/figure-html/limma_3-1.png b/docs/articles/venndir_gene_expression_files/figure-html/limma_3-1.png index 65fb8cb..1612a1b 100644 Binary files a/docs/articles/venndir_gene_expression_files/figure-html/limma_3-1.png and b/docs/articles/venndir_gene_expression_files/figure-html/limma_3-1.png differ diff --git a/docs/articles/venndir_gene_expression_files/figure-html/limma_3p-1.png b/docs/articles/venndir_gene_expression_files/figure-html/limma_3p-1.png index f7c8d35..2ac6b6b 100644 Binary files a/docs/articles/venndir_gene_expression_files/figure-html/limma_3p-1.png and b/docs/articles/venndir_gene_expression_files/figure-html/limma_3p-1.png differ diff --git a/docs/articles/venndir_gene_expression_files/figure-html/limma_4-1.png b/docs/articles/venndir_gene_expression_files/figure-html/limma_4-1.png index 97d9c03..c526604 100644 Binary files a/docs/articles/venndir_gene_expression_files/figure-html/limma_4-1.png and b/docs/articles/venndir_gene_expression_files/figure-html/limma_4-1.png differ diff --git a/docs/articles/venndir_gene_expression_files/figure-html/limma_5-1.png b/docs/articles/venndir_gene_expression_files/figure-html/limma_5-1.png index d293e29..b7960ff 100644 Binary files a/docs/articles/venndir_gene_expression_files/figure-html/limma_5-1.png and b/docs/articles/venndir_gene_expression_files/figure-html/limma_5-1.png differ diff --git a/docs/articles/venndir_gene_expression_files/figure-html/limma_6-1.png b/docs/articles/venndir_gene_expression_files/figure-html/limma_6-1.png index 25e0ade..eff81b7 100644 Binary files a/docs/articles/venndir_gene_expression_files/figure-html/limma_6-1.png and b/docs/articles/venndir_gene_expression_files/figure-html/limma_6-1.png differ diff --git a/docs/articles/venndir_gene_expression_files/figure-html/limma_6s-1.png b/docs/articles/venndir_gene_expression_files/figure-html/limma_6s-1.png index 39d597a..60e6e35 100644 Binary files a/docs/articles/venndir_gene_expression_files/figure-html/limma_6s-1.png and b/docs/articles/venndir_gene_expression_files/figure-html/limma_6s-1.png differ diff --git a/docs/articles/venndir_gene_expression_files/figure-html/limma_7-1.png b/docs/articles/venndir_gene_expression_files/figure-html/limma_7-1.png index e848ce4..1c7d08c 100644 Binary files a/docs/articles/venndir_gene_expression_files/figure-html/limma_7-1.png and b/docs/articles/venndir_gene_expression_files/figure-html/limma_7-1.png differ diff --git a/docs/articles/venndir_gene_expression_files/figure-html/limma_8-1.png b/docs/articles/venndir_gene_expression_files/figure-html/limma_8-1.png index 03be93a..d8b90bb 100644 Binary files a/docs/articles/venndir_gene_expression_files/figure-html/limma_8-1.png and b/docs/articles/venndir_gene_expression_files/figure-html/limma_8-1.png differ diff --git a/docs/authors.html b/docs/authors.html index 8483207..c0f2c15 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -17,7 +17,7 @@ venndir - 0.0.38.900 + 0.0.39.900 @@ -73,13 +73,13 @@

Citation

Ward J (2024). venndir: Directional Venn diagrams. -R package version 0.0.38.900, http://github.com/jmw86069/venndir. +R package version 0.0.39.900, http://github.com/jmw86069/venndir.

@Manual{,
   title = {venndir: Directional Venn diagrams},
   author = {James M. Ward},
   year = {2024},
-  note = {R package version 0.0.38.900},
+  note = {R package version 0.0.39.900},
   url = {http://github.com/jmw86069/venndir},
 }
diff --git a/docs/index.html b/docs/index.html index 596bc2c..0960575 100644 --- a/docs/index.html +++ b/docs/index.html @@ -33,7 +33,7 @@ venndir - 0.0.38.900 + 0.0.39.900 @@ -364,9 +364,8 @@

Text Venn for the R Console#> X: 1 X: 16 #> #> C ^: 30 -#> 71 v: 41 -
-
+#>                            71    v: 41
+
 # Revert options
 # options("jam.htmlOut"=FALSE, "jam.comment"=TRUE)

Sorry, no proportional text Venn diagrams (yet)!

@@ -376,7 +375,7 @@

Nudge Venn circles
+
 overlaps <- c(set_A=187, set_B=146, set_C=499,
    `set_A&set_B`=1,
    `set_A&set_C`=181,
@@ -391,9 +390,8 @@ 

Nudge Venn circles=1.4, set_colors=c("firebrick2", "dodgerblue", "#9999AA"))

-
#> ##  (17:42:03) 18Jul2024:   warning_label exists

The argument circle_nudge lets you nudge (move) a Venn circle given x,y coordinates. Provide a list named by the set you want to move, with a numeric vector for the x,y coordinates direction.

-
+
 vo_nudge <- venndir(setlist_o,
    expand_fraction=0.15,
    # label_style="lite box",
@@ -431,7 +429,7 @@ 

Item labels
+
 setlist <- make_venn_test(100, 3, do_signed=TRUE);
 venndir(setlist,
    poly_alpha=0.3,
@@ -440,7 +438,7 @@ 

Item labels

Interestingly, the density of labels gives some indication of the relative overlaps.

The same plot using proportional circles makes the label density effectively uniform. Note the option show_items="sign" displays only the directional arrow, and item_cex=2 makes the arrows twice as large as normal.

-
+
 setlist <- make_venn_test(100, 3, do_signed=TRUE);
 venndir(setlist,
    poly_alpha=0.3,
@@ -450,7 +448,7 @@ 

Item labels=TRUE);

The sign is an interesting visual summary when there are too many labels to display otherwise.

-
+
 setlist <- make_venn_test(1000, 3, do_signed=TRUE);
 venndir(setlist,
    show_labels="Ni",
@@ -461,7 +459,7 @@ 

Item labels=10000);

Again, proportional Venn circles effectively makes the density uniform.

-
+
 venndir(setlist,
    show_labels="Ni",
    overlap_type="each",
diff --git a/docs/news/index.html b/docs/news/index.html
index 8957dc3..0e689de 100644
--- a/docs/news/index.html
+++ b/docs/news/index.html
@@ -17,7 +17,7 @@
       
       
         venndir
-        0.0.38.900
+        0.0.39.900
       
     
@@ -57,6 +57,106 @@

Changelog

Source: NEWS.md
+
+ +
+

changes to existing functions

+
  • +

    render_venndir()

    +
    • Signed output now uses ":" instead of ": " between the directional arrow and the count, for example "^^:20" instead of "^^: 20". Somehow the whitespace calculation is inconsistent, causing some labels to be wider than others with gridtext::richtext_grob(), with much wider whitespace than anticipated. The effect was inconsistent even on the same machine, between RStudio and R console, and differed across other machines also. Workarounds include choosing different fonts, apparently some provide more reliable whitespace calculations. The change only occurs during rendering when grobs are created. The underlying Venndir data is not changed.
    • +
  • +
  • +

    plot.JamPolygon(), affecting venndir() and render_venndir()

    +
    • Now renders borders using gridGeometry thanks to suggestion from pmur002. Borders are more consistent, without small visual artifacts.

    • +
    • Added "outerborder" as a formal border type.

    • +
    • +

      All three types of borders can be rendered, in order: outer, inner, border

      +
      • “outerborder” - begins at the outer edge of the boundary
      • +
      • “border” - is centered on the boundary itself
      • +
      • “innerborder” - begins at the inner edge of the boundary
      • +
      • when border is not drawn, either the innerborder or outerborder are drawn on the border itself to prevent a tiny artifact gap between the innerborder and outerborder.
      • +
    • +
  • +
  • +

    venndir()

    +
    • The Venndir object now uses outerborder instead of border, and sets border to NA.
    • +
    • New argument lwd controls default border line width.
    • +
    • +unicode (silent argument passed to curate_venn_labels() controls the Unicode character with up/down arrows, disagreement, etc. You can supply unicode=2 for alternate symbols, though they are font-dependent, R-dependent, and terminal-dependent. All things must work well together (apparently). Use unicode=FALSE for simple text.
    • +
    • New default poly_alpha=0.6 makes background less intense.
    • +
    • Now calls make_color_contrast() properly without forcing saturation, previously caused blue to become cyan instead of light blue.
    • +
  • +
  • sample_JamPolygon() changed n_ratio=1 after testing and disliking the previous n_ratio=4.

  • +
  • +

    venndir_to_df() gained some new features:

    +
    • +

      new argument df_format with three formats:

      +
      • +"hits" - essentially a hit matrix with 1, 0, -1 indicating direction
      • +
      • +"items" - each column of a data.frame contains items for a Venn overlap.
      • +
      • +"wide" - intended as an RMarkdown summary - it uses grouped rows to display items in each Venn overlap. Not sure it works very well.
      • +
    • +
    • +

      argument return_type:

      +
      • +"data.frame" (default) - returns a data.frame
      • +
      • +"kable" - returns a colorized kable table for RMarkdown HTML
      • +
    • +
  • +
  • +

    textvenn()

    +
  • +
  • +

    get_venn_polygon_shapes()

    +
    • Changed default return_type="JamPolygon" since transition to JamPolygon, removed the option for "polygon_list".
    • +
  • +
  • polygon_circles(), polygon_ellipses() both now return JamPolygon.

  • +
+
+

new functions

+
+
+

added generic functions

+
  • Cleaned up some generic function logic, probably more to do.

  • +
  • +

    Venndir objects

    +
  • +
  • +

    rbind2.JamPolygon()

    +
    • This function was enhanced to be able to combine multiple JamPolygon objects either in a single list, multiple list, and will now retain all colnames across all JamPolygon objects.
    • +
  • +
+
+ +

The polygon_list format loosely conformed to polyclip data input/output, but had several exceptions that motivated me to use JamPolygon: simple polygons encoded as list, complex polygons encoded as nested list; solid polygon encoded as clockwise points, holes encoded counterclockwise.

+
  • bbox_polygon_list()
  • +
  • get_largest_polygon_list()
  • +
  • intersect_polygon_list()
  • +
  • labelr_polygon_list()
  • +
  • minus_polygon_list()
  • +
  • plot_polygon_list()
  • +
  • polygon_list_labelr()
  • +
  • rescale_polygon_list()
  • +
  • union_polygon_list()
  • +
  • get_venn_shapes()
  • +
  • eulerr_to_polygon_list()
  • +
  • polygon_areas()
  • +
  • nudge_polygon_coords()
  • +
  • nudge_polygon_list()
  • +
  • polygon_list_to_xy_list()
  • +
  • xy_list_to_polygon_list()
  • +
+
@@ -741,7 +841,7 @@

changes to existing functions

venndir() now adds the Venn shapes to the output venn_spdf with type="set"; all other polygons have type="overlap". The shapes will serve as an anchor for set labels, in the event we want to label one or more circles – like when one circle is fully contained inside another.

  • polygon_label_outside() now determines a reasonable text alignment adj based upon the angle offset, to help minimize label overlap with the line segment.

  • polygon_label_outside() was updated to correct some internal use of coordinates. New argument sp_buffer to allow the line segment to end slightly inside each polygon.

  • -
  • get_venn_shapes() default 4-way Venn ellipses were slightly adjusted so the middle ellipses broke the outer ellipses into two polygons. This change helps the automated position of labels by polygon_label_outside() with certain settings.

  • +
  • get_venn_shapes() default 4-way Venn ellipses were slightly adjusted so the middle ellipses broke the outer ellipses into two polygons. This change helps the automated position of labels by polygon_label_outside() with certain settings.

  • venndir_label_style() was refactored to be able to position labels inside or outside the polygon, for four types of labels:

  • "set" - e.g. "set_A"

  • "overlap" - e.g. "set_A&set_B" normally this label is not shown

  • @@ -791,7 +891,7 @@

    bug fixes signed_overlaps() was updated to allow using sep="|". Previous this delimited was used to make unique rownames, and needed to be parsed properly to prevent errors.
  • -venndir() new argument sep which is now properly passed to signed_overlaps() and get_venn_shapes().
  • +venndir() new argument sep which is now properly passed to signed_overlaps() and get_venn_shapes().
  • find_vennpoly_overlaps(), overlaplist2setlist(), counts2setlist() now call strsplit(..., fixed=TRUE) so the sep character is not treated like a regular expression, thus allowing delimiter sep="|" if specified.
  • diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 019b4e5..c178f1f 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -3,5 +3,5 @@ pkgdown: 2.0.7 pkgdown_sha: ~ articles: venndir_gene_expression: venndir_gene_expression.html -last_built: 2024-08-05T21:14Z +last_built: 2024-08-29T02:28Z diff --git a/docs/reference/JamPolygon-class.html b/docs/reference/JamPolygon-class.html index 5f3b2fc..25e82f2 100644 --- a/docs/reference/JamPolygon-class.html +++ b/docs/reference/JamPolygon-class.html @@ -1,5 +1,6 @@ -JamPolygon class — JamPolygon-class • venndirJamPolygon class — JamPolygon-class • venndir @@ -17,7 +18,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -59,7 +60,8 @@

    JamPolygon class

    -

    JamPolygon class

    +

    JamPolygon class contains one slot "polygons" which is a data.frame +with one polygon per row. An individual polygon can

    @@ -67,6 +69,7 @@

    JamPolygon class

    See also

    Other JamPolygon: Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -84,10 +87,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/JamPolygon-methods-1.png b/docs/reference/JamPolygon-methods-1.png new file mode 100644 index 0000000..557d89e Binary files /dev/null and b/docs/reference/JamPolygon-methods-1.png differ diff --git a/docs/reference/JamPolygon-methods-2.png b/docs/reference/JamPolygon-methods-2.png new file mode 100644 index 0000000..d82f255 Binary files /dev/null and b/docs/reference/JamPolygon-methods-2.png differ diff --git a/docs/reference/JamPolygon-methods.html b/docs/reference/JamPolygon-methods.html new file mode 100644 index 0000000..ef14766 --- /dev/null +++ b/docs/reference/JamPolygon-methods.html @@ -0,0 +1,235 @@ + +Subset JamPolygon object — [,JamPolygon-method • venndir + + +
    +
    + + + +
    +
    + + +
    +

    Plot JamPolygon object

    +

    Combine multiple JamPolygon objects, given two JamPolygon or multiple +objects in a list.

    +
    + +
    +
    # S4 method for JamPolygon
    +[(x, i, j, ..., drop = TRUE)
    +
    +# S4 method for JamPolygon,missing
    +plot(x, y, ...)
    +
    +rbind2.JamPolygon(x, y, ...)
    +
    +# S4 method for JamPolygon,ANY
    +rbind2(x, y, ...)
    +
    + +
    +

    Arguments

    +
    x, y
    +

    JamPolygon object

    + + +
    ...
    +

    additional JamPolygon objects if present

    + +
    +
    +

    Value

    + + +

    JamPolygon object, invisibly.

    +
    +
    +

    Details

    +

    This function is intended to support input as rbind2(list(JamPolygons)) +or do.call(rbind2.JamPolygon, list(JamPolygons)) with any +combination of one or more JamPolygon objects.

    +
    + + +
    +

    Examples

    +
    dfx <- data.frame(name=c("polygon1", "polygon2"),
    +   x=I(list(
    +      list(c(1, 4, 4, 1),
    +         c(2, 3, 3, 2)),
    +      c(5, 6, 6, 5))),
    +   y=I(list(
    +      list(c(1, 1, 4, 4),
    +         c(2, 2, 3, 3)),
    +      c(1, 1, 2, 2))),
    +   fill=c("gold", "firebrick"))
    +jpx <- new("JamPolygon", polygons=dfx);
    +plot(jpx);
    +
    +
    +dfz <- data.frame(name=c("polygon1", "polygon2", "polygon3"),
    +   x=I(list(
    +      list(c(1, 4, 4, 1),
    +         c(2, 3, 3, 2)),
    +      list(c(4.5, 6.5, 6.5, 4.5),
    +         c(5, 6, 6, 5)),
    +      list(c(1, 4, 4, 1),
    +         c(2, 3, 3, 2),
    +         c(5, 6, 6, 5)))),
    +   y=I(list(
    +      list(c(1, 1, 4, 4),
    +         c(2, 2, 3, 3)),
    +      list(c(1, 1, 3, 3),
    +         c(3, 3, 4, 4)+0.5),
    +      list(c(5, 5, 8, 8),
    +         c(6, 6, 7, 7),
    +         c(6, 6, 7, 7)))),
    +   fill=c("gold", "firebrick", "dodgerblue"));
    +jpz <- new("JamPolygon", polygons=dfz);
    +jpz@polygons[, c("label_x", "label_y")] <- as.data.frame(labelr_JamPolygon(jpz))
    +jpz@polygons$border <- c("orange", "gold", "purple");
    +jpz@polygons$border.lwd <- c(3, 4, 5);
    +jpz <- add_orientation_JamPolygon(jpz);
    +plot(jpz);
    +
    +
    +
    +
    +
    + +
    + + +
    + +
    +

    Site built with pkgdown 2.0.7.

    +
    + +
    + + + + + + + + diff --git a/docs/reference/Rplot002.png b/docs/reference/Rplot002.png index 423d86d..b561ca4 100644 Binary files a/docs/reference/Rplot002.png and b/docs/reference/Rplot002.png differ diff --git a/docs/reference/Rplot003.png b/docs/reference/Rplot003.png index 851a85b..178cd55 100644 Binary files a/docs/reference/Rplot003.png and b/docs/reference/Rplot003.png differ diff --git a/docs/reference/Rplot004.png b/docs/reference/Rplot004.png index 851a85b..178cd55 100644 Binary files a/docs/reference/Rplot004.png and b/docs/reference/Rplot004.png differ diff --git a/docs/reference/Rplot005.png b/docs/reference/Rplot005.png index 305caf3..8cc7f15 100644 Binary files a/docs/reference/Rplot005.png and b/docs/reference/Rplot005.png differ diff --git a/docs/reference/Rplot006.png b/docs/reference/Rplot006.png index 88e67eb..e9699b6 100644 Binary files a/docs/reference/Rplot006.png and b/docs/reference/Rplot006.png differ diff --git a/docs/reference/Rplot007.png b/docs/reference/Rplot007.png index 2013cc0..810e12d 100644 Binary files a/docs/reference/Rplot007.png and b/docs/reference/Rplot007.png differ diff --git a/docs/reference/Rplot008.png b/docs/reference/Rplot008.png index bd296e4..b8f7d55 100644 Binary files a/docs/reference/Rplot008.png and b/docs/reference/Rplot008.png differ diff --git a/docs/reference/Rplot009.png b/docs/reference/Rplot009.png index ec121fb..9f3bc79 100644 Binary files a/docs/reference/Rplot009.png and b/docs/reference/Rplot009.png differ diff --git a/docs/reference/Rplot010.png b/docs/reference/Rplot010.png index 5122e74..a1fb5d0 100644 Binary files a/docs/reference/Rplot010.png and b/docs/reference/Rplot010.png differ diff --git a/docs/reference/Venndir-class.html b/docs/reference/Venndir-class.html index b7394dd..db9af40 100644 --- a/docs/reference/Venndir-class.html +++ b/docs/reference/Venndir-class.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -141,6 +141,7 @@

    Details

    See also

    Other JamPolygon: JamPolygon-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -158,10 +159,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/add_orientation_JamPolygon-1.png b/docs/reference/add_orientation_JamPolygon-1.png index 0cd966f..3d234ee 100644 Binary files a/docs/reference/add_orientation_JamPolygon-1.png and b/docs/reference/add_orientation_JamPolygon-1.png differ diff --git a/docs/reference/add_orientation_JamPolygon.html b/docs/reference/add_orientation_JamPolygon.html index 44b9219..8c07eb6 100644 --- a/docs/reference/add_orientation_JamPolygon.html +++ b/docs/reference/add_orientation_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -134,6 +134,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, area_JamPolygon(), bbox_JamPolygon(), buffer_JamPolygon(), @@ -150,10 +151,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/area_JamPolygon-1.png b/docs/reference/area_JamPolygon-1.png index 0cd966f..3d234ee 100644 Binary files a/docs/reference/area_JamPolygon-1.png and b/docs/reference/area_JamPolygon-1.png differ diff --git a/docs/reference/area_JamPolygon-2.png b/docs/reference/area_JamPolygon-2.png index e1efb73..28e607a 100644 Binary files a/docs/reference/area_JamPolygon-2.png and b/docs/reference/area_JamPolygon-2.png differ diff --git a/docs/reference/area_JamPolygon.html b/docs/reference/area_JamPolygon.html index 925f2fc..20ecaa0 100644 --- a/docs/reference/area_JamPolygon.html +++ b/docs/reference/area_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -142,6 +142,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), bbox_JamPolygon(), buffer_JamPolygon(), @@ -158,10 +159,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/bbox_JamPolygon.html b/docs/reference/bbox_JamPolygon.html index 18a414f..0a23d24 100644 --- a/docs/reference/bbox_JamPolygon.html +++ b/docs/reference/bbox_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -81,6 +81,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), buffer_JamPolygon(), @@ -97,10 +98,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/buffer_JamPolygon-1.png b/docs/reference/buffer_JamPolygon-1.png new file mode 100644 index 0000000..ba3bc1a Binary files /dev/null and b/docs/reference/buffer_JamPolygon-1.png differ diff --git a/docs/reference/buffer_JamPolygon-2.png b/docs/reference/buffer_JamPolygon-2.png new file mode 100644 index 0000000..b68a195 Binary files /dev/null and b/docs/reference/buffer_JamPolygon-2.png differ diff --git a/docs/reference/buffer_JamPolygon.html b/docs/reference/buffer_JamPolygon.html index fd383d8..f38415a 100644 --- a/docs/reference/buffer_JamPolygon.html +++ b/docs/reference/buffer_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -66,7 +66,7 @@

    Apply buffer outside or inside JamPolygon

    buffer_JamPolygon(
       jp,
       buffer = -0.5,
    -  steps = 50,
    +  steps = 200,
       relative = TRUE,
       verbose = FALSE,
       ...
    @@ -85,12 +85,40 @@ 

    Arguments

    numeric buffer, where negative values cause the polygon to be reduced in size.

    + +
    steps
    +

    numeric number of steps, default 200, used to +determine relative unit sizes when relative=TRUE (which is default).

    + + +
    relative
    +

    logical default TRUE, indicating whether to resize +polygons using relative dimensions. Relative units are defined by +the minimum negative buffer that results in non-zero area, where +relative unit -1 would result in zero area.

    + + +
    verbose
    +

    logical indicating whether to print verbose output.

    + + +
    ...
    +

    additional arguments are ignored.

    +
    +
    +

    Value

    + + +

    JamPolygon with one polygon, although the polygon could +contain multiple disconnected parts.

    +
    +
    +

    Examples

    +
    DEdf <- data.frame(check.names=FALSE,
    +   name=c("D", "E"),
    +   x=I(list(
    +      c(-3, 3, 3, 0, -3),
    +      c(-4, 2, 2, -4))),
    +   y=I(list(
    +   c(-3, -3, 1.5, 4, 1.5),
    +   c(-2, -2, 4, 4))),
    +fill=c("#FFD70055", "#B2222255"))
    +jp <- new("JamPolygon", polygons=DEdf)
    +plot(jp)
    +
    +
    +jp2 <- nudge_JamPolygon(jp, nudge=list(D=c(10, 0)));
    +jp_jp2 <- rbind2(jp2, buffer_JamPolygon(jp2));
    +plot(jp_jp2,
    +   border.lty=c(1, 1, 2),
    +   fill=c(NA, NA, "gold"));
    +
    +
    +
    +
    @@ -89,6 +89,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -105,10 +106,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/check_Venndir.html b/docs/reference/check_Venndir.html index 9786f08..252ee7b 100644 --- a/docs/reference/check_Venndir.html +++ b/docs/reference/check_Venndir.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -87,6 +87,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -103,10 +104,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/counts2setlist-1.png b/docs/reference/counts2setlist-1.png index affa49a..2505dc2 100644 Binary files a/docs/reference/counts2setlist-1.png and b/docs/reference/counts2setlist-1.png differ diff --git a/docs/reference/counts2setlist-2.png b/docs/reference/counts2setlist-2.png index 574b1b3..5b1a72d 100644 Binary files a/docs/reference/counts2setlist-2.png and b/docs/reference/counts2setlist-2.png differ diff --git a/docs/reference/counts2setlist.html b/docs/reference/counts2setlist.html index 1ef0a50..c107bb5 100644 --- a/docs/reference/counts2setlist.html +++ b/docs/reference/counts2setlist.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    diff --git a/docs/reference/curate_venn_labels.html b/docs/reference/curate_venn_labels.html index c5bbc6e..8c8bfb6 100644 --- a/docs/reference/curate_venn_labels.html +++ b/docs/reference/curate_venn_labels.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900

    @@ -160,7 +160,6 @@

    Details

    See also

    Other venndir utility: expand_range(), -get_venn_shapes(), make_color_contrast(), make_venn_combn_df(), make_venn_test(), @@ -179,9 +178,9 @@

    Examples

    venn_labels <- c("0 1 0 -1", "1 -1", "1 1 1", "mixed", "agreement", "1 1 0 0"); (curate_venn_labels(venn_labels, "sign")) -#> [1] "-↑-↓" "↑↓" "↑↑↑" "X" "=" "↑↑--" +#> [1] "-↑-↓" "↑↓" "↑↑↑" "X" "‖" "↑↑--" (curate_venn_labels(venn_labels, "sign", unicode=FALSE)) -#> [1] "-^-v" "^v" "^^^" "X" ">>>" "^^--" +#> [1] "-^-v" "^v" "^^^" "X" "=" "^^--" (curate_venn_labels(venn_labels, "color")) #> [1] "#9E4497FF" "#9E4497FF" "#B22222FF" "#737373FF" "#1874CDFF" "#B22222FF" @@ -189,7 +188,7 @@

    Examples

    jamba::printDebug(as.list(curate_venn_labels(venn_labels, "sign")), collapse=", ", fgText=as.list(curate_venn_labels(venn_labels, "color"))) -#> ## (18:09:46) 23Jul2024: -↑-↓, ↑↓, ↑↑↑, X, =, ↑↑-- +#> ## (22:29:06) 28Aug2024: -↑-↓, ↑↓, ↑↑↑, X, , ↑↑--

    diff --git a/docs/reference/degrees_to_adj.html b/docs/reference/degrees_to_adj.html index 441b9b4..61d5215 100644 --- a/docs/reference/degrees_to_adj.html +++ b/docs/reference/degrees_to_adj.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/diff_degrees.html b/docs/reference/diff_degrees.html index 98d50a4..ce0b592 100644 --- a/docs/reference/diff_degrees.html +++ b/docs/reference/diff_degrees.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/display_angles.html b/docs/reference/display_angles.html index 00bcf83..6348f4d 100644 --- a/docs/reference/display_angles.html +++ b/docs/reference/display_angles.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/draw_gridtext_groups.html b/docs/reference/draw_gridtext_groups.html index cb2c35d..ecba6ae 100644 --- a/docs/reference/draw_gridtext_groups.html +++ b/docs/reference/draw_gridtext_groups.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/eulerr_to_JamPolygon.html b/docs/reference/eulerr_to_JamPolygon.html index 6d856d7..62fb9ca 100644 --- a/docs/reference/eulerr_to_JamPolygon.html +++ b/docs/reference/eulerr_to_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -77,6 +77,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -93,10 +94,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/expand_range.html b/docs/reference/expand_range.html index 4652155..85a7fb2 100644 --- a/docs/reference/expand_range.html +++ b/docs/reference/expand_range.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -124,7 +124,6 @@

    Details

    See also

    Other venndir utility: curate_venn_labels(), -get_venn_shapes(), make_color_contrast(), make_venn_combn_df(), make_venn_test(), diff --git a/docs/reference/farthest_point_JamPolygon.html b/docs/reference/farthest_point_JamPolygon.html index 6826541..bd987bb 100644 --- a/docs/reference/farthest_point_JamPolygon.html +++ b/docs/reference/farthest_point_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900

    @@ -93,6 +93,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -109,10 +110,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/figures/README-label_preset_1-1.png b/docs/reference/figures/README-label_preset_1-1.png index b2c1ab0..ace3800 100644 Binary files a/docs/reference/figures/README-label_preset_1-1.png and b/docs/reference/figures/README-label_preset_1-1.png differ diff --git a/docs/reference/figures/README-label_preset_1l-1.png b/docs/reference/figures/README-label_preset_1l-1.png index cdf3725..5d9367b 100644 Binary files a/docs/reference/figures/README-label_preset_1l-1.png and b/docs/reference/figures/README-label_preset_1l-1.png differ diff --git a/docs/reference/figures/README-nudge_1-1.png b/docs/reference/figures/README-nudge_1-1.png index 593a4d1..427a9d9 100644 Binary files a/docs/reference/figures/README-nudge_1-1.png and b/docs/reference/figures/README-nudge_1-1.png differ diff --git a/docs/reference/figures/README-nudge_2-1.png b/docs/reference/figures/README-nudge_2-1.png index c952c2f..b4ecc05 100644 Binary files a/docs/reference/figures/README-nudge_2-1.png and b/docs/reference/figures/README-nudge_2-1.png differ diff --git a/docs/reference/figures/README-venn_1-1.png b/docs/reference/figures/README-venn_1-1.png index e2b5cb9..66abe7d 100644 Binary files a/docs/reference/figures/README-venn_1-1.png and b/docs/reference/figures/README-venn_1-1.png differ diff --git a/docs/reference/figures/README-venn_1e-1.png b/docs/reference/figures/README-venn_1e-1.png index aaa15ad..4eefde9 100644 Binary files a/docs/reference/figures/README-venn_1e-1.png and b/docs/reference/figures/README-venn_1e-1.png differ diff --git a/docs/reference/figures/README-venn_intro-1.png b/docs/reference/figures/README-venn_intro-1.png index 7d3f0c3..7efe386 100644 Binary files a/docs/reference/figures/README-venn_intro-1.png and b/docs/reference/figures/README-venn_intro-1.png differ diff --git a/docs/reference/figures/README-venndir_1-1.png b/docs/reference/figures/README-venndir_1-1.png index 4d76601..c2b6340 100644 Binary files a/docs/reference/figures/README-venndir_1-1.png and b/docs/reference/figures/README-venndir_1-1.png differ diff --git a/docs/reference/figures/README-venndir_agreement-1.png b/docs/reference/figures/README-venndir_agreement-1.png index f7eaf9b..a76aa58 100644 Binary files a/docs/reference/figures/README-venndir_agreement-1.png and b/docs/reference/figures/README-venndir_agreement-1.png differ diff --git a/docs/reference/figures/README-venndir_each-1.png b/docs/reference/figures/README-venndir_each-1.png index 475303e..453b32d 100644 Binary files a/docs/reference/figures/README-venndir_each-1.png and b/docs/reference/figures/README-venndir_each-1.png differ diff --git a/docs/reference/figures/README-venndir_each_p-1.png b/docs/reference/figures/README-venndir_each_p-1.png index 508dfe0..dd5b2ef 100644 Binary files a/docs/reference/figures/README-venndir_each_p-1.png and b/docs/reference/figures/README-venndir_each_p-1.png differ diff --git a/docs/reference/figures/README-venndir_overlap-1.png b/docs/reference/figures/README-venndir_overlap-1.png index e2b5cb9..66abe7d 100644 Binary files a/docs/reference/figures/README-venndir_overlap-1.png and b/docs/reference/figures/README-venndir_overlap-1.png differ diff --git a/docs/reference/figures/README-venndir_overlap_p-1.png b/docs/reference/figures/README-venndir_overlap_p-1.png index a554027..dcc8efc 100644 Binary files a/docs/reference/figures/README-venndir_overlap_p-1.png and b/docs/reference/figures/README-venndir_overlap_p-1.png differ diff --git a/docs/reference/figures/README-vennitems_1-1.png b/docs/reference/figures/README-vennitems_1-1.png index ebf8272..0561e4c 100644 Binary files a/docs/reference/figures/README-vennitems_1-1.png and b/docs/reference/figures/README-vennitems_1-1.png differ diff --git a/docs/reference/figures/README-vennitems_1p-1.png b/docs/reference/figures/README-vennitems_1p-1.png index 5941d33..07d4f73 100644 Binary files a/docs/reference/figures/README-vennitems_1p-1.png and b/docs/reference/figures/README-vennitems_1p-1.png differ diff --git a/docs/reference/figures/README-vennitems_2-1.png b/docs/reference/figures/README-vennitems_2-1.png index c1e5992..1ce6d87 100644 Binary files a/docs/reference/figures/README-vennitems_2-1.png and b/docs/reference/figures/README-vennitems_2-1.png differ diff --git a/docs/reference/figures/README-vennitems_2p-1.png b/docs/reference/figures/README-vennitems_2p-1.png index 6f31a6a..856b3ef 100644 Binary files a/docs/reference/figures/README-vennitems_2p-1.png and b/docs/reference/figures/README-vennitems_2p-1.png differ diff --git a/docs/reference/find_venn_overlaps_JamPolygon-1.png b/docs/reference/find_venn_overlaps_JamPolygon-1.png index 05c9f52..2f60b08 100644 Binary files a/docs/reference/find_venn_overlaps_JamPolygon-1.png and b/docs/reference/find_venn_overlaps_JamPolygon-1.png differ diff --git a/docs/reference/find_venn_overlaps_JamPolygon-2.png b/docs/reference/find_venn_overlaps_JamPolygon-2.png index 758fb4e..b72df75 100644 Binary files a/docs/reference/find_venn_overlaps_JamPolygon-2.png and b/docs/reference/find_venn_overlaps_JamPolygon-2.png differ diff --git a/docs/reference/find_venn_overlaps_JamPolygon.html b/docs/reference/find_venn_overlaps_JamPolygon.html index c639f81..cadfa25 100644 --- a/docs/reference/find_venn_overlaps_JamPolygon.html +++ b/docs/reference/find_venn_overlaps_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -160,6 +160,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -176,10 +177,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), @@ -198,11 +201,10 @@

    Examples

    xo <- find_venn_overlaps_JamPolygon(jp=jp1, venn_counts=test_counts) -xo@polygons$border <- jamba::makeColorDarker(darkFactor=1.2, +xo@polygons$outerborder <- jamba::makeColorDarker(darkFactor=1.2, xo@polygons$venn_color) - xo@polygons$border.lwd <- 2; -plot(xo, flip_sign=-1); -#> ## (18:09:48) 23Jul2024: Handling flip_sign:-1 +xo@polygons$outerborder.lwd <- 4; +plot(xo);
    diff --git a/docs/reference/get_venn_polygon_shapes-1.png b/docs/reference/get_venn_polygon_shapes-1.png index 687a0bb..dcc2094 100644 Binary files a/docs/reference/get_venn_polygon_shapes-1.png and b/docs/reference/get_venn_polygon_shapes-1.png differ diff --git a/docs/reference/get_venn_polygon_shapes-2.png b/docs/reference/get_venn_polygon_shapes-2.png index 8f845a8..2798df0 100644 Binary files a/docs/reference/get_venn_polygon_shapes-2.png and b/docs/reference/get_venn_polygon_shapes-2.png differ diff --git a/docs/reference/get_venn_polygon_shapes.html b/docs/reference/get_venn_polygon_shapes.html index 1662043..42490a1 100644 --- a/docs/reference/get_venn_polygon_shapes.html +++ b/docs/reference/get_venn_polygon_shapes.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -70,7 +70,7 @@

    Get Venn shapes as polygon_list

    circles_only = FALSE, circle_nudge = NULL, rotate_degrees = 0, - return_type = c("polygon_list", "JamPolygon"), + return_type = c("JamPolygon"), ... )
    @@ -145,24 +145,7 @@

    Details

    @@ -170,20 +153,16 @@

    Examples

    counts <- c(A=1, B=2, `A&B`=3, C=4)
     venn_colors <- colorjam::rainbowJam(3, alpha=0.5);
     
    -venn_polygon_list <- get_venn_polygon_shapes(counts)
    -plot_polygon_list(venn_polygon_list, col=venn_colors)
    +vjp <- get_venn_polygon_shapes(counts, return_type="JamPolygon")
    +plot(vjp, fill=venn_colors)
     
     
    -venn_polygon_list <- get_venn_polygon_shapes(counts, proportional=TRUE)
    -plot_polygon_list(venn_polygon_list, col=venn_colors)
    +vjp <- get_venn_polygon_shapes(counts,
    +   return_type="JamPolygon",
    +   proportional=TRUE)
    +plot(vjp, fill=venn_colors)
     
     
    -# TODO: examples showing circle_nudge, rotate_degrees
    -jpdf <- get_venn_polygon_shapes(counts, return_type="JamPolygon")
    -
    -counts4 <- c(A=1, B=2, `A&B`=3, C=4, `C&D`=2, D=3, `A&C`=2, `A&D`=1, `A&B&C&D`=3)
    -jpdf <- get_venn_polygon_shapes(counts4, return_type="JamPolygon")
    -
     
    diff --git a/docs/reference/grobs_exts.html b/docs/reference/grobs_exts.html index aaddfe9..35b9f82 100644 --- a/docs/reference/grobs_exts.html +++ b/docs/reference/grobs_exts.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/grobs_stack.html b/docs/reference/grobs_stack.html index ac70f85..11ebaec 100644 --- a/docs/reference/grobs_stack.html +++ b/docs/reference/grobs_stack.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/grobs_tile.html b/docs/reference/grobs_tile.html index 56ab3e9..6923dfb 100644 --- a/docs/reference/grobs_tile.html +++ b/docs/reference/grobs_tile.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/grobs_xalign.html b/docs/reference/grobs_xalign.html index 13a5ec0..800e0e7 100644 --- a/docs/reference/grobs_xalign.html +++ b/docs/reference/grobs_xalign.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/grobs_yalign.html b/docs/reference/grobs_yalign.html index 11a0be2..eb38bb2 100644 --- a/docs/reference/grobs_yalign.html +++ b/docs/reference/grobs_yalign.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/has_point_in_JamPolygon.html b/docs/reference/has_point_in_JamPolygon.html index 12860bd..69aaf32 100644 --- a/docs/reference/has_point_in_JamPolygon.html +++ b/docs/reference/has_point_in_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -102,6 +102,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -118,10 +119,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/im2list.html b/docs/reference/im2list.html index 21bd8b1..c204b0f 100644 --- a/docs/reference/im2list.html +++ b/docs/reference/im2list.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    diff --git a/docs/reference/im_value2list.html b/docs/reference/im_value2list.html index fccda32..a52ae50 100644 --- a/docs/reference/im_value2list.html +++ b/docs/reference/im_value2list.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/index.html b/docs/reference/index.html index 0138add..5bd1df6 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -17,7 +17,7 @@ venndir - 0.0.38.900 + 0.0.39.900 @@ -120,6 +120,10 @@

    JamPolygon object and functions JamPolygon-class

    JamPolygon class

    + +

    `[`(<JamPolygon>) plot(<JamPolygon>,<missing>) rbind2.JamPolygon() rbind2(<JamPolygon>,<ANY>)

    + +

    Subset JamPolygon object

    Venndir-class

    @@ -193,9 +197,9 @@

    JamPolygon object and functions

    Get the nearest polygon point to a reference point

    -

    plot(<JamPolygon>,<missing>)

    +

    nudge_JamPolygon()

    -

    Plot JamPolygon object

    +

    Nudge JamPolygon coordinates

    plot(<JamPolygon>)

    @@ -208,6 +212,14 @@

    JamPolygon object and functions polyclip_to_JamPolygon()

    Convert polyclip polygon to JamPolygon

    + +

    polygon_circles()

    + +

    Make polygon_list circles

    + +

    polygon_ellipses()

    + +

    Make polygon_list ellipses

    sample_JamPolygon()

    @@ -229,81 +241,13 @@

    venndir polygon Functions

    Functions for polygons

    -

    bbox_polygon_list()

    - -

    Bounding box for polygon list

    - -

    eulerr_to_polygon_list()

    - -

    Convert euler output to polygons

    - -

    get_largest_polygon_list()

    - -

    Largest polygon in a polygon list

    -

    get_venn_polygon_shapes()

    Get Venn shapes as polygon_list

    - -

    intersect_polygon_list()

    - -

    Intersect one or more polygons

    - -

    labelr_polygon_list()

    - -

    Calculate polygon label positions using Pole of Inaccessibility

    - -

    minus_polygon_list()

    - -

    Subtract one or more polygons

    - -

    nudge_polygon_coords()

    - -

    Nudge polygon coordinates

    - -

    nudge_polygon_list()

    - -

    Nudge polygon_list

    - -

    plot_polygon_list()

    - -

    Plot polygon_list using base R

    - -

    polygon_areas()

    - -

    Polygon area for simple or list of polygons

    - -

    polygon_circles()

    - -

    Make polygon_list circles

    - -

    polygon_ellipses()

    - -

    Make polygon_list ellipses

    - -

    polygon_list_labelr()

    - -

    Simple wrapper to polylabelr::poi() for polygon_list

    - -

    polygon_list_to_xy_list()

    - -

    Convert polygon list of x,y coordinate into a list by x and y

    - -

    rescale_polygon_list()

    - -

    Rescale a polygon_list object

    simple_ellipse()

    Simple ellipse function

    - -

    union_polygon_list()

    - -

    Union one or more polygons

    - -

    xy_list_to_polygon_list()

    - -

    Convert coordinate list of x and y into polygon list of x,y coordinates

    venndir Spatial Functions

    Functions for spatial objects and polygon manipulation

    @@ -360,10 +304,6 @@

    venndir Utility Functions expand_range()

    Expand numeric range

    - -

    get_venn_shapes()

    - -

    Get Venn shapes

    make_color_contrast()

    diff --git a/docs/reference/intersect_JamPolygon.html b/docs/reference/intersect_JamPolygon.html index 2820753..de392e9 100644 --- a/docs/reference/intersect_JamPolygon.html +++ b/docs/reference/intersect_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -93,6 +93,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -109,10 +110,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/label_fill_JamPolygon-1.png b/docs/reference/label_fill_JamPolygon-1.png index 0cd966f..3d234ee 100644 Binary files a/docs/reference/label_fill_JamPolygon-1.png and b/docs/reference/label_fill_JamPolygon-1.png differ diff --git a/docs/reference/label_fill_JamPolygon-2.png b/docs/reference/label_fill_JamPolygon-2.png new file mode 100644 index 0000000..20f4cee Binary files /dev/null and b/docs/reference/label_fill_JamPolygon-2.png differ diff --git a/docs/reference/label_fill_JamPolygon.html b/docs/reference/label_fill_JamPolygon.html index 0b117f3..4516e2f 100644 --- a/docs/reference/label_fill_JamPolygon.html +++ b/docs/reference/label_fill_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -136,6 +136,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -152,10 +153,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), @@ -186,13 +189,17 @@

    Examples

    jp3 <- new("JamPolygon", polygons=df3); plot(jp3); -label_fill_JamPolygon(jp3[1,], labels=1:20) +lfj <- label_fill_JamPolygon(jp3[1,], labels=1:20) -test_x <- jp3[1,]@polygons$x[[1]]; -test_y <- jp3[1,]@polygons$y[[1]]; -P <- list(x=c(3.5, 4.5), y=c(3.5, 4.5)) -A <- lapply(seq_along(test_x), function(i){ - list(x=test_x[[i]], y=test_y[[i]])}) +plot(lfj$items_df[, c("x", "y")], cex=0) +text(lfj$items_df[, c("x", "y")], labels=lfj$items_df$text) + + +#test_x <- jp3[1,]@polygons$x[[1]]; +#test_y <- jp3[1,]@polygons$y[[1]]; +#P <- list(x=c(3.5, 4.5), y=c(3.5, 4.5)) +#A <- lapply(seq_along(test_x), function(i){ +# list(x=test_x[[i]], y=test_y[[i]])})
    diff --git a/docs/reference/label_outside_JamPolygon.html b/docs/reference/label_outside_JamPolygon.html index 7c4dce5..2fbbb55 100644 --- a/docs/reference/label_outside_JamPolygon.html +++ b/docs/reference/label_outside_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -125,6 +125,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -141,10 +142,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/label_segment_JamPolygon.html b/docs/reference/label_segment_JamPolygon.html index 412e66f..ab24651 100644 --- a/docs/reference/label_segment_JamPolygon.html +++ b/docs/reference/label_segment_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -83,6 +83,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -99,10 +100,12 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/labelr_JamPolygon.html b/docs/reference/labelr_JamPolygon.html index d4075c5..fff7577 100644 --- a/docs/reference/labelr_JamPolygon.html +++ b/docs/reference/labelr_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -113,6 +113,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -129,10 +130,12 @@

    See also

    label_segment_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/list2im_opt.html b/docs/reference/list2im_opt.html index 6c5e59d..5100629 100644 --- a/docs/reference/list2im_opt.html +++ b/docs/reference/list2im_opt.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    diff --git a/docs/reference/list2im_value.html b/docs/reference/list2im_value.html index 402778f..de77cd2 100644 --- a/docs/reference/list2im_value.html +++ b/docs/reference/list2im_value.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/make_color_contrast.html b/docs/reference/make_color_contrast.html index 1298d2c..ee49387 100644 --- a/docs/reference/make_color_contrast.html +++ b/docs/reference/make_color_contrast.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -102,7 +102,6 @@

    See also

    Other venndir utility: curate_venn_labels(), expand_range(), -get_venn_shapes(), make_venn_combn_df(), make_venn_test(), match_list(), diff --git a/docs/reference/make_venn_combn_df.html b/docs/reference/make_venn_combn_df.html index 7758586..04503d8 100644 --- a/docs/reference/make_venn_combn_df.html +++ b/docs/reference/make_venn_combn_df.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900

    @@ -108,7 +108,6 @@

    See also

    Other venndir utility: curate_venn_labels(), expand_range(), -get_venn_shapes(), make_color_contrast(), make_venn_test(), match_list(), diff --git a/docs/reference/make_venn_test.html b/docs/reference/make_venn_test.html index 3c8d96d..ea59145 100644 --- a/docs/reference/make_venn_test.html +++ b/docs/reference/make_venn_test.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900

    @@ -169,7 +169,6 @@

    See also

    Other venndir utility: curate_venn_labels(), expand_range(), -get_venn_shapes(), make_color_contrast(), make_venn_combn_df(), match_list(), @@ -307,34 +306,34 @@

    Examples

    ## text venn diagram textvenn(setlist, overlap_type="overlap") #> set_A&set_B -#> 8 +#> 8 #> set_A set_B -#> 16 7 +#> 16 7 #> #> set_A&set_B&set_C -#> 1 +#> 1 #> set_A&set_C set_B&set_C -#> 7 0 +#> 7 0 #> #> #> set_C -#> 7 +#> 7 ## text venn diagram with signed direction textvenn(setlist, overlap_type="each") #> set_A&set_B ↑↑: 3 -#> 8 ↑↓: 2 +#> 8 ↑↓: 2 #> set_A ↑: 9 ↓↓: 3 set_B ↑: 4 -#> 16 ↓: 7 7 ↓: 3 +#> 16 ↓: 7 7 ↓: 3 #> #> set_A&set_B&set_C ↑↑↑: 1 -#> 1 +#> 1 #> set_A&set_C ↑↑: 2 set_B&set_C ↑↑: 0 -#> 7 ↑↓: 1 0 +#> 7 ↑↓: 1 0 #> ↓↑: 1 #> ↓↓: 3 #> set_C ↑: 5 -#> 7 ↓: 2 +#> 7 ↓: 2
    diff --git a/docs/reference/match_list.html b/docs/reference/match_list.html index e158696..ada92f8 100644 --- a/docs/reference/match_list.html +++ b/docs/reference/match_list.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -106,7 +106,6 @@

    See also

    Other venndir utility: curate_venn_labels(), expand_range(), -get_venn_shapes(), make_color_contrast(), make_venn_combn_df(), make_venn_test(), diff --git a/docs/reference/mean_degree_arc.html b/docs/reference/mean_degree_arc.html index 0d6add1..0165ad5 100644 --- a/docs/reference/mean_degree_arc.html +++ b/docs/reference/mean_degree_arc.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900

    diff --git a/docs/reference/mean_degrees.html b/docs/reference/mean_degrees.html index a9e45eb..c7a9245 100644 --- a/docs/reference/mean_degrees.html +++ b/docs/reference/mean_degrees.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/minus_JamPolygon.html b/docs/reference/minus_JamPolygon.html index 7c9cd0e..36a8fbd 100644 --- a/docs/reference/minus_JamPolygon.html +++ b/docs/reference/minus_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -85,6 +85,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -101,10 +102,12 @@

    See also

    label_segment_JamPolygon(), labelr_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/nearest_point_JamPolygon.html b/docs/reference/nearest_point_JamPolygon.html index 7ebf381..fda5301 100644 --- a/docs/reference/nearest_point_JamPolygon.html +++ b/docs/reference/nearest_point_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -93,6 +93,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -109,10 +110,12 @@

    See also

    label_segment_JamPolygon(), labelr_JamPolygon(), minus_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/nudge_JamPolygon-1.png b/docs/reference/nudge_JamPolygon-1.png new file mode 100644 index 0000000..ba3bc1a Binary files /dev/null and b/docs/reference/nudge_JamPolygon-1.png differ diff --git a/docs/reference/nudge_JamPolygon-2.png b/docs/reference/nudge_JamPolygon-2.png new file mode 100644 index 0000000..30c4547 Binary files /dev/null and b/docs/reference/nudge_JamPolygon-2.png differ diff --git a/docs/reference/nudge_JamPolygon-3.png b/docs/reference/nudge_JamPolygon-3.png new file mode 100644 index 0000000..0b6934e Binary files /dev/null and b/docs/reference/nudge_JamPolygon-3.png differ diff --git a/docs/reference/nudge_JamPolygon.html b/docs/reference/nudge_JamPolygon.html new file mode 100644 index 0000000..9a1370c --- /dev/null +++ b/docs/reference/nudge_JamPolygon.html @@ -0,0 +1,176 @@ + +Nudge JamPolygon coordinates — nudge_JamPolygon • venndir + + +
    +
    + + + +
    +
    + + +
    +

    Nudge JamPolygon coordinates

    +
    + +
    +
    nudge_JamPolygon(jp, nudge = NULL, verbose = FALSE, ...)
    +
    + +
    +

    Arguments

    +
    jp
    +

    JamPolygon object

    + + +
    nudge
    +

    list whose names match names(jp), containing numeric +vector with names "x" and "y". For example: +nudge=list(polyname1=c(x=1, y=0))

    + + +
    ...
    +

    additional arguments are ignored

    + +
    +
    +

    Details

    +

    Polygon coordinates within a JamPolygon object are nudged by name +or polygon number, such that all parts of each polygon are adjusted +together. For multi-part polygons, and/or polygons with internal holes, +all parts are moved the identical amount.

    +
    + + +
    +

    Examples

    +
    DEdf <- data.frame(check.names=FALSE,
    +   name=c("D", "E"),
    +   x=I(list(
    +      c(-3, 3, 3, 0, -3),
    +      c(-4, 2, 2, -4))),
    +   y=I(list(
    +      c(-3, -3, 1.5, 4, 1.5),
    +      c(-2, -2, 4, 4))),
    +   fill=c("#FFD70055", "#B2222255"))
    +DEjp <- new("JamPolygon", polygons=DEdf)
    +plot(DEjp)
    +
    +nudge <- list(D=c(7, 1), E=c(-1, -1));
    +DEjp_nudged <- nudge_JamPolygon(DEjp, nudge=nudge)
    +plot(DEjp_nudged)
    +
    +
    +plot(rbind2(DEjp, DEjp_nudged),
    +   fill=c("#FFD70055", "#B2222255", "gold", "firebrick"),
    +   label=c("D_old", "E_old", "D_new", "E_new"),
    +   border.lty=c(2, 2, 1, 1))
    +
    +
    +
    +
    +
    + +
    + + +
    + +
    +

    Site built with pkgdown 2.0.7.

    +
    + +
    + + + + + + + + diff --git a/docs/reference/nudge_venndir_label-1.png b/docs/reference/nudge_venndir_label-1.png index fc51ca9..59a9c2c 100644 Binary files a/docs/reference/nudge_venndir_label-1.png and b/docs/reference/nudge_venndir_label-1.png differ diff --git a/docs/reference/nudge_venndir_label-2.png b/docs/reference/nudge_venndir_label-2.png index fc51ca9..59a9c2c 100644 Binary files a/docs/reference/nudge_venndir_label-2.png and b/docs/reference/nudge_venndir_label-2.png differ diff --git a/docs/reference/nudge_venndir_label-3.png b/docs/reference/nudge_venndir_label-3.png index 6dfebc7..e62c4fd 100644 Binary files a/docs/reference/nudge_venndir_label-3.png and b/docs/reference/nudge_venndir_label-3.png differ diff --git a/docs/reference/nudge_venndir_label.html b/docs/reference/nudge_venndir_label.html index 14ee28a..574b646 100644 --- a/docs/reference/nudge_venndir_label.html +++ b/docs/reference/nudge_venndir_label.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -100,7 +100,6 @@

    See also

    Other venndir utility: curate_venn_labels(), expand_range(), -get_venn_shapes(), make_color_contrast(), make_venn_combn_df(), make_venn_test(), diff --git a/docs/reference/overlaplist2setlist-1.png b/docs/reference/overlaplist2setlist-1.png index f117dab..a2b498c 100644 Binary files a/docs/reference/overlaplist2setlist-1.png and b/docs/reference/overlaplist2setlist-1.png differ diff --git a/docs/reference/overlaplist2setlist-2.png b/docs/reference/overlaplist2setlist-2.png index 9972d67..3b6a997 100644 Binary files a/docs/reference/overlaplist2setlist-2.png and b/docs/reference/overlaplist2setlist-2.png differ diff --git a/docs/reference/overlaplist2setlist.html b/docs/reference/overlaplist2setlist.html index 1b0657c..ff0a123 100644 --- a/docs/reference/overlaplist2setlist.html +++ b/docs/reference/overlaplist2setlist.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900

    diff --git a/docs/reference/plot.JamPolygon-1.png b/docs/reference/plot.JamPolygon-1.png index def0f30..557d89e 100644 Binary files a/docs/reference/plot.JamPolygon-1.png and b/docs/reference/plot.JamPolygon-1.png differ diff --git a/docs/reference/plot.JamPolygon-2.png b/docs/reference/plot.JamPolygon-2.png index 073e7d1..cf9a4f5 100644 Binary files a/docs/reference/plot.JamPolygon-2.png and b/docs/reference/plot.JamPolygon-2.png differ diff --git a/docs/reference/plot.JamPolygon-3.png b/docs/reference/plot.JamPolygon-3.png new file mode 100644 index 0000000..5ec9a7f Binary files /dev/null and b/docs/reference/plot.JamPolygon-3.png differ diff --git a/docs/reference/plot.JamPolygon.html b/docs/reference/plot.JamPolygon.html index d1c8b8d..1a1bde6 100644 --- a/docs/reference/plot.JamPolygon.html +++ b/docs/reference/plot.JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -80,6 +80,7 @@

    Plot JamPolygon object

    do_viewport = TRUE, do_pop_viewport = TRUE, do_draw = TRUE, + do_experimental = TRUE, verbose = FALSE, debug = FALSE, ... @@ -177,6 +178,11 @@

    Arguments

    do_viewport=FALSE, and do_pop_viewport=FALSE.

    +
    do_experimental
    +

    logical indicating whether to use experimental +rendering with gridGeometry as potential replacement for vwline.

    + +
    verbose

    logical indicating whether to print verbose output.

    @@ -253,6 +259,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -270,9 +277,11 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), point_in_JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), @@ -295,6 +304,24 @@

    Examples

    plot(jpx); +# if you want to add to the plot, you must capture output +# to use the viewport +jpxout <- plot(jpx); +vp <- attr(jpxout, "viewport"); +adjx <- attr(jpxout, "adjx"); +adjy <- attr(jpxout, "adjy"); +grid::grid.path(x=adjx(c(4, 5, 5, 4) + 0.5), + y=adjy(c(3, 3, 4, 4)), + vp=vp, + gp=grid::gpar(fill="purple", col="red1", lwd=2), + default.units="snpc") +grid::grid.text(x=adjx(5), y=adjy(3.5), + label="new grob", + vp=vp, + gp=grid::gpar(col="yellow", fontsize=20), + default.units="snpc") + + dfz <- data.frame(name=c("polygon1", "polygon2", "polygon3"), x=I(list( list(c(1, 4, 4, 1), @@ -315,11 +342,16 @@

    Examples

    fill=c("gold", "firebrick", "dodgerblue")); jpz <- new("JamPolygon", polygons=dfz); jpz@polygons[, c("label_x", "label_y")] <- as.data.frame(labelr_JamPolygon(jpz)) -jpz@polygons$border <- c("orange", "gold", "purple"); -jpz@polygons$border.lwd <- c(3, 4, 5); +jpz@polygons$outerborder <- c("orange", "gold", "purple"); +jpz@polygons$outerborder.lwd <- 0; +jpz@polygons$outerborder.lwd <- c(3, 4, 5); +jpz@polygons$innerborder <- c("orange4", "gold3", "purple4"); +jpz@polygons$innerborder.lwd <- c(3, 4, 5); +jpz@polygons$border.lwd <- 1; +jpz@polygons$border.lty <- 2; #jpz <- add_orientation_JamPolygon(jpz); plot(jpz); - +
    diff --git a/docs/reference/point_in_JamPolygon.html b/docs/reference/point_in_JamPolygon.html index 3c5f74b..eff4ca0 100644 --- a/docs/reference/point_in_JamPolygon.html +++ b/docs/reference/point_in_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -118,6 +118,7 @@

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -135,9 +136,11 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), polyclip_to_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/polyclip_to_JamPolygon.html b/docs/reference/polyclip_to_JamPolygon.html index 17e6ba0..397b01c 100644 --- a/docs/reference/polyclip_to_JamPolygon.html +++ b/docs/reference/polyclip_to_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -66,11 +66,18 @@

    Convert polyclip polygon to JamPolygon

    polyclip_to_JamPolygon(A, ...)
    +
    +

    Arguments

    +
    A
    +

    output from polyclip functions.

    + +

    See also

    Other JamPolygon: JamPolygon-class, Venndir-class, +[,JamPolygon-method, add_orientation_JamPolygon(), area_JamPolygon(), bbox_JamPolygon(), @@ -88,9 +95,11 @@

    See also

    labelr_JamPolygon(), minus_JamPolygon(), nearest_point_JamPolygon(), -plot,JamPolygon,missing-method, +nudge_JamPolygon(), plot.JamPolygon(), point_in_JamPolygon(), +polygon_circles(), +polygon_ellipses(), sample_JamPolygon(), split_JamPolygon(), union_JamPolygon(), diff --git a/docs/reference/polygon_circles-1.png b/docs/reference/polygon_circles-1.png index 1b1d3c3..83d063b 100644 Binary files a/docs/reference/polygon_circles-1.png and b/docs/reference/polygon_circles-1.png differ diff --git a/docs/reference/polygon_circles.html b/docs/reference/polygon_circles.html index f306c1e..c1f7c75 100644 --- a/docs/reference/polygon_circles.html +++ b/docs/reference/polygon_circles.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -97,7 +97,7 @@

    Arguments

    Value

    -

    object list with a number of circles encoded as polygons.

    +

    JamPolygon object

    Details

    @@ -105,32 +105,42 @@

    Details

    Examples

    -
    polygon_list <- polygon_circles(c(3, 2), c(2, 3))
    -plot_polygon_list(polygon_list)
    -points(x=c(3, 2), y=c(2, 3), pch=c("1", "2"), add=TRUE);
    +    
    circle_jp <- polygon_circles(c(3, 2), c(2, 3))
    +plot(circle_jp, fill=c("red", "gold"))
     
     
     
    diff --git a/docs/reference/polygon_ellipses-1.png b/docs/reference/polygon_ellipses-1.png index 6271a2f..b56bae9 100644 Binary files a/docs/reference/polygon_ellipses-1.png and b/docs/reference/polygon_ellipses-1.png differ diff --git a/docs/reference/polygon_ellipses.html b/docs/reference/polygon_ellipses.html index 6b3da50..538038a 100644 --- a/docs/reference/polygon_ellipses.html +++ b/docs/reference/polygon_ellipses.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -113,7 +113,7 @@

    Arguments

    Value

    -

    object list with a number of circles encoded as polygons.

    +

    JamPolygon object

    Details

    @@ -121,34 +121,44 @@

    Details

    Examples

    -
    polygon_list <- polygon_ellipses(c(3, 2), c(2, 3),
    +    
    ejp <- polygon_ellipses(c(3, 2), c(2, 3),
        xradius=c(1, 4),
        yradius=c(5, 2))
    -plot_polygon_list(polygon_list, col=c("#FF000077", "#FFDD0077"));
    -points(x=c(3, 2), y=c(2, 3), pch=c("1", "2"), add=TRUE);
    +plot(ejp, fill=c("#FF000077", "#FFDD0077"))
     
     
     
    diff --git a/docs/reference/print_color_df.html b/docs/reference/print_color_df.html index b62d191..f65d93e 100644 --- a/docs/reference/print_color_df.html +++ b/docs/reference/print_color_df.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    @@ -137,7 +137,6 @@

    See also

    Other venndir utility: curate_venn_labels(), expand_range(), -get_venn_shapes(), make_color_contrast(), make_venn_combn_df(), make_venn_test(), diff --git a/docs/reference/render_venndir.html b/docs/reference/render_venndir.html index c1618e5..d27fa42 100644 --- a/docs/reference/render_venndir.html +++ b/docs/reference/render_venndir.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900

    diff --git a/docs/reference/reposition_venn_gridtext_labels.html b/docs/reference/reposition_venn_gridtext_labels.html index 189ef24..dc7f308 100644 --- a/docs/reference/reposition_venn_gridtext_labels.html +++ b/docs/reference/reposition_venn_gridtext_labels.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900
    diff --git a/docs/reference/rescale_coordinates.html b/docs/reference/rescale_coordinates.html index 87a4ce0..d741c95 100644 --- a/docs/reference/rescale_coordinates.html +++ b/docs/reference/rescale_coordinates.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/sample_JamPolygon-1.png b/docs/reference/sample_JamPolygon-1.png index 6d9412b..751f776 100644 Binary files a/docs/reference/sample_JamPolygon-1.png and b/docs/reference/sample_JamPolygon-1.png differ diff --git a/docs/reference/sample_JamPolygon-2.png b/docs/reference/sample_JamPolygon-2.png index 58d5c95..de0b4b3 100644 Binary files a/docs/reference/sample_JamPolygon-2.png and b/docs/reference/sample_JamPolygon-2.png differ diff --git a/docs/reference/sample_JamPolygon-3.png b/docs/reference/sample_JamPolygon-3.png index 3c03d03..7f8b53a 100644 Binary files a/docs/reference/sample_JamPolygon-3.png and b/docs/reference/sample_JamPolygon-3.png differ diff --git a/docs/reference/sample_JamPolygon-4.png b/docs/reference/sample_JamPolygon-4.png index 3f7295a..f6456a8 100644 Binary files a/docs/reference/sample_JamPolygon-4.png and b/docs/reference/sample_JamPolygon-4.png differ diff --git a/docs/reference/sample_JamPolygon.html b/docs/reference/sample_JamPolygon.html index c0698f2..c99cca3 100644 --- a/docs/reference/sample_JamPolygon.html +++ b/docs/reference/sample_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -67,7 +67,8 @@

    Sample points within JamPolygon

    jp, n = 100, xyratio = 1.1, - spread = FALSE, + spread = TRUE, + n_ratio = 1, pattern = c("offset", "rectangle"), buffer = 0, byCols = c("-y", "x"), @@ -93,9 +94,32 @@

    Arguments

    spread
    -

    logical when more then n points can be fit inside -jp, spread=TRUE spreads the points evenly across the available -points, while spread=FALSE only takes the first n points.

    +

    logical (default TRUE) when more then n points can +be fit inside the polygon, spread=TRUE spreads the points evenly +across the available points, while spread=FALSE simply uses +the first n points.

    + + +
    n_ratio
    +

    numeric ratio which must be 1 or higher, indicating +how many total sampled points should be defined, before choosing +the points to use. This option is used only when spread=TRUE, +which causes more points to be defined, from which it uses +evenly distributed values.

    + + +
    pattern
    +

    character string indicating how to array the points:

    • "offset" (default) uses a rectangular grid where alternating +points on each row are offset slightly on the y-axis.

    • +
    • "rectangle" uses a rectangular grid with points on each row +that share the same y-axis value.

    • +
    + + +
    buffer
    +

    numeric optional buffer used to adjust the jp polygon +size overall, where negative values will slightly shrink the +polygon border. Points are sampled after this adjustment.

    byCols
    @@ -134,6 +158,7 @@

    See also

    diff --git a/docs/reference/shrink_df.html b/docs/reference/shrink_df.html index c9ed479..08f5c47 100644 --- a/docs/reference/shrink_df.html +++ b/docs/reference/shrink_df.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -88,7 +88,6 @@

    See also

    Other venndir utility: curate_venn_labels(), expand_range(), -get_venn_shapes(), make_color_contrast(), make_venn_combn_df(), make_venn_test(), diff --git a/docs/reference/signed_counts2setlist-1.png b/docs/reference/signed_counts2setlist-1.png index 98e02ba..69f262d 100644 Binary files a/docs/reference/signed_counts2setlist-1.png and b/docs/reference/signed_counts2setlist-1.png differ diff --git a/docs/reference/signed_counts2setlist-2.png b/docs/reference/signed_counts2setlist-2.png index 92b0654..7ddedee 100644 Binary files a/docs/reference/signed_counts2setlist-2.png and b/docs/reference/signed_counts2setlist-2.png differ diff --git a/docs/reference/signed_counts2setlist-3.png b/docs/reference/signed_counts2setlist-3.png index 8b28c68..8d9c790 100644 Binary files a/docs/reference/signed_counts2setlist-3.png and b/docs/reference/signed_counts2setlist-3.png differ diff --git a/docs/reference/signed_counts2setlist.html b/docs/reference/signed_counts2setlist.html index 4bc1e29..23f5683 100644 --- a/docs/reference/signed_counts2setlist.html +++ b/docs/reference/signed_counts2setlist.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900

    diff --git a/docs/reference/signed_overlaps.html b/docs/reference/signed_overlaps.html index 5c72e7e..9d370a1 100644 --- a/docs/reference/signed_overlaps.html +++ b/docs/reference/signed_overlaps.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/simple_ellipse.html b/docs/reference/simple_ellipse.html index e9294f6..389d600 100644 --- a/docs/reference/simple_ellipse.html +++ b/docs/reference/simple_ellipse.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -69,24 +69,7 @@

    Simple ellipse function

    diff --git a/docs/reference/split_JamPolygon.html b/docs/reference/split_JamPolygon.html index 4539e52..386e0f6 100644 --- a/docs/reference/split_JamPolygon.html +++ b/docs/reference/split_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -86,6 +86,7 @@

    See also

    diff --git a/docs/reference/spread_degrees.html b/docs/reference/spread_degrees.html index 2826dd0..1e79e2a 100644 --- a/docs/reference/spread_degrees.html +++ b/docs/reference/spread_degrees.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/textvenn.html b/docs/reference/textvenn.html index 2cf1b49..712cb54 100644 --- a/docs/reference/textvenn.html +++ b/docs/reference/textvenn.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -178,63 +178,63 @@

    Examples

    # two-way Venn by default shows concordance textvenn(setlist, sets=c(1,2)) #> set_A ↑: 13 set_A&set_B X: 2 set_B ↑: 6 -#> 26 ↓: 13 6 ↑↑: 3 10 ↓: 4 +#> 26 ↓: 13 6 ↑↑: 3 10 ↓: 4 #> ↓↓: 1 # without signed directionality use overlap_type="overlap" textvenn(setlist, sets=c(1,2), overlap_type="overlap") #> set_A set_A&set_B set_B -#> 26 6 10 +#> 26 6 10 # three-way Venn showing each signed directionality textvenn(setlist, sets=c(1,2,3), overlap_type="each") #> set_A&set_B ↑↑: 3 -#> 5 ↓↑: 1 +#> 5 ↓↑: 1 #> set_A ↑: 9 ↓↓: 1 set_B ↑: 6 -#> 18 ↓: 9 10 ↓: 4 +#> 18 ↓: 9 10 ↓: 4 #> #> set_A&set_B&set_C ↓↑↑: 1 -#> 1 +#> 1 #> set_A&set_C ↑↑: 2 set_B&set_C ↑↑: 0 -#> 8 ↑↓: 2 0 +#> 8 ↑↓: 2 0 #> ↓↑: 2 #> ↓↓: 2 #> set_C ↑: 1 -#> 6 ↓: 5 +#> 6 ↓: 5 # larger number of items setlist <- make_venn_test(n_items=1000000, sizes=200000, do_signed=TRUE) # text Venn with directionality textvenn(setlist, sets=c(1,2,3), "agreement") -#> set_A&set_B =: 24,013 -#> 31,988 X: 7,975 -#> set_A =: 128,007 set_B =: 128,192 -#> 128,007 128,192 +#> set_A&set_B X: 7,975 +#> 31,988 ‖: 24,013 +#> set_A ‖: 128,007 set_B ‖: 128,192 +#> 128,007 128,192 #> -#> set_A&set_B&set_C =: 4,497 -#> 8,054 X: 3,557 -#> set_A&set_C =: 15,882 set_B&set_C =: 23,863 -#> 31,951 X: 16,069 31,766 X: 7,903 +#> set_A&set_B&set_C X: 3,557 +#> 8,054 ‖: 4,497 +#> set_A&set_C X: 16,069 set_B&set_C X: 7,903 +#> 31,951 ‖: 15,882 31,766 ‖: 23,863 #> #> -#> set_C =: 128,229 -#> 128,229 +#> set_C ‖: 128,229 +#> 128,229 # basic text Venn with directionality textvenn(setlist, sets=c(1,2,3), "each") #> set_A&set_B ↑↑: 11,990 -#> 31,988 ↑↓: 4,007 +#> 31,988 ↑↓: 4,007 #> set_A ↑: 64,078 ↓↑: 3,968 set_B ↑: 63,910 -#> 128,007 ↓: 63,929 ↓↓: 12,023 128,192 ↓: 64,282 +#> 128,007 ↓: 63,929 ↓↓: 12,023 128,192 ↓: 64,282 #> #> set_A&set_B&set_C ↑↑↑: 2,243 ↓↑↑: 757 -#> 8,054 ↑↑↓: 766 ↓↑↓: 243 +#> 8,054 ↑↑↓: 766 ↓↑↓: 243 #> set_A&set_C ↑↑: 7,950 ↑↓↑: 287 ↓↓↑: 756 set_B&set_C ↑↑: 11,919 -#> 31,951 ↑↓: 7,902 ↑↓↓: 748 ↓↓↓: 2,254 31,766 ↑↓: 3,918 +#> 31,951 ↑↓: 7,902 ↑↓↓: 748 ↓↓↓: 2,254 31,766 ↑↓: 3,918 #> ↓↑: 8,167 ↓↑: 3,985 #> ↓↓: 7,932 ↓↓: 11,944 #> set_C ↑: 64,000 -#> 128,229 ↓: 64,229 +#> 128,229 ↓: 64,229
    diff --git a/docs/reference/three_point_angle.html b/docs/reference/three_point_angle.html index 235734e..faa5459 100644 --- a/docs/reference/three_point_angle.html +++ b/docs/reference/three_point_angle.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -78,7 +78,6 @@

    See also

    Other venndir utility: curate_venn_labels(), expand_range(), -get_venn_shapes(), make_color_contrast(), make_venn_combn_df(), make_venn_test(), diff --git a/docs/reference/to_basic.GeomRichText.html b/docs/reference/to_basic.GeomRichText.html index 274833c..787d136 100644 --- a/docs/reference/to_basic.GeomRichText.html +++ b/docs/reference/to_basic.GeomRichText.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900

    diff --git a/docs/reference/to_basic.GeomTextBox.html b/docs/reference/to_basic.GeomTextBox.html index d1a5585..9aa9210 100644 --- a/docs/reference/to_basic.GeomTextBox.html +++ b/docs/reference/to_basic.GeomTextBox.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/union_JamPolygon-1.png b/docs/reference/union_JamPolygon-1.png index 0cd966f..3d234ee 100644 Binary files a/docs/reference/union_JamPolygon-1.png and b/docs/reference/union_JamPolygon-1.png differ diff --git a/docs/reference/union_JamPolygon-2.png b/docs/reference/union_JamPolygon-2.png index c18b9ff..2f51ff9 100644 Binary files a/docs/reference/union_JamPolygon-2.png and b/docs/reference/union_JamPolygon-2.png differ diff --git a/docs/reference/union_JamPolygon.html b/docs/reference/union_JamPolygon.html index 2f4fb3b..9533c38 100644 --- a/docs/reference/union_JamPolygon.html +++ b/docs/reference/union_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -96,6 +96,7 @@

    See also

    diff --git a/docs/reference/update_JamPolygon.html b/docs/reference/update_JamPolygon.html index ccf39b6..cae787a 100644 --- a/docs/reference/update_JamPolygon.html +++ b/docs/reference/update_JamPolygon.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -77,6 +77,7 @@

    See also

    diff --git a/docs/reference/venn_meme-1.png b/docs/reference/venn_meme-1.png index 077e2d0..a61d74f 100644 Binary files a/docs/reference/venn_meme-1.png and b/docs/reference/venn_meme-1.png differ diff --git a/docs/reference/venn_meme-2.png b/docs/reference/venn_meme-2.png index 3bc108b..73f8fc7 100644 Binary files a/docs/reference/venn_meme-2.png and b/docs/reference/venn_meme-2.png differ diff --git a/docs/reference/venn_meme-3.png b/docs/reference/venn_meme-3.png index fc38324..07ad0f2 100644 Binary files a/docs/reference/venn_meme-3.png and b/docs/reference/venn_meme-3.png differ diff --git a/docs/reference/venn_meme-4.png b/docs/reference/venn_meme-4.png index d9ff91b..fb8aa5a 100644 Binary files a/docs/reference/venn_meme-4.png and b/docs/reference/venn_meme-4.png differ diff --git a/docs/reference/venn_meme-5.png b/docs/reference/venn_meme-5.png index 72af584..45a2133 100644 Binary files a/docs/reference/venn_meme-5.png and b/docs/reference/venn_meme-5.png differ diff --git a/docs/reference/venn_meme-6.png b/docs/reference/venn_meme-6.png index 962b5e6..06b056d 100644 Binary files a/docs/reference/venn_meme-6.png and b/docs/reference/venn_meme-6.png differ diff --git a/docs/reference/venn_meme-7.png b/docs/reference/venn_meme-7.png index 3128b3b..737b8f9 100644 Binary files a/docs/reference/venn_meme-7.png and b/docs/reference/venn_meme-7.png differ diff --git a/docs/reference/venn_meme-8.png b/docs/reference/venn_meme-8.png index 1afba4b..6c83c5c 100644 Binary files a/docs/reference/venn_meme-8.png and b/docs/reference/venn_meme-8.png differ diff --git a/docs/reference/venn_meme-9.png b/docs/reference/venn_meme-9.png index 81026a4..8d52c61 100644 Binary files a/docs/reference/venn_meme-9.png and b/docs/reference/venn_meme-9.png differ diff --git a/docs/reference/venn_meme.html b/docs/reference/venn_meme.html index f9a6524..4194faf 100644 --- a/docs/reference/venn_meme.html +++ b/docs/reference/venn_meme.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/venndir-1.png b/docs/reference/venndir-1.png index b765297..a72660c 100644 Binary files a/docs/reference/venndir-1.png and b/docs/reference/venndir-1.png differ diff --git a/docs/reference/venndir-2.png b/docs/reference/venndir-2.png index 776f173..04dff55 100644 Binary files a/docs/reference/venndir-2.png and b/docs/reference/venndir-2.png differ diff --git a/docs/reference/venndir-3.png b/docs/reference/venndir-3.png index 6cf66a6..64a38e5 100644 Binary files a/docs/reference/venndir-3.png and b/docs/reference/venndir-3.png differ diff --git a/docs/reference/venndir-4.png b/docs/reference/venndir-4.png index dadf02e..d5a0341 100644 Binary files a/docs/reference/venndir-4.png and b/docs/reference/venndir-4.png differ diff --git a/docs/reference/venndir-5.png b/docs/reference/venndir-5.png index 5ec5922..3b3f747 100644 Binary files a/docs/reference/venndir-5.png and b/docs/reference/venndir-5.png differ diff --git a/docs/reference/venndir.html b/docs/reference/venndir.html index cf64c08..54c30e8 100644 --- a/docs/reference/venndir.html +++ b/docs/reference/venndir.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -79,7 +79,7 @@

    Directional Venn diagram

    font_cex = c(1, 1, 0.8), show_label = NA, display_counts = TRUE, - poly_alpha = 0.8, + poly_alpha = 0.6, alpha_by_counts = FALSE, label_style = c("basic", "fill", "shaded", "shaded_box", "lite", "lite_box"), label_preset = "none", @@ -100,6 +100,7 @@

    Directional Venn diagram

    verbose = FALSE, debug = 0, circle_nudge = NULL, + lwd = 1, rotate_degrees = 0, ... )
    @@ -225,7 +226,7 @@

    Arguments

    poly_alpha
    -

    numeric (default 0.8) value between 0 and 1, for +

    numeric (default 0.6) value between 0 and 1, for alpha transparency of the polygon fill color. This value is ignored when alpha_by_counts=TRUE.

    • poly_alpha=1 is completely opaque (no transparency)

    • poly_alpha=0.8 is 80% opaque

    • diff --git a/docs/reference/venndir_label_style.html b/docs/reference/venndir_label_style.html index 0ddd0cb..53a9ac7 100644 --- a/docs/reference/venndir_label_style.html +++ b/docs/reference/venndir_label_style.html @@ -17,7 +17,7 @@ venndir - 0.0.37.900 + 0.0.39.900 diff --git a/docs/reference/venndir_legender-1.png b/docs/reference/venndir_legender-1.png index b765297..a72660c 100644 Binary files a/docs/reference/venndir_legender-1.png and b/docs/reference/venndir_legender-1.png differ diff --git a/docs/reference/venndir_legender-2.png b/docs/reference/venndir_legender-2.png index 2a2579f..6cbc83e 100644 Binary files a/docs/reference/venndir_legender-2.png and b/docs/reference/venndir_legender-2.png differ diff --git a/docs/reference/venndir_legender-3.png b/docs/reference/venndir_legender-3.png index 2a2579f..6cbc83e 100644 Binary files a/docs/reference/venndir_legender-3.png and b/docs/reference/venndir_legender-3.png differ diff --git a/docs/reference/venndir_legender-4.png b/docs/reference/venndir_legender-4.png index 4322c48..78aa641 100644 Binary files a/docs/reference/venndir_legender-4.png and b/docs/reference/venndir_legender-4.png differ diff --git a/docs/reference/venndir_legender-5.png b/docs/reference/venndir_legender-5.png index 3ccfe00..9d5bc01 100644 Binary files a/docs/reference/venndir_legender-5.png and b/docs/reference/venndir_legender-5.png differ diff --git a/docs/reference/venndir_legender-6.png b/docs/reference/venndir_legender-6.png index 795e233..5bc9322 100644 Binary files a/docs/reference/venndir_legender-6.png and b/docs/reference/venndir_legender-6.png differ diff --git a/docs/reference/venndir_legender-7.png b/docs/reference/venndir_legender-7.png index 090d1e3..ca1e2bb 100644 Binary files a/docs/reference/venndir_legender-7.png and b/docs/reference/venndir_legender-7.png differ diff --git a/docs/reference/venndir_legender-8.png b/docs/reference/venndir_legender-8.png index fb0d5fb..20a1367 100644 Binary files a/docs/reference/venndir_legender-8.png and b/docs/reference/venndir_legender-8.png differ diff --git a/docs/reference/venndir_legender.html b/docs/reference/venndir_legender.html index cb2ae9e..f3832b1 100644 --- a/docs/reference/venndir_legender.html +++ b/docs/reference/venndir_legender.html @@ -19,7 +19,7 @@ venndir - 0.0.37.900 + 0.0.39.900 @@ -271,7 +271,6 @@

      See also

      Other venndir utility: curate_venn_labels(), expand_range(), -get_venn_shapes(), make_color_contrast(), make_venn_combn_df(), make_venn_test(), diff --git a/docs/reference/venndir_to_df-1.png b/docs/reference/venndir_to_df-1.png index 7481a00..4609c63 100644 Binary files a/docs/reference/venndir_to_df-1.png and b/docs/reference/venndir_to_df-1.png differ diff --git a/docs/reference/venndir_to_df.html b/docs/reference/venndir_to_df.html index 2615f5c..1b0cacf 100644 --- a/docs/reference/venndir_to_df.html +++ b/docs/reference/venndir_to_df.html @@ -18,7 +18,7 @@ venndir - 0.0.37.900 + 0.0.39.900

      @@ -67,11 +67,15 @@

      Convert venndir output to data.frame

      venndir_to_df(
         venndir_out,
      -  return_type = c("kable", "data.frame"),
      +  df_format = c("hits", "items", "wide"),
      +  return_type = c("data.frame", "kable"),
         trim_blanks = TRUE,
         wrap_width = 80,
         colorize_headers = TRUE,
         set_colors = NULL,
      +  item_type = "gene",
      +  add_counts = TRUE,
      +  verbose = FALSE,
         ...
       )
      @@ -129,7 +133,6 @@

      See also

      Other venndir utility: curate_venn_labels(), expand_range(), -get_venn_shapes(), make_color_contrast(), make_venn_combn_df(), make_venn_test(), @@ -143,111 +146,651 @@

      See also

      Examples

      -
      setlist <- venndir::make_venn_test(100, 3);
      +    
      setlist <- venndir::make_venn_test(100, 3, do_signed=TRUE);
       venndir_out <- venndir::venndir(setlist, overlap_type="each")
       
      -kdf <- venndir_to_df(venndir_out)
      +df <- venndir_to_df(venndir_out)
      +head(df, 10)
      +#>              gene set_A set_B set_C
      +#> item_042 item_042     1     0     0
      +#> item_057 item_057     1     0     0
      +#> item_026 item_026     1     0     0
      +#> item_083 item_083     1     0     0
      +#> item_036 item_036     1     0     0
      +#> item_078 item_078     1     0     0
      +#> item_032 item_032     1     0     0
      +#> item_084 item_084     1     0     0
      +#> item_023 item_023     1     0     0
      +#> item_067 item_067    -1     0     0
      +
      +kdf <- venndir_to_df(venndir_out, return_type="kable")
       kdf
       #> <table class="table" style="margin-left: auto; margin-right: auto;">
      +#>  <thead>
      +#>   <tr>
      +#>    <th style="text-align:left;"> gene </th>
      +#>    <th style="text-align:right;"> set_A </th>
      +#>    <th style="text-align:right;"> set_B </th>
      +#>    <th style="text-align:right;"> set_C </th>
      +#>   </tr>
      +#>  </thead>
       #> <tbody>
      -#>   <tr grouplength="3"><td colspan="1" style="background-color: #EEC12EFF;color: #000000FF;color: rgba(0, 0, 0, 1) !important;background-color: rgba(238, 193, 46, 1) !important;"><strong>set_A</strong></td></tr>
      -#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #EEC12EFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 1) !important;background-color: rgba(238, 193, 46, 1) !important;"><strong>set_A   16</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #590000 !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_042 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="2"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #EEC12EFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 1) !important;background-color: rgba(238, 193, 46, 1) !important;"><strong>set_A   ↑: 16</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #A73232 !important;padding-left: 4em;" indentlevel="2"> item_007, item_009, item_014, item_015, item_023, item_026, item_032, item_036, </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_057 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
       #>   <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #A73232 !important;padding-left: 4em;" indentlevel="2"> item_042, item_043, item_057, item_067, item_078, item_083, item_084, item_099 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_026 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="2"><td colspan="1" style="background-color: #D54848FF;color: #FFFFFFFF;color: rgba(255, 255, 255, 1) !important;background-color: rgba(213, 72, 72, 1) !important;"><strong>set_B</strong></td></tr>
      -#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #FFFFFFFF ; background-color: #D54848FF ; text-indent: 1.2em;color: rgba(255, 255, 255, 1) !important;background-color: rgba(213, 72, 72, 1) !important;"><strong>set_B   7</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #590000 !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_083 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #FFFFFFFF ; background-color: #D54848FF ; text-indent: 1.2em;color: rgba(255, 255, 255, 1) !important;background-color: rgba(213, 72, 72, 1) !important;"><strong>set_B   ↑: 7</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #AB4D4D !important;padding-left: 4em;" indentlevel="2"> item_013, item_021, item_034, item_038, item_063, item_082, item_096 </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_036 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="2"><td colspan="1" style="background-color: #9F8DFFFF;color: #000000FF;color: rgba(0, 0, 0, 1) !important;background-color: rgba(159, 141, 255, 1) !important;"><strong>set_C</strong></td></tr>
      -#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #9F8DFFFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 1) !important;background-color: rgba(159, 141, 255, 1) !important;"><strong>set_C   7</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #590000 !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_078 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #9F8DFFFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 1) !important;background-color: rgba(159, 141, 255, 1) !important;"><strong>set_C   ↑: 7</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #A73232 !important;padding-left: 4em;" indentlevel="2"> item_006, item_016, item_031, item_039, item_047, item_081, item_095 </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_032 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="2"><td colspan="1" style="background-color: #CE926CFF;color: #000000FF;color: rgba(0, 0, 0, 1) !important;background-color: rgba(206, 146, 108, 1) !important;"><strong>set_A&amp;set_B</strong></td></tr>
      -#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #CE926CFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 1) !important;background-color: rgba(206, 146, 108, 1) !important;"><strong>set_A&amp;set_B   8</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #590000 !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_084 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #CE926CFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 1) !important;background-color: rgba(206, 146, 108, 1) !important;"><strong>set_A&amp;set_B   ↑↑: 8</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #A73232 !important;padding-left: 4em;" indentlevel="2"> item_025, item_027, item_053, item_069, item_076, item_089, item_093, item_097 </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_023 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="2"><td colspan="1" style="background-color: #79C0A0FF;color: #000000FF;color: rgba(0, 0, 0, 1) !important;background-color: rgba(121, 192, 160, 1) !important;"><strong>set_A&amp;set_C</strong></td></tr>
      -#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #79C0A0FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 1) !important;background-color: rgba(121, 192, 160, 1) !important;"><strong>set_A&amp;set_C   7</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #590000 !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_067 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #79C0A0FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 1) !important;background-color: rgba(121, 192, 160, 1) !important;"><strong>set_A&amp;set_C   ↑↑: 7</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #A73232 !important;padding-left: 4em;" indentlevel="2"> item_041, item_050, item_060, item_079, item_086, item_090, item_091 </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_043 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="1"><td colspan="1" style="background-color: #D162B8FF;color: #FFFFFFFF;color: rgba(255, 255, 255, 1) !important;background-color: rgba(209, 98, 184, 1) !important;"><strong>set_B&amp;set_C</strong></td></tr>
      -#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #FFFFFFFF ; background-color: #D162B8FF ; text-indent: 1.2em;color: rgba(255, 255, 255, 1) !important;background-color: rgba(209, 98, 184, 1) !important;"><strong>set_B&amp;set_C   0</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #590000 !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_014 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="2"><td colspan="1" style="background-color: #BF92A2FF;color: #000000FF;color: rgba(0, 0, 0, 1) !important;background-color: rgba(191, 146, 162, 1) !important;"><strong>set_A&amp;set_B&amp;set_C</strong></td></tr>
      -#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #BF92A2FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 1) !important;background-color: rgba(191, 146, 162, 1) !important;"><strong>set_A&amp;set_B&amp;set_C   1</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #590000 !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_009 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
       #>   </tr>
      -#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #BF92A2FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 1) !important;background-color: rgba(191, 146, 162, 1) !important;"><strong>set_A&amp;set_B&amp;set_C   ↑↑↑: 1</strong></td></tr>
      -#> <tr>
      -#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: #A73232 !important;padding-left: 4em;" indentlevel="2"> item_072 </td>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_007 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_099 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_015 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_096 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_063 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_013 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_082 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_038 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_034 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_021 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_047 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_095 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_016 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_039 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_081 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_006 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_031 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_093 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_076 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_053 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_025 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_097 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_069 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_089 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_027 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_086 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_060 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_050 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_091 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_090 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_041 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_079 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(0, 0, 0, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: transparent !important;">0</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: dodgerblue !important;">-1</span> </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_072 </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
      +#>    <td style="text-align:right;border-left:1px solid #DDDDDD;white-space: nowrap;"> <span style="     color: rgba(255, 255, 255, 255) !important;border-radius: 4px; padding-right: 4px; padding-left: 4px; background-color: rgba(205, 38, 38, 255) !important;">1</span> </td>
       #>   </tr>
       #> </tbody>
       #> </table>
       
      -kdf <- venndir_to_df(venndir_out, return_type="data.frame")
      -kdf
      +df2 <- venndir_to_df(venndir_out, df_format="items")
      +head(df2, 10)
      +#>    set_A (16 genes) set_A&set_B (8 genes) set_B (7 genes) set_B&set_C (0 genes)
      +#> 1          item_042              item_093        item_096                      
      +#> 2          item_057              item_076        item_063                      
      +#> 3          item_026              item_053        item_013                      
      +#> 4          item_083              item_025        item_082                      
      +#> 5          item_036              item_097        item_038                      
      +#> 6          item_078              item_069        item_034                      
      +#> 7          item_032              item_089        item_021                      
      +#> 8          item_084              item_027                                      
      +#> 9          item_023                                                            
      +#> 10         item_067                                                            
      +#>    set_C (7 genes) set_A&set_C (7 genes) set_A&set_B&set_C (1 gene)
      +#> 1         item_047              item_086                   item_072
      +#> 2         item_095              item_060                           
      +#> 3         item_016              item_050                           
      +#> 4         item_039              item_091                           
      +#> 5         item_081              item_090                           
      +#> 6         item_006              item_041                           
      +#> 7         item_031              item_079                           
      +#> 8                                                                  
      +#> 9                                                                  
      +#> 10                                                                 
      +
      +kdf2 <- venndir_to_df(venndir_out, df_format="items", return_type="kable")
      +kdf2
      +#> <table class="table" style="margin-left: auto; margin-right: auto;">
      +#>  <thead>
      +#>   <tr>
      +#>    <th style="text-align:left;"> set_A (16 genes) </th>
      +#>    <th style="text-align:left;"> set_A&amp;set_B (8 genes) </th>
      +#>    <th style="text-align:left;"> set_B (7 genes) </th>
      +#>    <th style="text-align:left;"> set_B&amp;set_C (0 genes) </th>
      +#>    <th style="text-align:left;"> set_C (7 genes) </th>
      +#>    <th style="text-align:left;"> set_A&amp;set_C (7 genes) </th>
      +#>    <th style="text-align:left;"> set_A&amp;set_B&amp;set_C (1 gene) </th>
      +#>   </tr>
      +#>  </thead>
      +#> <tbody>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_042 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_093 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_096 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_047 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_086 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_072 </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_057 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_076 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_063 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_095 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_060 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_026 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_053 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_013 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_016 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_050 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_083 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_025 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_082 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_039 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_091 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_036 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_097 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_038 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_081 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_090 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_078 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_069 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_034 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_006 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_041 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_032 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_089 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_021 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_031 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_079 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_084 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_027 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_023 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_067 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_043 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_014 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_009 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_007 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_099 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;"> item_015 </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;">  </td>
      +#>   </tr>
      +#> </tbody>
      +#> </table>
      +
      +df3 <- venndir_to_df(venndir_out, df_format="wide", return_type="data.frame")
      +df3
       #>                               overlap_set   text            overlap_sign
       #> set_A                               set_A     16                        
      -#> set_A.1                             set_A  ↑: 16             set_A|1 0 0
      -#> set_A.1.1                           set_A  ↑: 16             set_A|1 0 0
      +#> set_A.1                             set_A   ↑: 9             set_A|1 0 0
      +#> set_A.1.1                           set_A   ↑: 9             set_A|1 0 0
      +#> set_A.-1                            set_A   ↓: 7            set_A|-1 0 0
       #> set_B                               set_B      7                        
      -#> set_B.1                             set_B   ↑: 7             set_B|0 1 0
      +#> set_B.1                             set_B   ↑: 4             set_B|0 1 0
      +#> set_B.-1                            set_B   ↓: 3            set_B|0 -1 0
       #> set_C                               set_C      7                        
      -#> set_C.1                             set_C   ↑: 7             set_C|0 0 1
      +#> set_C.1                             set_C   ↑: 5             set_C|0 0 1
      +#> set_C.-1                            set_C   ↓: 2            set_C|0 0 -1
       #> set_A&set_B                   set_A&set_B      8                        
      -#> set_A&set_B.1 1               set_A&set_B  ↑↑: 8       set_A&set_B|1 1 0
      +#> set_A&set_B.1 1               set_A&set_B  ↑↑: 3       set_A&set_B|1 1 0
      +#> set_A&set_B.1 -1              set_A&set_B  ↑↓: 2      set_A&set_B|1 -1 0
      +#> set_A&set_B.-1 -1             set_A&set_B  ↓↓: 3     set_A&set_B|-1 -1 0
       #> set_A&set_C                   set_A&set_C      7                        
      -#> set_A&set_C.1 1               set_A&set_C  ↑↑: 7       set_A&set_C|1 0 1
      +#> set_A&set_C.1 1               set_A&set_C  ↑↑: 2       set_A&set_C|1 0 1
      +#> set_A&set_C.1 -1              set_A&set_C  ↑↓: 1      set_A&set_C|1 0 -1
      +#> set_A&set_C.-1 1              set_A&set_C  ↓↑: 1      set_A&set_C|-1 0 1
      +#> set_A&set_C.-1 -1             set_A&set_C  ↓↓: 3     set_A&set_C|-1 0 -1
       #> set_B&set_C                   set_B&set_C      0                        
       #> set_A&set_B&set_C       set_A&set_B&set_C      1                        
       #> set_A&set_B&set_C.1 1 1 set_A&set_B&set_C ↑↑↑: 1 set_A&set_B&set_C|1 1 1
       #>                                                                                                   items
       #> set_A                                                                                                  
      -#> set_A.1                 item_007, item_009, item_014, item_015, item_023, item_026, item_032, item_036,
      -#> set_A.1.1                item_042, item_043, item_057, item_067, item_078, item_083, item_084, item_099
      +#> set_A.1                 item_023, item_026, item_032, item_036, item_042, item_057, item_078, item_083,
      +#> set_A.1.1                                                                                      item_084
      +#> set_A.-1                           item_007, item_009, item_014, item_015, item_043, item_067, item_099
       #> set_B                                                                                                  
      -#> set_B.1                            item_013, item_021, item_034, item_038, item_063, item_082, item_096
      +#> set_B.1                                                          item_013, item_063, item_082, item_096
      +#> set_B.-1                                                                   item_021, item_034, item_038
       #> set_C                                                                                                  
      -#> set_C.1                            item_006, item_016, item_031, item_039, item_047, item_081, item_095
      +#> set_C.1                                                item_016, item_039, item_047, item_081, item_095
      +#> set_C.-1                                                                             item_006, item_031
       #> set_A&set_B                                                                                            
      -#> set_A&set_B.1 1          item_025, item_027, item_053, item_069, item_076, item_089, item_093, item_097
      +#> set_A&set_B.1 1                                                            item_053, item_076, item_093
      +#> set_A&set_B.1 -1                                                                     item_025, item_097
      +#> set_A&set_B.-1 -1                                                          item_027, item_069, item_089
       #> set_A&set_C                                                                                            
      -#> set_A&set_C.1 1                    item_041, item_050, item_060, item_079, item_086, item_090, item_091
      +#> set_A&set_C.1 1                                                                      item_060, item_086
      +#> set_A&set_C.1 -1                                                                               item_050
      +#> set_A&set_C.-1 1                                                                               item_091
      +#> set_A&set_C.-1 -1                                                          item_041, item_079, item_090
       #> set_B&set_C                                                                                            
       #> set_A&set_B&set_C                                                                                      
       #> set_A&set_B&set_C.1 1 1                                                                        item_072
       
      +kdf3 <- venndir_to_df(venndir_out, df_format="wide", return_type="kable")
      +kdf3
      +#> <table class="table" style="margin-left: auto; margin-right: auto;">
      +#> <tbody>
      +#>   <tr grouplength="4"><td colspan="1" style="background-color: #EEC12EFF;color: #000000FF;color: rgba(0, 0, 0, 255) !important;background-color: rgba(238, 193, 46, 255) !important;"><strong>set_A</strong></td></tr>
      +#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #EEC12EFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(238, 193, 46, 255) !important;"><strong>set_A   16</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(89, 0, 0, 255) !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   </tr>
      +#>   <tr grouplength="2"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #EEC12EFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(238, 193, 46, 255) !important;"><strong>set_A   ↑: 9</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(167, 50, 50, 255) !important;padding-left: 4em;" indentlevel="2"> item_023, item_026, item_032, item_036, item_042, item_057, item_078, item_083, </td>
      +#>   </tr>
      +#>   <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(167, 50, 50, 255) !important;padding-left: 4em;" indentlevel="2"> item_084 </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #EEC12EFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(238, 193, 46, 255) !important;"><strong>set_A   ↓: 7</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(0, 96, 191, 255) !important;padding-left: 4em;" indentlevel="2"> item_007, item_009, item_014, item_015, item_043, item_067, item_099 </td>
      +#>   </tr>
      +#>   <tr grouplength="3"><td colspan="1" style="background-color: #D54848FF;color: #FFFFFFFF;color: rgba(255, 255, 255, 255) !important;background-color: rgba(213, 72, 72, 255) !important;"><strong>set_B</strong></td></tr>
      +#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #FFFFFFFF ; background-color: #D54848FF ; text-indent: 1.2em;color: rgba(255, 255, 255, 255) !important;background-color: rgba(213, 72, 72, 255) !important;"><strong>set_B   7</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(89, 0, 0, 255) !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #FFFFFFFF ; background-color: #D54848FF ; text-indent: 1.2em;color: rgba(255, 255, 255, 255) !important;background-color: rgba(213, 72, 72, 255) !important;"><strong>set_B   ↑: 4</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(167, 50, 50, 255) !important;padding-left: 4em;" indentlevel="2"> item_013, item_063, item_082, item_096 </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #FFFFFFFF ; background-color: #D54848FF ; text-indent: 1.2em;color: rgba(255, 255, 255, 255) !important;background-color: rgba(213, 72, 72, 255) !important;"><strong>set_B   ↓: 3</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(0, 96, 191, 255) !important;padding-left: 4em;" indentlevel="2"> item_021, item_034, item_038 </td>
      +#>   </tr>
      +#>   <tr grouplength="3"><td colspan="1" style="background-color: #9F8DFFFF;color: #000000FF;color: rgba(0, 0, 0, 255) !important;background-color: rgba(159, 141, 255, 255) !important;"><strong>set_C</strong></td></tr>
      +#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #9F8DFFFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(159, 141, 255, 255) !important;"><strong>set_C   7</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(89, 0, 0, 255) !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #9F8DFFFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(159, 141, 255, 255) !important;"><strong>set_C   ↑: 5</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(167, 50, 50, 255) !important;padding-left: 4em;" indentlevel="2"> item_016, item_039, item_047, item_081, item_095 </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #9F8DFFFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(159, 141, 255, 255) !important;"><strong>set_C   ↓: 2</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(0, 96, 191, 255) !important;padding-left: 4em;" indentlevel="2"> item_006, item_031 </td>
      +#>   </tr>
      +#>   <tr grouplength="4"><td colspan="1" style="background-color: #CE926CFF;color: #000000FF;color: rgba(0, 0, 0, 255) !important;background-color: rgba(206, 146, 108, 255) !important;"><strong>set_A&amp;set_B</strong></td></tr>
      +#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #CE926CFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(206, 146, 108, 255) !important;"><strong>set_A&amp;set_B   8</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(89, 0, 0, 255) !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #CE926CFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(206, 146, 108, 255) !important;"><strong>set_A&amp;set_B   ↑↑: 3</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(167, 50, 50, 255) !important;padding-left: 4em;" indentlevel="2"> item_053, item_076, item_093 </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #CE926CFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(206, 146, 108, 255) !important;"><strong>set_A&amp;set_B   ↑↓: 2</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(171, 0, 162, 255) !important;padding-left: 4em;" indentlevel="2"> item_025, item_097 </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #CE926CFF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(206, 146, 108, 255) !important;"><strong>set_A&amp;set_B   ↓↓: 3</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(0, 96, 191, 255) !important;padding-left: 4em;" indentlevel="2"> item_027, item_069, item_089 </td>
      +#>   </tr>
      +#>   <tr grouplength="5"><td colspan="1" style="background-color: #79C0A0FF;color: #000000FF;color: rgba(0, 0, 0, 255) !important;background-color: rgba(121, 192, 160, 255) !important;"><strong>set_A&amp;set_C</strong></td></tr>
      +#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #79C0A0FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(121, 192, 160, 255) !important;"><strong>set_A&amp;set_C   7</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(89, 0, 0, 255) !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #79C0A0FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(121, 192, 160, 255) !important;"><strong>set_A&amp;set_C   ↑↑: 2</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(167, 50, 50, 255) !important;padding-left: 4em;" indentlevel="2"> item_060, item_086 </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #79C0A0FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(121, 192, 160, 255) !important;"><strong>set_A&amp;set_C   ↑↓: 1</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(171, 0, 162, 255) !important;padding-left: 4em;" indentlevel="2"> item_050 </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #79C0A0FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(121, 192, 160, 255) !important;"><strong>set_A&amp;set_C   ↓↑: 1</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(171, 0, 162, 255) !important;padding-left: 4em;" indentlevel="2"> item_091 </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #79C0A0FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(121, 192, 160, 255) !important;"><strong>set_A&amp;set_C   ↓↓: 3</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(0, 96, 191, 255) !important;padding-left: 4em;" indentlevel="2"> item_041, item_079, item_090 </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="background-color: #D162B8FF;color: #FFFFFFFF;color: rgba(255, 255, 255, 255) !important;background-color: rgba(209, 98, 184, 255) !important;"><strong>set_B&amp;set_C</strong></td></tr>
      +#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #FFFFFFFF ; background-color: #D162B8FF ; text-indent: 1.2em;color: rgba(255, 255, 255, 255) !important;background-color: rgba(209, 98, 184, 255) !important;"><strong>set_B&amp;set_C   0</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(89, 0, 0, 255) !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   </tr>
      +#>   <tr grouplength="2"><td colspan="1" style="background-color: #BF92A2FF;color: #000000FF;color: rgba(0, 0, 0, 255) !important;background-color: rgba(191, 146, 162, 255) !important;"><strong>set_A&amp;set_B&amp;set_C</strong></td></tr>
      +#> <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #BF92A2FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(191, 146, 162, 255) !important;"><strong>set_A&amp;set_B&amp;set_C   1</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(89, 0, 0, 255) !important;padding-left: 4em;" indentlevel="2">  </td>
      +#>   </tr>
      +#>   <tr grouplength="1"><td colspan="1" style="border-bottom: 1px solid; border-bottom-color: #000; color: #000000FF ; background-color: #BF92A2FF ; text-indent: 1.2em;color: rgba(0, 0, 0, 255) !important;background-color: rgba(191, 146, 162, 255) !important;"><strong>set_A&amp;set_B&amp;set_C   ↑↑↑: 1</strong></td></tr>
      +#> <tr>
      +#>    <td style="text-align:left;border-left:1px solid #DDDDDD;white-space: nowrap;color: rgba(167, 50, 50, 255) !important;padding-left: 4em;" indentlevel="2"> item_072 </td>
      +#>   </tr>
      +#> </tbody>
      +#> </table>
      +
       
      diff --git a/docs/sitemap.xml b/docs/sitemap.xml index 1d6f9e0..cdd1bf6 100644 --- a/docs/sitemap.xml +++ b/docs/sitemap.xml @@ -36,6 +36,9 @@ /reference/JamPolygon-class.html + + /reference/JamPolygon-methods.html + /reference/Venndir-class.html @@ -207,6 +210,9 @@ /reference/nearest_point_JamPolygon.html + + /reference/nudge_JamPolygon.html + /reference/nudge_polygon_coords.html diff --git a/man/JamPolygon-class.Rd b/man/JamPolygon-class.Rd index 1c7551a..5e8109c 100644 --- a/man/JamPolygon-class.Rd +++ b/man/JamPolygon-class.Rd @@ -5,7 +5,8 @@ \alias{JamPolygon-class} \title{JamPolygon class} \description{ -JamPolygon class +JamPolygon class contains one slot \code{"polygons"} which is a \code{data.frame} +with one polygon per row. An individual polygon can } \examples{ df <- data.frame(name=c("polygon1", "polygon2"), @@ -24,6 +25,7 @@ jpdf <- new("JamPolygon", polygons=df); \seealso{ Other JamPolygon: \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -41,10 +43,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/plot-JamPolygon-missing-method.Rd b/man/JamPolygon-methods.Rd similarity index 55% rename from man/plot-JamPolygon-missing-method.Rd rename to man/JamPolygon-methods.Rd index 5a8cc20..c3ff53a 100644 --- a/man/plot-JamPolygon-missing-method.Rd +++ b/man/JamPolygon-methods.Rd @@ -1,29 +1,39 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/JamPolygon.R -\name{plot,JamPolygon,missing-method} +\docType{methods} +\name{[,JamPolygon-method} +\alias{[,JamPolygon-method} \alias{plot,JamPolygon,missing-method} -\title{Plot JamPolygon object} +\alias{rbind2.JamPolygon} +\alias{rbind2,JamPolygon,ANY-method} +\title{Subset JamPolygon object} \usage{ +\S4method{[}{JamPolygon}(x, i, j, ..., drop = TRUE) + \S4method{plot}{JamPolygon,missing}(x, y, ...) + +rbind2.JamPolygon(x, y, ...) + +\S4method{rbind2}{JamPolygon,ANY}(x, y, ...) +} +\arguments{ +\item{x, y}{\code{JamPolygon} object} + +\item{...}{additional \code{JamPolygon} objects if present} } \value{ \code{JamPolygon} object, invisibly. } \description{ Plot JamPolygon object + +Combine multiple JamPolygon objects, given two JamPolygon or multiple +objects in a list. } \details{ -Todo: -\itemize{ -\item Consider re-factoring so that inner/outer borders are rendered -in proper order, immediately after each polygon is drawn. -This change means the polygons can no longer be rendered in -vectorized fashion, since each polygon should have the opportunity -to overlap existing polygons and their borders. -\item Implement method to render inner and outer borders where defined. -Currently only the outer border is rendered. -\item Consider disabling the thin black border by default. -} +This function is intended to support input as \code{rbind2(list(JamPolygons))} +or \code{do.call(rbind2.JamPolygon, list(JamPolygons))} with any +combination of one or more \code{JamPolygon} objects. } \examples{ dfx <- data.frame(name=c("polygon1", "polygon2"), @@ -86,9 +96,43 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, +\code{\link{nudge_JamPolygon}()}, +\code{\link{plot.JamPolygon}()}, +\code{\link{point_in_JamPolygon}()}, +\code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, +\code{\link{sample_JamPolygon}()}, +\code{\link{split_JamPolygon}()}, +\code{\link{union_JamPolygon}()}, +\code{\link{update_JamPolygon}()} + +Other JamPolygon: +\code{\link{JamPolygon-class}}, +\code{\link{Venndir-class}}, +\code{\link{add_orientation_JamPolygon}()}, +\code{\link{area_JamPolygon}()}, +\code{\link{bbox_JamPolygon}()}, +\code{\link{buffer_JamPolygon}()}, +\code{\link{check_JamPolygon}()}, +\code{\link{check_Venndir}()}, +\code{\link{eulerr_to_JamPolygon}()}, +\code{\link{farthest_point_JamPolygon}()}, +\code{\link{find_venn_overlaps_JamPolygon}()}, +\code{\link{has_point_in_JamPolygon}()}, +\code{\link{intersect_JamPolygon}()}, +\code{\link{label_fill_JamPolygon}()}, +\code{\link{label_outside_JamPolygon}()}, +\code{\link{label_segment_JamPolygon}()}, +\code{\link{labelr_JamPolygon}()}, +\code{\link{minus_JamPolygon}()}, +\code{\link{nearest_point_JamPolygon}()}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/Venndir-class.Rd b/man/Venndir-class.Rd index a1fd0b2..a5ebc62 100644 --- a/man/Venndir-class.Rd +++ b/man/Venndir-class.Rd @@ -91,6 +91,7 @@ That said, \code{setlist} can be an empty \code{list()}. \seealso{ Other JamPolygon: \code{\link{JamPolygon-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -108,10 +109,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/add_orientation_JamPolygon.Rd b/man/add_orientation_JamPolygon.Rd index 369fd75..d1d8888 100644 --- a/man/add_orientation_JamPolygon.Rd +++ b/man/add_orientation_JamPolygon.Rd @@ -95,6 +95,7 @@ add_orientation_JamPolygon(jp3, Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, \code{\link{buffer_JamPolygon}()}, @@ -111,10 +112,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/area_JamPolygon.Rd b/man/area_JamPolygon.Rd index f582c8e..73f3d2a 100644 --- a/man/area_JamPolygon.Rd +++ b/man/area_JamPolygon.Rd @@ -106,6 +106,7 @@ plot(jp3) Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, \code{\link{buffer_JamPolygon}()}, @@ -122,10 +123,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/bbox_JamPolygon.Rd b/man/bbox_JamPolygon.Rd index c700e67..2052f0f 100644 --- a/man/bbox_JamPolygon.Rd +++ b/man/bbox_JamPolygon.Rd @@ -18,6 +18,7 @@ Bounding box for JamPolygon Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{buffer_JamPolygon}()}, @@ -34,10 +35,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/bbox_polygon_list.Rd b/man/bbox_polygon_list.Rd deleted file mode 100644 index cd89964..0000000 --- a/man/bbox_polygon_list.Rd +++ /dev/null @@ -1,40 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{bbox_polygon_list} -\alias{bbox_polygon_list} -\title{Bounding box for polygon list} -\usage{ -bbox_polygon_list(polygon_list, ...) -} -\description{ -Bounding box for polygon list -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3, C=5, `B&C`=2, `A&C`=2, `A&B&C`=1) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) -bbox_polygon_list(polygon_list) - -} -\seealso{ -Other venndir polygons: -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/buffer_JamPolygon.Rd b/man/buffer_JamPolygon.Rd index 9b5c4c8..499ff40 100644 --- a/man/buffer_JamPolygon.Rd +++ b/man/buffer_JamPolygon.Rd @@ -7,7 +7,7 @@ buffer_JamPolygon( jp, buffer = -0.5, - steps = 50, + steps = 200, relative = TRUE, verbose = FALSE, ... @@ -20,14 +20,51 @@ one overall buffer can be provided.} \item{buffer}{\code{numeric} buffer, where negative values cause the polygon to be reduced in size.} + +\item{steps}{\code{numeric} number of steps, default 200, used to +determine relative unit sizes when \code{relative=TRUE} (which is default).} + +\item{relative}{\code{logical} default \code{TRUE}, indicating whether to resize +polygons using relative dimensions. Relative units are defined by +the minimum negative buffer that results in non-zero area, where +relative unit -1 would result in zero area.} + +\item{verbose}{\code{logical} indicating whether to print verbose output.} + +\item{...}{additional arguments are ignored.} +} +\value{ +\code{JamPolygon} with one polygon, although the polygon could +contain multiple disconnected parts. } \description{ Apply buffer outside or inside JamPolygon +} +\examples{ +DEdf <- data.frame(check.names=FALSE, + name=c("D", "E"), + x=I(list( + c(-3, 3, 3, 0, -3), + c(-4, 2, 2, -4))), + y=I(list( + c(-3, -3, 1.5, 4, 1.5), + c(-2, -2, 4, 4))), +fill=c("#FFD70055", "#B2222255")) +jp <- new("JamPolygon", polygons=DEdf) +plot(jp) + +jp2 <- nudge_JamPolygon(jp, nudge=list(D=c(10, 0))); +jp_jp2 <- rbind2(jp2, buffer_JamPolygon(jp2)); +plot(jp_jp2, + border.lty=c(1, 1, 2), + fill=c(NA, NA, "gold")); + } \seealso{ Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -44,10 +81,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/check_JamPolygon.Rd b/man/check_JamPolygon.Rd index 5e0b742..4ff341c 100644 --- a/man/check_JamPolygon.Rd +++ b/man/check_JamPolygon.Rd @@ -36,6 +36,7 @@ empty polygons and handle or ignore them accordingly. Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -52,10 +53,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/check_Venndir.Rd b/man/check_Venndir.Rd index 6107444..e454156 100644 --- a/man/check_Venndir.Rd +++ b/man/check_Venndir.Rd @@ -23,6 +23,7 @@ Check Venndir object integrity Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -39,10 +40,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/curate_venn_labels.Rd b/man/curate_venn_labels.Rd index 2b425f5..1b68c4c 100644 --- a/man/curate_venn_labels.Rd +++ b/man/curate_venn_labels.Rd @@ -107,7 +107,6 @@ jamba::printDebug(as.list(curate_venn_labels(venn_labels, "sign")), \seealso{ Other venndir utility: \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_combn_df}()}, \code{\link{make_venn_test}()}, diff --git a/man/eulerr_to_JamPolygon.Rd b/man/eulerr_to_JamPolygon.Rd index abb57a5..11b64e1 100644 --- a/man/eulerr_to_JamPolygon.Rd +++ b/man/eulerr_to_JamPolygon.Rd @@ -16,6 +16,7 @@ Convert eulerr output to JamPolygon Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -32,10 +33,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/eulerr_to_polygon_list.Rd b/man/eulerr_to_polygon_list.Rd deleted file mode 100644 index 250b1d7..0000000 --- a/man/eulerr_to_polygon_list.Rd +++ /dev/null @@ -1,55 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{eulerr_to_polygon_list} -\alias{eulerr_to_polygon_list} -\title{Convert euler output to polygons} -\usage{ -eulerr_to_polygon_list(x) -} -\arguments{ -\item{x}{output from \code{eulerr::euler()}} -} -\value{ -\code{list} polygon object with one polygon -for each Euler circle or ellipse. - -\code{list} with polygons for each unique set defined by \code{names(x)}, -where each list contains \code{numeric} vectors named \code{"x"} and \code{"y"}. -} -\description{ -Convert euler output to polygons -} -\details{ -This function takes the output from \code{eulerr::euler()} and -converts it to polygons in \code{list} format. -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) - -polygon_areas(polygon_list) - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/expand_range.Rd b/man/expand_range.Rd index b361581..da7d5de 100644 --- a/man/expand_range.Rd +++ b/man/expand_range.Rd @@ -83,7 +83,6 @@ expand_range(list(xlim=xlim, ylim=ylim)) \seealso{ Other venndir utility: \code{\link{curate_venn_labels}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_combn_df}()}, \code{\link{make_venn_test}()}, diff --git a/man/farthest_point_JamPolygon.Rd b/man/farthest_point_JamPolygon.Rd index 13dc300..c623e2e 100644 --- a/man/farthest_point_JamPolygon.Rd +++ b/man/farthest_point_JamPolygon.Rd @@ -23,6 +23,7 @@ Get the farthest polygon point from a reference point Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -39,10 +40,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/figures/README-label_preset_1-1.png b/man/figures/README-label_preset_1-1.png index b2c1ab0..ace3800 100644 Binary files a/man/figures/README-label_preset_1-1.png and b/man/figures/README-label_preset_1-1.png differ diff --git a/man/figures/README-label_preset_1l-1.png b/man/figures/README-label_preset_1l-1.png index cdf3725..5d9367b 100644 Binary files a/man/figures/README-label_preset_1l-1.png and b/man/figures/README-label_preset_1l-1.png differ diff --git a/man/figures/README-nudge_1-1.png b/man/figures/README-nudge_1-1.png index 593a4d1..427a9d9 100644 Binary files a/man/figures/README-nudge_1-1.png and b/man/figures/README-nudge_1-1.png differ diff --git a/man/figures/README-nudge_2-1.png b/man/figures/README-nudge_2-1.png index c952c2f..b4ecc05 100644 Binary files a/man/figures/README-nudge_2-1.png and b/man/figures/README-nudge_2-1.png differ diff --git a/man/figures/README-venn_1-1.png b/man/figures/README-venn_1-1.png index e2b5cb9..66abe7d 100644 Binary files a/man/figures/README-venn_1-1.png and b/man/figures/README-venn_1-1.png differ diff --git a/man/figures/README-venn_1e-1.png b/man/figures/README-venn_1e-1.png index aaa15ad..4eefde9 100644 Binary files a/man/figures/README-venn_1e-1.png and b/man/figures/README-venn_1e-1.png differ diff --git a/man/figures/README-venn_intro-1.png b/man/figures/README-venn_intro-1.png index 7d3f0c3..7efe386 100644 Binary files a/man/figures/README-venn_intro-1.png and b/man/figures/README-venn_intro-1.png differ diff --git a/man/figures/README-venndir_1-1.png b/man/figures/README-venndir_1-1.png index 4d76601..c2b6340 100644 Binary files a/man/figures/README-venndir_1-1.png and b/man/figures/README-venndir_1-1.png differ diff --git a/man/figures/README-venndir_agreement-1.png b/man/figures/README-venndir_agreement-1.png index f7eaf9b..a76aa58 100644 Binary files a/man/figures/README-venndir_agreement-1.png and b/man/figures/README-venndir_agreement-1.png differ diff --git a/man/figures/README-venndir_each-1.png b/man/figures/README-venndir_each-1.png index 475303e..453b32d 100644 Binary files a/man/figures/README-venndir_each-1.png and b/man/figures/README-venndir_each-1.png differ diff --git a/man/figures/README-venndir_each_p-1.png b/man/figures/README-venndir_each_p-1.png index 508dfe0..dd5b2ef 100644 Binary files a/man/figures/README-venndir_each_p-1.png and b/man/figures/README-venndir_each_p-1.png differ diff --git a/man/figures/README-venndir_overlap-1.png b/man/figures/README-venndir_overlap-1.png index e2b5cb9..66abe7d 100644 Binary files a/man/figures/README-venndir_overlap-1.png and b/man/figures/README-venndir_overlap-1.png differ diff --git a/man/figures/README-venndir_overlap_p-1.png b/man/figures/README-venndir_overlap_p-1.png index a554027..dcc8efc 100644 Binary files a/man/figures/README-venndir_overlap_p-1.png and b/man/figures/README-venndir_overlap_p-1.png differ diff --git a/man/figures/README-vennitems_1-1.png b/man/figures/README-vennitems_1-1.png index ebf8272..0561e4c 100644 Binary files a/man/figures/README-vennitems_1-1.png and b/man/figures/README-vennitems_1-1.png differ diff --git a/man/figures/README-vennitems_1p-1.png b/man/figures/README-vennitems_1p-1.png index 5941d33..07d4f73 100644 Binary files a/man/figures/README-vennitems_1p-1.png and b/man/figures/README-vennitems_1p-1.png differ diff --git a/man/figures/README-vennitems_2-1.png b/man/figures/README-vennitems_2-1.png index c1e5992..1ce6d87 100644 Binary files a/man/figures/README-vennitems_2-1.png and b/man/figures/README-vennitems_2-1.png differ diff --git a/man/figures/README-vennitems_2p-1.png b/man/figures/README-vennitems_2p-1.png index 6f31a6a..856b3ef 100644 Binary files a/man/figures/README-vennitems_2p-1.png and b/man/figures/README-vennitems_2p-1.png differ diff --git a/man/find_venn_overlaps_JamPolygon.Rd b/man/find_venn_overlaps_JamPolygon.Rd index f75ef1e..e62c1b7 100644 --- a/man/find_venn_overlaps_JamPolygon.Rd +++ b/man/find_venn_overlaps_JamPolygon.Rd @@ -89,16 +89,17 @@ jp1@polygons$fill <- polygon_colors; plot(jp1) xo <- find_venn_overlaps_JamPolygon(jp=jp1, venn_counts=test_counts) -xo@polygons$border <- jamba::makeColorDarker(darkFactor=1.2, +xo@polygons$outerborder <- jamba::makeColorDarker(darkFactor=1.2, xo@polygons$venn_color) - xo@polygons$border.lwd <- 2; -plot(xo, flip_sign=-1); +xo@polygons$outerborder.lwd <- 4; +plot(xo); } \seealso{ Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -115,10 +116,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/get_largest_polygon_list.Rd b/man/get_largest_polygon_list.Rd deleted file mode 100644 index 5ca9206..0000000 --- a/man/get_largest_polygon_list.Rd +++ /dev/null @@ -1,64 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{get_largest_polygon_list} -\alias{get_largest_polygon_list} -\title{Largest polygon in a polygon list} -\usage{ -get_largest_polygon_list(polygon_list, ...) -} -\arguments{ -\item{polygon_list}{\code{list} with \code{"x"} and \code{"y"} elements with -polygon coordinates.} - -\item{...}{additional arguments are ignored.} -} -\value{ -\code{list} with polygon coordinates \code{"x"} and \code{"y"} -} -\description{ -Largest polygon in a polygon list -} -\details{ -This function returns the largest polygon in a polygon list, -intended when there are multiple polygons contained in one object. - -If two polygons have identical area, the first -polygon is returned. -\subsection{Todo:}{ -\itemize{ -\item Verify correct output when polygon(s) have holes. -} -} -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3, C=4) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) -largest_poly <- get_largest_polygon_list(polygon_list) -plot_polygon_list(polygon_list, col=colorjam::rainbowJam(3, alpha=0.5)) -plot_polygon_list(largest_poly, add=TRUE, border="red", lwd=3) - - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/get_venn_polygon_shapes.Rd b/man/get_venn_polygon_shapes.Rd index fc9ea91..0ff2164 100644 --- a/man/get_venn_polygon_shapes.Rd +++ b/man/get_venn_polygon_shapes.Rd @@ -11,7 +11,7 @@ get_venn_polygon_shapes( circles_only = FALSE, circle_nudge = NULL, rotate_degrees = 0, - return_type = c("polygon_list", "JamPolygon"), + return_type = c("JamPolygon"), ... ) } @@ -72,38 +72,17 @@ be represented in the output. counts <- c(A=1, B=2, `A&B`=3, C=4) venn_colors <- colorjam::rainbowJam(3, alpha=0.5); -venn_polygon_list <- get_venn_polygon_shapes(counts) -plot_polygon_list(venn_polygon_list, col=venn_colors) +vjp <- get_venn_polygon_shapes(counts, return_type="JamPolygon") +plot(vjp, fill=venn_colors) -venn_polygon_list <- get_venn_polygon_shapes(counts, proportional=TRUE) -plot_polygon_list(venn_polygon_list, col=venn_colors) - -# TODO: examples showing circle_nudge, rotate_degrees -jpdf <- get_venn_polygon_shapes(counts, return_type="JamPolygon") - -counts4 <- c(A=1, B=2, `A&B`=3, C=4, `C&D`=2, D=3, `A&C`=2, `A&D`=1, `A&B&C&D`=3) -jpdf <- get_venn_polygon_shapes(counts4, return_type="JamPolygon") +vjp <- get_venn_polygon_shapes(counts, + return_type="JamPolygon", + proportional=TRUE) +plot(vjp, fill=venn_colors) } \seealso{ Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} +\code{\link{simple_ellipse}()} } \concept{venndir polygons} diff --git a/man/get_venn_shapes.Rd b/man/get_venn_shapes.Rd deleted file mode 100644 index ea6fcfc..0000000 --- a/man/get_venn_shapes.Rd +++ /dev/null @@ -1,81 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-shapes.R -\name{get_venn_shapes} -\alias{get_venn_shapes} -\title{Get Venn shapes} -\usage{ -get_venn_shapes( - counts, - proportional = FALSE, - sep = "&", - circles_only = FALSE, - circle_nudge = NULL, - rotate_degrees = 0, - ... -) -} -\arguments{ -\item{counts}{\code{integer} vector whose names represent set overlaps, -where set names are separated by \code{sep} delimiter.} - -\item{proportional}{\code{logical} indicating whether to create proportional -circles, where \code{proportional=FALSE} creates standard Venn diagram, -and \code{proportional=TRUE} creates a Euler diagram.} - -\item{sep}{\code{character} delimiter used to separate set names in -\code{names(counts)}.} - -\item{circles_only}{\code{logical} indicating whether to force Venn -4-way diagram to use only circles; or passed to \code{eulerr::euler()} -to force it to return circles instead of allowing ellipse shapes.} - -\item{circle_nudge}{\code{list} of \code{numeric} vectors each length 2, whose -names match set names derived from \code{counts}. For example if -\code{counts=c(set_A=5, set_B=10, "setA&set_B"=3)}, then to nudge -the \code{set_A} circle, use \code{circle_nudge=list(set_A=c(1, 0))}. -This argument is intended to allow manipulation of specific -circle or ellipse positions for aesthetic effects. Particularly -for proportional Euler diagrams, sometimes the algorithm places -circles in non-ideal locations} - -\item{rotate_degrees}{\code{numeric} value indicating rotation in degrees -for the entire set of shapes. This argument is intended to -change the overall orientation, for example so that certain -sets are at the top.} - -\item{...}{additional arguments are ignored.} -} -\description{ -Get Venn shapes -} -\details{ -This function takes a Venn overlap counts and creates -corresponding circles or ellipses that represent -either a Venn diagram, or proportional Venn (Euler) -diagram. - -For non-proportional Venn diagrams, this function accepts -up to 5 sets, although the 5-way Venn diagram is not -visually intuitive. - -For proportional Euler diagrams, this function simply passes -the count vector to \code{eulerr::euler()} and returns the output. -That function accepts more sets, however not all overlaps may -be represented in the output. -} -\seealso{ -Other venndir utility: -\code{\link{curate_venn_labels}()}, -\code{\link{expand_range}()}, -\code{\link{make_color_contrast}()}, -\code{\link{make_venn_combn_df}()}, -\code{\link{make_venn_test}()}, -\code{\link{match_list}()}, -\code{\link{nudge_venndir_label}()}, -\code{\link{print_color_df}()}, -\code{\link{shrink_df}()}, -\code{\link{three_point_angle}()}, -\code{\link{venndir_legender}()}, -\code{\link{venndir_to_df}()} -} -\concept{venndir utility} diff --git a/man/has_point_in_JamPolygon.Rd b/man/has_point_in_JamPolygon.Rd index 16e55d3..09c6b63 100644 --- a/man/has_point_in_JamPolygon.Rd +++ b/man/has_point_in_JamPolygon.Rd @@ -32,6 +32,7 @@ Determine if a point is inside any JamPolygon Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -48,10 +49,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/intersect_JamPolygon.Rd b/man/intersect_JamPolygon.Rd index d74456c..6563fff 100644 --- a/man/intersect_JamPolygon.Rd +++ b/man/intersect_JamPolygon.Rd @@ -25,6 +25,7 @@ Intersect one or more JamPolygon objects Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -41,10 +42,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/intersect_polygon_list.Rd b/man/intersect_polygon_list.Rd deleted file mode 100644 index eed6781..0000000 --- a/man/intersect_polygon_list.Rd +++ /dev/null @@ -1,59 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{intersect_polygon_list} -\alias{intersect_polygon_list} -\title{Intersect one or more polygons} -\usage{ -intersect_polygon_list(polygon_list, new_name = NULL, ...) -} -\arguments{ -\item{polygon_list}{\code{list} object that contains one or more polygons.} - -\item{...}{additional arguments are ignored.} -} -\value{ -object \code{list} of polygons -} -\description{ -Intersect one or more polygons -} -\details{ -This function takes a \code{list} of polygons and iteratively -calls \code{polyclip::polyclip(A, B, op="intersect")} to produce the intersect -across one or more polygons, which otherwise only works with two -polygons. -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) - -circle_intersect <- intersect_polygon_list(polygon_list); -jamba::ssdim(circle_intersect) -circle_colors <- colorjam::rainbowJam(2); -plot_polygon_list(polygon_list, col=circle_colors, main="intersect") -plot_polygon_list(circle_intersect, col="#FFDD0088", border="red", lwd=3, add=TRUE) - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/label_fill_JamPolygon.Rd b/man/label_fill_JamPolygon.Rd index 0b56d3d..d40b742 100644 --- a/man/label_fill_JamPolygon.Rd +++ b/man/label_fill_JamPolygon.Rd @@ -99,18 +99,22 @@ df3 <- data.frame(name=c("polygon1", "polygon2"), jp3 <- new("JamPolygon", polygons=df3); plot(jp3); -label_fill_JamPolygon(jp3[1,], labels=1:20) -test_x <- jp3[1,]@polygons$x[[1]]; -test_y <- jp3[1,]@polygons$y[[1]]; -P <- list(x=c(3.5, 4.5), y=c(3.5, 4.5)) -A <- lapply(seq_along(test_x), function(i){ - list(x=test_x[[i]], y=test_y[[i]])}) +lfj <- label_fill_JamPolygon(jp3[1,], labels=1:20) +plot(lfj$items_df[, c("x", "y")], cex=0) +text(lfj$items_df[, c("x", "y")], labels=lfj$items_df$text) + +#test_x <- jp3[1,]@polygons$x[[1]]; +#test_y <- jp3[1,]@polygons$y[[1]]; +#P <- list(x=c(3.5, 4.5), y=c(3.5, 4.5)) +#A <- lapply(seq_along(test_x), function(i){ +# list(x=test_x[[i]], y=test_y[[i]])}) } \seealso{ Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -127,10 +131,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/label_outside_JamPolygon.Rd b/man/label_outside_JamPolygon.Rd index 78a30ab..e35e5f2 100644 --- a/man/label_outside_JamPolygon.Rd +++ b/man/label_outside_JamPolygon.Rd @@ -60,6 +60,7 @@ Position labels outside JamPolygon Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -76,10 +77,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/label_segment_JamPolygon.Rd b/man/label_segment_JamPolygon.Rd index 85e1ba5..e07da7c 100644 --- a/man/label_segment_JamPolygon.Rd +++ b/man/label_segment_JamPolygon.Rd @@ -25,6 +25,7 @@ Define a label segment for JamPolygon Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -41,10 +42,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/labelr_JamPolygon.Rd b/man/labelr_JamPolygon.Rd index c2f42f7..eb1b1d7 100644 --- a/man/labelr_JamPolygon.Rd +++ b/man/labelr_JamPolygon.Rd @@ -42,6 +42,7 @@ This rule could serve to solve (1) as well. Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -58,10 +59,12 @@ Other JamPolygon: \code{\link{label_segment_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/labelr_polygon_list.Rd b/man/labelr_polygon_list.Rd deleted file mode 100644 index 80ba391..0000000 --- a/man/labelr_polygon_list.Rd +++ /dev/null @@ -1,95 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{labelr_polygon_list} -\alias{labelr_polygon_list} -\title{Calculate polygon label positions using Pole of Inaccessibility} -\usage{ -labelr_polygon_list(polygon_list, add_labels = FALSE, ...) -} -\arguments{ -\item{polygon_list}{\code{list} containing elements \code{"x"} and \code{"y"} each -with \code{numeric} vectors, or \code{list} of \code{numeric} vectors.} - -\item{add_labels}{\code{logical} indicating whether to plot the labels -using \code{text()}} - -\item{...}{additional arguments are passed to \code{text()} when -\code{add_labels=TRUE}} -} -\description{ -Calculate polygon label positions using Pole of Inaccessibility, otherwise -known as the Visual Center. -} -\details{ -This function is a wrapper for \code{polylabelr::poi()} except that it -is applied to a \code{list} of polygons individually. - -When any one polygon is composed of two smaller polygon components, -as encoded with a nested list of coordinates, -first the polygons are combined using \code{union_polygon_list()}. -If the result is a single polygon, that is used to define the -label position. If the result is multiple separate polygon -components, the largest polygon component is used to find the label. -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3, C=5, `B&C`=2, `A&C`=2, `A&B&C`=1) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) - -# default is to label each polygon in its center -plot_polygon_list(polygon_list, - col=colorjam::rainbowJam(length(polygon_list), alpha=0.5)) -labelr_polygon_list(polygon_list, add_labels=TRUE) - -# create unique polygons for each label -A_only <- minus_polygon_list(polygon_list, new_name="A_only"); -B_only <- minus_polygon_list(polygon_list[c(2,1,3)], new_name="B_only"); -C_only <- minus_polygon_list(polygon_list[c(3,1,2)], new_name="C_only"); - -plot_polygon_list(polygon_list, - col=colorjam::rainbowJam(length(polygon_list), alpha=0.5)) -ABC_only <- c(A_only, B_only, C_only); -polygon_list_labelr(ABC_only, add_labels=TRUE) - -# label ABC intersection -ABC_int <- intersect_polygon_list(polygon_list[c(1,2,3)], new_name="ABC"); -plot_polygon_list(ABC_int, add=TRUE, col="gold") -polygon_list_labelr(ABC_int, add_labels=TRUE) - -# label AB intersection -AB_only <- minus_polygon_list( - c(intersect_polygon_list(polygon_list[c(1,2)], new_name="BC_only"), - polygon_list[3])) -plot_polygon_list(AB_only, add=TRUE, col="darkviolet") -polygon_list_labelr(AB_only, add_labels=TRUE, col="white") - -# label BC intersection -BC_only <- minus_polygon_list( - c(intersect_polygon_list(polygon_list[c(2,3)], new_name="BC_only"), - polygon_list[1])) -plot_polygon_list(BC_only, add=TRUE, col="skyblue") -polygon_list_labelr(BC_only, add_labels=TRUE) - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/make_color_contrast.Rd b/man/make_color_contrast.Rd index 5210792..63db993 100644 --- a/man/make_color_contrast.Rd +++ b/man/make_color_contrast.Rd @@ -56,7 +56,6 @@ make_color_contrast(x, y, do_plot=TRUE, C_floor=140); Other venndir utility: \code{\link{curate_venn_labels}()}, \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_venn_combn_df}()}, \code{\link{make_venn_test}()}, \code{\link{match_list}()}, diff --git a/man/make_venn_combn_df.Rd b/man/make_venn_combn_df.Rd index 43dc86c..822d72e 100644 --- a/man/make_venn_combn_df.Rd +++ b/man/make_venn_combn_df.Rd @@ -44,7 +44,6 @@ make_venn_combn_df(letters[1:3]); Other venndir utility: \code{\link{curate_venn_labels}()}, \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_test}()}, \code{\link{match_list}()}, diff --git a/man/make_venn_test.Rd b/man/make_venn_test.Rd index e9b6375..50e5ac1 100644 --- a/man/make_venn_test.Rd +++ b/man/make_venn_test.Rd @@ -132,7 +132,6 @@ textvenn(setlist, overlap_type="each") Other venndir utility: \code{\link{curate_venn_labels}()}, \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_combn_df}()}, \code{\link{match_list}()}, diff --git a/man/match_list.Rd b/man/match_list.Rd index cf267c0..4302ea5 100644 --- a/man/match_list.Rd +++ b/man/match_list.Rd @@ -58,7 +58,6 @@ match_list(y, x) Other venndir utility: \code{\link{curate_venn_labels}()}, \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_combn_df}()}, \code{\link{make_venn_test}()}, diff --git a/man/minus_JamPolygon.Rd b/man/minus_JamPolygon.Rd index 1ad6b6a..cc9b975 100644 --- a/man/minus_JamPolygon.Rd +++ b/man/minus_JamPolygon.Rd @@ -21,6 +21,7 @@ Subtract one or more JamPolygon objects Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -37,10 +38,12 @@ Other JamPolygon: \code{\link{label_segment_JamPolygon}()}, \code{\link{labelr_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/minus_polygon_list.Rd b/man/minus_polygon_list.Rd deleted file mode 100644 index ffd06a8..0000000 --- a/man/minus_polygon_list.Rd +++ /dev/null @@ -1,64 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{minus_polygon_list} -\alias{minus_polygon_list} -\title{Subtract one or more polygons} -\usage{ -minus_polygon_list(polygon_list, new_name = NULL, ...) -} -\arguments{ -\item{polygon_list}{\code{list} object that contains one or more polygons.} - -\item{new_name}{\code{character} string with optional new name for the -output polygon.} - -\item{...}{additional arguments are ignored.} -} -\value{ -object \code{list} of polygons -} -\description{ -Subtract one or more polygons -} -\details{ -This function takes a \code{list} of polygons and iteratively -calls \code{polyclip::polyclip(A, B, op="minus")} to produce a union -across one or more polygons, which otherwise only works with two -polygons. -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3) -counts <- c(A=1, B=2, `A&B`=3, C=5, `B&C`=2, `A&C`=2, `A&B&C`=1) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) - -circle_minus <- minus_polygon_list(polygon_list); -circle_colors <- colorjam::rainbowJam(length(polygon_list), alpha=0.5); -plot_polygon_list(polygon_list, col=circle_colors, main="minus") -plot_polygon_list(circle_minus, col="#FFDD0088", border="red", lwd=3, add=TRUE) - -circle_minus2 <- minus_polygon_list(polygon_list[c(2,1,3)]); -plot_polygon_list(circle_minus2, col="#FFDD0088", border="blue", lwd=3, add=TRUE) -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/nearest_point_JamPolygon.Rd b/man/nearest_point_JamPolygon.Rd index 4c9b838..4fbffed 100644 --- a/man/nearest_point_JamPolygon.Rd +++ b/man/nearest_point_JamPolygon.Rd @@ -23,6 +23,7 @@ Get the nearest polygon point to a reference point Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -39,10 +40,12 @@ Other JamPolygon: \code{\link{label_segment_JamPolygon}()}, \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/nudge_JamPolygon.Rd b/man/nudge_JamPolygon.Rd new file mode 100644 index 0000000..be414c3 --- /dev/null +++ b/man/nudge_JamPolygon.Rd @@ -0,0 +1,81 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/venndir-polyclip.R +\name{nudge_JamPolygon} +\alias{nudge_JamPolygon} +\title{Nudge JamPolygon coordinates} +\usage{ +nudge_JamPolygon(jp, nudge = NULL, verbose = FALSE, ...) +} +\arguments{ +\item{jp}{\code{JamPolygon} object} + +\item{nudge}{\code{list} whose names match \code{names(jp)}, containing \code{numeric} +vector with names \code{"x"} and \code{"y"}. For example: +\code{nudge=list(polyname1=c(x=1, y=0))}} + +\item{...}{additional arguments are ignored} +} +\description{ +Nudge JamPolygon coordinates +} +\details{ +Polygon coordinates within a \code{JamPolygon} object are nudged by name +or polygon number, such that all parts of each polygon are adjusted +together. For multi-part polygons, and/or polygons with internal holes, +all parts are moved the identical amount. +} +\examples{ +DEdf <- data.frame(check.names=FALSE, + name=c("D", "E"), + x=I(list( + c(-3, 3, 3, 0, -3), + c(-4, 2, 2, -4))), + y=I(list( + c(-3, -3, 1.5, 4, 1.5), + c(-2, -2, 4, 4))), + fill=c("#FFD70055", "#B2222255")) +DEjp <- new("JamPolygon", polygons=DEdf) +plot(DEjp) +nudge <- list(D=c(7, 1), E=c(-1, -1)); +DEjp_nudged <- nudge_JamPolygon(DEjp, nudge=nudge) +plot(DEjp_nudged) + +plot(rbind2(DEjp, DEjp_nudged), + fill=c("#FFD70055", "#B2222255", "gold", "firebrick"), + label=c("D_old", "E_old", "D_new", "E_new"), + border.lty=c(2, 2, 1, 1)) + +} +\seealso{ +Other JamPolygon: +\code{\link{JamPolygon-class}}, +\code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, +\code{\link{add_orientation_JamPolygon}()}, +\code{\link{area_JamPolygon}()}, +\code{\link{bbox_JamPolygon}()}, +\code{\link{buffer_JamPolygon}()}, +\code{\link{check_JamPolygon}()}, +\code{\link{check_Venndir}()}, +\code{\link{eulerr_to_JamPolygon}()}, +\code{\link{farthest_point_JamPolygon}()}, +\code{\link{find_venn_overlaps_JamPolygon}()}, +\code{\link{has_point_in_JamPolygon}()}, +\code{\link{intersect_JamPolygon}()}, +\code{\link{label_fill_JamPolygon}()}, +\code{\link{label_outside_JamPolygon}()}, +\code{\link{label_segment_JamPolygon}()}, +\code{\link{labelr_JamPolygon}()}, +\code{\link{minus_JamPolygon}()}, +\code{\link{nearest_point_JamPolygon}()}, +\code{\link{plot.JamPolygon}()}, +\code{\link{point_in_JamPolygon}()}, +\code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, +\code{\link{sample_JamPolygon}()}, +\code{\link{split_JamPolygon}()}, +\code{\link{union_JamPolygon}()}, +\code{\link{update_JamPolygon}()} +} +\concept{JamPolygon} diff --git a/man/nudge_polygon_coords.Rd b/man/nudge_polygon_coords.Rd deleted file mode 100644 index f4dcbcd..0000000 --- a/man/nudge_polygon_coords.Rd +++ /dev/null @@ -1,51 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{nudge_polygon_coords} -\alias{nudge_polygon_coords} -\title{Nudge polygon coordinates} -\usage{ -nudge_polygon_coords(polygon_list, nudge, ...) -} -\description{ -Nudge polygon coordinates -} -\details{ -This function differs from \code{nudge_polygon_list()} in that all polygons -are nudged the exact same amount. If there are nested polygons, they -are iteratively all nudged the same. -} -\examples{ -D <- list( - x=c(-3, 3, 3, 0, -3), - y=c(-3, -3, 1.5, 4, 1.5)) -E <- list( - x=c(-3, 3, 3, -3), - y=c(-3, -3, 3, 3)) -DElist <- list(D=D, E=E, DE=list(D=D, E=E)) -nudge <- c(x=10, y=-10) -new_polygon_list <- nudge_polygon_coords(polygon_list=DElist, nudge=nudge) -plot_polygon_list(new_polygon_list) - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/nudge_polygon_list.Rd b/man/nudge_polygon_list.Rd deleted file mode 100644 index bf0cc4f..0000000 --- a/man/nudge_polygon_list.Rd +++ /dev/null @@ -1,87 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{nudge_polygon_list} -\alias{nudge_polygon_list} -\title{Nudge polygon_list} -\usage{ -nudge_polygon_list(polygon_list = NULL, nudge = NULL, ...) -} -\arguments{ -\item{polygon_list}{\code{list} object with \code{"x"} and \code{"y"} elements.} - -\item{nudge}{\code{list} whose names are found in \code{names(polygon_list)}, -and whose values are \code{x} and \code{y} coordinates to be moved.} - -\item{...}{additional arguments are ignored.} - -\item{rotate_degrees}{\code{numeric} value in degrees (0, 360) to -rotate the \code{polygon_list} object and all contained polygons. -(Not yet implemented.)} -} -\value{ -object \code{list} polygon_list object with \code{"x"} and \code{"y"} elements. -} -\description{ -Nudge polygon_list -} -\details{ -This helper function is intended to take \code{list} polygon_list coordinates -and "nudge" (move by adding a scalar value to each coordinate) -only a subset of polygons identified by name. -} -\examples{ -D <- list( - x=c(-3, 3, 3, 0, -3), - y=c(-3, -3, 1.5, 4, 1.5)) -E <- list( - x=c(-3, 3, 3, -3), - y=c(-3, -3, 3, 3)) -DElist <- list(D=D, E=E, DE=list(D=D, E=E)) -nudge <- list(D=c(x=0, y=10), E=c(x=0, y=-10), DE=c(x=10, y=0)) -new_polygon_list <- nudge_polygon_list(polygon_list=DElist, - nudge=nudge) -poly_colors <- colorjam::rainbowJam(3, alpha=0.5); -plot_polygon_list(DElist, col=poly_colors) -plot_polygon_list(new_polygon_list, col=poly_colors) - -polygon_list <- polygon_ellipses(c(3, 2), c(2, 3), - xradius=c(1, 4), - yradius=c(5, 2)) -plot_polygon_list(polygon_list, - col=c("#FF000077", "#FFDD0000"), - xlim=c(-2, 9)); -polygon_list2 <- nudge_polygon_list(polygon_list, - nudge=list(`2`=c(x=3, y=-2)) -) -plot_polygon_list(polygon_list2, - col=c("#FF000077", "#FFDD0077"), - add=TRUE, - xlim=c(-2, 9)); - -plot_polygon_list(polygon_list[2], border="blue", lty="dotted", lwd=3, add=TRUE); -plot_polygon_list(polygon_list2[2], border="blue", lty="dotted", lwd=3, add=TRUE); -arrows(x0=2, x1=5, y0=3, y1=1) - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/nudge_venndir_label.Rd b/man/nudge_venndir_label.Rd index 2ec557c..bdfd864 100644 --- a/man/nudge_venndir_label.Rd +++ b/man/nudge_venndir_label.Rd @@ -49,7 +49,6 @@ render_venndir(vo2) Other venndir utility: \code{\link{curate_venn_labels}()}, \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_combn_df}()}, \code{\link{make_venn_test}()}, diff --git a/man/plot.JamPolygon.Rd b/man/plot.JamPolygon.Rd index 97a6dfa..9f0acf7 100644 --- a/man/plot.JamPolygon.Rd +++ b/man/plot.JamPolygon.Rd @@ -20,6 +20,7 @@ do_viewport = TRUE, do_pop_viewport = TRUE, do_draw = TRUE, + do_experimental = TRUE, verbose = FALSE, debug = FALSE, ... @@ -89,6 +90,9 @@ or other \code{grid} functions.} When \code{do_draw=FALSE}, it also forces \code{do_newpage=FALSE}, \code{do_viewport=FALSE}, and \code{do_pop_viewport=FALSE}.} +\item{do_experimental}{\code{logical} indicating whether to use experimental +rendering with \code{gridGeometry} as potential replacement for \code{vwline}.} + \item{verbose}{\code{logical} indicating whether to print verbose output.} \item{debug}{\code{logical} (default FALSE) indicating whether to enable @@ -180,6 +184,23 @@ dfx <- data.frame(name=c("polygon1", "polygon2"), jpx <- new("JamPolygon", polygons=dfx); plot(jpx); +# if you want to add to the plot, you must capture output +# to use the viewport +jpxout <- plot(jpx); +vp <- attr(jpxout, "viewport"); +adjx <- attr(jpxout, "adjx"); +adjy <- attr(jpxout, "adjy"); +grid::grid.path(x=adjx(c(4, 5, 5, 4) + 0.5), + y=adjy(c(3, 3, 4, 4)), + vp=vp, + gp=grid::gpar(fill="purple", col="red1", lwd=2), + default.units="snpc") +grid::grid.text(x=adjx(5), y=adjy(3.5), + label="new grob", + vp=vp, + gp=grid::gpar(col="yellow", fontsize=20), + default.units="snpc") + dfz <- data.frame(name=c("polygon1", "polygon2", "polygon3"), x=I(list( list(c(1, 4, 4, 1), @@ -200,8 +221,13 @@ dfz <- data.frame(name=c("polygon1", "polygon2", "polygon3"), fill=c("gold", "firebrick", "dodgerblue")); jpz <- new("JamPolygon", polygons=dfz); jpz@polygons[, c("label_x", "label_y")] <- as.data.frame(labelr_JamPolygon(jpz)) -jpz@polygons$border <- c("orange", "gold", "purple"); -jpz@polygons$border.lwd <- c(3, 4, 5); +jpz@polygons$outerborder <- c("orange", "gold", "purple"); +jpz@polygons$outerborder.lwd <- 0; +jpz@polygons$outerborder.lwd <- c(3, 4, 5); +jpz@polygons$innerborder <- c("orange4", "gold3", "purple4"); +jpz@polygons$innerborder.lwd <- c(3, 4, 5); +jpz@polygons$border.lwd <- 1; +jpz@polygons$border.lty <- 2; #jpz <- add_orientation_JamPolygon(jpz); plot(jpz); @@ -210,6 +236,7 @@ plot(jpz); Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -227,9 +254,11 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/plot_polygon_list.Rd b/man/plot_polygon_list.Rd deleted file mode 100644 index 0b9b209..0000000 --- a/man/plot_polygon_list.Rd +++ /dev/null @@ -1,61 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{plot_polygon_list} -\alias{plot_polygon_list} -\title{Plot polygon_list using base R} -\usage{ -plot_polygon_list( - polygon_list, - col = NULL, - border = "black", - lwd = 1, - add = FALSE, - asp = 1, - bty = "n", - xaxt = "n", - yaxt = "n", - xlab = "", - ylab = "", - xlim = NULL, - ylim = NULL, - rule = c("evenodd", "none"), - ... -) -} -\description{ -Plot polygon_list using base R -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3, C=5, `B&C`=2, `A&C`=2, `A&B&C`=1) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) -plot_polygon_list(polygon_list, - col=colorjam::rainbowJam(length(polygon_list), alpha=0.5)) - -polygon_list2 <- list(A=polygon_list$A, BC=polygon_list[c("B", "C")]) -plot_polygon_list(polygon_list2, - col=colorjam::rainbowJam(length(polygon_list2), alpha=0.5)) - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/point_in_JamPolygon.Rd b/man/point_in_JamPolygon.Rd index 11b2c84..ed24c89 100644 --- a/man/point_in_JamPolygon.Rd +++ b/man/point_in_JamPolygon.Rd @@ -46,6 +46,7 @@ Determine if a point is inside a JamPolygon Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -63,9 +64,11 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/polyclip_to_JamPolygon.Rd b/man/polyclip_to_JamPolygon.Rd index fd04e48..7c7a8da 100644 --- a/man/polyclip_to_JamPolygon.Rd +++ b/man/polyclip_to_JamPolygon.Rd @@ -6,6 +6,9 @@ \usage{ polyclip_to_JamPolygon(A, ...) } +\arguments{ +\item{A}{output from \code{polyclip} functions.} +} \description{ Convert polyclip polygon to JamPolygon } @@ -27,6 +30,7 @@ jpdf <- new("JamPolygon", polygons=df); Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -44,9 +48,11 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, diff --git a/man/polygon_areas.Rd b/man/polygon_areas.Rd deleted file mode 100644 index a2e6bb0..0000000 --- a/man/polygon_areas.Rd +++ /dev/null @@ -1,107 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polygon-areas.R -\name{polygon_areas} -\alias{polygon_areas} -\title{Polygon area for simple or list of polygons} -\usage{ -polygon_areas(x, y = NULL, simplify = FALSE, verbose = FALSE, ...) -} -\arguments{ -\item{x}{\code{numeric} input in one of the following formats: -\itemize{ -\item \code{numeric} vector of coordinates for single polygon input, which -also requires \code{y} is supplied as \code{numeric} vector with equal length. -\item \code{list} of \code{numeric} vectors representing multiple polygons, -which also requires \code{y} is supplied as equivalent \code{list}. -\item \code{list} of polygons, each polygon contains elements \code{"x"} and \code{"y"}. -\item \code{list} of polygons, each polygon contains a \code{list} of polygon -component parts which each contain elements \code{"x"} and \code{"y"}. -}} - -\item{y}{\code{numeric} vector or \code{list} of numeric vectors, compatible -with \code{x}, or \code{NULL} when \code{x} contains both coordinates.} - -\item{simplify}{\code{logical} indicating whether area should be summed -for each polygon, potentially containing nested component polygons. -\itemize{ -\item \code{simplify=TRUE} returns \code{numeric} vector with one total area -per polygon. -\item \code{simplify=FALSE} returns a \code{list} of \code{numeric} areas, using nested -list to indicate component polygons. -\item Note that this step does not manipulate the polygons in any way, -for example it does not call union over component polygons, therefore -the component polygons may overlap. -}} - -\item{verbose}{\code{logical} indicating whether to print verbose output.} - -\item{...}{additional arguments are ignored.} -} -\value{ -\code{numeric} vector with polygon area for each individual polygon -in the input \code{x},\code{y}. -\itemize{ -\item When \code{x} is a \code{list} that contains \code{"x"} and \code{"y"} elements, those -elements are used. -\item When \code{x} and \code{y} both contain a \code{list} of \code{numeric} vectors, each -vector is considered coordinates of a polygon, and the area is returned -for each polygon. -\item When \code{x} and \code{y} are \code{numeric} vectors, it is considered a single -polygon, and thus one area is returned. -} -} -\description{ -Polygon area for simple or list of polygons -} -\examples{ -D <- list( - x=c(-3, 3, 3, 0, -3), - y=c(-3, -3, 1.5, 4, 1.5)) -polygon_areas(D) - -E <- list( - x=c(-3, 3, 3, -3), - y=c(-3, -3, 3, 3)) -polygon_areas(E) - -DElist <- list( - x=list( - D=c(-3, 3, 3, 0, -3), - E=c(-3, 3, 3, -3)), - y=list( - D=c(-3, -3, 1.5, 4, 1.5), - E=c(-3, -3, 3, 3))) -polygon_areas(DElist) - -# list of polygons -poly_list <- list(D=D, E=E) -polygon_areas(poly_list) - -# list of nested polygons -polygon_areas(list(DE=poly_list, D=D, E=E)) - -polygon_areas(list(DE=poly_list, D=D, E=E), simplify=TRUE) - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/polygon_circles.Rd b/man/polygon_circles.Rd index 7c3c61d..b8b027a 100644 --- a/man/polygon_circles.Rd +++ b/man/polygon_circles.Rd @@ -23,7 +23,7 @@ use in the circle.} \item{...}{additional arguments are ignored.} } \value{ -object \code{list} with a number of circles encoded as polygons. +\code{JamPolygon} object } \description{ Make polygon_list circles @@ -32,30 +32,40 @@ Make polygon_list circles This function creates one or more circles as polygon_list \code{list} objects. } \examples{ -polygon_list <- polygon_circles(c(3, 2), c(2, 3)) -plot_polygon_list(polygon_list) -points(x=c(3, 2), y=c(2, 3), pch=c("1", "2"), add=TRUE); +circle_jp <- polygon_circles(c(3, 2), c(2, 3)) +plot(circle_jp, fill=c("red", "gold")) } \seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, +Other JamPolygon: +\code{\link{JamPolygon-class}}, +\code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, +\code{\link{add_orientation_JamPolygon}()}, +\code{\link{area_JamPolygon}()}, +\code{\link{bbox_JamPolygon}()}, +\code{\link{buffer_JamPolygon}()}, +\code{\link{check_JamPolygon}()}, +\code{\link{check_Venndir}()}, +\code{\link{eulerr_to_JamPolygon}()}, +\code{\link{farthest_point_JamPolygon}()}, +\code{\link{find_venn_overlaps_JamPolygon}()}, +\code{\link{has_point_in_JamPolygon}()}, +\code{\link{intersect_JamPolygon}()}, +\code{\link{label_fill_JamPolygon}()}, +\code{\link{label_outside_JamPolygon}()}, +\code{\link{label_segment_JamPolygon}()}, +\code{\link{labelr_JamPolygon}()}, +\code{\link{minus_JamPolygon}()}, +\code{\link{nearest_point_JamPolygon}()}, +\code{\link{nudge_JamPolygon}()}, +\code{\link{plot.JamPolygon}()}, +\code{\link{point_in_JamPolygon}()}, +\code{\link{polyclip_to_JamPolygon}()}, \code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} +\code{\link{sample_JamPolygon}()}, +\code{\link{split_JamPolygon}()}, +\code{\link{union_JamPolygon}()}, +\code{\link{update_JamPolygon}()} } -\concept{venndir polygons} +\concept{JamPolygon} diff --git a/man/polygon_ellipses.Rd b/man/polygon_ellipses.Rd index f1fc9a2..ce383ad 100644 --- a/man/polygon_ellipses.Rd +++ b/man/polygon_ellipses.Rd @@ -37,7 +37,7 @@ rotate each ellipse after it is created, where values are conformed to between \code{0} and \code{360}, rotating clockwise.} } \value{ -object \code{list} with a number of circles encoded as polygons. +\code{JamPolygon} object } \description{ Make polygon_list ellipses @@ -46,32 +46,42 @@ Make polygon_list ellipses This function creates one or more ellipses as polygon_list \code{list} objects. } \examples{ -polygon_list <- polygon_ellipses(c(3, 2), c(2, 3), +ejp <- polygon_ellipses(c(3, 2), c(2, 3), xradius=c(1, 4), yradius=c(5, 2)) -plot_polygon_list(polygon_list, col=c("#FF000077", "#FFDD0077")); -points(x=c(3, 2), y=c(2, 3), pch=c("1", "2"), add=TRUE); +plot(ejp, fill=c("#FF000077", "#FFDD0077")) } \seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, +Other JamPolygon: +\code{\link{JamPolygon-class}}, +\code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, +\code{\link{add_orientation_JamPolygon}()}, +\code{\link{area_JamPolygon}()}, +\code{\link{bbox_JamPolygon}()}, +\code{\link{buffer_JamPolygon}()}, +\code{\link{check_JamPolygon}()}, +\code{\link{check_Venndir}()}, +\code{\link{eulerr_to_JamPolygon}()}, +\code{\link{farthest_point_JamPolygon}()}, +\code{\link{find_venn_overlaps_JamPolygon}()}, +\code{\link{has_point_in_JamPolygon}()}, +\code{\link{intersect_JamPolygon}()}, +\code{\link{label_fill_JamPolygon}()}, +\code{\link{label_outside_JamPolygon}()}, +\code{\link{label_segment_JamPolygon}()}, +\code{\link{labelr_JamPolygon}()}, +\code{\link{minus_JamPolygon}()}, +\code{\link{nearest_point_JamPolygon}()}, +\code{\link{nudge_JamPolygon}()}, +\code{\link{plot.JamPolygon}()}, +\code{\link{point_in_JamPolygon}()}, +\code{\link{polyclip_to_JamPolygon}()}, \code{\link{polygon_circles}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} +\code{\link{sample_JamPolygon}()}, +\code{\link{split_JamPolygon}()}, +\code{\link{union_JamPolygon}()}, +\code{\link{update_JamPolygon}()} } -\concept{venndir polygons} +\concept{JamPolygon} diff --git a/man/polygon_list_labelr.Rd b/man/polygon_list_labelr.Rd deleted file mode 100644 index 3deebca..0000000 --- a/man/polygon_list_labelr.Rd +++ /dev/null @@ -1,90 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{polygon_list_labelr} -\alias{polygon_list_labelr} -\title{Simple wrapper to polylabelr::poi() for polygon_list} -\usage{ -polygon_list_labelr(polygon_list, precision = 1, add_labels = FALSE, ...) -} -\arguments{ -\item{polygon_list}{\code{list} object} -} -\value{ -\code{matrix} with nrow \code{length(polygon_list)} with x,y coordinates -representing the visual center of each polygon in the list. -} -\description{ -Simple wrapper to polylabelr::poi() for polygon_list -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3, C=5, `B&C`=2, `A&C`=2, `A&B&C`=1) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) - -# default is to label each polygon in its center -plot_polygon_list(polygon_list, - col=colorjam::rainbowJam(length(polygon_list), alpha=0.5)) -polygon_list_labelr(polygon_list, add_labels=TRUE) - -# create unique polygons for each label -A_only <- minus_polygon_list(polygon_list, new_name="A_only"); -B_only <- minus_polygon_list(polygon_list[c(2,1,3)], new_name="B_only"); -C_only <- minus_polygon_list(polygon_list[c(3,1,2)], new_name="C_only"); - -plot_polygon_list(polygon_list, - col=colorjam::rainbowJam(length(polygon_list), alpha=0.5)) -ABC_only <- c(A_only, B_only, C_only); -polygon_list_labelr(ABC_only, add_labels=TRUE) - -# label ABC intersection -ABC_int <- intersect_polygon_list(polygon_list[c(1,2,3)], new_name="ABC"); -plot_polygon_list(ABC_int, add=TRUE, col="gold") -polygon_list_labelr(ABC_int, add_labels=TRUE) - -# label AB intersection -AB_only <- minus_polygon_list( - c(intersect_polygon_list(polygon_list[c(1,2)], new_name="BC_only"), - polygon_list[3])) -plot_polygon_list(AB_only, add=TRUE, col="darkviolet") -polygon_list_labelr(AB_only, add_labels=TRUE, col="white") - -# label BC intersection -BC_only <- minus_polygon_list( - c(intersect_polygon_list(polygon_list[c(2,3)], new_name="BC_only"), - polygon_list[1])) -plot_polygon_list(BC_only, add=TRUE, col="skyblue") -polygon_list_labelr(BC_only, add_labels=TRUE) - -# test with fully overlapping polygon (to create a hole) -counts <- c(A=5, B=0, C=3, `A&B`=1) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) -plot_polygon_list(polygon_list[1:3], col=c("red")) -A_only <- minus_polygon_list(polygon_list[c(1, 2, 3)], new_name="A_only"); -plot_polygon_list(A_only, col="gold", add=TRUE) -polygon_list_labelr(A_only, add_labels=TRUE) - -polygon_list_labelr(c(A_only, polygon_list[2:3]), add_labels=TRUE) -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/polygon_list_to_xy_list.Rd b/man/polygon_list_to_xy_list.Rd deleted file mode 100644 index 2117db7..0000000 --- a/man/polygon_list_to_xy_list.Rd +++ /dev/null @@ -1,69 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-poly-conversions.R -\name{polygon_list_to_xy_list} -\alias{polygon_list_to_xy_list} -\title{Convert polygon list of x,y coordinate into a list by x and y} -\usage{ -polygon_list_to_xy_list(x, flatten = FALSE, ...) -} -\arguments{ -\item{x}{\code{list} of polygons -\itemize{ -\item each polygon should contain a \code{list} with elements \code{"x"} and \code{"y"}. -\item each polygon can contain multiple component polygons as a -nested list, in which case this function is called iteratively -so that the component \code{"x"} and \code{"y"} are returned as equivalent -nested \code{list} objects. -\item In all cases, \code{names(output$x)} and \code{names(output$y)} should equal -\code{names(x)}. -}} - -\item{flatten}{\code{logical} indicating whether all polygons should be -flattened to the same level, without nested polygons.} - -\item{...}{additional arguments are ignored.} -} -\value{ -\code{list} with elements \code{"x"} and \code{"y"} which each contain a -\code{list} with length \code{length(x)}. -} -\description{ -Convert polygon list of x,y coordinate into a list by x and y -} -\details{ -Input is a list of polygons, where each polygon contains a \code{list} -with elements \code{"x"} and \code{"y"}. Output is a list of \code{"x"} and \code{"y"} -split by each polygon. -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) -jamba::ssdim(polygon_list) -jamba::ssdim(polygon_list_to_xy_list(polygon_list)) - -jamba::ssdim(polygon_list_to_xy_list(list(AB=polygon_list))) - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/print_color_df.Rd b/man/print_color_df.Rd index c9389c5..59e493a 100644 --- a/man/print_color_df.Rd +++ b/man/print_color_df.Rd @@ -78,7 +78,6 @@ print_color_df(df, df, dfinvert, Other venndir utility: \code{\link{curate_venn_labels}()}, \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_combn_df}()}, \code{\link{make_venn_test}()}, diff --git a/man/rescale_polygon_list.Rd b/man/rescale_polygon_list.Rd deleted file mode 100644 index 8a56b00..0000000 --- a/man/rescale_polygon_list.Rd +++ /dev/null @@ -1,145 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{rescale_polygon_list} -\alias{rescale_polygon_list} -\title{Rescale a polygon_list object} -\usage{ -rescale_polygon_list( - polygon_list, - rotate_degrees = 0, - scale = c(1, 1), - shift = c(0, 0), - center = NULL, - share_center = FALSE, - share_polygon_center = TRUE, - ... -) -} -\arguments{ -\item{polygon_list}{\code{list} object} - -\item{rotate_degrees}{\code{numeric} value in degrees indicating -rotation around the \code{center}, where positive values are -clockwise rotation. This rotation is only applied to two -columns in \code{x} defined by \code{rotation_axes}.} - -\item{scale}{\code{numeric} vector whose values are expanded to length -\code{ncol(x)}. After subtracting the \code{center}, the coordinates -in each column are multiplied by the \code{scale}.} - -\item{shift}{\code{numeric} vector whose values are expanded to length -\code{ncol(x)}. The coordinates in each column are added to -the \code{shift}, after applying \code{scale} and \code{rotate_degrees}} - -\item{center}{\code{numeric} vector whose values are expanded to length -\code{ncol(x)}, indicating the center point used for \code{scale} and -\code{rotate_degrees} transformations. When \code{center=NULL} it -is derived from the bounding box, which is the mean of the range -for each column in \code{x}.} - -\item{share_center}{\code{logical} indicating whether all polygons -should share the same center, where \code{share_center=TRUE} will -adjust everything collectively, and \code{share_center=FALSE} will -adjust each polygon independently relative to its own center -coordinate.} - -\item{...}{additional arguments are ignored.} -} -\value{ -object \code{list} polygon_list -} -\description{ -Rescale a polygon_list object -} -\details{ -This function simply applies \code{rescale_coordinates()} to an -\code{list} polygon_list object. -} -\examples{ -polygon_list <- polygon_ellipses(c(3, 2), c(2, 3), - xradius=c(1, 4), - yradius=c(5, 2)) -polygon_list1 <- intersect_polygon_list(polygon_list); -polygon_list2 <- minus_polygon_list(polygon_list[1:2]); -polygon_list3 <- minus_polygon_list(polygon_list[2:1]); -polygon_list123 <- c(polygon_list1, - polygon_list2, - polygon_list3); - -polygon_list123a <- rescale_polygon_list(polygon_list123, - scale=c(1.5, 1.5), - share_center=TRUE); -polygon_list123b <- rescale_polygon_list(polygon_list123, - scale=c(1.5, 1.5)); -col3 <- c("#FF000077", "#FFDD0077", "#0000DD77"); -par("mfrow"=c(2, 2)); -plot_polygon_list(polygon_list123, - col=col3, - main="original polygons", - xlim=c(-10, 15), ylim=c(-5, 10)); -axis(1, las=2); axis(2, las=2); -plot_polygon_list(polygon_list123a, - col=col3, - main="share_center=TRUE", - xlim=c(-10, 15), ylim=c(-5, 10)); -axis(1, las=2); axis(2, las=2); -plot_polygon_list(polygon_list123[1:2], - col=col3[1:2], - main="share_center=FALSE\nrescaling only the blue polygon", - xlim=c(-10, 15), ylim=c(-5, 10)); -axis(1, las=2); axis(2, las=2); -plot_polygon_list(polygon_list123b[3], - col=col3[3], - add=TRUE); -plot_polygon_list(polygon_list123[2:3], - col=col3[2:3], - main="share_center=FALSE\nrescaling only the red polygon", - xlim=c(-10, 15), ylim=c(-5, 10)); -axis(1, las=2); axis(2, las=2); -plot_polygon_list(polygon_list123b[1], - col=col3[1], - add=TRUE); -par("mfrow"=c(1, 1)); - -{par("mfrow"=c(2, 2)); -plot_polygon_list(polygon_list123, col=col3, - xlim=c(-4, 8), ylim=c(-4, 8)) -title(main="Original polygons", line=0); -plot_polygon_list(rescale_polygon_list(polygon_list123, rotate_degrees=c(`11`=45, `12`=-10)), col=col3, - xlim=c(-4, 8), ylim=c(-4, 8)) -title(sub="yellow +45 degrees\nblue -10 degrees", line=0, - main="share_polygon_center=TRUE (default)") -plot_polygon_list(rescale_polygon_list(polygon_list123, rotate_degrees=c(`11`=45, `12`=-10), share_polygon_center=FALSE), col=col3, - xlim=c(-4, 8), ylim=c(-4, 8)) -title(sub="yellow +45 degrees\nblue -10 degrees", line=0, - main="share_polygon_center=FALSE\n(each polygon uses its center)") -plot_polygon_list(rescale_polygon_list(polygon_list123, rotate_degrees=c(`11`=45, `12`=-10), share_center=TRUE), col=col3, - xlim=c(-4, 8), ylim=c(-4, 8)) -title(sub="yellow +45 degrees\nblue -10 degrees", line=0, - main="share_center=TRUE\n(all polygons share one global center)") -par("mfrow"=c(1, 1));} - - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/sample_JamPolygon.Rd b/man/sample_JamPolygon.Rd index 06c636b..ec7b439 100644 --- a/man/sample_JamPolygon.Rd +++ b/man/sample_JamPolygon.Rd @@ -8,7 +8,8 @@ sample_JamPolygon( jp, n = 100, xyratio = 1.1, - spread = FALSE, + spread = TRUE, + n_ratio = 1, pattern = c("offset", "rectangle"), buffer = 0, byCols = c("-y", "x"), @@ -25,9 +26,28 @@ sample_JamPolygon( \item{xyratio}{\code{numeric} adjustment for the x/y ratio, numbers larger than 1 make the x-axis spacing larger than the y-axis spacing.} -\item{spread}{\code{logical} when more then \code{n} points can be fit inside -\code{jp}, \code{spread=TRUE} spreads the points evenly across the available -points, while \code{spread=FALSE} only takes the first \code{n} points.} +\item{spread}{\code{logical} (default \code{TRUE}) when more then \code{n} points can +be fit inside the polygon, \code{spread=TRUE} spreads the points evenly +across the available points, while \code{spread=FALSE} simply uses +the first \code{n} points.} + +\item{n_ratio}{\code{numeric} ratio which must be \code{1} or higher, indicating +how many total sampled points should be defined, before choosing +the points to use. This option is used only when \code{spread=TRUE}, +which causes more points to be defined, from which it uses +evenly distributed values.} + +\item{pattern}{\code{character} string indicating how to array the points: +\itemize{ +\item \code{"offset"} (default) uses a rectangular grid where alternating +points on each row are offset slightly on the y-axis. +\item \code{"rectangle"} uses a rectangular grid with points on each row +that share the same y-axis value. +}} + +\item{buffer}{\code{numeric} optional buffer used to adjust the \code{jp} polygon +size overall, where negative values will slightly shrink the +polygon border. Points are sampled after this adjustment.} \item{byCols}{\code{character} passed to \code{jamba::mixedSortDF()} to determine how to sort the resulting coordinates. Default \code{byCols=c("-y", "x")} @@ -88,6 +108,7 @@ sample_JamPolygon(jp3[1,], n=40, xyratio=1/1.5, do_plot=TRUE) Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -105,10 +126,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()}, \code{\link{update_JamPolygon}()} diff --git a/man/shrink_df.Rd b/man/shrink_df.Rd index fcbf768..440a358 100644 --- a/man/shrink_df.Rd +++ b/man/shrink_df.Rd @@ -30,7 +30,6 @@ This function uses \code{data.table} for overall speed. Other venndir utility: \code{\link{curate_venn_labels}()}, \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_combn_df}()}, \code{\link{make_venn_test}()}, diff --git a/man/simple_ellipse.Rd b/man/simple_ellipse.Rd index e4a8e13..9897ce2 100644 --- a/man/simple_ellipse.Rd +++ b/man/simple_ellipse.Rd @@ -11,23 +11,6 @@ Simple ellipse function } \seealso{ Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{union_polygon_list}()}, -\code{\link{xy_list_to_polygon_list}()} +\code{\link{get_venn_polygon_shapes}()} } \concept{venndir polygons} diff --git a/man/split_JamPolygon.Rd b/man/split_JamPolygon.Rd index d38f2c5..28002df 100644 --- a/man/split_JamPolygon.Rd +++ b/man/split_JamPolygon.Rd @@ -21,6 +21,7 @@ Split JamPolygon multipart polygons Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -38,10 +39,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{union_JamPolygon}()}, \code{\link{update_JamPolygon}()} diff --git a/man/three_point_angle.Rd b/man/three_point_angle.Rd index d48af3d..21ed224 100644 --- a/man/three_point_angle.Rd +++ b/man/three_point_angle.Rd @@ -17,7 +17,6 @@ Calculate angle between three consecutive points Other venndir utility: \code{\link{curate_venn_labels}()}, \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_combn_df}()}, \code{\link{make_venn_test}()}, diff --git a/man/union_JamPolygon.Rd b/man/union_JamPolygon.Rd index b69126c..e8515e5 100644 --- a/man/union_JamPolygon.Rd +++ b/man/union_JamPolygon.Rd @@ -61,6 +61,7 @@ union_JamPolygon(jp3na) Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -78,10 +79,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{update_JamPolygon}()} diff --git a/man/union_polygon_list.Rd b/man/union_polygon_list.Rd deleted file mode 100644 index b6c7ebc..0000000 --- a/man/union_polygon_list.Rd +++ /dev/null @@ -1,64 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-polyclip.R -\name{union_polygon_list} -\alias{union_polygon_list} -\title{Union one or more polygons} -\usage{ -union_polygon_list(polygon_list, ...) -} -\arguments{ -\item{polygon_list}{\code{list} object that contains one or more polygons.} - -\item{...}{additional arguments are ignored.} -} -\value{ -object \code{list} of polygons -} -\description{ -Union one or more polygons -} -\details{ -This function takes a \code{list} of polygons and iteratively -calls \code{polyclip::polyclip(A, B, op="union")} to produce a union -across one or more polygons, which otherwise only works with two -polygons. -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) - -circle_union <- union_polygon_list(polygon_list); -jamba::ssdim(circle_union) -circle_colors <- colorjam::rainbowJam(2); -plot_polygon_list(polygon_list, col=circle_colors, main="union") -plot_polygon_list(circle_union, col="#FFDD0088", border="red", lwd=3, add=TRUE) - -counts2 <- c(A=1, B=2, `A&B`=3, C=4) -x2 <- eulerr::euler(counts2) -polygon_list2 <- eulerr_to_polygon_list(x2) -plot_polygon_list(polygon_list2) - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{xy_list_to_polygon_list}()} -} -\concept{venndir polygons} diff --git a/man/update_JamPolygon.Rd b/man/update_JamPolygon.Rd index 828fb51..f442d04 100644 --- a/man/update_JamPolygon.Rd +++ b/man/update_JamPolygon.Rd @@ -16,6 +16,7 @@ Update attributes for a JamPolygon object Other JamPolygon: \code{\link{JamPolygon-class}}, \code{\link{Venndir-class}}, +\code{\link{[,JamPolygon-method}}, \code{\link{add_orientation_JamPolygon}()}, \code{\link{area_JamPolygon}()}, \code{\link{bbox_JamPolygon}()}, @@ -33,10 +34,12 @@ Other JamPolygon: \code{\link{labelr_JamPolygon}()}, \code{\link{minus_JamPolygon}()}, \code{\link{nearest_point_JamPolygon}()}, -\code{\link{plot,JamPolygon,missing-method}}, +\code{\link{nudge_JamPolygon}()}, \code{\link{plot.JamPolygon}()}, \code{\link{point_in_JamPolygon}()}, \code{\link{polyclip_to_JamPolygon}()}, +\code{\link{polygon_circles}()}, +\code{\link{polygon_ellipses}()}, \code{\link{sample_JamPolygon}()}, \code{\link{split_JamPolygon}()}, \code{\link{union_JamPolygon}()} diff --git a/man/venndir.Rd b/man/venndir.Rd index b78de65..507373d 100644 --- a/man/venndir.Rd +++ b/man/venndir.Rd @@ -20,7 +20,7 @@ venndir( font_cex = c(1, 1, 0.8), show_label = NA, display_counts = TRUE, - poly_alpha = 0.8, + poly_alpha = 0.6, alpha_by_counts = FALSE, label_style = c("basic", "fill", "shaded", "shaded_box", "lite", "lite_box"), label_preset = "none", @@ -41,6 +41,7 @@ venndir( verbose = FALSE, debug = 0, circle_nudge = NULL, + lwd = 1, rotate_degrees = 0, ... ) @@ -148,7 +149,7 @@ count zero label is displayed, otherwise no count label is shown.} The default \code{c(1, 1, 0.8)} defines the signed count label slightly smaller than other labels.} -\item{poly_alpha}{\code{numeric} (default 0.8) value between 0 and 1, for +\item{poly_alpha}{\code{numeric} (default 0.6) value between 0 and 1, for alpha transparency of the polygon fill color. This value is ignored when \code{alpha_by_counts=TRUE}. \itemize{ diff --git a/man/venndir_legender.Rd b/man/venndir_legender.Rd index 4626e03..274808c 100644 --- a/man/venndir_legender.Rd +++ b/man/venndir_legender.Rd @@ -249,7 +249,6 @@ venndir_legender(setlist=setlist, venndir_output=vo124) Other venndir utility: \code{\link{curate_venn_labels}()}, \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_combn_df}()}, \code{\link{make_venn_test}()}, diff --git a/man/venndir_to_df.Rd b/man/venndir_to_df.Rd index 962f3a0..334e0e7 100644 --- a/man/venndir_to_df.Rd +++ b/man/venndir_to_df.Rd @@ -6,11 +6,15 @@ \usage{ venndir_to_df( venndir_out, - return_type = c("kable", "data.frame"), + df_format = c("hits", "items", "wide"), + return_type = c("data.frame", "kable"), trim_blanks = TRUE, wrap_width = 80, colorize_headers = TRUE, set_colors = NULL, + item_type = "gene", + add_counts = TRUE, + verbose = FALSE, ... ) } @@ -50,20 +54,31 @@ for visual review. } } \examples{ -setlist <- venndir::make_venn_test(100, 3); +setlist <- venndir::make_venn_test(100, 3, do_signed=TRUE); venndir_out <- venndir::venndir(setlist, overlap_type="each") -kdf <- venndir_to_df(venndir_out) -kdf +df <- venndir_to_df(venndir_out) +head(df, 10) -kdf <- venndir_to_df(venndir_out, return_type="data.frame") +kdf <- venndir_to_df(venndir_out, return_type="kable") kdf +df2 <- venndir_to_df(venndir_out, df_format="items") +head(df2, 10) + +kdf2 <- venndir_to_df(venndir_out, df_format="items", return_type="kable") +kdf2 + +df3 <- venndir_to_df(venndir_out, df_format="wide", return_type="data.frame") +df3 + +kdf3 <- venndir_to_df(venndir_out, df_format="wide", return_type="kable") +kdf3 + } \seealso{ Other venndir utility: \code{\link{curate_venn_labels}()}, \code{\link{expand_range}()}, -\code{\link{get_venn_shapes}()}, \code{\link{make_color_contrast}()}, \code{\link{make_venn_combn_df}()}, \code{\link{make_venn_test}()}, diff --git a/man/xy_list_to_polygon_list.Rd b/man/xy_list_to_polygon_list.Rd deleted file mode 100644 index d79bd74..0000000 --- a/man/xy_list_to_polygon_list.Rd +++ /dev/null @@ -1,42 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/venndir-poly-conversions.R -\name{xy_list_to_polygon_list} -\alias{xy_list_to_polygon_list} -\title{Convert coordinate list of x and y into polygon list of x,y coordinates} -\usage{ -xy_list_to_polygon_list(x, ...) -} -\description{ -Convert coordinate list of x and y into polygon list of x,y coordinates -} -\examples{ -counts <- c(A=1, B=2, `A&B`=3) -x <- eulerr::euler(counts) -polygon_list <- eulerr_to_polygon_list(x) -xy_list <- polygon_list_to_xy_list(polygon_list) -polygon_list2 <- xy_list_to_polygon_list(xy_list) -identical(polygon_list, polygon_list2) - -} -\seealso{ -Other venndir polygons: -\code{\link{bbox_polygon_list}()}, -\code{\link{eulerr_to_polygon_list}()}, -\code{\link{get_largest_polygon_list}()}, -\code{\link{get_venn_polygon_shapes}()}, -\code{\link{intersect_polygon_list}()}, -\code{\link{labelr_polygon_list}()}, -\code{\link{minus_polygon_list}()}, -\code{\link{nudge_polygon_coords}()}, -\code{\link{nudge_polygon_list}()}, -\code{\link{plot_polygon_list}()}, -\code{\link{polygon_areas}()}, -\code{\link{polygon_circles}()}, -\code{\link{polygon_ellipses}()}, -\code{\link{polygon_list_labelr}()}, -\code{\link{polygon_list_to_xy_list}()}, -\code{\link{rescale_polygon_list}()}, -\code{\link{simple_ellipse}()}, -\code{\link{union_polygon_list}()} -} -\concept{venndir polygons} diff --git a/tests/testthat/_snaps/proportional-figure/euler-2-way-venndir.svg b/tests/testthat/_snaps/proportional-figure/euler-2-way-venndir.svg index b18ddae..7652943 100644 --- a/tests/testthat/_snaps/proportional-figure/euler-2-way-venndir.svg +++ b/tests/testthat/_snaps/proportional-figure/euler-2-way-venndir.svg @@ -18,57 +18,38 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + + + + + - - + + -25 -↑: -12 -↓: -13 +25 +↑:12 +↓:13 set_A -7 -↑↑: -4 -↓↓: -2 -X: -1 -9 -↑: -5 -↓: -4 +7 +↑↑:4 +↓↓:2 +X:1 +9 +↑:5 +↓:4 set_B - - + + @@ -96,7 +77,7 @@ - + @@ -106,7 +87,7 @@ - + @@ -126,7 +107,7 @@ - + @@ -136,7 +117,7 @@ - + diff --git a/tests/testthat/_snaps/proportional-figure/euler-4-way-venndir.svg b/tests/testthat/_snaps/proportional-figure/euler-4-way-venndir.svg index 698a2bb..56bbaa7 100644 --- a/tests/testthat/_snaps/proportional-figure/euler-4-way-venndir.svg +++ b/tests/testthat/_snaps/proportional-figure/euler-4-way-venndir.svg @@ -18,145 +18,94 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + - - - - - + + + + + - - + + - + -18 -↑: -9 -↓: -9 +18 +↑:9 +↓:9 set_A -4 -↑↑: -2 -↓↓: -1 -X: -1 -1 -X: -1 -1 -↑↑↑: -1 -8 -↑↑: -2 -↓↓: -2 -X: -4 -8 -↑: -5 -↓: -3 +4 +↑↑:2 +↓↓:1 +X:1 +1 +X:1 +1 +↑↑↑:1 +8 +↑↑:2 +↓↓:2 +X:4 +8 +↑:5 +↓:3 set_B -2 -↑↑: -1 -↓↓: -1 -6 -↑: -1 -↓: -5 +2 +↑↑:1 +↓↓:1 +6 +↑:1 +↓:5 set_C -1 -↑: -1 +1 +↑:1 set_D - - - - + + + + @@ -184,7 +133,7 @@ - + @@ -194,7 +143,7 @@ - + @@ -204,7 +153,7 @@ - + @@ -214,7 +163,7 @@ - + @@ -234,7 +183,7 @@ - + @@ -244,7 +193,7 @@ - + @@ -254,7 +203,7 @@ - + @@ -264,7 +213,7 @@ - + diff --git a/tests/testthat/_snaps/proportional-figure/proportional-nested-render-venndir.svg b/tests/testthat/_snaps/proportional-figure/proportional-nested-render-venndir.svg index 616642d..7f08692 100644 --- a/tests/testthat/_snaps/proportional-figure/proportional-nested-render-venndir.svg +++ b/tests/testthat/_snaps/proportional-figure/proportional-nested-render-venndir.svg @@ -18,45 +18,16 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + @@ -69,9 +40,9 @@ set_C 2 set_B - - - + + + @@ -99,7 +70,7 @@ - + @@ -109,7 +80,7 @@ - + @@ -119,7 +90,7 @@ - + @@ -139,7 +110,7 @@ - + @@ -149,7 +120,7 @@ - + @@ -159,7 +130,7 @@ - + diff --git a/tests/testthat/_snaps/proportional-figure/proportional-nested-venndir.svg b/tests/testthat/_snaps/proportional-figure/proportional-nested-venndir.svg index 616642d..7f08692 100644 --- a/tests/testthat/_snaps/proportional-figure/proportional-nested-venndir.svg +++ b/tests/testthat/_snaps/proportional-figure/proportional-nested-venndir.svg @@ -18,45 +18,16 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + @@ -69,9 +40,9 @@ set_C 2 set_B - - - + + + @@ -99,7 +70,7 @@ - + @@ -109,7 +80,7 @@ - + @@ -119,7 +90,7 @@ - + @@ -139,7 +110,7 @@ - + @@ -149,7 +120,7 @@ - + @@ -159,7 +130,7 @@ - + diff --git a/tests/testthat/_snaps/proportional-figure/venn-2-way-venndir.svg b/tests/testthat/_snaps/proportional-figure/venn-2-way-venndir.svg index 9a615c5..0497b2d 100644 --- a/tests/testthat/_snaps/proportional-figure/venn-2-way-venndir.svg +++ b/tests/testthat/_snaps/proportional-figure/venn-2-way-venndir.svg @@ -18,57 +18,38 @@ - - - - - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + + + + - - - + + + set_A -25 -↑: -12 -↓: -13 -7 -↑↑: -4 -↓↓: -2 -X: -1 -9 -↑: -5 -↓: -4 +25 +↑:12 +↓:13 +7 +↑↑:4 +↓↓:2 +X:1 +9 +↑:5 +↓:4 set_B - - + + @@ -96,7 +77,7 @@ - + @@ -106,7 +87,7 @@ - + @@ -126,7 +107,7 @@ - + @@ -136,7 +117,7 @@ - + diff --git a/tests/testthat/_snaps/proportional-figure/venn-3-way-render-venndir.svg b/tests/testthat/_snaps/proportional-figure/venn-3-way-render-venndir.svg index e237006..51c5ab0 100644 --- a/tests/testthat/_snaps/proportional-figure/venn-3-way-render-venndir.svg +++ b/tests/testthat/_snaps/proportional-figure/venn-3-way-render-venndir.svg @@ -18,56 +18,33 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + + + + + + + + + + + + + + + + + + @@ -80,9 +57,9 @@ 2 set_B set_C - - - + + + @@ -110,7 +87,7 @@ - + @@ -120,7 +97,7 @@ - + @@ -130,7 +107,7 @@ - + @@ -150,7 +127,7 @@ - + @@ -160,7 +137,7 @@ - + @@ -170,7 +147,7 @@ - + diff --git a/tests/testthat/_snaps/proportional-figure/venn-3-way-venndir.svg b/tests/testthat/_snaps/proportional-figure/venn-3-way-venndir.svg index e237006..51c5ab0 100644 --- a/tests/testthat/_snaps/proportional-figure/venn-3-way-venndir.svg +++ b/tests/testthat/_snaps/proportional-figure/venn-3-way-venndir.svg @@ -18,56 +18,33 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + + + + + + + + + + + + + + + + + + @@ -80,9 +57,9 @@ 2 set_B set_C - - - + + + @@ -110,7 +87,7 @@ - + @@ -120,7 +97,7 @@ - + @@ -130,7 +107,7 @@ - + @@ -150,7 +127,7 @@ - + @@ -160,7 +137,7 @@ - + @@ -170,7 +147,7 @@ - + diff --git a/tests/testthat/_snaps/proportional-figure/venn-4-way-venndir.svg b/tests/testthat/_snaps/proportional-figure/venn-4-way-venndir.svg index a5f84d4..634d388 100644 --- a/tests/testthat/_snaps/proportional-figure/venn-4-way-venndir.svg +++ b/tests/testthat/_snaps/proportional-figure/venn-4-way-venndir.svg @@ -18,197 +18,106 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + - - - - - + + + + + - - - + + + - + set_A -18 -↑: -9 -↓: -9 -4 -↑↑: -2 -↓↓: -1 -X: -1 -1 -X: -1 -1 -↑↑↑: -1 -8 -↑↑: -2 -↓↓: -2 -X: -4 +18 +↑:9 +↓:9 +4 +↑↑:2 +↓↓:1 +X:1 +1 +X:1 +1 +↑↑↑:1 +8 +↑↑:2 +↓↓:2 +X:4 set_B -8 -↑: -5 -↓: -3 -2 -↑↑: -1 -↓↓: -1 -6 -↑: -1 -↓: -5 +8 +↑:5 +↓:3 +2 +↑↑:1 +↓↓:1 +6 +↑:1 +↓:5 set_C set_D -1 -↑: -1 - - - - +1 +↑:1 + + + + @@ -236,7 +145,7 @@ - + @@ -246,7 +155,7 @@ - + @@ -256,7 +165,7 @@ - + @@ -266,7 +175,7 @@ - + @@ -286,7 +195,7 @@ - + @@ -296,7 +205,7 @@ - + @@ -306,7 +215,7 @@ - + @@ -316,7 +225,7 @@ - + diff --git a/tests/testthat/_snaps/venn-meme/venn-meme-bix.svg b/tests/testthat/_snaps/venn-meme/venn-meme-bix.svg index 44f52ea..a7a80d6 100644 --- a/tests/testthat/_snaps/venn-meme/venn-meme-bix.svg +++ b/tests/testthat/_snaps/venn-meme/venn-meme-bix.svg @@ -18,65 +18,42 @@ - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -Stats -Computer -Science -Biology -Data -Science -Biostatistics -Computational -Biology -Bioinformatics + + + + + + + + + + + + + + + + + + + + + + + + + + + +Stats +Computer +Science +Biology +Data +Science +Biostatistics +Computational +Biology +Bioinformatics diff --git a/tests/testthat/test-proportional-figure.R b/tests/testthat/test-proportional-figure.R index 5482d5b..493a758 100644 --- a/tests/testthat/test-proportional-figure.R +++ b/tests/testthat/test-proportional-figure.R @@ -59,6 +59,7 @@ test_that("proportional_nested_figure", { set.seed(123) run_venndir <- function() { vo5p <- venndir(setlist=list(set_A=LETTERS, set_B=LETTERS[1:10], set_C=LETTERS[6:7]), + innerborder.lwd=0, proportional=TRUE, do_plot=TRUE, center_method="label") } if (jamba::check_pkg_installed("vdiffr")) { @@ -70,7 +71,8 @@ test_that("proportional_nested_figure", { vo5p <- venndir(setlist=list(set_A=LETTERS, set_B=LETTERS[1:10], set_C=LETTERS[6:7]), proportional=TRUE, do_plot=FALSE, center_method="label") run_vo5p <- function() { - render_venndir(vo5p) + render_venndir(vo5p, + innerborder.lwd=0) } if (jamba::check_pkg_installed("vdiffr")) { vdiffr::expect_doppelganger("Proportional, nested render_venndir()", run_vo5p)