diff --git a/DESCRIPTION b/DESCRIPTION index 268d0ff3..5167dbfe 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: tmap Title: Thematic Maps -Version: 3.99.9001 +Version: 3.99.9002 Authors@R: c( person("Martijn", "Tennekes", , "mtennekes@gmail.com", role = c("aut", "cre")), person("Jakub", "Nowosad", , "nowosad.jakub@gmail.com", role = "ctb"), diff --git a/NAMESPACE b/NAMESPACE index fab5fcaa..183cdf08 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -187,9 +187,6 @@ export(tm_logo) export(tm_markers) export(tm_minimap) export(tm_mouse_coordinates) -export(tm_mv) -export(tm_mv_dim) -export(tm_mv_shape_vars) export(tm_options) export(tm_place_legends_bottom) export(tm_place_legends_inside) @@ -229,7 +226,6 @@ export(tm_scale_rgba) export(tm_scalebar) export(tm_sf) export(tm_shape) -export(tm_shape_vars) export(tm_squares) export(tm_style) export(tm_symbols) @@ -238,6 +234,7 @@ export(tm_tiles) export(tm_title) export(tm_title_in) export(tm_title_out) +export(tm_vars) export(tm_view) export(tm_xlab) export(tm_ylab) diff --git a/R/messages_v4_v3.R b/R/messages_v4_v3.R index f7c08ff6..db6ed02c 100644 --- a/R/messages_v4_v3.R +++ b/R/messages_v4_v3.R @@ -247,6 +247,12 @@ v3_opt = function(olds, news, layer_fun) { message("[v3->v4] ", layer_fun, "(): migrate the layer options ", x, " to 'options = opt_", layer_fun, "()'") } + +v3_tm_rgb = function(r, g, b) { + message("[v3->v4] ", "tm_rgb", "(): instead of using r = ", r, ", g = ", g, ", and b = ", b, ", please use col = tm_vars(c(", r, ", ", g, ", ", b, "), multivariate = TRUE)") +} + + # v3_multiple = function(layer_fun, vv) { # if (!message_thrown("multiple_args")) { # message("[v3->v4] ", layer_fun, "(): use '", vv, ".scale = list(, , ...)' to specify small multiples") diff --git a/R/process_meta.R b/R/process_meta.R index 22d30b9b..ceb3bac8 100644 --- a/R/process_meta.R +++ b/R/process_meta.R @@ -87,7 +87,6 @@ preprocess_meta = function(o, cdt) { set_to_stack_message = FALSE } - }) } @@ -141,7 +140,6 @@ process_meta = function(o, d, cdt, aux) { o$credits.defined = (!is.na(cid)) bbx = d$bbox[[1]] - within(o, { # sasp shape aspect ratio (NA if free coordinates) diff_asp = any(d$asp != d$asp[1]) @@ -164,6 +162,7 @@ process_meta = function(o, d, cdt, aux) { if (gs == "Grid") { + bufferH = lineH / 2 bufferW = lineW / 2 @@ -397,7 +396,7 @@ process_meta = function(o, d, cdt, aux) { stacks = o$legend.stack - + cdt2[is.na(by1__) & is.na(by2__) & class == "autoout", ':='(cell.h = legend.position.all$cell.h, cell.v = legend.position.all$cell.v)] cdt2[!is.na(by1__) & is.na(by2__) & class == "autoout", ':='(cell.h = legend.position.sides$cell.h, cell.v = "by")] cdt2[is.na(by1__) & !is.na(by2__) & class == "autoout", ':='(cell.h = "by", cell.v = legend.position.sides$cell.v)] diff --git a/R/qtm.R b/R/qtm.R index 99e03142..71312c40 100644 --- a/R/qtm.R +++ b/R/qtm.R @@ -135,7 +135,7 @@ qtm <- function(shp, args_rst = args[nms_rst] if (!any(c("col", "raster") %in% called)) { - args_rst$col = tm_shape_vars() + args_rst$col = tm_vars() } nms_rst_v3 = names(args)[substr(names(args), 1, 7) == "raster."] diff --git a/R/step1_helper_facets.R b/R/step1_helper_facets.R index f083c54e..e060910e 100644 --- a/R/step1_helper_facets.R +++ b/R/step1_helper_facets.R @@ -81,86 +81,106 @@ step1_rearrange_facets = function(tmo, o) { assign("c2d_vars", character(0), envir = .TMAP) precheck_aes = function(a, layer, shpvars, args) { - within(a, { + b = within(a, { + if (inherits(value, "tmapAsIs")) { + if (inherits(scale, "tm_scale_auto")) { + class(scale) = c("tm_scale_asis", "tm_scale", "list") + scale$FUN = tmapScaleAsIs + } + } - if (inherits(value, "tmapDimVars") || (inherits(value, "tmapMVShpVars") && length(shpvars) == 1L)) { - if (inherits(value, "tmapDimVars")) { - if (!(value$x %in% smeta$dims)) stop("Unknown dimension in tm_dim_vars", call. = FALSE) + # check if dimension is or should be used + if (inherits(value, "tmapVars") && (length(smeta$dims) != 0) && (!is.null(value$dimvalues) || (!is.na(value$x[1]) && length(value$x) == 1L) || (value$multivariate && length(shpvars) == 1L))) { + if (is.na(value$x)) { + value$x = smeta$dims[1] } else { - value = list(x = smeta$dims[1], values = { - if (is.na(value$n)) smeta$dims_vals[[1]] else smeta$dims_vals[[1]][1L:value$n] - }) + if (length(value$x) > 1L) { + warning("dimvalues specified while more than one dimension name is specified. Only the first will be used", call. = FALSE) + value$x = value$x[1] + } + if (!(value$x %in% smeta$dims)) { + stop("dimvalues specified, but dimension \"" , x, "\" not found. Available dimension name(s): ", paste(smeta$dims,collapse = ", "), call. = FALSE) + } } - + if (is.null(value$dimvalues)) { + if (!is.na(value$n)) { + value$dimvalues = smeta$dims_vals[[value$x]][1L:value$n] + } else { + if (!all(value$dimvalues) %in% smeta$dims_vals[[value$x]]) stop("Incorrect dimvalues", call. = FALSE) + } + } + split_stars_dim = value$x - if (!all(value$values %in% smeta$dims_vals[[split_stars_dim]])) stop("Unknown values in tm_dim_vars", call. = FALSE) - - update_grp_vars(lev = value$x) - add_used_vars(value$values) + add_used_vars(value$dimvalues) # redefine value for step 2 - value = structure(list(as.character(value$values)), names = value$x, class = "tmapVars") - + if (value$multivariate) { + update_grp_vars(lev = value$x) + value = structure(list(as.character(value$dimvalues)), names = paste(as.character(value$dimvalues), collapse = "_"), class = "tmapVars") + } else { + update_grp_vars(lev = value$dimvalues) + value = structure(as.list(as.character(value$dimvalues)), names = as.character(value$dimvalues), class = "tmapVars") + } data_vars = TRUE geo_vars = FALSE - + } else { split_stars_dim = "" - value_orig = value # just for the case of L156 - if (length(value) && is.na(value[[1]][1]) && !inherits(value, c("tmapMVShpVars", "tmapShpVars"))) { + + #value_orig = value # just for the case of L156 + if (length(value) && is.na(value[[1]][1]) && !inherits(value, c("tmapOption", "tmapVars", "tmapAsIs", "tmapSpecial"))) { # NA -> value.blank - value = tmapVars(getAesOption("value.blank", o, aes = aes, layer = layer)) + value = tmapVV(getAesOption("value.blank", o, aes = aes, layer = layer)) } if (inherits(value, "tmapOption")) { - value_orig = tmapVars(getAesOption(value[[1]], o, aes = aes, layer = layer)) + #value_orig = tmapVV(getAesOption(value[[1]], o, aes = aes, layer = layer)) + value = tmapVV(getAesOption(value[[1]], o, aes = aes, layer = layer)) + data_vars = FALSE + geo_vars = FALSE #if (!is.list(value_orig)) value = list(value_orig) - value = value_orig - names(value) = sapply(value, "[", 1) - } else if (inherits(value, "tmapShpVars")) { - if (!is.na(value$ids[1])) { - if (!all(value$ids %in% 1L:length(shpvars))) stop("tm_shape_vars defined for ids = ", paste(value$ids, collapse = ", "), " while there are only ", length(shpvars), " variables", call. = FALSE) - value = as.list(shpvars[value$ids]) + #value = value_orig + #names(value) = sapply(value, "[", 1) + } else if (inherits(value, "tmapVars")) { + if (!is.na(value$x[1])) { + if (is.character(value$x)) { + if (!all(value$x %in% shpvars)) stop("not all variables specified in tm_vars are found", call. = FALSE) + vars = value$x + } else { + if (!all(value$x %in% 1L:length(shpvars))) stop("tm_vars defined for x = ", paste(value$ids, collapse = ", "), " while there are only ", length(shpvars), " variables", call. = FALSE) + vars = shpvars[value$x] + } } else if (!is.na(value$n)) { - if (length(shpvars) < value$n) stop("tm_shape_vars defined for n = ", value$n, " while there are only ", length(shpvars), " variables", call. = FALSE) - value = as.list(shpvars[1L:value$n]) + if (length(shpvars) < value$n) stop("tm_vars defined for n = ", value$n, " while there are only ", length(shpvars), " variables", call. = FALSE) + vars = shpvars[1L:value$n] } else { - value = as.list(shpvars) + vars = shpvars } - } else if (inherits(value, "tmapMVShpVars")) { - if (!is.na(value$ids[1])) { - if (!all(value$ids %in% 1L:length(shpvars))) stop("tm_shape_vars defined for ids = ", paste(value$ids, collapse = ", "), " while there are only ", length(shpvars), " variables", call. = FALSE) - value = list(shpvars[value$ids]) - } else if (!is.na(value$n)) { - if (length(shpvars) < value$n) stop("tm_shape_vars specified with n = ", value$n, " but there are only ", length(shpvars), " variables available", call. = FALSE) - value = list(shpvars[1L:value$n]) + names(vars) = vars + if (value$multivariate) { + value = structure(list(unname(vars)), names = paste(vars, collapse = "_"), class = "tmapStandard") } else { - value = list(shpvars) + value = structure(as.list(vars), class = "tmapStandard") } - } else { - value_orig = value - #value = lapply(value_orig, make.names) - names(value) = value_orig - if (inherits(value_orig, "tmapAsIs")) { - if (inherits(scale, "tm_scale_auto")) { - class(scale) = c("tm_scale_asis", "tm_scale", "list") - scale$FUN = tmapScaleAsIs - } + data_vars = TRUE + geo_vars = FALSE + } else { + if (inherits(value, "tmapStandard")) { + uvalue = unlist(value) + data_vars = all(uvalue %in% shpvars) + geo_vars = all(uvalue %in% c("AREA", "LENGTH", "MAP_COLORS")) && !data_vars + if (data_vars) vars = uvalue + } else { + data_vars = FALSE + geo_vars = FALSE + vars = character(0) } } nvars = length(value) #m nvari = vapply(value, length, integer(1)) - if (inherits(value_orig, c("tmapSpecial", "tmapAsIs"))) { - data_vars = FALSE - geo_vars = FALSE - } else { - vars = unlist(value) - data_vars = all(vars %in% shpvars) - geo_vars = all(vars %in% c("AREA", "LENGTH", "MAP_COLORS")) && !data_vars - } - + convert2density = "convert2density" %in% names(scale) && scale$convert2density nflvar = nvars @@ -176,9 +196,7 @@ step1_rearrange_facets = function(tmo, o) { # if (aes == "shape") browser() mfun = paste0("tmapValuesSubmit_", aes) if (exists(mfun)) { - value = do.call(mfun, list(x = value_orig, args = args)) - } else { - value = value_orig + value = do.call(mfun, list(x = value, args = args)) } nvars = length(value) nflvar = nvars @@ -190,6 +208,7 @@ step1_rearrange_facets = function(tmo, o) { } } }) + b } @@ -243,7 +262,7 @@ step1_rearrange_facets = function(tmo, o) { # split stars if needed (dimension -> attributes) split_stars_dim = get_split_stars_dim(tmg$tmls) - shp = tmapSplitShp(shp, split_stars_dim) + shp = tmapSplitShp(shp, split_stars_dim, smeta) if (split_stars_dim != "") { smeta = tmapGetShapeMeta1(shp, o) if (dev) timing_add(s3 = "get_shape_meta1_2") @@ -409,7 +428,6 @@ step1_rearrange_facets = function(tmo, o) { } } } - if (is.na(free.coords)) { if (type %in% c("wrapstack", "wrap", "stack", "page")) { @@ -443,6 +461,7 @@ step1_rearrange_facets = function(tmo, o) { }) tmf = get_tmf(lapply(tmo, function(tmoi) tmoi$tmf)) + tmo$tmf_global = tmf tmo } diff --git a/R/step2_helper_data.R b/R/step2_helper_data.R index 7d9e60b6..af946bfb 100644 --- a/R/step2_helper_data.R +++ b/R/step2_helper_data.R @@ -112,9 +112,9 @@ getdts = function(aes, unm, p, q, o, dt, shpvars, layer, mfun, args, plot.order) if (inherits(val, "tmapUsrCls")) { temp = local({ - # not data driven variable: visual variable to support tm_mv of other visual variable (e.g. fill of donut maps) - k = length(aes$value[[1]]) - vls = unname(aes$value[[1]]) + # not data driven variable: visual variable to support tm_vars(multivariate = TRUE) of other visual variable (e.g. fill of donut maps) + k = length(aes$value[[1]]$x) + vls = unname(aes$value[[1]]$x) dtl = data.table::data.table(tmapID__ = 1L:k, sel = TRUE, value = factor(vls, levels = vls)) @@ -142,7 +142,6 @@ getdts = function(aes, unm, p, q, o, dt, shpvars, layer, mfun, args, plot.order) submit_legend = TRUE) dtl[, c(varname, legname, crtname) := do.call(f, c(unname(.SD), arglist)), .SDcols = "value"] - list(val = paste(dtl[[varname]], collapse = "__"), legnr = dtl$legnr_1[1], ctrnr = dtl$crtnr_1[1]) @@ -161,8 +160,8 @@ getdts = function(aes, unm, p, q, o, dt, shpvars, layer, mfun, args, plot.order) if (!aes$data_vars && !aes$geo_vars) { #cat("step2_grp_lyr_aes_const", unm," \n") - # constant values (take first value (of possible tm_mv per facet) - if (any(nvari) > 1) warning("Aesthetic values considered as direct visual variables, which cannot be used with tm_mv", call. = FALSE) + # constant values (take first value (of possible multivariate per facet) + if (any(nvari) > 1) warning("Aesthetic values considered as direct visual variables, which cannot be used with multivariate variables", call. = FALSE) val1 = sapply(vars, "[[", 1, USE.NAMES = FALSE) check_fun = paste0("tmapValuesCheck_", nm) check = do.call(check_fun, list(x = val1)) @@ -304,9 +303,8 @@ getdts = function(aes, unm, p, q, o, dt, shpvars, layer, mfun, args, plot.order) names(val) = val_name vars = vars[1] # only needed for update_fl? } - if (length(v)) update_fl(k = v, lev = vars) - + apply_scale = function(s, l, crt, v, varname, ordname, legname, crtname, sortRev, bypass_ord) { l = update_l(o = o, l = l, v = v, mfun = mfun, unm = unm, active = TRUE) crt = update_crt(o = o, crt = crt, v = v, mfun = mfun, unm = unm, active = TRUE) @@ -340,6 +338,19 @@ getdts = function(aes, unm, p, q, o, dt, shpvars, layer, mfun, args, plot.order) if (all(is.ena(l$title))) l$title = paste0(names(v), attr(cls, "units"), unit) } + if (f != "tmapScaleAuto") { + # number of variables needed + fnames = names(formals(f)) + fnvar = which(fnames == "scale") - 1L + if (fnames[1] != "...") { + if (fnvar > length(v)) { + stop("Too few variables defined") + } else if (fnvar < length(v)) { + warning("Too many variables defined") + v = v[1L:fnvar] + } + } + } #aesname = aes$aes @@ -416,7 +427,6 @@ getdts = function(aes, unm, p, q, o, dt, shpvars, layer, mfun, args, plot.order) ordnames = paste(unm__ord, 1L:nvars, sep = "_") legnames = paste("legnr", 1L:nvars, sep = "_") crtnames = paste("crtnr", 1L:nvars, sep = "_") - for (i in 1L:nvars) { dtl = apply_scale(scale[[i]], legend[[i]], crt[[i]], val[[i]], varnames[[i]], ordnames[[i]], legnames[[i]], crtnames[[i]], sortRev = sortRev, bypass_ord = bypass_ord) } @@ -434,6 +444,7 @@ getdts = function(aes, unm, p, q, o, dt, shpvars, layer, mfun, args, plot.order) #sel = !vapply(dtl_leg$legend, is.null, logical(1)) dtl_leg = dtl_leg[legnr != 0, c(grp_bv_fr, "legnr"), with = FALSE] dtl_crt = dtl_crt[crtnr != 0, c(grp_bv_fr, "crtnr"), with = FALSE] + } else { #cat("step2_grp_lyr_aes_var_one_aes_column\n") diff --git a/R/step2_helper_facets.R b/R/step2_helper_facets.R index 4abb5246..aba4309f 100644 --- a/R/step2_helper_facets.R +++ b/R/step2_helper_facets.R @@ -70,7 +70,6 @@ get_tmf = function(tmfs) { if (tmf$type == "wrapstack") { tmf$type = if (tmf$n > 3) "wrap" else "stack" } - tmf } diff --git a/R/tm_layers_raster.R b/R/tm_layers_raster.R index ac5d2d96..f2d8cf76 100644 --- a/R/tm_layers_raster.R +++ b/R/tm_layers_raster.R @@ -55,7 +55,7 @@ opt_tm_raster = function(interpolate = FALSE) { #' @param ... to catch deprecated arguments from version < 4.0 #' @example ./examples/tm_raster.R #' @export -tm_raster = function(col = tm_shape_vars(), +tm_raster = function(col = tm_vars(), col.scale = tm_scale(value.na = "#00000000"), col.legend = tm_legend(), col.chart = tm_chart_none(), diff --git a/R/tm_layers_rgb.R b/R/tm_layers_rgb.R index 77437b1a..ad0b2482 100644 --- a/R/tm_layers_rgb.R +++ b/R/tm_layers_rgb.R @@ -11,22 +11,52 @@ opt_tm_rgb = function(interpolate = FALSE) { #' Map layer that an rgb image.. The used (multivariate) visual variable is `col`, which should be specified with 3 or 4 variables for `tm_rgb` and `tm_rgba` respectively. The first three correspond to the red, green, and blue channels. The optional fourth is the alpha transparency channel. #' #' @param col,col.scale,col.legend,col.chart,col.free Visual variable that determines -#' the col color. `col` is a multivariate variable, with 3 (`tm_rgb`) or 4 (`tm_rgba`) numeric data variables. These can be specified via [tm_mv()] or [tm_mv_dim()] +#' the col color. `col` is a multivariate variable, with 3 (`tm_rgb`) or 4 (`tm_rgba`) numeric data variables. These can be specified via [tm_vars()] with `multivarite = TRUE` #' @param options options passed on to the corresponding `opt_` function +#' @param ... to catch deprecated arguments from version < 4.0 #' @example ./examples/tm_rgb.R #' @export -tm_rgb = function(col = tm_mv_shape_vars(n = 3), +tm_rgb = function(col = tm_vars(n = 3, multivariate = TRUE), col.scale = tm_scale_rgb(), col.legend = tm_legend(), col.chart = tm_chart_none(), col.free = NA, - options = opt_tm_rgb()) { + options = opt_tm_rgb(), + ...) { + args = list(...) + args_called = as.list(match.call()[-1]) + + if (any(v3_only("tm_rgb") %in% names(args)) || is.numeric(col.scale)) { + v3_start_message() + + # second condition needed to catch tm_rgb(1, 2, 3) + layer_fun = if ("called_from" %in% names(args)) { + args$called_from + } else { + "tm_rgb" + } + + if (all(c("r", "g", "b") %in% names(args))) { + v3_tm_rgb(args$r, args$g, args$b) + col = tm_vars(c(args$r, args$g, args$b), multivariate = TRUE) + } + if (is.numeric(col) && is.numeric(col.scale) && is.numeric(col.legend)) { + col = tm_vars(c(col, col.scale, col.legend), multivariate = TRUE) + col.scale = tm_scale_rgb() + col.legend = tm_legend() + } + + v3_start_message() + + } + + do.call(tm_raster, args = list(col = col, col.scale = col.scale, col.legend = col.legend, col.chart = col.chart, col.free = col.free, options = options)) } #' @rdname tm_rgb #' @export -tm_rgba = function(col = tm_mv_shape_vars(n = 4), +tm_rgba = function(col = tm_vars(n = 4, multivariate = TRUE), col.scale = tm_scale_rgba(), col.legend = tm_legend(), col.chart = tm_chart_none(), diff --git a/R/tm_scale_.R b/R/tm_scale_.R index 3e41d221..602064a7 100644 --- a/R/tm_scale_.R +++ b/R/tm_scale_.R @@ -7,24 +7,6 @@ tm_const = function() { tmapOption("value.const") } -#' tmap function to specify all variables in the shape object -#' -#' tmap function to specify all variables in the shape object -#' -#' @param n if specified, the first `n` shape variables are used -#' @param ids index numbers of the used shape variables -#' @export -tm_shape_vars = function(ids = NA, n = NA) { - structure(list(ids = ids, n = n), class = c("tm_shape_vars", "list")) -} - - -#' @rdname tm_shape_vars -#' @export -tm_mv_shape_vars = function(ids = NA, n = NA) { - structure(list(ids = ids, n = n), class = c("tm_mv_shape_vars", "list")) -} - #' Scales: automatic scale #' #' Scales in tmap are configured by the family of functions with prefix `tm_scale`. @@ -239,6 +221,7 @@ tm_scale_discrete = function(ticks = NA, #' @param label.format (generic scale argument) Label formatting (similar to `legend.format` in tmap3) #' @param trans.args list of additional argument for the transformation (generic transformation arguments) #' @inheritParams scales::transform_pseudo_log +#' @example ./examples/tm_scale_continuous.R #' @seealso [tm_scale()] #' @export #' @rdname tm_scale_continuous @@ -369,22 +352,32 @@ tm_scale_continuous_pseudo_log = function(..., base = exp(1), sigma = 1) { #' Scales: RGB #' -#' Scales: RGB +#' Scales in tmap are configured by the family of functions with prefix `tm_scale`. +#' Such function should be used for the input of the `.scale` arguments in the layer +#' functions (e.g. `fill.scale` in [tm_polygons()]). +#' The function [tm_scale_rgb()] is used to transform r, g, b band variables to colors. This function is adopted from (and works similar as) [stars::st_rgb()] #' #' @param value.na value for missing values -#' @param maxValue maximum value -#' @seealso [tm_scale()] +#' @param stretch should each (r, g, b) band be stretched? Possible values: `"percent"` (same as `TRUE`) and `"histogram"`. In the first case, the values are stretched to `probs[1]...probs[2]`. In the secodn case, a histogram equalization is performed +#' @param probs probability (quantile) values when `stretch = "percent"` +#' @param maxColorValue maximum value +#' @seealso [tm_scale()] and [stars::st_rgb()] #' @rdname tm_scale_rgb +#' @example ./examples/tm_scale_rgb.R #' @export tm_scale_rgb = function(value.na = NA, - maxValue = 255) { + stretch = FALSE, + probs = c(0, 1), + maxColorValue = 255L) { structure(c(list(FUN = "tmapScaleRGB"), as.list(environment())), class = c("tm_scale_rgb", "tm_scale", "list")) } #' @rdname tm_scale_rgb #' @export tm_scale_rgba = function(value.na = NA, - maxValue = 255) { + stretch = FALSE, + probs = c(0, 1), + maxColorValue = 255) { structure(c(list(FUN = "tmapScaleRGBA"), as.list(environment())), class = c("tm_scale_rgba", "tm_scale", "list")) } diff --git a/R/tm_vars.R b/R/tm_vars.R new file mode 100644 index 00000000..9fdc16b1 --- /dev/null +++ b/R/tm_vars.R @@ -0,0 +1,37 @@ +#' tmap function to specify variables +#' +#' tmap function to specify all variables in the shape object +#' +#' @param x variable names, variable indices, or a dimension name +#' @param dimvalues dimension values +#' @param n if specified the first `n` variables are taken (or the first `n` dimension values) +#' @param multivariate in case multiple variables are specified, should they serve as facets (FALSE) or as a multivariate visual variable? +#' @export +tm_vars = function(x = NA, dimvalues = NULL, n = NA, multivariate = FALSE) { + structure(list(x = x, dimvalues = dimvalues, n = n, multivariate = multivariate), class = c("tmapVars", "list")) +} + + +# process visual variable specification. Can either be tmapVars (output of tm_vars) or a list of values. +tmapVV = function(x) { + if (inherits(x, c("tmapOption", "tmapVars"))) return(x) + + # if (inherits(x, "tm_shape_vars")) return(structure(list(ids = x$ids, n = x$n), class = "tmapShpVars")) + # if (inherits(x, "tm_mv_shape_vars")) return(structure(list(ids = x$ids, n = x$n), class = "tmapMVShpVars")) + # if (inherits(x, "tmapDimVars")) return(x) + + cls = if (inherits(x, "AsIs")) "tmapAsIs" else if (inherits(x, "tmapUsrCls")) "tmapUsrCls" else "tbd" + + isL = is.list(x) + isSpecialL = isL && !setequal(class(x), "list") + isSpecialNestedL = isL && is.list(x[[1]]) && !setequal(class(x[[1]]), "list") + if (!isL) { + x = as.list(x) + } else if (isSpecialL) { + x = list(x) + } + + if (cls == "tbd") cls = if (isSpecialL) "tmapSpecial" else if (isSpecialNestedL) "tmapSpecial" else "tmapStandard" + + structure(x, names = x, class = cls) +} \ No newline at end of file diff --git a/R/tmapGridAux.R b/R/tmapGridAux.R index 47f9634f..c467c60c 100644 --- a/R/tmapGridAux.R +++ b/R/tmapGridAux.R @@ -80,7 +80,7 @@ tmapGridTilesPrep = function(a, bs, id, o) { if (is.null(x)) NULL else do.call(tmapShape, list(shp = x, is.main = FALSE, crs = crs, bbox = NULL, unit=NULL, filter=NULL, shp_name = "x", smeta = list(), o = o, tmf = NULL)) }) - srgb = tm_scale_rgb(maxValue = 255, value.na = "#FFFFFF") + srgb = tm_scale_rgb(maxColorValue = 255, value.na = "#FFFFFF") ds = lapply(ss, function(s) { diff --git a/R/tmapGridComp_leg_landscape.R b/R/tmapGridComp_leg_landscape.R index d478c847..f4d26445 100644 --- a/R/tmapGridComp_leg_landscape.R +++ b/R/tmapGridComp_leg_landscape.R @@ -365,11 +365,7 @@ tmapGridLegPlot.tm_legend_standard_landscape = function(comp, o, fH, fW) { grItems = mapply(function(id, gpari, gpari1, gpari2) { grobs = if (gpari$shape > 999) { - grbs = if (gpari$lwd == 0) { - gList(shapeLib[[gpari$shape-999]]) - } else { - gList(shapeLib[[gpari$shape-999]], rectGrob(gp=gpar(fill=NA, col=gpari$col, lwd=gpari$lwd))) - } + grbs = gList(shapeLib[[gpari$shape-999]]) grid::gTree(children=grbs, vp=viewport(x=0.5, y=0.5, width=unit(gpari$size*9/10, "lines"), diff --git a/R/tmapGridInit.R b/R/tmapGridInit.R index 3926890f..138c88a3 100644 --- a/R/tmapGridInit.R +++ b/R/tmapGridInit.R @@ -1,5 +1,6 @@ tmapGridInit = function(o, return.asp = FALSE, vp, prx, ...) { rlang::check_installed("grid") + rows = with(o, { x = c(outer.margins.top = outer.margins[3], meta.buffers.top.out = meta.buffers[3], diff --git a/R/tmapGridLegend.R b/R/tmapGridLegend.R index 67d273fa..80d1b040 100644 --- a/R/tmapGridLegend.R +++ b/R/tmapGridLegend.R @@ -385,7 +385,6 @@ tmapGridLegend = function(comp, o, facet_row = NULL, facet_col = NULL, facet_pag if (length(w1) && length(w4)) qW[c(1,4)] = align_values(c(1,4), "h") # bottom edge - grbs = do.call(grid::gList, lapply(1:5, function(i) { id = get(paste0("w", i)) if (length(id)) { diff --git a/R/tmapScaleRGB.R b/R/tmapScaleRGB.R index f55c9d3f..63fbe0f9 100644 --- a/R/tmapScaleRGB.R +++ b/R/tmapScaleRGB.R @@ -22,11 +22,52 @@ tmapScaleRGB_RGBA = function(xlist, scale, legend, chart, o, aes, layer, layer_a isna = Reduce("|", lapply(xlist, is.na)) + mx = max(unlist(xlist, recursive = FALSE, use.names = FALSE), na.rm = TRUE) + + scale = within(scale, { + if (is.logical(stretch)) { + if (stretch) + stretch.method = "percent" + else maxColorValue = max(maxColorValue, mx) + } + if (is.character(stretch)) { + if (!stretch %in% c("percent", "histogram")) + stretch.method = "percent" + else stretch.method = stretch + stretch = TRUE + } + }) + cutoff = function(x, probs, stretch.method = "percent", maxColorValue = 255L) { + if (stretch.method == "percent") { + qs = if (all(probs == c(0, 1))) + range(x) + else quantile(x, probs, na.rm = TRUE) + x = (x - qs[1])/(qs[2] - qs[1]) + x[x > 1] = 1 + x[x < 0] = 0 + x * maxColorValue + } + else if (stretch.method == "histogram") { + x = (stats::ecdf(x))(x) + x * maxColorValue + } + else { + qs = range(x) + (x - qs[1])/(qs[2] - qs[1]) * maxColorValue + } + } + + if (scale$stretch) { + xlist2 = lapply(xlist, cutoff, probs = scale$probs, stretch.method = scale$stretch.method, maxColorValue = scale$maxColorValue) + } else { + xlist2 = xlist + } + if (any(isna)) { values = rep(scale$value.na, n) - values[!isna] = do.call(grDevices::rgb, c(lapply(xlist, function(xl) xl[!isna]), list(maxColorValue = scale$maxValue))) + values[!isna] = do.call(grDevices::rgb, c(lapply(xlist2, function(xl) xl[!isna]), list(maxColorValue = scale$maxColorValue))) } else { - values = do.call(grDevices::rgb, c(xlist, list(maxColorValue = scale$maxValue))) + values = do.call(grDevices::rgb, c(xlist2, list(maxColorValue = scale$maxColorValue))) } diff --git a/R/tmapScale_.R b/R/tmapScale_.R index 9e407f6d..3584b9ad 100644 --- a/R/tmapScale_.R +++ b/R/tmapScale_.R @@ -1,49 +1,3 @@ -#' define multivariate variable -#' -#' define multivariate variable -#' -#' @param ... variable names -#' @export -tm_mv = function(...) { - list(c(...)) -} - -#' define multivariate variable based on stars dimension -#' -#' define multivariate variable based on stars dimension -#' -#' @param x dimension name -#' @param values values to be used -#' @export -tm_mv_dim = function(x, values) { - structure(list(x = x, values = values), class = "tmapDimVars") -} - -tmapVars = function(x) { - if (inherits(x, "tmapOption")) return(x) - - if (inherits(x, "tm_shape_vars")) return(structure(list(ids = x$ids, n = x$n), class = "tmapShpVars")) - if (inherits(x, "tm_mv_shape_vars")) return(structure(list(ids = x$ids, n = x$n), class = "tmapMVShpVars")) - if (inherits(x, "tmapDimVars")) return(x) - - cls = if (inherits(x, "AsIs")) "tmapAsIs" else if (inherits(x, "tmapUsrCls")) "tmapUsrCls" else "tbd" - - isL = is.list(x) - isSpecialL = isL && !setequal(class(x), "list") - isSpecialNestedL = isL && is.list(x[[1]]) && !setequal(class(x[[1]]), "list") - if (!isL) { - x = as.list(x) - } else if (isSpecialL) { - x = list(x) - } - - if (cls == "tbd") cls = if (isSpecialL) "tmapSpecial" else if (isSpecialNestedL) "tmapSpecial" else "tmapStandard" - - - - structure(x, class = cls) -} - #' @param x x #' @export #' @name tmapUsrCls @@ -179,7 +133,7 @@ data_class = function(x, check_for_color_class = FALSE) { #' @rdname tmap_internal #' @keywords internal tmapScale = function(aes, value, scale, legend, chart, free) { - structure(list(aes = aes, value = tmapVars(value), scale = scale, legend = legend, chart = chart, free = free), class = c("tmapScale", "list")) + structure(list(aes = aes, value = tmapVV(value), scale = scale, legend = legend, chart = chart, free = free), class = c("tmapScale", "list")) } tmapScaleAuto = function(x1, scale, legend, chart, o, aes, layer, layer_args, sortRev, bypass_ord, submit_legend = TRUE, ...) { diff --git a/R/tmapSplitShp.R b/R/tmapSplitShp.R index 403e1ae5..88d21c42 100644 --- a/R/tmapSplitShp.R +++ b/R/tmapSplitShp.R @@ -7,13 +7,15 @@ #' @param split_stars_dim name of the dimension to split (`""` to skip) #' @export #' @keywords internal -tmapSplitShp = function(shp, split_stars_dim) { +tmapSplitShp = function(shp, split_stars_dim, smeta) { UseMethod("tmapSplitShp") } #' @export -tmapSplitShp.stars = function(shp, split_stars_dim) { +tmapSplitShp.stars = function(shp, split_stars_dim, smeta) { if (split_stars_dim != "") { + if (length(smeta$vars) > 1L) shp = merge(shp, name = "DIMVARS__") + vals = stars::st_get_dimension_values(shp, split_stars_dim) shp = split(shp, split_stars_dim) names(shp) = vals @@ -22,6 +24,6 @@ tmapSplitShp.stars = function(shp, split_stars_dim) { } #' @export -tmapSplitShp.default = function(shp, split_stars_dim) { +tmapSplitShp.default = function(shp, split_stars_dim, smeta) { shp } \ No newline at end of file diff --git a/examples/tm_chart.R b/examples/tm_chart.R index 090e25c0..d3accb93 100644 --- a/examples/tm_chart.R +++ b/examples/tm_chart.R @@ -54,6 +54,7 @@ tm_shape(World) + fill.scale = tm_scale_categorical(), fill.chart = tm_chart_donut()) -# bivariate (in development) tm_shape(World) + - tm_polygons(tm_mv("HPI", "well_being"), fill.chart = tm_chart_heatmap()) + tm_polygons(tm_vars(c("HPI", "well_being"), multivariate = TRUE), fill.chart = tm_chart_heatmap()) + + diff --git a/examples/tm_polygons.R b/examples/tm_polygons.R index 0d24aaf7..b3f940cc 100644 --- a/examples/tm_polygons.R +++ b/examples/tm_polygons.R @@ -34,4 +34,4 @@ tm_layout(frame = FALSE) # bivariate scale tm_shape(World) + - tm_polygons(tm_mv("inequality", "well_being")) + tm_polygons(tm_vars(c("inequality", "well_being"), multivariate = TRUE)) diff --git a/examples/tm_rgb.R b/examples/tm_rgb.R index 0919a7b5..2af05f2d 100644 --- a/examples/tm_rgb.R +++ b/examples/tm_rgb.R @@ -9,7 +9,7 @@ tm_shape(L7) + \dontrun{ # the previous example was a shortcut of this call tm_shape(L7) + - tm_rgb(col = tm_mv_dim("band", 1:3)) + tm_rgb(col = tm_vars("band", dimvalues = 1:3)) # alternative format: using a stars dimension instead of attributes L7_alt = split(L7, "band") @@ -18,11 +18,11 @@ tm_shape(L7_alt) + # with attribute names tm_shape(L7_alt) + - tm_rgb(col = tm_mv("X1", "X2", "X3")) + tm_rgb(col = tm_vars(c("X1", "X2", "X3"), multivariate = TRUE)) # with attribute indices tm_shape(L7_alt) + - tm_rgb(col = tm_mv_shape_vars(1:3)) + tm_rgb(col = tm_vars(1:3, multivariate = TRUE)) if (requireNamespace("terra")) { L7_terra = terra::rast(file) @@ -32,11 +32,11 @@ if (requireNamespace("terra")) { # with layer names tm_shape(L7_terra) + - tm_rgb(tm_mv(names(L7_terra)[1:3])) + tm_rgb(tm_vars(names(L7_terra)[1:3], multivariate = TRUE)) # with layer indices tm_shape(L7_alt) + - tm_rgb(col = tm_mv_shape_vars(1:3)) + tm_rgb(col = tm_vars(1:3, multivariate = TRUE)) } } diff --git a/examples/tm_scale_continuous.R b/examples/tm_scale_continuous.R index 6220e36c..4edfd96e 100644 --- a/examples/tm_scale_continuous.R +++ b/examples/tm_scale_continuous.R @@ -10,7 +10,6 @@ tm_shape(metro) + values.scale = 1), size.legend = tm_legend("Population in 1950", frame = FALSE)) -# Note that for this type of legend, we recommend tm_scale_intervals() tm_shape(metro) + tm_bubbles( size = "pop1950", @@ -18,6 +17,8 @@ tm_shape(metro) + values.scale = 2, limits = c(0, 12e6), ticks = c(1e5, 3e5, 8e5, 4e6, 1e7), - labels = c("0 - 200,000", "200,000 - 500,000", "500,000 - 1,000,000", "1,000,000 - 10,000,000", "10,000,000 or more"), + labels = c("0 - 200,000", "200,000 - 500,000", "500,000 - 1,000,000", + "1,000,000 - 10,000,000", "10,000,000 or more"), outliers.trunc = c(TRUE, TRUE)), size.legend = tm_legend("Population in 1950", frame = FALSE)) +# Note that for this type of legend, we recommend tm_scale_intervals() diff --git a/examples/tm_scale_rgb.R b/examples/tm_scale_rgb.R new file mode 100644 index 00000000..ebc77c39 --- /dev/null +++ b/examples/tm_scale_rgb.R @@ -0,0 +1,10 @@ +require(stars) +file = system.file("tif/L7_ETMs.tif", package = "stars") + +L7 = stars::read_stars(file) + +tm_shape(L7) + + tm_rgb(col.scale = tm_scale_rgb(probs = c(0, .99), stretch = TRUE)) + +tm_shape(L7) + + tm_rgb(col.scale = tm_scale_rgb(stretch = "histogram")) diff --git a/man/tm_chart.Rd b/man/tm_chart.Rd index 96c1abb2..18efc2ea 100644 --- a/man/tm_chart.Rd +++ b/man/tm_chart.Rd @@ -147,7 +147,8 @@ tm_shape(World) + fill.scale = tm_scale_categorical(), fill.chart = tm_chart_donut()) -# bivariate (in development) tm_shape(World) + - tm_polygons(tm_mv("HPI", "well_being"), fill.chart = tm_chart_heatmap()) + tm_polygons(tm_vars(c("HPI", "well_being"), multivariate = TRUE), fill.chart = tm_chart_heatmap()) + + } diff --git a/man/tm_mv.Rd b/man/tm_mv.Rd deleted file mode 100644 index ac8af2d5..00000000 --- a/man/tm_mv.Rd +++ /dev/null @@ -1,14 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/tmapScale_.R -\name{tm_mv} -\alias{tm_mv} -\title{define multivariate variable} -\usage{ -tm_mv(...) -} -\arguments{ -\item{...}{variable names} -} -\description{ -define multivariate variable -} diff --git a/man/tm_mv_dim.Rd b/man/tm_mv_dim.Rd deleted file mode 100644 index 6c262be2..00000000 --- a/man/tm_mv_dim.Rd +++ /dev/null @@ -1,16 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/tmapScale_.R -\name{tm_mv_dim} -\alias{tm_mv_dim} -\title{define multivariate variable based on stars dimension} -\usage{ -tm_mv_dim(x, values) -} -\arguments{ -\item{x}{dimension name} - -\item{values}{values to be used} -} -\description{ -define multivariate variable based on stars dimension -} diff --git a/man/tm_polygons.Rd b/man/tm_polygons.Rd index 78c47511..aced90ee 100644 --- a/man/tm_polygons.Rd +++ b/man/tm_polygons.Rd @@ -183,5 +183,5 @@ tm_layout(frame = FALSE) # bivariate scale tm_shape(World) + - tm_polygons(tm_mv("inequality", "well_being")) + tm_polygons(tm_vars(c("inequality", "well_being"), multivariate = TRUE)) } diff --git a/man/tm_raster.Rd b/man/tm_raster.Rd index cf5a36b5..7bbddc31 100644 --- a/man/tm_raster.Rd +++ b/man/tm_raster.Rd @@ -8,7 +8,7 @@ opt_tm_raster(interpolate = FALSE) tm_raster( - col = tm_shape_vars(), + col = tm_vars(), col.scale = tm_scale(value.na = "#00000000"), col.legend = tm_legend(), col.chart = tm_chart_none(), diff --git a/man/tm_rgb.Rd b/man/tm_rgb.Rd index b34290ab..79c902f8 100644 --- a/man/tm_rgb.Rd +++ b/man/tm_rgb.Rd @@ -9,16 +9,17 @@ opt_tm_rgb(interpolate = FALSE) tm_rgb( - col = tm_mv_shape_vars(n = 3), + col = tm_vars(n = 3, multivariate = TRUE), col.scale = tm_scale_rgb(), col.legend = tm_legend(), col.chart = tm_chart_none(), col.free = NA, - options = opt_tm_rgb() + options = opt_tm_rgb(), + ... ) tm_rgba( - col = tm_mv_shape_vars(n = 4), + col = tm_vars(n = 4, multivariate = TRUE), col.scale = tm_scale_rgba(), col.legend = tm_legend(), col.chart = tm_chart_none(), @@ -30,9 +31,11 @@ tm_rgba( \item{interpolate}{Should the raster image be interpolated? Currently only applicable in view mode (passed on to \code{\link[grid:grid.raster]{grid}})} \item{col, col.scale, col.legend, col.chart, col.free}{Visual variable that determines -the col color. \code{col} is a multivariate variable, with 3 (\code{tm_rgb}) or 4 (\code{tm_rgba}) numeric data variables. These can be specified via \code{\link[=tm_mv]{tm_mv()}} or \code{\link[=tm_mv_dim]{tm_mv_dim()}}} +the col color. \code{col} is a multivariate variable, with 3 (\code{tm_rgb}) or 4 (\code{tm_rgba}) numeric data variables. These can be specified via \code{\link[=tm_vars]{tm_vars()}} with \code{multivarite = TRUE}} \item{options}{options passed on to the corresponding \verb{opt_} function} + +\item{...}{to catch deprecated arguments from version < 4.0} } \description{ Map layer that an rgb image.. The used (multivariate) visual variable is \code{col}, which should be specified with 3 or 4 variables for \code{tm_rgb} and \code{tm_rgba} respectively. The first three correspond to the red, green, and blue channels. The optional fourth is the alpha transparency channel. @@ -49,7 +52,7 @@ tm_shape(L7) + \dontrun{ # the previous example was a shortcut of this call tm_shape(L7) + - tm_rgb(col = tm_mv_dim("band", 1:3)) + tm_rgb(col = tm_vars("band", dimvalues = 1:3)) # alternative format: using a stars dimension instead of attributes L7_alt = split(L7, "band") @@ -58,11 +61,11 @@ tm_shape(L7_alt) + # with attribute names tm_shape(L7_alt) + - tm_rgb(col = tm_mv("X1", "X2", "X3")) + tm_rgb(col = tm_vars(c("X1", "X2", "X3"), multivariate = TRUE)) # with attribute indices tm_shape(L7_alt) + - tm_rgb(col = tm_mv_shape_vars(1:3)) + tm_rgb(col = tm_vars(1:3, multivariate = TRUE)) if (requireNamespace("terra")) { L7_terra = terra::rast(file) @@ -72,11 +75,11 @@ if (requireNamespace("terra")) { # with layer names tm_shape(L7_terra) + - tm_rgb(tm_mv(names(L7_terra)[1:3])) + tm_rgb(tm_vars(names(L7_terra)[1:3], multivariate = TRUE)) # with layer indices tm_shape(L7_alt) + - tm_rgb(col = tm_mv_shape_vars(1:3)) + tm_rgb(col = tm_vars(1:3, multivariate = TRUE)) } } diff --git a/man/tm_scale_continuous.Rd b/man/tm_scale_continuous.Rd index 4b18cfec..f5e6a2d9 100644 --- a/man/tm_scale_continuous.Rd +++ b/man/tm_scale_continuous.Rd @@ -93,6 +93,32 @@ functions (e.g. \code{fill.scale} in \code{\link[=tm_polygons]{tm_polygons()}}). The function \code{\link[=tm_scale_continuous]{tm_scale_continuous()}} is used for continuous data. The functions \verb{tm_scale_continuous_()} use transformation functions x. } +\examples{ +tm_shape(World) + + tm_polygons( + fill = "HPI", + fill.scale = tm_scale_continuous(values = "scico.roma", midpoint = 30)) + +tm_shape(metro) + + tm_bubbles( + size = "pop1950", + size.scale = tm_scale_continuous( + values.scale = 1), + size.legend = tm_legend("Population in 1950", frame = FALSE)) + +tm_shape(metro) + + tm_bubbles( + size = "pop1950", + size.scale = tm_scale_continuous( + values.scale = 2, + limits = c(0, 12e6), + ticks = c(1e5, 3e5, 8e5, 4e6, 1e7), + labels = c("0 - 200,000", "200,000 - 500,000", "500,000 - 1,000,000", + "1,000,000 - 10,000,000", "10,000,000 or more"), + outliers.trunc = c(TRUE, TRUE)), + size.legend = tm_legend("Population in 1950", frame = FALSE)) +# Note that for this type of legend, we recommend tm_scale_intervals() +} \seealso{ \code{\link[=tm_scale]{tm_scale()}} } diff --git a/man/tm_scale_rgb.Rd b/man/tm_scale_rgb.Rd index 91cedcda..e5cea092 100644 --- a/man/tm_scale_rgb.Rd +++ b/man/tm_scale_rgb.Rd @@ -5,18 +5,47 @@ \alias{tm_scale_rgba} \title{Scales: RGB} \usage{ -tm_scale_rgb(value.na = NA, maxValue = 255) +tm_scale_rgb( + value.na = NA, + stretch = FALSE, + probs = c(0, 1), + maxColorValue = 255L +) -tm_scale_rgba(value.na = NA, maxValue = 255) +tm_scale_rgba( + value.na = NA, + stretch = FALSE, + probs = c(0, 1), + maxColorValue = 255 +) } \arguments{ \item{value.na}{value for missing values} -\item{maxValue}{maximum value} +\item{stretch}{should each (r, g, b) band be stretched? Possible values: \code{"percent"} (same as \code{TRUE}) and \code{"histogram"}. In the first case, the values are stretched to \verb{probs[1]...probs[2]}. In the secodn case, a histogram equalization is performed} + +\item{probs}{probability (quantile) values when \code{stretch = "percent"}} + +\item{maxColorValue}{maximum value} } \description{ -Scales: RGB +Scales in tmap are configured by the family of functions with prefix \code{tm_scale}. +Such function should be used for the input of the \code{.scale} arguments in the layer +functions (e.g. \code{fill.scale} in \code{\link[=tm_polygons]{tm_polygons()}}). +The function \code{\link[=tm_scale_rgb]{tm_scale_rgb()}} is used to transform r, g, b band variables to colors. This function is adopted from (and works similar as) \code{\link[stars:st_rgb]{stars::st_rgb()}} +} +\examples{ +require(stars) +file = system.file("tif/L7_ETMs.tif", package = "stars") + +L7 = stars::read_stars(file) + +tm_shape(L7) + + tm_rgb(col.scale = tm_scale_rgb(probs = c(0, .99), stretch = TRUE)) + +tm_shape(L7) + + tm_rgb(col.scale = tm_scale_rgb(stretch = "histogram")) } \seealso{ -\code{\link[=tm_scale]{tm_scale()}} +\code{\link[=tm_scale]{tm_scale()}} and \code{\link[stars:st_rgb]{stars::st_rgb()}} } diff --git a/man/tm_shape_vars.Rd b/man/tm_shape_vars.Rd deleted file mode 100644 index 4757e0d1..00000000 --- a/man/tm_shape_vars.Rd +++ /dev/null @@ -1,19 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/tm_scale_.R -\name{tm_shape_vars} -\alias{tm_shape_vars} -\alias{tm_mv_shape_vars} -\title{tmap function to specify all variables in the shape object} -\usage{ -tm_shape_vars(ids = NA, n = NA) - -tm_mv_shape_vars(ids = NA, n = NA) -} -\arguments{ -\item{ids}{index numbers of the used shape variables} - -\item{n}{if specified, the first \code{n} shape variables are used} -} -\description{ -tmap function to specify all variables in the shape object -} diff --git a/man/tm_vars.Rd b/man/tm_vars.Rd new file mode 100644 index 00000000..777d0db3 --- /dev/null +++ b/man/tm_vars.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/tm_vars.R +\name{tm_vars} +\alias{tm_vars} +\title{tmap function to specify variables} +\usage{ +tm_vars(x = NA, dimvalues = NULL, n = NA, multivariate = FALSE) +} +\arguments{ +\item{x}{variable names, variable indices, or a dimension name} + +\item{dimvalues}{dimension values} + +\item{n}{if specified the first \code{n} variables are taken (or the first \code{n} dimension values)} + +\item{multivariate}{in case multiple variables are specified, should they serve as facets (FALSE) or as a multivariate visual variable?} +} +\description{ +tmap function to specify all variables in the shape object +} diff --git a/man/tmapSplitShp.Rd b/man/tmapSplitShp.Rd index 48f3540d..9f3b8e53 100644 --- a/man/tmapSplitShp.Rd +++ b/man/tmapSplitShp.Rd @@ -4,7 +4,7 @@ \alias{tmapSplitShp} \title{Internal method that split shape objects} \usage{ -tmapSplitShp(shp, split_stars_dim) +tmapSplitShp(shp, split_stars_dim, smeta) } \arguments{ \item{shp}{shape} diff --git a/sandbox/main2.R b/sandbox/main2.R index f729a46e..a0d3bc10 100644 --- a/sandbox/main2.R +++ b/sandbox/main2.R @@ -339,7 +339,7 @@ tm_shape(landsat_stars) + tm_shape(landsat_terra) + - tm_rgb(tm_mv("landsat_4", "landsat_3", "landsat_2"), col.scale = tm_scale_rgb(maxValue = 31961)) + tm_rgb(tm_mv("landsat_4", "landsat_3", "landsat_2"), col.scale = tm_scale_rgb(maxColorValue = 31961)) land_terra = terra::rast(methods::as(land, "Raster")) @@ -408,7 +408,7 @@ tm_shape(landsat_terra) + tm_raster(col = "lan_1", col_alpha = "lan_2") tm_shape(landsat_terra) + - tm_rgb(tm_mv("lan_4", "lan_3", "lan_2"), col.scale = tm_scale_rgb(maxValue = 31961)) + tm_rgb(tm_mv("lan_4", "lan_3", "lan_2"), col.scale = tm_scale_rgb(maxColorValue = 31961)) diff --git a/sandbox/testing_tmapVars.R b/sandbox/testing_tmapVars.R index b9ac9267..f559960f 100644 --- a/sandbox/testing_tmapVars.R +++ b/sandbox/testing_tmapVars.R @@ -108,7 +108,7 @@ tm_shape(World) + # shape vars tm_shape(World) + - tm_polygons(fill = tm_shape_vars()) + tm_polygons(fill = tm_vars()) tm_shape(land) + tm_raster() @@ -117,6 +117,7 @@ tm_shape(land) + require(stars) require(terra) require(sf) + file = system.file("tif/L7_ETMs.tif", package = "stars") L7 = stars::read_stars(file) @@ -124,9 +125,10 @@ L7 = stars::read_stars(file) tm_shape(L7) + tm_rgb() + # the previous example was a shortcut of this call tm_shape(L7) + - tm_rgb(col = tm_mv_dim("band", 1:3)) + tm_rgb(col = tm_vars("band", dimvalues = 1:3)) # alternative format: using a stars dimension instead of attributes L7_alt = split(L7, "band") @@ -135,28 +137,50 @@ tm_shape(L7_alt) + # with attribute names tm_shape(L7_alt) + - tm_rgb(col = tm_mv("X1", "X2", "X3")) + tm_rgb(col = tm_vars(c("X1", "X2", "X3"), multivariate = TRUE)) # with attribute indices tm_shape(L7_alt) + - tm_rgb(col = tm_mv_shape_vars(1:3)) + tm_rgb(col = tm_vars(1:3, multivariate = TRUE)) +if (requireNamespace("terra")) { + L7_terra = terra::rast(file) + + tm_shape(L7_terra) + + tm_rgb() + + # with layer names + tm_shape(L7_terra) + + tm_rgb(tm_vars(names(L7_terra)[1:3], multivariate = TRUE)) + + # with layer indices + tm_shape(L7_alt) + + tm_rgb(col = tm_vars(1:3, multivariate = TRUE)) + +} -L7_terra = terra::rast(file) -tm_shape(L7_terra) + - tm_rgb() +# complex stars +L7alt = L7 +L7alt$L7_ETMs.tif = 255 - L7alt$L7_ETMs.tif -# with layer names -tm_shape(L7_terra) + - tm_rgb(tm_mv(names(L7_terra)[1:3])) +L7duo = c(L7, L7alt) +L7duo2 = merge(L7duo) -# with layer indices -tm_shape(L7_alt) + - tm_rgb(col = tm_mv_shape_vars(1:3)) +tm_shape(L7duo) + + tm_rgb(tm_vars("band", dimvalues = 1:3), col.scale = tm_scale_rgb(stretch = F)) + +tm_facets(by = "VARS__") +tm_shape(L7duo2) + + tm_rgb(tm_vars("band", dimvalues = 1:3), col.scale = tm_scale_rgb(stretch = F)) + + tm_facets(by = "attributes") +tm_shape(World) + + tm_polygons(c("HPI", "footprint")) + + tm_facets_grid(rows = "VARS__", columns = "continent") +tm_shape(L7) + + tm_raster() diff --git a/sandbox/vv2.R b/sandbox/vv2.R new file mode 100644 index 00000000..f4250227 --- /dev/null +++ b/sandbox/vv2.R @@ -0,0 +1,207 @@ +################## +# VECTOR DATA +################## + +# tm_polygons without specifications +tm_shape(World) + + tm_polygons() + +# these default values are configured by the option value.const: +str(tmap_options("value.const")) + +# the 'fill' of polygons is "grey85", the border 'col' is "grey40", the default line width 'lwd' is 1, etc + +# the visual values can be set as follows: +tm_shape(World) + + tm_polygons(fill = "pink") + +# vector of values -> facets +tm_shape(World) + + tm_polygons(fill = c("pink", "purple"), + col = c("black", "white"), + lwd = c(1, 2)) + +## Visual variables + +# scale and legend are determined automatically based on the type of variable +tm_shape(World) + + tm_polygons(fill = "HPI") + +# other scale and legend +tm_shape(World) + + tm_polygons(fill = "HPI", + fill.scale = tm_scale_continuous(values = "carto.army_rose"), + fill.legend = tm_legend(orientation = "landscape")) + +# facets +tm_shape(World) + + tm_polygons(fill = c("HPI", "footprint")) + +# if there is one 'facet dimension', facets are wrapped, similar to ggplot2's facet_wrap +tm_shape(World) + + tm_polygons(fill = "HPI") + + tm_facets(by = "continent") + +# note: facets can be forced into a single row or column via respectively tm_facets_hstack or tm_facets_vstack + +# a facet grid (similar to ggplot2's facet_grid) can be achieved via tm_facets_grid +tm_shape(World) + + tm_polygons(fill = c("HPI", "footprint")) + + tm_facets_grid(columns = "continent") + + +################## +# Multivariate +################## + +# the follow plot shows two variables +tm_shape(World) + + tm_polygons(tm_vars(c("HPI", "well_being"))) + +# in this example, tm_vars is not needed explicily (tm_polygons(c("HPI", "well_being")) is identical +# however, tm_vars can be used to specify multivariate visual variables, e.g. a bivariate choropleth: + +tm_shape(World) + + tm_polygons(tm_vars(c("HPI", "well_being"), multivariate = TRUE)) + +# multivariate visual variables are also used in RGB maps and glyphs (see below) + +################## +# RASTER DATA +################## + +# 'land' is a spatial raster data object with four attributes (variables). It is a 'stars' object ("stars" package), but these examples also work for a SpatRaster object ("terra" package) +(land) + +# + +# note that default of tm_raster() is not value.const (like polygons) but all variables as facets: +tm_shape(land) + + tm_raster() + +# to plot just one variable +tm_shape(land) + + tm_raster(col = "elevation") + +tm_shape(land) + + tm_raster(col = c("elevation", "trees")) + + tm_facets_hstack() + + + +# stars objects +file = system.file("tif/L7_ETMs.tif", package = "stars") +L7 = stars::read_stars(file) + +# 'L7' is a stars object with one attribute, and one non-spatial dimension (called "band"): +(L7) + +# by default all band values are plotted: +tm_shape(L7) + + tm_raster() + +# in order to 'extract' and plot only some dimension values, use tm_vars +tm_shape(L7) + + tm_raster(col = tm_vars(dimvalues = 1:3)) + +tm_shape(L7) + + tm_rgb(col = tm_vars(dimvalues = 1:3, multivariate = TRUE)) + +# we have a dedicated scale for rgb values (that maps 3 numeric variables to hex colors codes) +# this scale is adopted from stars::st_rgb +tm_shape(L7) + + tm_rgb(col = tm_vars(dimvalues = 1:3, multivariate = TRUE), + col.scale = tm_scale_rgb(stretch = "histogram")) + +L7split = split(L7) + +tm_shape(L7split) + + tm_raster() + +tm_shape(L7split) + + tm_raster(col = tm_vars(1:3)) + +tm_shape(L7split) + + tm_rgb(col = tm_vars(1:3, multivariate = TRUE)) + + + +# complex stars +L7neg = L7 +L7neg$L7_ETMs.tif = 255 - L7alt$L7_ETMs.tif + +L7duo = c(L7, L7neg) +L7duo2 = merge(L7duo) + +tm_shape(L7duo) + + tm_rgb(tm_vars("band", dimvalues = 1:3, multivariate = TRUE), col.scale = tm_scale_rgb(stretch = F)) + +tm_shape(L7duo) + + tm_rgb(tm_vars("band", dimvalues = 1:3, multivariate = TRUE), col.scale = tm_scale_rgb(stretch = F)) + + tm_facets(by = "VARS__") + + +tm_shape(L7duo2) + + tm_rgb(tm_vars("band", dimvalues = 1:3, multivariate = TRUE), col.scale = tm_scale_rgb(stretch = F)) + +tm_shape(L7duo2) + + tm_rgb(tm_vars("band", dimvalues = 1:3, multivariate = TRUE), col.scale = tm_scale_rgb(stretch = F)) + + tm_facets(by = "attributes") + + +tm_shape(L7duo) + + tm_raster(tm_vars("band", dimvalues = 1:3, multivariate = FALSE)) + +tm_shape(L7duo) + + tm_raster(tm_vars("band", dimvalues = 1:3, multivariate = FALSE)) + + tm_facets_grid(columns = "VARS__") + + +tm_shape(L7duo2) + + tm_raster(tm_vars("band", dimvalues = 1:3, multivariate = FALSE)) + + tm_facets_grid(columns = "VARS__") + + +# terra objects +L7_terra = terra::rast(file) + +(L7_terra) + +tm_shape(L7_terra) + + tm_raster() + +tm_shape(L7_terra) + + tm_rgb(tm_vars(dimvalues = 1:3, multivariate = TRUE)) + + +# tmap vars +tm_shape(World) + + tm_polygons(tm_vars(c("HPI", "footprint"))) + +tm_shape(World) + + tm_polygons(tm_vars(c("HPI", "footprint"), multivariate = TRUE)) + +tm_shape(World) + + tm_polygons(c("HPI", "footprint")) + +tm_shape(World) + + tm_polygons(tm_vars(c("HPI", "footprint"))) + +tm_shape(World) + + tm_polygons(tm_vars()) + + + +## Glyphs + +#devtools::load_all("../tmap.glyphs/") +#remotes::install_github("https://github.com/r-tmap/tmap.glyphs") +library(tmap.glyphs) + + +tm_shape(NLD_prov) + + tm_polygons() + + tm_donuts(parts = tm_vars(c("origin_native", "origin_west", "origin_non_west"), multivariate = TRUE), + size = "population", + size.scale = tm_scale_continuous(values.scale = 1), + fill.scale = tm_scale_categorical(values = "brewer.dark2")) diff --git a/vignettes/tmap_sneak_peek.Rmd b/vignettes/tmap_sneak_peek.Rmd index 7e297ec2..de1df0ed 100644 --- a/vignettes/tmap_sneak_peek.Rmd +++ b/vignettes/tmap_sneak_peek.Rmd @@ -278,39 +278,13 @@ An example is the bivariate choropleth, which is not yet implemented, but will d # tmap v4 tm_shape(World) + tm_symbols( - fill = tm_mv("well_being", "footprint"), + fill = tm_vars(c("well_being", "footprint"), multivariate = TRUE), fill.scale = tm_scale_bivariate(scale1 = tm_scale_intervals(breaks = c(2, 5, 6, 8)), scale2 = tm_scale_intervals(breaks = c(0, 3, 6, 20)), values = "brewer.qualseq") ) ``` -Another example of multivariate aesthetics are glpys, which are small charts used as symbols. - -The following example is the donut map. -The current implementation is 'one-trick-pony' (see https://github.com/mtennekes/donutmaps) - -In **tmap v4** it will be much easier: - -```{r, eval = FALSE, class.source='bg-success'} -# tmap v4 (not implemented yet) -library(tmap) -library(tmapGlyps) # which include tm_donuts -library(sfnetworks) # for origin-destination data methods - -tm_mode("view") - -tm_shape(edges) + - tm_halflines(lwd = "flow", col = "dest", start = 0.5, end = 1.0) + -tm_shape(nodes) + - tm_donuts(size = "emplyoees", - parts = tm_mv("Amsterdam", "Rotterdam", "The Hague", "Utrecht", "Other_municipality", "Home_municipality")) -``` - -Donut maps - ## Legends