From 7059c5cabbf14be513cdb380e436d47eb31342cf Mon Sep 17 00:00:00 2001 From: Roman Pahl Date: Sat, 23 Oct 2021 20:37:46 +0200 Subject: [PATCH] Update docs and add OrderedSet class (#3) * Update docs * Revise order function in Set class * derive OrderedSet from Set which now does not sort its elements anymore * Update docs * Update docs * fix names<- function * Remove outdated class diagram --- NAMESPACE | 5 + R/0-ContainerS3.R | 8 +- R/0-DequeS3.R | 4 +- R/0-DictS3.R | 14 +- R/0-SetR6.R | 92 +++- R/0-SetS3.R | 61 ++- R/0-dict.table.R | 40 +- R/Ops-extract.R | 7 +- R/add.R | 10 +- R/at.R | 4 +- R/at2.R | 4 +- R/clear.R | 8 +- R/clone.R | 4 +- R/delete_at.R | 4 +- R/discard_at.R | 4 +- R/format.R | 6 + R/has.R | 4 +- R/has_name.R | 4 +- R/is_empty.R | 4 +- R/peek_at.R | 4 +- R/peek_at2.R | 4 +- R/pop.R | 4 +- R/rename.R | 4 +- R/replace_at.R | 4 +- R/update.R | 4 +- README.Rmd | 94 ++-- README.md | 114 ++--- _pkgdown.yml | 12 +- docs/404.html | 13 +- docs/articles/Container.html | 246 ++--------- docs/articles/class-overview.html | 414 ++++++++++++++++++ .../header-attrs-2.11/header-attrs.js | 12 + docs/articles/code-development.html | 139 ++++++ .../header-attrs-2.11/header-attrs.js | 12 + docs/articles/dict.table.html | 139 ++++++ .../header-attrs-2.11/header-attrs.js | 12 + docs/articles/index.html | 23 +- docs/articles/parameter-list.html | 259 +++++++++++ .../header-attrs-2.11/header-attrs.js | 12 + docs/articles/reference-semantics.html | 139 ++++++ .../header-attrs-2.11/header-attrs.js | 12 + docs/articles/serious-coding.html | 206 +++++++++ .../header-attrs-2.11/header-attrs.js | 12 + docs/authors.html | 13 +- docs/index.html | 139 +++--- docs/pkgdown.yml | 9 +- docs/reference/Container.html | 13 +- docs/reference/ContainerS3.html | 28 +- docs/reference/Deque.html | 13 +- docs/reference/Dict.html | 13 +- docs/reference/Iterable.html | 13 +- docs/reference/Iterator.html | 13 +- docs/reference/OpsArithmetic.html | 17 +- docs/reference/OpsCompare.html | 13 +- docs/reference/OpsExtract.html | 13 +- docs/reference/OpsLogic.html | 13 +- docs/reference/OpsReplace.html | 13 +- docs/reference/OrderedSet.html | 291 ++++++++++++ docs/reference/Set.html | 28 +- docs/reference/add.html | 25 +- docs/reference/addleft.html | 13 +- docs/reference/at.html | 15 +- docs/reference/at2.html | 15 +- docs/reference/clear.html | 19 +- docs/reference/clone.html | 15 +- docs/reference/container_options.html | 13 +- docs/reference/count.html | 13 +- docs/reference/delete.html | 13 +- docs/reference/delete_at.html | 15 +- docs/reference/deprecated.html | 13 +- docs/reference/dequeS3.html | 19 +- docs/reference/dict.table.html | 73 +-- docs/reference/dictS3.html | 41 +- docs/reference/dicttable.html | 37 +- docs/reference/discard.html | 13 +- docs/reference/discard_at.html | 15 +- docs/reference/has.html | 15 +- docs/reference/has_name.html | 15 +- docs/reference/index.html | 31 +- docs/reference/is_empty.html | 15 +- docs/reference/iterS3.html | 13 +- docs/reference/peek.html | 13 +- docs/reference/peek_at.html | 15 +- docs/reference/peek_at2.html | 15 +- docs/reference/pop.html | 15 +- docs/reference/rename.html | 17 +- docs/reference/replace.html | 13 +- docs/reference/replace_at.html | 15 +- docs/reference/rev.html | 13 +- docs/reference/rotate.html | 13 +- docs/reference/setS3.html | 91 ++-- docs/reference/unpack.html | 13 +- docs/reference/update.html | 17 +- docs/sitemap.xml | 20 +- inst/tinytest/test_0-ContainerS3.R | 11 + inst/tinytest/test_0-SetR6.R | 51 ++- inst/tinytest/test_0-SetS3.R | 12 +- inst/tinytest/test_GroupGenericMath.R | 7 +- inst/tinytest/test_Ops-arithmetic.R | 2 +- inst/tinytest/test_Ops-compare.R | 6 +- inst/tinytest/test_Ops-logic.R | 12 +- inst/tinytest/test_all.equal.R | 6 +- inst/tinytest/test_format.R | 2 +- inst/tinytest/test_replace.R | 8 +- man/ContainerS3.Rd | 4 +- man/OrderedSet.Rd | 138 ++++++ man/Set.Rd | 11 +- man/add.Rd | 6 +- man/clear.Rd | 4 +- man/dequeS3.Rd | 4 +- man/{dicttable.Rd => dict.table.Rd} | 29 +- man/dictS3.Rd | 14 +- man/setS3.Rd | 40 +- vignettes/class-diagram.png | Bin 6238 -> 0 bytes vignettes/overview.Rmd | 108 ----- 115 files changed, 3101 insertions(+), 923 deletions(-) create mode 100644 docs/articles/class-overview.html create mode 100644 docs/articles/class-overview_files/header-attrs-2.11/header-attrs.js create mode 100644 docs/articles/code-development.html create mode 100644 docs/articles/code-development_files/header-attrs-2.11/header-attrs.js create mode 100644 docs/articles/dict.table.html create mode 100644 docs/articles/dict.table_files/header-attrs-2.11/header-attrs.js create mode 100644 docs/articles/parameter-list.html create mode 100644 docs/articles/parameter-list_files/header-attrs-2.11/header-attrs.js create mode 100644 docs/articles/reference-semantics.html create mode 100644 docs/articles/reference-semantics_files/header-attrs-2.11/header-attrs.js create mode 100644 docs/articles/serious-coding.html create mode 100644 docs/articles/serious-coding_files/header-attrs-2.11/header-attrs.js create mode 100644 docs/reference/OrderedSet.html create mode 100644 man/OrderedSet.Rd rename man/{dicttable.Rd => dict.table.Rd} (89%) delete mode 100644 vignettes/class-diagram.png delete mode 100644 vignettes/overview.Rmd diff --git a/NAMESPACE b/NAMESPACE index 268fc453..14f41839 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -21,6 +21,7 @@ S3method("[",Container) S3method("[<-",Container) S3method("[[",Container) S3method("[[<-",Container) +S3method("names<-",Container) S3method("|",Dict) S3method("|",Set) S3method(Math,Container) @@ -46,6 +47,7 @@ S3method(at2,dict.table) S3method(c,Container) S3method(c,Deque) S3method(c,Dict) +S3method(c,OrderedSet) S3method(c,Set) S3method(cbind,dict.table) S3method(clear,Container) @@ -128,6 +130,7 @@ export(Container) export(Deque) export(Dict) export(Iterator) +export(OrderedSet) export(Set) export(add) export(addleft) @@ -136,6 +139,7 @@ export(as.container) export(as.deque) export(as.dict) export(as.dict.table) +export(as.orderedset) export(as.set) export(at) export(at2) @@ -167,6 +171,7 @@ export(is.dict) export(is.dict.table) export(is.iterable) export(is.iterator) +export(is.orderedset) export(is.set) export(is_empty) export(iter) diff --git a/R/0-ContainerS3.R b/R/0-ContainerS3.R index 04244476..cf13cefc 100644 --- a/R/0-ContainerS3.R +++ b/R/0-ContainerS3.R @@ -2,7 +2,7 @@ #' #' @description A container is a data structure with typical member #' functions to insert, delete and access elements from the container -#' object. The [container] can be seen as a base R [list] with +#' object. It can be considered as a base R [list] with #' extended functionality. The [Container] class also serves as the base #' class for [Deque], [Set], and [Dict] objects. #' @param ... (possibly named) elements to be put into or removed from the @@ -113,5 +113,11 @@ str.Container <- function(object, ...) } +#' @export +"names<-.Container" <- function(x, value) +{ + x$rename(names(x), value) +} + # TODO: implement generic %in% diff --git a/R/0-DequeS3.R b/R/0-DequeS3.R index b33f43b6..6d7c341d 100644 --- a/R/0-DequeS3.R +++ b/R/0-DequeS3.R @@ -2,7 +2,7 @@ #' #' @description Deques are a generalization of stacks and queues typically #' with methods to add, remove and access elements at both sides of the -#' underlying data sequence. As such, the [deque()] can also be used to mimic +#' underlying data sequence. As such, the [deque] can also be used to mimic #' both stacks and queues. #' @param ... initial elements put into the `Deque`. #' @param x `R` object of `ANY` type for [as.deque()] and [is.deque()] @@ -11,7 +11,7 @@ #' documentation see [Deque()] and it's superclass [Container()]. #' @name DequeS3 #' @details -#' Methods that alter `Deque` objects usually come in two versions +#' Methods that alter [Deque] objects usually come in two versions #' providing either copy or reference semantics where the latter start with #' `'ref_'` to note the reference semantic, for example, `add()` and `ref_add()`. #' @examples diff --git a/R/0-DictS3.R b/R/0-DictS3.R index 3e480847..e9231054 100644 --- a/R/0-DictS3.R +++ b/R/0-DictS3.R @@ -1,14 +1,18 @@ #' @title A Dictionary #' -#' @description The [dict()] resembles Python's dict type, and is implemented -#' as a specialized associative [Container()] thus sharing all [container()] -#' methods with some of them being overridden to account for the associative -#' key-value pair semantic. +#' @description The [Dict] initially was developed to resemble Python's +#' dict type, but by now offers both more features and flexibility, for +#' example, by providing both associative key-value pair as well as +#' positional array semantics. +#' It is implemented as a specialized associative [Container] thus sharing +#' all [Container] methods with some of them being adapted to account for +#' the key-value pair semantic. +#' All Dict elements must be named and are always sorted by their name. #' @param ... elements put into the `Dict`. #' @param x `R` object of `ANY` type for [as.dict()] and [is.dict()] #' or of class `Dict` for the `S3` methods. #' @seealso See [container()] for all inherited methods. For the full class -#' documentation see [Dict()] and it's superclass [Container()]. +#' documentation see [Dict] and it's superclass [Container]. #' @name DictS3 #' @details Internally, all key-value pairs are stored in a hash-table and the #' elements are sorted lexicographically by their keys. diff --git a/R/0-SetR6.R b/R/0-SetR6.R index 2f7f7fe5..5f00506f 100644 --- a/R/0-SetR6.R +++ b/R/0-SetR6.R @@ -1,13 +1,10 @@ #' Set Class #' -#' @description The [Set()] is considered and implemented as a specialized -#' [Container()], that is, elements are always unique in the [Container()] and +#' @description The [Set] is considered and implemented as a specialized +#' [Container], that is, elements are always unique in the [Container] and #' it provides typical set operations such as `union` and `intersect`. #' For the standard S3 interface, see [setnew()]. -#' @details Under the hood, elements of a set object are stored in a hash-table -#' and always sorted by their length and, in case of ties, by their lexicographical -#' representation. -#' @seealso [Container()], [set()] +#' @seealso [Container], [set()] #' @export #' @examples #' s1 = Set$new(1, 2) @@ -58,7 +55,6 @@ Set <- R6::R6Class("Set", hash_value = private$.get_hash_value(value) private$elems[[hash_value]] = elem - private$.reorder_values() self }, @@ -173,16 +169,92 @@ Set <- R6::R6Class("Set", .replace_value_at = function(pos, value, name) { self$discard_at(pos) self$add(value, name) + self + } + ), + lock_class = TRUE +) + + +#' Ordered Set Class +#' +#' @description The [OrderedSet] is as [Set] where all elements are always +#' ordered. +#' @details The order of elements is determined sequentially as follows: +#' * element's length +#' * whether it is an [atomic](is.atomic) element +#' * the element's class(es) +#' * by numeric value (if applicable) +#' * it's representation when printed +#' * the name of the element in the [Set] +#' +#' @seealso [Container], [Set] +#' @export +#' @examples +#' s1 = OrderedSet$new(2, 1) +#' s1 +OrderedSet <- R6::R6Class("OrderedSet", + inherit = Set, + public = list( + #' @description `OrderedSet` constructor + #' @param ... initial elements put into the `OrderedSet` + #' @return returns the `OrderedSet` object + initialize = function(...) { + + super$initialize() + + it = iter(list(...), .subset = .subset) + while (has_next(it)) { + value = get_next(it) + self$add(value[[1]], name = names(value)) + } + self }, + #' @description Add element + #' @param value value of `ANY` type to be added to the `OrderedSet`. + #' @param name `character` optional name attribute of the value. + #' @return the `OrderedSet` object. + add = function(value, name = NULL) { + + len = self$length() + super$add(value, name) + + hasAdded = len < self$length() + if (hasAdded) + private$.reorder_values() + + self + } + ), + private = list( .reorder_values = function() { - new_order = order(lengths(self$values()), - sapply(self$values(), .get_label), - names(private$elems)) + v = self$values() + lens = lengths(v) + classes = paste(lapply(v, class)) + labs = sapply(v, .get_label) + labnames = names(labs) + + atom = sapply(v, is.atomic) + + inum = which(sapply(v, is.numeric) & lens == 1) + numbers = numeric(self$length()) + numbers[inum] = as.numeric(v[inum]) + + orderCriteria = list(lens, + !atom, + classes, + numbers, + labs, + names(labs)) + orderCriteria = Filter(function(x) length(x) > 0, orderCriteria) + + new_order = do.call(order, args = orderCriteria) private$elems = private$elems[new_order] } ), lock_class = TRUE ) + diff --git a/R/0-SetS3.R b/R/0-SetS3.R index 117b0620..bcf4766e 100644 --- a/R/0-SetS3.R +++ b/R/0-SetS3.R @@ -1,22 +1,20 @@ -#' @title Set +#' @title Set and ordered Set #' -#' @description The [Set()] is considered and implemented as a specialized -#' [Container()], that is, `Set` elements are always unique. It provides +#' @description The [Set] is considered and implemented as a specialized +#' [Container], that is, `Set` elements are always unique. It provides #' typical set operations such as `union` and `intersect`. #' @param ... initial elements put into the `Set`. +#' @param .ordered `logical` if `TRUE` all elements in the [Set] will be +#' ordered. #' @param x `R` object of `ANY` type for [as.set()] and [is.set()] #' or of class `Set` for the `S3` methods. #' @name SetS3 #' @seealso See [container()] for all inherited methods. For the full class -#' documentation see [Set()] and it's superclass [Container()]. -#' @details Under the hood, elements of a set object are stored in a hash-table -#' and sorted by their length and, in case of ties, by their lexicographical -#' representation. -#' For a description of basic methods such as adding and removing elements, -#' see the help of [container()]. -#' Methods that alter `Set` objects usually come in two versions +#' documentation see [Set] and it's superclass [Container]. +#' @details +#' Methods that alter [Set] objects usually come in two versions #' providing either copy or reference semantics where the latter start with -#' `'ref_'` to note the reference semantic, for example, `add()` and `ref_add()`. +#' `'ref_'` to note the reference semantic, for example, [add()] and [ref_add()]. #' @examples #' s = setnew(1, b = NA, 1:3, c = container("a", 1)) #' is.set(s) @@ -26,12 +24,21 @@ #' as.list(s) #' unpack(s) # flatten recursively similar to unlist #' +#' so = setnew(2, 1, .ordered = TRUE) +#' print(so) +#' add(so, 0) NULL #' @rdname SetS3 #' @details * `setnew(...)` initializes and returns a [Set()] object. #' @export -setnew <- function(...) Set$new(...)$clone(deep = TRUE) +setnew <- function(..., .ordered = FALSE) +{ + if (.ordered) + OrderedSet$new(...)$clone(deep = TRUE) + else + Set$new(...)$clone(deep = TRUE) +} #' @rdname SetS3 #' @details * `as.set(x)` coerces `x` to a set. @@ -43,15 +50,33 @@ as.set <- function(x) { do.call(setnew, args = as.list(x)) } +#' @rdname SetS3 +#' @details * `as.orderedset(x)` coerces `x` to an ordered set. +#' @export +as.orderedset <- function(x) { + newset = function(...) setnew(..., .ordered = TRUE) + if (length(x) == 0) + return(newset()) + + do.call(newset, args = as.list(x)) +} + methods::setOldClass("Set") methods::setAs("list", "Set", function(from) as.set(from)) + #' @rdname SetS3 #' @details * `is.set(x)` returns `TRUE` if `x` is of class `Set` and `FALSE` #' otherwise. #' @export is.set <- function(x) inherits(x, "Set") +#' @rdname SetS3 +#' @details * `is.orderedset(x)` returns `TRUE` if `x` is of class `OrderedSet` +#' and `FALSE` otherwise. +#' @export +is.orderedset <- function(x) inherits(x, "OrderedSet") + #' @export c.Set <- function(..., recursive = FALSE, use.names = TRUE) @@ -64,3 +89,15 @@ c.Set <- function(..., recursive = FALSE, use.names = TRUE) as.set(concat) } +#' @export +c.OrderedSet <- function(..., recursive = FALSE, use.names = TRUE) +{ + concat = c.Container(..., recursive = recursive, use.names = use.names) + + if (recursive) + concat + else { + as.orderedset(concat) + } +} + diff --git a/R/0-dict.table.R b/R/0-dict.table.R index 4f6ce1d7..43e00345 100644 --- a/R/0-dict.table.R +++ b/R/0-dict.table.R @@ -19,24 +19,28 @@ #' @title Combining Dict and data.table #' -#' @description The [dict.table](dicttable) is a combination of [dict] and -#' [data.table] and basically can be considered a [data.table] with extended -#' functionality to manage its data columns in a stricter way. For example, -#' in contrast to [data.table], [dict.table](dicttable) does not allow -#' duplicated column names. -#' A [dict.table](dicttable) object provides all [dict] and [data.table] +#' @description The [dict.table] is a combination of [dict] and +#' [data.table](https://CRAN.R-project.org/package=data.table) +#' and basically can be considered a +#' [data.table](https://CRAN.R-project.org/package=data.table) +#' with unique +#' column names and an extended set of functions to add, extract and +#' remove data columns with the goal to further facilitate code development +#' using [data.table](https://CRAN.R-project.org/package=data.table). +#' A [dict.table] object provides all [dict] and +#' [data.table](https://CRAN.R-project.org/package=data.table) #' functions and operators at the same time. #' -#' @param ... elements put into the [dict.table](dicttable) and/or additional +#' @param ... elements put into the [dict.table] and/or additional #' arguments to be passed on. -#' @param x any `R` object or a [dict.table](dicttable) object. -#' @name dicttable +#' @param x any `R` object or a [dict.table] object. +#' @name dict.table #' @details -#' Methods that alter [dict.table](dicttable) objects usually come in two versions +#' Methods that alter [dict.table] objects usually come in two versions #' providing either copy or reference semantics where the latter start with -#' `'ref_'` to note the reference semantic, for example, [add] and [ref_add]. +#' `'ref_'` to note the reference semantic, for example, [add()] and [ref_add()]. #' @import data.table -#' @seealso [dict], [data.table] +#' @seealso [dict], [data.table](https://CRAN.R-project.org/package=data.table) #' @examples #' # Some basic examples using some typical data.table and dict operations. #' # The constructor can take the 'key' argument known from data.table(): @@ -63,7 +67,7 @@ NULL -#' @rdname dicttable +#' @rdname dict.table #' @details #' * `dict.table(...)` initializes and returns a [dict] object. #' @export @@ -78,7 +82,7 @@ dict.table <- function(...) dat } -#' @rdname dicttable +#' @rdname dict.table #' @details #' * `as.dict.table(x, ...)` coerce `x` to a [dict.table] #' @export @@ -88,7 +92,7 @@ as.dict.table <- function(x, ...) UseMethod("as.dict.table") } -#' @rdname dicttable +#' @rdname dict.table #' @param copy if `TRUE` creates a copy of the [data.table] object otherwise #' works on the passed object by reference. #' @examples @@ -127,7 +131,7 @@ as.dict.table.default <- function(x, ...) do.call(dict.table, args = as.list(x)) } -#' @rdname dicttable +#' @rdname dict.table #' @details * `is.dict.table(x)` check if `x` is a `dict.table` #' @export is.dict.table <- function(x) inherits(x, "dict.table") @@ -146,7 +150,7 @@ print.dict.table <- function(x, ...) } -#' @rdname dicttable +#' @rdname dict.table #' @examples #' dit = dict.table(a = 1:2, b = 1:2) #' rbind(dit, dit) @@ -168,7 +172,7 @@ rbind.dict.table <- function(x, ...) } -#' @rdname dicttable +#' @rdname dict.table #' @examples #' #' # cbind ... diff --git a/R/Ops-extract.R b/R/Ops-extract.R index 5d4fefad..80f0e9b4 100644 --- a/R/Ops-extract.R +++ b/R/Ops-extract.R @@ -26,11 +26,16 @@ NULL #' @export "[.Container" <- function(x, ...) { - dots = tryCatch(as.list(...), error = identity) + dots = tryCatch(list(...), error = identity) if (inherits(dots, "error")) return(x) + if (all(sapply(dots, is.logical))) { + v = rep(unlist(dots), length.out = length(x)) + return(peek_at(x, which(v))) + } + peek_at(x, ...) } diff --git a/R/add.R b/R/add.R index 8945d699..49b05d6f 100644 --- a/R/add.R +++ b/R/add.R @@ -58,7 +58,7 @@ ref_add.Container <- function(.x, ...) #' @rdname add #' @note -#' If `.x` is a [Dict] or [dict.table](dicttable) object, +#' If `.x` is a [Dict] or [dict.table] object, #' all elements *must* be of the form `key = value`. #' If one of the keys already exists, an error is given. #' @export @@ -114,8 +114,8 @@ ref_add.Dict <- function(.x, ...) #' @rdname add -#' @return For [dict.table](dicttable) an object of class -#' [dict.table](dicttable). +#' @return For [dict.table] an object of class +#' [dict.table]. #' @export #' @examples #' @@ -131,8 +131,8 @@ add.dict.table <- function(.x, ...) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `add(.x, ...)` and `ref_add(.x, ...)` add columns to `.x`. If the column name #' already exists, an error is given. diff --git a/R/at.R b/R/at.R index bcd151fd..a2ffdc87 100644 --- a/R/at.R +++ b/R/at.R @@ -95,8 +95,8 @@ at.dict.table <- function(.x, ...) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `at(.x, ...)` returns the columns at the given indices. Indices #' can be letters or numbers or both. All columns must exist. diff --git a/R/at2.R b/R/at2.R index 57119bc8..8194b686 100644 --- a/R/at2.R +++ b/R/at2.R @@ -86,8 +86,8 @@ at2.dict.table <- function(x, index, ...) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `at2(x, index)` returns the column at the given `index` or signals #' an error if not found. diff --git a/R/clear.R b/R/clear.R index 12f88698..c7d1269a 100644 --- a/R/clear.R +++ b/R/clear.R @@ -45,8 +45,8 @@ ref_clear.Container <- function(x) #' @rdname clear -#' @return For [dict.table](dicttable) an object of class -#' [dict.table](dicttable). +#' @return For [dict.table] an object of class +#' [dict.table]. #' @export #' @examples #' @@ -57,8 +57,8 @@ ref_clear.Container <- function(x) #' dit # original was cleared clear.dict.table <- function(x) dict.table() -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `clear(x)` and `ref_clear(x)` remove all elements from `x`. #' @examples diff --git a/R/clone.R b/R/clone.R index 38ffd545..1f314fce 100644 --- a/R/clone.R +++ b/R/clone.R @@ -38,8 +38,8 @@ NULL #' print(d2) clone.dict.table <- function(x) (copy(x)) -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `clone(x)` create a copy of `x`. #' @examples diff --git a/R/delete_at.R b/R/delete_at.R index 33489d0e..16e7ccbf 100644 --- a/R/delete_at.R +++ b/R/delete_at.R @@ -144,8 +144,8 @@ delete_at.dict.table <- function(.x, ...) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `delete_at(.x, ...)` and `ref_delete_at(.x, ...)` find and remove columns either by #' name or index (or both). If one or more columns don't exist, an error is signaled. diff --git a/R/discard_at.R b/R/discard_at.R index 93ad92ac..1f6d4d7a 100644 --- a/R/discard_at.R +++ b/R/discard_at.R @@ -79,8 +79,8 @@ discard_at.dict.table <- function(.x, ...) (ref_discard_at(clone(.x), ...)) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `discard_at(.x, ...)` and `ref_discard_at(.x, ...)` find and remove columns #' either by name or index (or both). Invalid column indices are ignored. diff --git a/R/format.R b/R/format.R index 811cb753..6b54f2f6 100644 --- a/R/format.R +++ b/R/format.R @@ -34,6 +34,12 @@ function(x, ...) { .format_values(x$values(), left = "{", right = "}", ...) } +format.OrderedSet <- +function(x, ...) { + .format_values(x$values(), left = "{", right = "}", ...) +} + + format.list <- function(x, ...) { .format_values(x, left = "list(", right = ")", ...) diff --git a/R/has.R b/R/has.R index d5b40b5a..4e9b7e66 100644 --- a/R/has.R +++ b/R/has.R @@ -58,8 +58,8 @@ has.dict.table <- function(x, column, ...) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `has(x, column)` check if some `column` is in dict.table object. #' @examples diff --git a/R/has_name.R b/R/has_name.R index 8d8a5a87..f4bbbdff 100644 --- a/R/has_name.R +++ b/R/has_name.R @@ -69,8 +69,8 @@ has_name.dict.table <- function(x, name) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `has_name(x, name)` check if `x` has the given column name. #' @examples diff --git a/R/is_empty.R b/R/is_empty.R index d71922b6..a411c81a 100644 --- a/R/is_empty.R +++ b/R/is_empty.R @@ -37,8 +37,8 @@ NULL is_empty.dict.table <- function(x) ncol(x) == 0 -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `is_empty(x)` `TRUE` if object is empty otherwise `FALSE` #' @examples diff --git a/R/peek_at.R b/R/peek_at.R index ae6d288d..e188212d 100644 --- a/R/peek_at.R +++ b/R/peek_at.R @@ -89,8 +89,8 @@ peek_at.dict.table <- function(.x, ..., .default = NULL) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `peek_at(x, ..., .default = NULL)` returns the columns at the given #' indices or (if not found) columns with the given default value. diff --git a/R/peek_at2.R b/R/peek_at2.R index 77322aa4..cfb36e90 100644 --- a/R/peek_at2.R +++ b/R/peek_at2.R @@ -84,8 +84,8 @@ peek_at2.dict.table <- function(x, index, default = NULL) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `peek_at2(x, index, default = NULL)` return column named `index` if it exist #' otherwise the given `default` value. If the default length does not match diff --git a/R/pop.R b/R/pop.R index 70650acd..c434a736 100644 --- a/R/pop.R +++ b/R/pop.R @@ -112,8 +112,8 @@ ref_pop.dict.table <- function(.x, index, ...) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `ref_pop(.x, index)` return element at given column index and remove the #' column from the dict.table object. diff --git a/R/rename.R b/R/rename.R index 56ec4f91..0e1dd4be 100644 --- a/R/rename.R +++ b/R/rename.R @@ -117,8 +117,8 @@ ref_rename.dict.table <- function(.x, old, new) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `rename(.x, old, new)` and `ref_rename(.x, old, new)` rename one or more #' columns from `old` to `new`, respectively, by copy and in place (i.e. by diff --git a/R/replace_at.R b/R/replace_at.R index 58700352..13578efd 100644 --- a/R/replace_at.R +++ b/R/replace_at.R @@ -164,8 +164,8 @@ ref_replace_at.dict.table <- function(.x, ..., .add = FALSE) invisible(.x) } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `replace_at(.x, .., .add = FALSE)` and `ref_replace_at(.x, ..., .add = FALSE)` #' replace values at given indices. If a given index is invalid, an error is diff --git a/R/update.R b/R/update.R index 88b8bc73..fcb77597 100644 --- a/R/update.R +++ b/R/update.R @@ -91,8 +91,8 @@ ref_update.dict.table <- function(object, other, ...) object } -#' @name dicttable -#' @rdname dicttable +#' @name dict.table +#' @rdname dict.table #' @details #' * `update(object, other)` and `ref_update(object, other)` adds columns of `other` dict #' that are not yet in `object` and replaces the values at existing columns. diff --git a/README.Rmd b/README.Rmd index 7637c40f..98f09322 100644 --- a/README.Rmd +++ b/README.Rmd @@ -24,26 +24,27 @@ knitr::opts_chunk$set( # container -## Update -Update to version 1.0.0 is coming soon to [CRAN](https://cran.r-project.org/). +### Update to NEW version 1.0.0 soon on [CRAN](https://cran.r-project.org/). -## Intro +*container* extends base R *list* functionality with the goal to +serve as an *easy and safe* to use *list* alternative, +applicable not only for interactive R sessions but specifically to make +life easier in *serious code* development. -This package extends the functionality of base R [list] and the [data.table] -package and with [deque], [set], and [dict] provides additional common data -structures. It furthermore implements [iterators] and supports both reference -and copy semantics. +In addition, this package provides specialized data structures *deque*, +*set*, *dict*, and *dict.table*, the latter to extend the +[data.table](https://CRAN.R-project.org/package=data.table) package. -## Why `container`? +### Why `container` over list? +A `container` is based on `list` but with +* compact printing +* feature rich add, extract, replace, or removal operations +* safer data operations (no more unintended `NULL` or `NA`) +* optional reference semantics +* some more ... -## Features - - -## Installation - -You can install the released version of container from -[CRAN](https://CRAN.R-project.org) with: +### Installation ```{r, eval = FALSE} # Install release version from CRAN @@ -53,65 +54,54 @@ install.packages("container") devtools::install_github("rpahl/container") ``` -```{r load-container, include = FALSE} -library(container) +```{r pre-load, include = FALSE} +library(container, warn.conflicts = FALSE) ``` -### container vs list -Basically all you can do with a [list] can also be done with a [container], -but the [container] is capable of much more. +### Usage -```{r container-vs-list} -library(container) +Use `container` the same way you would use a base R `list`, but enjoy +additional functionalities. -co <- container(1:10, l = list("a", 1)) -li <- as.list(co) +```{r} +library(container) +co <- container(x = c(1.0, 2.0), y = 1:2, data = cars) +co ``` -While the [list] output can be very long and hard to read +Some standard operations ... ```{r} -li +co[1:2] ``` - -the elements of a [container] object are printed very compact. ```{r} -co +co[["n"]] ``` - -Find and replace of [list] elements requires to determine the index first. +Some new operations ... ```{r} -element = list("a", 1) -index = which(sapply(li, identical, list("a", 1))) -li[[index]] <- 1:3 -li +co[1:2, "data", "n"] ``` - -With [container] just pass the element directly in `{}` ```{r} -co[[{element}]] <- 1:3 +co[[{cars}]] <- iris co ``` - -Update parameter lists with ease. ```{r} -param = cont(x = 1, foo = "bar") # cont is a shortcut for container -param +co2 = container(x = 1:10, data = NULL, -111) +co = update(co, co2) +co ``` - ```{r} -new_param = cont(z = 2, foo = "my foo") -update(param, new_param) +rename(co, "x", "X") ``` +### Getting Started +There is much more to explore. To get started, see + +* Get started vignette +* Manage parameter lists with dict +* Why and how container for code development +* Enhancing data.table with dict.table -### dict.table vs data.frame -Basically all you can do with a [data.table] can also be done with a -[dict.table], but the [dict.table] also provides [dict] functionality. -```{r dict.table-vs-data.frame} -dit = dict.table(a = 1:2, b = 3:4) -dit -``` diff --git a/README.md b/README.md index 01676d5b..b2cb9661 100644 --- a/README.md +++ b/README.md @@ -12,26 +12,28 @@ status](https://github.com/rpahl/container/workflows/R-CMD-check/badge.svg)](htt # container -## Update +### Update to NEW version 1.0.0 soon on [CRAN](https://cran.r-project.org/). -Update to version 1.0.0 is coming soon to -[CRAN](https://cran.r-project.org/). +*container* extends base R *list* functionality with the goal to serve +as an *easy and safe* to use *list* alternative, applicable not only for +interactive R sessions but specifically to make life easier in *serious +code* development. -## Intro +In addition, this package provides specialized data structures *deque*, +*set*, *dict*, and *dict.table*, the latter to extend the +[data.table](https://CRAN.R-project.org/package=data.table) package. -This package extends the functionality of base R \[list\] and the -\[data.table\] package and with \[deque\], \[set\], and \[dict\] -provides additional common data structures. It furthermore implements -\[iterators\] and supports both reference and copy semantics. +### Why `container` over list? -## Why `container`? +A `container` is based on `list` but with -## Features +- compact printing +- feature rich add, extract, replace, or removal operations +- safer data operations (no more unintended `NULL` or `NA`) +- optional reference semantics +- some more … -## Installation - -You can install the released version of container from -[CRAN](https://CRAN.R-project.org) with: +### Installation ``` r # Install release version from CRAN @@ -41,88 +43,60 @@ install.packages("container") devtools::install_github("rpahl/container") ``` -### container vs list +### Usage -Basically all you can do with a \[list\] can also be done with a -\[container\], but the \[container\] is capable of much more. +Use `container` the same way you would use a base R `list`, but enjoy +additional functionalities. ``` r library(container) - -co <- container(1:10, l = list("a", 1)) -li <- as.list(co) +co <- container(x = c(1.0, 2.0), y = 1:2, data = cars) +co +#> [x = (1 2), y = (1L 2L), data = <>] ``` -While the \[list\] output can be very long and hard to read +Some standard operations … ``` r -li -#> [[1]] -#> [1] 1 2 3 4 5 6 7 8 9 10 -#> -#> $l -#> $l[[1]] -#> [1] "a" -#> -#> $l[[2]] -#> [1] 1 +co[1:2] +#> [x = (1 2), y = (1L 2L)] ``` -the elements of a \[container\] object are printed very compact. - ``` r -co -#> [(1L 2L 3L 4L ...), l = list("a", 1)] +co[["n"]] +#> NULL ``` -Find and replace of \[list\] elements requires to determine the index -first. +Some new operations … ``` r -element = list("a", 1) -index = which(sapply(li, identical, list("a", 1))) -li[[index]] <- 1:3 -li -#> [[1]] -#> [1] 1 2 3 4 5 6 7 8 9 10 -#> -#> $l -#> [1] 1 2 3 +co[1:2, "data", "n"] +#> [x = (1 2), y = (1L 2L), data = <>] ``` -With \[container\] just pass the element directly in `{}` - ``` r -co[[{element}]] <- 1:3 +co[[{cars}]] <- iris co -#> [(1L 2L 3L 4L ...), l = (1L 2L 3L)] +#> [x = (1 2), y = (1L 2L), data = <>] ``` -Update parameter lists with ease. - ``` r -param = cont(x = 1, foo = "bar") # cont is a shortcut for container -param -#> [x = 1, foo = "bar"] +co2 = container(x = 1:10, data = NULL, -111) +co = update(co, co2) +co +#> [x = (1L 2L 3L 4L ...), y = (1L 2L), data = NULL, -111] ``` ``` r -new_param = cont(z = 2, foo = "my foo") -update(param, new_param) -#> [x = 1, foo = "my foo", z = 2] +rename(co, "x", "X") +#> [X = (1L 2L 3L 4L ...), y = (1L 2L), data = NULL, -111] ``` -### dict.table vs data.frame +### Getting Started -Basically all you can do with a \[data.table\] can also be done with a -\[dict.table\], but the \[dict.table\] also provides \[dict\] -functionality. +There is much more to explore. To get started, see -``` r -dit = dict.table(a = 1:2, b = 3:4) -dit -#> with 2 rows and 2 columns -#> a b -#> 1: 1 3 -#> 2: 2 4 -``` +- Get started vignette +- Manage parameter lists with dict +- Why and how container for code development +- Enhancing data.table with dict.table diff --git a/_pkgdown.yml b/_pkgdown.yml index b98d8d34..8efb67d7 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -12,7 +12,7 @@ authors: reference: - title: "Container" - desc: "A container can be considered a basic R list with extended functionality." + desc: "A container can be considered a base R list with extended functionality." contents: - Container - container @@ -59,18 +59,18 @@ reference: - rotate - title: "Set" - desc: "Derives all Container methods. Set elements are always unique." + desc: > + Derives all Container methods. Set elements are always unique. contents: - Set + - OrderedSet - setnew - title: "Dict" desc: > - Derives all Container methods. - The dict resembles Python's dict type but here is more flexible by - providing both associative key-value pair as well as positional array - semantics. + Derives all Container methods. All Dict elements must be named and are + always sorted by their name. contents: - Dict - dict diff --git a/docs/404.html b/docs/404.html index e81c15e7..eb0c167a 100644 --- a/docs/404.html +++ b/docs/404.html @@ -90,6 +90,9 @@ +
  • + Get started +
  • Reference
  • @@ -101,10 +104,16 @@ diff --git a/docs/articles/Container.html b/docs/articles/Container.html index 464147af..686d548f 100644 --- a/docs/articles/Container.html +++ b/docs/articles/Container.html @@ -5,7 +5,7 @@ -Container introduction • container +Get started • container @@ -17,7 +17,7 @@ - + + + + + + +Class overview • container + + + + + + + + + + + + + + + + +
    +
    + + + + +
    +
    + + + + +
    +

    +Introduction

    +

    This package aims at providing common container data structures with typical member functions to insert, delete and access container elements. Specifically, it comes with the types deque, set, and dict, an associative container resembling Python’s dict type. In addition, a specialized data structure called dict.frame is provided, which is a dict containing elements with identical length. The dict.frame can be considered a generalized and more powerful version of the base data.frame.

    +

    The backbone of this package are classes implemented using the R6 framework. The focus for developing this package was to provide a concise data structure and specifically making use of inheritance and the reference semantics provided by the R6 package. The basic class hierarchy is outlined in the class diagram below.

    + +
    +Basic class hierarchy of the container package.

    +Basic class hierarchy of the container package. +

    +
    +

    +
    +
    +

    +R6 classes and member methods

    +

    The Container class as the central element serves as the base class for Deque, Set, and Dict, which inherit all methods from Container, with some of them being overwritten (see below). In addition, the Container class inherits from the abstract Iterable class and therefore provides a method to create an Iterator, which can be used to iterate through the elements of any container object.

    +

    The following table shows member methods divided by class. The top half contains all Container methods, each derived by a subclass to the right unless there is a new entry in a subclass column, meaning that the method is redefined in the subclass. The bottom half contains methods unique to each subclass. Note that Dict.frame (right-most column) inherits all methods from both Container and Dict.

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
    Overview of classes and member methods
    ContainerDequeSetDict
    Container$new()Deque$new()s <- Set$new()Dict$new()
    add(elem)add(key, value)
    clear()
    count(elem)
    delete(elem)delete(key)
    discard(elem)discard(key)
    has(elem)has(key)
    is_empty()
    replace(old, new, add = F)replace(key, value, add = F)
    values()
    addleft(elem)diff(s)get(key)
    peek()intersect(s)peek(key, default = NULL)
    peekleft()is_equal(s)pop(key)
    pop()is_subset(s)rename(old, new)
    popleft()is_proper_subset(s)update(other)
    rev()union(s)
    rotate(n)
    +

    +

    For more details visit the respective online helps (see ?Container, ?Deque, ?Set, ?Dict. Usage examples are found in the corresponding Container, Deque, Set, and Dict vignettes.

    +
    +
    +

    +S3 classes and methods

    +

    On top of the above classes and methods, a complete S3 interface is available, which might be more familiar to most typical R users. More importantly, it allows to provide operators, for example, to access elements in the dict.frame via [[. In the table below, standard set operators are already listed for the set class.

    + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
    Overview of S3 classes and methods
    containerdequesetdict
    co = container()d = deque()s = setnew()d = dict()
    add(co, elem)add(d, key, val)
    clear(co)
    delete(co, elem, right=F)delete(d, key)
    discard(co, elem, right=F)discard(d, key)
    has(co, elem)has(d, key)
    is_empty(co)
    values(co)
    addleft(d, elem)s1 - s2getval(d, key)
    count(d, elem)s1 / s2keys(d)
    peek(d)s1 == s2peek(d, key, default=NULL)
    peekleft(d)s1 < s2pop(d, key)
    pop(d)s1 > s2
    popleft(d)s1 + s2rename(d, old, new)
    reverse(d)setval(d, key, val, add=FALSE)
    rotate(d, n=1L)sortkey(decr=FALSE)
    +

    For more details and to see the provided operators for each class again refer to the corresponding Container, Deque, Set, Dict, and Dict.frame vignettes.

    +
    +
    + + + +
    + + + + +
    + + + + + + diff --git a/docs/articles/class-overview_files/header-attrs-2.11/header-attrs.js b/docs/articles/class-overview_files/header-attrs-2.11/header-attrs.js new file mode 100644 index 00000000..dd57d92e --- /dev/null +++ b/docs/articles/class-overview_files/header-attrs-2.11/header-attrs.js @@ -0,0 +1,12 @@ +// Pandoc 2.9 adds attributes on both header and div. We remove the former (to +// be compatible with the behavior of Pandoc < 2.8). +document.addEventListener('DOMContentLoaded', function(e) { + var hs = document.querySelectorAll("div.section[class*='level'] > :first-child"); + var i, h, a; + for (i = 0; i < hs.length; i++) { + h = hs[i]; + if (!/^h[1-6]$/i.test(h.tagName)) continue; // it should be a header h1-h6 + a = h.attributes; + while (a.length > 0) h.removeAttribute(a[0].name); + } +}); diff --git a/docs/articles/code-development.html b/docs/articles/code-development.html new file mode 100644 index 00000000..626de4ee --- /dev/null +++ b/docs/articles/code-development.html @@ -0,0 +1,139 @@ + + + + + + + +Why and how container for code development • container + + + + + + + + + + + + + + + + +
    +
    + + + + +
    +
    + + + + +
    +library(container, warn.conflicts = FALSE)
    +
    + + + +
    + + + + +
    + + + + + + diff --git a/docs/articles/code-development_files/header-attrs-2.11/header-attrs.js b/docs/articles/code-development_files/header-attrs-2.11/header-attrs.js new file mode 100644 index 00000000..dd57d92e --- /dev/null +++ b/docs/articles/code-development_files/header-attrs-2.11/header-attrs.js @@ -0,0 +1,12 @@ +// Pandoc 2.9 adds attributes on both header and div. We remove the former (to +// be compatible with the behavior of Pandoc < 2.8). +document.addEventListener('DOMContentLoaded', function(e) { + var hs = document.querySelectorAll("div.section[class*='level'] > :first-child"); + var i, h, a; + for (i = 0; i < hs.length; i++) { + h = hs[i]; + if (!/^h[1-6]$/i.test(h.tagName)) continue; // it should be a header h1-h6 + a = h.attributes; + while (a.length > 0) h.removeAttribute(a[0].name); + } +}); diff --git a/docs/articles/dict.table.html b/docs/articles/dict.table.html new file mode 100644 index 00000000..7ef949a8 --- /dev/null +++ b/docs/articles/dict.table.html @@ -0,0 +1,139 @@ + + + + + + + +Enhancing data.table with dict.table • container + + + + + + + + + + + + + + + + +
    +
    + + + + +
    +
    + + + + +
    +library(container, warn.conflicts = FALSE)
    +
    + + + +
    + + + + +
    + + + + + + diff --git a/docs/articles/dict.table_files/header-attrs-2.11/header-attrs.js b/docs/articles/dict.table_files/header-attrs-2.11/header-attrs.js new file mode 100644 index 00000000..dd57d92e --- /dev/null +++ b/docs/articles/dict.table_files/header-attrs-2.11/header-attrs.js @@ -0,0 +1,12 @@ +// Pandoc 2.9 adds attributes on both header and div. We remove the former (to +// be compatible with the behavior of Pandoc < 2.8). +document.addEventListener('DOMContentLoaded', function(e) { + var hs = document.querySelectorAll("div.section[class*='level'] > :first-child"); + var i, h, a; + for (i = 0; i < hs.length; i++) { + h = hs[i]; + if (!/^h[1-6]$/i.test(h.tagName)) continue; // it should be a header h1-h6 + a = h.attributes; + while (a.length > 0) h.removeAttribute(a[0].name); + } +}); diff --git a/docs/articles/index.html b/docs/articles/index.html index 2a700472..01631832 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -90,6 +90,9 @@ +
  • + Get started +
  • Reference
  • @@ -101,10 +104,16 @@ @@ -137,9 +146,15 @@

    All vignettes

    -
    Container introduction
    +
    Why and how container for code development
    +
    +
    Get started
    +
    +
    Enhancing data.table with dict.table
    +
    +
    Manage parameter lists with dict
    -
    Overview
    +
    Reference semantics
    diff --git a/docs/articles/parameter-list.html b/docs/articles/parameter-list.html new file mode 100644 index 00000000..dacdd0e8 --- /dev/null +++ b/docs/articles/parameter-list.html @@ -0,0 +1,259 @@ + + + + + + + +Manage parameter lists with dict • container + + + + + + + + + + + + + + + + +
    +
    + + + + +
    +
    + + + + +
    +

    +Motivation

    +

    The original motivation for the development of this package actually was that the author found himself writing countless checks and helper code over and over again when managing parameter lists in larger applications. It became apparent that something similar to python’s dictionary would make life easier and so the idea of the container package was born.

    +

    The package has undergone some changes since it’s initial version, but the dict as a use-case for parameter lists remains very valid. So without further ado, let’s see how this works out in practice.

    +
    +library(container, warn.conflicts = FALSE)
    +
    +# Define some parameters
    +params = dict(a = 1:10, b = "foo")
    +
    +
    +

    +Add or Replace

    +

    With a dict the problem of accidentally overriding an existing parameter value is solved out of the box using the add function.

    +
    +params = add(params, a = 0)
    +#> Error: name 'a' exists already
    +add(params, x = 0) # ok
    +#> {a = (1L 2L 3L 4L ...), b = "foo", x = 0}
    +

    Of course, it’s also possible to indeed override a parameter.

    +
    +replace_at(params, a = 0)
    +#> {a = 0, b = "foo"}
    +

    What if you intend to replace something, but there is nothing to replace?

    +
    +replace_at(params, x = 0)
    +#> Error: names(s) not found: 'x'
    +

    Now you might wonder, what if ‘I don’t care if it is replaced or added’. That’s easy.

    +
    +replace_at(params, a = 0, .add=TRUE)
    +#> {a = 0, b = "foo"}
    +replace_at(params, x = 0, .add=TRUE)
    +#> {a = (1L 2L 3L 4L ...), b = "foo", x = 0}
    +

    That is, using .add = TRUE basically means, ‘replace it, or, if it is not there, just add it’

    +

    Maybe you agree that even these simple use-cases already require some effort when using base R lists.

    +
    +
    +

    +Extract

    +

    When extracting a parameter, you might want to be sure it exists and signal an error otherwise.

    +
    +at(params, "x")
    +#> Error: index 'x' not found
    +at(params, "a", "b")
    +#> {a = (1L 2L 3L 4L ...), b = "foo"}
    +

    To extract a single raw element, use at2

    +
    +at2(params, "a")
    +#>  [1]  1  2  3  4  5  6  7  8  9 10
    +

    Alternatively, you could use the standard access operators, which behave like base R list and therefore return an empty dict (or NULL) if the index is not found.

    +
    +params["x"]
    +#> {}
    +params[["x"]]
    +#> NULL
    +params["a"]
    +#> {a = (1L 2L 3L 4L ...)}
    +params[["a"]]
    +#>  [1]  1  2  3  4  5  6  7  8  9 10
    +
    +

    +Default values

    +

    A nice property of the dict is that it provides an easy and flexible way to manage default values.

    +
    +peek_at(params, "x")
    +#> {}
    +peek_at(params, "x", .default = 3:1)
    +#> {x = (3L 2L 1L)}
    +

    That is, if you peek at a non-existing parameter, by default an empty dict is returned, but with the option to explicitly set the default. This also works for multiple peeks.

    +
    +peek_at(params, "a", "x", "y", .default = 3:1)
    +#> {a = (1L 2L 3L 4L ...), x = (3L 2L 1L), y = (3L 2L 1L)}
    +
    +
    +
    +

    +Remove

    +

    Similar to the above examples, the user can control how removal of existing/non-existing parameters is handled. If you expect a parameter and want to be signaled if it was not there, use delete.

    +
    +delete_at(params, "x")
    +#> Error: names(s) not found: 'x'
    +delete_at(params, "a") # ok
    +#> {b = "foo"}
    +

    Otherwise to loosely delete a parameter, regardless of whether it exists or not, use discard.

    +
    +discard_at(params, "a", "x")
    +#> {b = "foo"}
    +

    It’s important to note, that the “base R list way” to delete elements does not work, because it just inserts a NULL.

    +
    +params[["a"]] <- NULL
    +
    +params
    +#> {a = NULL, b = "foo"}
    +
    +
    +

    +Merge

    +

    Last but not least, dict allows to easily merge and/or update parameter lists.

    +
    +par1 = dict(a = 1, b = "foo")
    +par2 = dict(b = "bar", x = 2, y = 3)
    +
    +update(par1, par2)
    +#> {a = 1, b = "bar", x = 2, y = 3}
    +

    As can be seen, existing parameters are updated and new parameters added. Using as.dict you can also do this with ordinary lists.

    +
    +update(par1, as.dict(list(b = "my b", x = 100)))
    +#> {a = 1, b = "my b", x = 100}
    +

    That’s it. I hope, it will free you some time and safe some bugs next time you need to manage parameter lists.

    +

    As a very last note, keep in mind that since container version 1.0.0, dict elements are always sorted by their name, while you are still able to access elements by position (based on the sorted values).

    +
    +d = dict(x = 1, z = 2, a = 3)
    +d
    +#> {a = 3, x = 1, z = 2}
    +d[[1]]
    +#> [1] 3
    +d[2:3]
    +#> {x = 1, z = 2}
    +
    +
    + + + +
    + + + + +
    + + + + + + diff --git a/docs/articles/parameter-list_files/header-attrs-2.11/header-attrs.js b/docs/articles/parameter-list_files/header-attrs-2.11/header-attrs.js new file mode 100644 index 00000000..dd57d92e --- /dev/null +++ b/docs/articles/parameter-list_files/header-attrs-2.11/header-attrs.js @@ -0,0 +1,12 @@ +// Pandoc 2.9 adds attributes on both header and div. We remove the former (to +// be compatible with the behavior of Pandoc < 2.8). +document.addEventListener('DOMContentLoaded', function(e) { + var hs = document.querySelectorAll("div.section[class*='level'] > :first-child"); + var i, h, a; + for (i = 0; i < hs.length; i++) { + h = hs[i]; + if (!/^h[1-6]$/i.test(h.tagName)) continue; // it should be a header h1-h6 + a = h.attributes; + while (a.length > 0) h.removeAttribute(a[0].name); + } +}); diff --git a/docs/articles/reference-semantics.html b/docs/articles/reference-semantics.html new file mode 100644 index 00000000..2e951ac3 --- /dev/null +++ b/docs/articles/reference-semantics.html @@ -0,0 +1,139 @@ + + + + + + + +Reference semantics • container + + + + + + + + + + + + + + + + +
    +
    + + + + +
    +
    + + + + +
    +library(container, warn.conflicts = FALSE)
    +
    + + + +
    + + + + +
    + + + + + + diff --git a/docs/articles/reference-semantics_files/header-attrs-2.11/header-attrs.js b/docs/articles/reference-semantics_files/header-attrs-2.11/header-attrs.js new file mode 100644 index 00000000..dd57d92e --- /dev/null +++ b/docs/articles/reference-semantics_files/header-attrs-2.11/header-attrs.js @@ -0,0 +1,12 @@ +// Pandoc 2.9 adds attributes on both header and div. We remove the former (to +// be compatible with the behavior of Pandoc < 2.8). +document.addEventListener('DOMContentLoaded', function(e) { + var hs = document.querySelectorAll("div.section[class*='level'] > :first-child"); + var i, h, a; + for (i = 0; i < hs.length; i++) { + h = hs[i]; + if (!/^h[1-6]$/i.test(h.tagName)) continue; // it should be a header h1-h6 + a = h.attributes; + while (a.length > 0) h.removeAttribute(a[0].name); + } +}); diff --git a/docs/articles/serious-coding.html b/docs/articles/serious-coding.html new file mode 100644 index 00000000..a22092cf --- /dev/null +++ b/docs/articles/serious-coding.html @@ -0,0 +1,206 @@ + + + + + + + +Get started • container + + + + + + + + + + + + + + + + +
    +
    + + + + +
    +
    + + + + +
    +

    +R in interactive sessions

    +

    From its start R has been used not only as a programming language but also as an interactive tool, which is visible in many places. For example, R by default often tries to auto-simplify data types of returned values.

    +
    +daf = data.frame(a = 1:3, b =3:1)
    +daf[, 1]    # returns a vector instead of a data.frame
    +#> [1] 1 2 3
    +

    This can also be seen in the apply, sapply, and similar functions, which all by default have an argument set to simplify = TRUE.

    +

    Likewise R in some cases auto-fills missing values.

    +
    +daf = data.frame(a = 1:4)
    +daf[, "b"] = 0:1
    +daf
    +#>   a b
    +#> 1 1 0
    +#> 2 2 1
    +#> 3 3 0
    +#> 4 4 1
    +
    +v = 1:3
    +v[7] = 7
    +v
    +#> [1]  1  2  3 NA NA NA  7
    +

    Sometimes an error or warning is given.

    +
    +daf[, 5] = 1
    +#> Error in `[<-.data.frame`(`*tmp*`, , 5, value = 1): new columns would leave holes after existing columns
    +daf[[5]] = 1
    +daf
    +#> Warning in format.data.frame(if (omit) x[seq_len(n0), , drop = FALSE] else x, :
    +#> corrupt data frame: columns will be truncated or padded with NAs
    +#>   a b        .1 V5
    +#> 1 1 0 NULL NULL  1
    +#> 2 2 1 <NA> <NA>  1
    +#> 3 3 0 <NA> <NA>  1
    +#> 4 4 1 <NA> <NA>  1
    +

    Non-existing elements yield NA/NULL on vectors/lists without errors or warnings.

    +
    +(1:3)[5]
    +#> [1] NA
    +list(1, 2, 3)[5]
    +#> [[1]]
    +#> NULL
    +
    +

    +R in serious code

    +

    As a result, when writing serious code, the user has to check carefully for index overflow or missing elements, which otherwise can lead to unintended results or bugs that are hard to spot. Silly example:

    +
    +v = 1:3
    +v[7] = 7
    +sum = 0
    +for (i in 1:length(v))
    +    sum = sum + v[i]
    +
    +sum
    +#> [1] NA
    +# Checked version
    +sum = 0
    +for (i in 1:length(v))
    +    sum = sum + ifelse(is.na(v[i]), 0, v[i])
    +
    +sum
    +#> [1] 13
    +
    +
    +

    +container in serious code

    +
    +
    +
    + + + +
    + + + + +
    + + + + + + diff --git a/docs/articles/serious-coding_files/header-attrs-2.11/header-attrs.js b/docs/articles/serious-coding_files/header-attrs-2.11/header-attrs.js new file mode 100644 index 00000000..dd57d92e --- /dev/null +++ b/docs/articles/serious-coding_files/header-attrs-2.11/header-attrs.js @@ -0,0 +1,12 @@ +// Pandoc 2.9 adds attributes on both header and div. We remove the former (to +// be compatible with the behavior of Pandoc < 2.8). +document.addEventListener('DOMContentLoaded', function(e) { + var hs = document.querySelectorAll("div.section[class*='level'] > :first-child"); + var i, h, a; + for (i = 0; i < hs.length; i++) { + h = hs[i]; + if (!/^h[1-6]$/i.test(h.tagName)) continue; // it should be a header h1-h6 + a = h.attributes; + while (a.length > 0) h.removeAttribute(a[0].name); + } +}); diff --git a/docs/authors.html b/docs/authors.html index 10f56a51..7c63f66a 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -90,6 +90,9 @@ +
  • + Get started +
  • Reference
  • @@ -101,10 +104,16 @@ diff --git a/docs/index.html b/docs/index.html index fa7bc165..e4446000 100644 --- a/docs/index.html +++ b/docs/index.html @@ -53,6 +53,9 @@ +
  • + Get started +
  • Reference
  • @@ -64,10 +67,16 @@ @@ -97,97 +106,77 @@ -
    -

    -Update

    -

    Update to version 1.0.0 is coming soon to CRAN.

    -
    -
    -

    -Intro

    -

    This package extends the functionality of base R list and the data.table package and with deque, set, and dict provides additional common data structures. It furthermore implements iterators and supports both reference and copy semantics.

    -
    -
    -

    -Why container?

    -
    -
    -

    -Features

    -
    -
    -

    -Installation

    -

    You can install the released version of container from CRAN with:

    +
    +

    +Update to NEW version 1.0.0 soon on CRAN.

    +

    container extends base R list functionality with the goal to serve as an easy and safe to use list alternative, applicable not only for interactive R sessions but specifically to make life easier in serious code development.

    +

    In addition, this package provides specialized data structures deque, set, dict, and dict.table, the latter to extend the data.table package.

    +
    +
    +

    +Why container over list?

    +

    A container is based on list but with

    +
      +
    • compact printing
    • +
    • feature rich add, extract, replace, or removal operations
    • +
    • safer data operations (no more unintended NULL or NA)
    • +
    • optional reference semantics
    • +
    • some more …
    • +
    +
    +
    +

    +Installation

     # Install release version from CRAN
     install.packages("container")
     
     # Install development version from GitHub
     devtools::install_github("rpahl/container")
    -
    +
    +

    -container vs list

    -

    Basically all you can do with a list can also be done with a container, but the container is capable of much more.

    +Usage +

    Use container the same way you would use a base R list, but enjoy additional functionalities.

     library(container)
    -
    -co <- container(1:10, l = list("a", 1))
    -li <- as.list(co)
    -

    While the list output can be very long and hard to read

    +co <- container(x = c(1.0, 2.0), y = 1:2, data = cars) +co +#> [x = (1 2), y = (1L 2L), data = <<data.frame(50x2)>>]
    +

    Some standard operations …

    -li
    -#> [[1]]
    -#>  [1]  1  2  3  4  5  6  7  8  9 10
    -#> 
    -#> $l
    -#> $l[[1]]
    -#> [1] "a"
    -#> 
    -#> $l[[2]]
    -#> [1] 1
    -

    the elements of a container object are printed very compact.

    +co[1:2] +#> [x = (1 2), y = (1L 2L)]
    -co
    -#> [(1L 2L 3L 4L ...), l = list("a", 1)]
    -

    Find and replace of list elements requires to determine the index first.

    +co[["n"]] +#> NULL
    +

    Some new operations …

    -element = list("a", 1)
    -index = which(sapply(li, identical, list("a", 1)))
    -li[[index]] <- 1:3
    -li
    -#> [[1]]
    -#>  [1]  1  2  3  4  5  6  7  8  9 10
    -#> 
    -#> $l
    -#> [1] 1 2 3
    -

    With container just pass the element directly in {}

    +co[1:2, "data", "n"] +#> [x = (1 2), y = (1L 2L), data = <<data.frame(50x2)>>]
    -co[[{element}]] <- 1:3
    +co[[{cars}]] <- iris
     co
    -#> [(1L 2L 3L 4L ...), l = (1L 2L 3L)]
    -

    Update parameter lists with ease.

    +#> [x = (1 2), y = (1L 2L), data = <<data.frame(150x5)>>]
    -param = cont(x = 1, foo = "bar") # cont is a shortcut for container
    -param
    -#> [x = 1, foo = "bar"]
    +co2 = container(x = 1:10, data = NULL, -111) +co = update(co, co2) +co +#> [x = (1L 2L 3L 4L ...), y = (1L 2L), data = NULL, -111]
    -new_param = cont(z = 2, foo = "my foo")
    -update(param, new_param)
    -#> [x = 1, foo = "my foo", z = 2]
    +rename(co, "x", "X") +#> [X = (1L 2L 3L 4L ...), y = (1L 2L), data = NULL, -111] -
    +

    -dict.table vs data.frame

    -

    Basically all you can do with a data.table can also be done with a dict.table, but the dict.table also provides dict functionality.

    -
    -dit = dict.table(a = 1:2, b = 3:4)
    -dit
    -#> <dict.table> with 2 rows and 2 columns
    -#>    a b
    -#> 1: 1 3
    -#> 2: 2 4
    -
    +Getting Started +

    There is much more to explore. To get started, see

    +
      +
    • Get started vignette
    • +
    • Manage parameter lists with dict
    • +
    • Why and how container for code development
    • +
    • Enhancing data.table with dict.table
    • +
    diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 123ac020..069126d0 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -2,9 +2,12 @@ pandoc: 2.11.4 pkgdown: 1.6.1 pkgdown_sha: ~ articles: - Container: Container.html - overview: overview.html -last_built: 2021-10-11T20:22Z + code-development: code-development.html + container: container.html + dict.table: dict.table.html + parameter-list: parameter-list.html + reference-semantics: reference-semantics.html +last_built: 2021-10-23T17:34Z urls: reference: https://github.com/rpahl/container/reference article: https://github.com/rpahl/container/articles diff --git a/docs/reference/Container.html b/docs/reference/Container.html index d877573a..0e79b96d 100644 --- a/docs/reference/Container.html +++ b/docs/reference/Container.html @@ -93,6 +93,9 @@ +
  • + Get started +
  • Reference
  • @@ -104,10 +107,16 @@ diff --git a/docs/reference/ContainerS3.html b/docs/reference/ContainerS3.html index 54eea7ea..cfc605f7 100644 --- a/docs/reference/ContainerS3.html +++ b/docs/reference/ContainerS3.html @@ -49,7 +49,7 @@ @@ -95,6 +95,9 @@ +
  • + Get started +
  • Reference
  • @@ -106,10 +109,16 @@ @@ -142,8 +151,8 @@

    Container - Enhancing R's list

    A container is a data structure with typical member functions to insert, delete and access elements from the container -object. The container can be seen as a base R list with -extended functionality. The Container class also serves as the base +object. It can be considered as a base R list with +extended functionality. The Container class also serves as the base class for Deque, Set, and Dict objects.

    @@ -164,7 +173,10 @@

    Container - Enhancing R's list

    length(x) # S3 method for Container -names(x) +names(x) + +# S3 method for Container +names(x) <- value

    Arguments

    @@ -215,6 +227,10 @@

    Details
  • names(x) return the names of the elements contained in x.

  • +
      +
    • names(x) <- value set names of the elements contained in x.

    • +
    +

    - + - + -
    ...

    elements put into the dict.table and/or additional arguments -to be passed on.

    elements put into the dict.table and/or additional +arguments to be passed on.

    x

    any R object or a dict.table object.

    any R object or a dict.table object.

    copy

    if TRUE creates a copy of the data.table object otherwise +

    if TRUE creates a copy of the data.table object otherwise works on the passed object by reference.

    Details

    -

    Methods that alter dict.table objects usually come in two versions +

    Methods that alter dict.table objects usually come in two versions providing either copy or reference semantics where the latter start with 'ref_' to note the reference semantic, for example, add() and ref_add().

      -
    • dict.table(...) initializes and returns a dict() object.

    • +
    • dict.table(...) initializes and returns a dict object.

      -
    • as.dict.table(x, ...) coerces x to a dict.table

    • +
    • as.dict.table(x, ...) coerce x to a dict.table

      @@ -278,19 +299,15 @@

      Details that are not yet in object and replaces the values at existing columns.

    -

    Note

    - -

    In contrast to data.table::data.table, -dict.table does not allow duplicated keys.

    See also

    - +

    Examples

    # Some basic examples using some typical data.table and dict operations. # The constructor can take the 'key' argument known from data.table(): require(data.table) -dit = dict.table(x = rep(c("b","a","c"), each = 3), y = c(1,3,6), key = "y") +
    #> Loading required package: data.table
    dit = dict.table(x = rep(c("b","a","c"), each = 3), y = c(1,3,6), key = "y") print(dit)
    #> <dict.table> with 9 rows and 2 columns #> x y diff --git a/docs/reference/dictS3.html b/docs/reference/dictS3.html index 57900d14..79366cbc 100644 --- a/docs/reference/dictS3.html +++ b/docs/reference/dictS3.html @@ -47,10 +47,14 @@ - + @@ -94,6 +98,9 @@ +
  • + Get started +
  • Reference
  • @@ -105,10 +112,16 @@ @@ -139,10 +152,14 @@

    A Dictionary

    -

    The dict() resembles Python's dict type, and is implemented -as a specialized associative Container() thus sharing all container() -methods with some of them being overridden to account for the associative -key-value pair semantic.

    +

    The Dict initially was developed to resemble Python's +dict type, but by now offers both more features and flexibility, for +example, by providing both associative key-value pair as well as +positional array semantics. +It is implemented as a specialized associative Container thus sharing +all Container methods with some of them being adapted to account for +the key-value pair semantic. +All Dict elements must be named and are always sorted by their name.

    dict(...)
    @@ -225,7 +242,7 @@ 

    Details

    See also

    See container() for all inherited methods. For the full class -documentation see Dict() and it's superclass Container().

    +documentation see Dict and it's superclass Container.

    Examples

    d = dict(a = 1, b = "one", f = mean, na = NA) @@ -241,7 +258,7 @@

    Examp #> $f #> function (x, ...) #> UseMethod("mean") -#> <bytecode: 0x0000000015e8b250> +#> <bytecode: 0x00000000167ef8f0> #> <environment: namespace:base> #> #> $na diff --git a/docs/reference/dicttable.html b/docs/reference/dicttable.html index 369cbf85..99f4e789 100644 --- a/docs/reference/dicttable.html +++ b/docs/reference/dicttable.html @@ -48,10 +48,9 @@ @@ -97,6 +96,9 @@ +
  • + Get started +
  • Reference
  • @@ -108,10 +110,16 @@ @@ -142,12 +150,11 @@

    Combining Dict and data.table

    -

    The dict.table is a combination of dict and -data.table and basically can be considered a data.table with extended -functionality to manage its data columns in a stricter way. For example, -in contrast to data.table, dict.table does not allow -duplicated column names. -A dict.table object provides all dict and data.table +

    The dict.table is a combination of dict and +data.table and basically can be considered a data.table with no +duplicated column names plus an extended set of functions to add, insert and +remove its data columns. +A dict.table object provides all dict and data.table functions and operators at the same time.

    @@ -187,9 +194,9 @@

    Arg

    Details

    -

    Methods that alter dict.table objects usually come in two versions +

    Methods that alter dict.table objects usually come in two versions providing either copy or reference semantics where the latter start with -'ref_' to note the reference semantic, for example, add and ref_add.

    +'ref_' to note the reference semantic, for example, add() and ref_add().

    • dict.table(...) initializes and returns a dict object.

    @@ -290,7 +297,7 @@

    Examp
    # Some basic examples using some typical data.table and dict operations. # The constructor can take the 'key' argument known from data.table(): require(data.table) -
    #> Loading required package: data.table
    dit = dict.table(x = rep(c("b","a","c"), each = 3), y = c(1,3,6), key = "y") +
    #> Loading required package: data.table
    #> data.table 1.14.0 using 6 threads (see ?getDTthreads). Latest news: r-datatable.com
    dit = dict.table(x = rep(c("b","a","c"), each = 3), y = c(1,3,6), key = "y") print(dit)
    #> <dict.table> with 9 rows and 2 columns #> x y diff --git a/docs/reference/discard.html b/docs/reference/discard.html index 84e32619..410f8fed 100644 --- a/docs/reference/discard.html +++ b/docs/reference/discard.html @@ -92,6 +92,9 @@ +
  • + Get started +
  • Reference
  • @@ -103,10 +106,16 @@ diff --git a/docs/reference/discard_at.html b/docs/reference/discard_at.html index 8ec3aa60..8979a48e 100644 --- a/docs/reference/discard_at.html +++ b/docs/reference/discard_at.html @@ -92,6 +92,9 @@ +
  • + Get started +
  • Reference
  • @@ -103,10 +106,16 @@ @@ -184,7 +193,7 @@

    Examp

    #> [3]
    discard_at(co, "a", 3) # [b = 2]
    #> [b = 2]
    discard_at(co, "x") # ignored
    #> [a = 1, b = 2, 3]
    -dit = as.dict.table(head(sleep)) +dit = as.dict.table(head(sleep)) discard_at(dit, "ID")
    #> <dict.table> with 6 rows and 2 columns #> extra group diff --git a/docs/reference/has.html b/docs/reference/has.html index 5602ac80..95d4577b 100644 --- a/docs/reference/has.html +++ b/docs/reference/has.html @@ -91,6 +91,9 @@ +
  • + Get started +
  • Reference
  • @@ -102,10 +105,16 @@ @@ -184,7 +193,7 @@

    Examp

    #> [1] TRUE
    has(co, mean) # TRUE
    #> [1] TRUE
    has(co, 1:2) # FALSE
    #> [1] FALSE
    -dit = dict.table(a = 1:3, b = as.list(4:6)) +dit = dict.table(a = 1:3, b = as.list(4:6)) has(dit, 1:3) # TRUE
    #> [1] TRUE
    has(dit, 4:6) # FALSE
    #> [1] FALSE
    has(dit, as.list(4:6)) # TRUE diff --git a/docs/reference/has_name.html b/docs/reference/has_name.html index 19fcac17..b25a1ba6 100644 --- a/docs/reference/has_name.html +++ b/docs/reference/has_name.html @@ -91,6 +91,9 @@ +
  • + Get started +
  • Reference
  • @@ -102,10 +105,16 @@ @@ -176,7 +185,7 @@

    Examp

    #> [1] TRUE
    has_name(co, "f") # TRUE
    #> [1] TRUE
    has_name(co, "2") # FALSE
    #> [1] FALSE
    -dit = dict.table(a = 1:2, b = 3:4) +dit = dict.table(a = 1:2, b = 3:4) has_name(dit, "a") # TRUE
    #> [1] TRUE
    has_name(dit, "x") # FALSE
    #> [1] FALSE
    diff --git a/docs/reference/index.html b/docs/reference/index.html index e1d0c2c8..7cd95385 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -90,6 +90,9 @@ +
  • + Get started +
  • Reference
  • @@ -101,10 +104,16 @@ @@ -144,7 +153,7 @@

    Reference

    Container

    -

    A container can be considered a basic R list with extended functionality.

    +

    A container can be considered a base R list with extended functionality.

    @@ -161,7 +170,7 @@

    -

    container() cont() as.container() as.cont() is.container() as.list(<Container>) length(<Container>) names(<Container>)

    +

    container() cont() as.container() as.cont() is.container() as.list(<Container>) length(<Container>) names(<Container>) `names<-`(<Container>)

    Container - Enhancing R's list

    @@ -444,15 +453,21 @@

    -

    setnew() as.set() is.set()

    +

    OrderedSet

    + +

    Ordered Set Class

    + + + +

    setnew() as.set() as.orderedset() is.set() is.orderedset()

    -

    Set

    +

    Set and ordered Set

    Dict

    -

    Derives all Container methods. The dict resembles Python’s dict type but here is more flexible by providing both associative key-value pair as well as positional array semantics.

    +

    Derives all Container methods. All Dict elements must be named and are always sorted by their name.

    @@ -488,7 +503,7 @@

    -

    dict.table() as.dict.table() is.dict.table() rbind(<dict.table>) cbind(<dict.table>)

    +

    dict.table() as.dict.table() is.dict.table() rbind(<dict.table>) cbind(<dict.table>)

    Combining Dict and data.table

    diff --git a/docs/reference/is_empty.html b/docs/reference/is_empty.html index d4cb6e5c..e5a8db94 100644 --- a/docs/reference/is_empty.html +++ b/docs/reference/is_empty.html @@ -91,6 +91,9 @@ +
  • + Get started +
  • Reference
  • @@ -102,10 +105,16 @@ @@ -166,7 +175,7 @@

    Examp is_empty(co)
    #> [1] FALSE
    is_empty(clear(co))
    #> [1] TRUE
    -d = dict.table(a = 1:4, b = 4:1) +d = dict.table(a = 1:4, b = 4:1) is_empty(d)
    #> [1] FALSE
    is_empty(clear(d))
    #> [1] TRUE

    diff --git a/docs/reference/iterS3.html b/docs/reference/iterS3.html index 22fd9ae6..892e7479 100644 --- a/docs/reference/iterS3.html +++ b/docs/reference/iterS3.html @@ -94,6 +94,9 @@ +
  • + Get started +
  • Reference
  • @@ -105,10 +108,16 @@ diff --git a/docs/reference/peek.html b/docs/reference/peek.html index 930452e0..41dd497b 100644 --- a/docs/reference/peek.html +++ b/docs/reference/peek.html @@ -93,6 +93,9 @@ +
  • + Get started +
  • Reference
  • @@ -104,10 +107,16 @@ diff --git a/docs/reference/peek_at.html b/docs/reference/peek_at.html index cb6cbae1..3f1bfbb9 100644 --- a/docs/reference/peek_at.html +++ b/docs/reference/peek_at.html @@ -93,6 +93,9 @@ +
  • + Get started +
  • Reference
  • @@ -104,10 +107,16 @@ @@ -198,7 +207,7 @@

    Examp
    #> {}
    peek_at(d, "x", .default = 4:7)
    #> {x = (4L 5L 6L 7L)}
    # dict.table -dit = dict.table(a = 1:3, b = 4:6) +dit = dict.table(a = 1:3, b = 4:6) peek_at(dit, "a")
    #> <dict.table> with 3 rows and 1 column #> a diff --git a/docs/reference/peek_at2.html b/docs/reference/peek_at2.html index 1b132c06..81a2fdfe 100644 --- a/docs/reference/peek_at2.html +++ b/docs/reference/peek_at2.html @@ -93,6 +93,9 @@ +
  • + Get started +
  • Reference
  • @@ -104,10 +107,16 @@ @@ -197,7 +206,7 @@

    Examp

    #> NULL
    peek_at2(d, "x", default = 4:7)
    #> [1] 4 5 6 7
    # dict.table -dit = dict.table(a = 1:3, b = 4:6) +dit = dict.table(a = 1:3, b = 4:6) peek_at2(dit, "a")
    #> [1] 1 2 3
    peek_at2(dit, 1)
    #> [1] 1 2 3
    peek_at2(dit, 3) diff --git a/docs/reference/pop.html b/docs/reference/pop.html index f08a5aa9..c5d5b084 100644 --- a/docs/reference/pop.html +++ b/docs/reference/pop.html @@ -92,6 +92,9 @@ +
  • + Get started +
  • Reference
  • @@ -103,10 +106,16 @@ @@ -211,7 +220,7 @@

    Examp } # dict.table -dit = dict.table(a = 1:3, b = 4:6) +dit = dict.table(a = 1:3, b = 4:6) ref_pop(dit, "a")

    #> [1] 1 2 3
    ref_pop(dit, 1)
    #> [1] 4 5 6
    diff --git a/docs/reference/rename.html b/docs/reference/rename.html index 0f95cba4..da52303f 100644 --- a/docs/reference/rename.html +++ b/docs/reference/rename.html @@ -93,6 +93,9 @@ +
  • + Get started +
  • Reference
  • @@ -104,10 +107,16 @@ @@ -183,7 +192,7 @@

    Value

    For Container, an object of class Container (or one of the respective derived classes).

    For dict.table renames key old to new in place (i.e. by -reference) and invisibly returns the dict.table() object.

    +reference) and invisibly returns the dict.table() object.

    Details

    The passed old and new names can be vectors but always must have @@ -201,7 +210,7 @@

    Examp

    #> [a1 = 1, y = 2, 3]
    print(co)
    #> [a1 = 1, y = 2, 3]
    # dict.table -dit = dict.table(a = 1, b = 2, c = 3) +dit = dict.table(a = 1, b = 2, c = 3) rename(dit, c("a", "b"), c("a1", "y"))
    #> <dict.table> with 1 row and 3 columns #> a1 y c diff --git a/docs/reference/replace.html b/docs/reference/replace.html index d3f5a09d..830a6bd8 100644 --- a/docs/reference/replace.html +++ b/docs/reference/replace.html @@ -92,6 +92,9 @@ +
  • + Get started +
  • Reference
  • @@ -103,10 +106,16 @@ diff --git a/docs/reference/replace_at.html b/docs/reference/replace_at.html index f2cc51c0..89a3fc1c 100644 --- a/docs/reference/replace_at.html +++ b/docs/reference/replace_at.html @@ -93,6 +93,9 @@ +
  • + Get started +
  • Reference
  • @@ -104,10 +107,16 @@ @@ -203,7 +212,7 @@

    Examp replace_at(co, x = 1, .add = TRUE) # ok (adds x = 1)

    #> [a = 0, b = "z", x = 1]
    -dit = dict.table(a = 1:3, b = 4:6) +dit = dict.table(a = 1:3, b = 4:6) replace_at(dit, a = 3:1)
    #> <dict.table> with 3 rows and 2 columns #> a b diff --git a/docs/reference/rev.html b/docs/reference/rev.html index f7b4142a..a1f596f9 100644 --- a/docs/reference/rev.html +++ b/docs/reference/rev.html @@ -91,6 +91,9 @@ +
  • + Get started +
  • Reference
  • @@ -102,10 +105,16 @@ diff --git a/docs/reference/rotate.html b/docs/reference/rotate.html index bf8468c4..6dad0c82 100644 --- a/docs/reference/rotate.html +++ b/docs/reference/rotate.html @@ -92,6 +92,9 @@ +
  • + Get started +
  • Reference
  • @@ -103,10 +106,16 @@ diff --git a/docs/reference/setS3.html b/docs/reference/setS3.html index a17b9256..01f6e57e 100644 --- a/docs/reference/setS3.html +++ b/docs/reference/setS3.html @@ -6,7 +6,7 @@ -Set — SetS3 • container +Set and ordered Set — SetS3 • container @@ -46,9 +46,9 @@ - - + @@ -93,6 +93,9 @@ +
  • + Get started +
  • Reference
  • @@ -104,10 +107,16 @@ @@ -132,22 +141,26 @@
    -

    The Set() is considered and implemented as a specialized -Container(), that is, Set elements are always unique. It provides +

    The Set is considered and implemented as a specialized +Container, that is, Set elements are always unique. It provides typical set operations such as union and intersect.

    -
    setnew(...)
    +    
    setnew(..., .ordered = FALSE)
     
     as.set(x)
     
    -is.set(x)
    +as.orderedset(x) + +is.set(x) + +is.orderedset(x)

    Arguments

    @@ -156,6 +169,11 @@

    Arg

    + + + +
    ...

    initial elements put into the Set.

    .ordered

    logical if TRUE all elements in the Set will be +ordered.

    x

    R object of ANY type for as.set() and is.set() @@ -165,12 +183,7 @@

    Arg

    Details

    -

    Under the hood, elements of a set object are stored in a hash-table -and sorted by their length and, in case of ties, by their lexicographical -representation. -For a description of basic methods such as adding and removing elements, -see the help of container(). -Methods that alter Set objects usually come in two versions +

    Methods that alter Set objects usually come in two versions providing either copy or reference semantics where the latter start with 'ref_' to note the reference semantic, for example, add() and ref_add().

      @@ -181,11 +194,20 @@

      Details
    • as.set(x) coerces x to a set.

    +
      +
    • as.orderedset(x) coerces x to an ordered set.

    • +
    +
    • is.set(x) returns TRUE if x is of class Set and FALSE otherwise.

    +
      +
    • is.orderedset(x) returns TRUE if x is of class OrderedSet +and FALSE otherwise.

    • +
    +
    • x & y performs the set intersection of x and y

    @@ -197,37 +219,40 @@

    Details

    See also

    See container() for all inherited methods. For the full class -documentation see Set() and it's superclass Container().

    +documentation see Set and it's superclass Container.

    Examples

    s = setnew(1, b = NA, 1:3, c = container("a", 1)) is.set(s)
    #> [1] TRUE
    print(s) -
    #> {1, b = NA, c = ["a", 1], (1L 2L 3L)}
    length(s) +
    #> {1, b = NA, (1L 2L 3L), c = ["a", 1]}
    length(s)
    #> [1] 4
    names(s) -
    #> [1] "" "b" "c" ""
    as.list(s) +
    #> [1] "" "b" "" "c"
    #> [[1]] #> [1] 1 #> #> $b #> [1] NA #> +#> [[3]] +#> [1] 1 2 3 +#> #> $c #> ["a", 1] -#> -#> [[4]] -#> [1] 1 2 3 #>
    unpack(s) # flatten recursively similar to unlist -
    #> b c1 c2 -#> "1" NA "a" "1" "1" "2" "3"
    -# Math +
    #> b c1 c2 +#> "1" NA "1" "2" "3" "a" "1"
    +so = setnew(2, 1, .ordered = TRUE) +print(so) +
    #> {1, 2}
    add(so, 0) +
    #> {0, 1, 2}
    # Math s = setnew(5:3, 1, 2) s -
    #> {1, 2, (5L 4L 3L)}
    abs(s) -
    #> {1, 2, 3, 4, 5}
    cumsum(s) -
    #> {1, 12, 15, 3, 8}
    round(s) -
    #> {1, 2, 3, 4, 5}
    exp(s) -
    #> {148.4132, 2.718282, 20.08554, 54.59815, 7.389056}
    +
    #> {(5L 4L 3L), 1, 2}
    abs(s) +
    #> {5, 4, 3, 1, 2}
    cumsum(s) +
    #> {5, 9, 12, 13, 15}
    round(s) +
    #> {5, 4, 3, 1, 2}
    exp(s) +
    #> {148.4132, 54.59815, 20.08554, 2.718282, 7.389056}
    # Summary range(s)
    #> [1] 1 5
    min(s) @@ -236,8 +261,8 @@

    Examp s1 = setnew(1, 1:2) s2 = setnew(2, 1:2) s1 + s2 # same as s1 | s2 or c(c1, s2) -

    #> {1, 2, (1L 2L)}
    s2 + s1 # same -
    #> {1, 2, (1L 2L)}
    +
    #> {1, (1L 2L), 2}
    s2 + s1 # same +
    #> {2, (1L 2L), 1}
    s1 - s2
    #> {1}
    s2 - s1
    #> {2}
    diff --git a/docs/reference/unpack.html b/docs/reference/unpack.html index 142716d7..c5926e44 100644 --- a/docs/reference/unpack.html +++ b/docs/reference/unpack.html @@ -94,6 +94,9 @@ +
  • + Get started +
  • Reference
  • @@ -105,10 +108,16 @@ diff --git a/docs/reference/update.html b/docs/reference/update.html index f77197d7..13b9594b 100644 --- a/docs/reference/update.html +++ b/docs/reference/update.html @@ -93,6 +93,9 @@ +
  • + Get started +
  • Reference
  • @@ -104,10 +107,16 @@ @@ -195,8 +204,8 @@

    Examp update(d1, d2) # {a = 1, b = 0, c = 3}

    #> {a = 1, b = 0, c = 3}
    update(d2, d1) # {a = 1, b = 2, c = 3}
    #> {a = 1, b = 2, c = 3}
    -dit1 = dict.table(a = 1:2, b = 3:4) -dit2 = dict.table( b = 5:6, c = 8:9) +dit1 = dict.table(a = 1:2, b = 3:4) +dit2 = dict.table( b = 5:6, c = 8:9) update(d1, d2)
    #> {a = 1, b = 0, c = 3}
    update(d2, d1)
    #> {a = 1, b = 2, c = 3}
    diff --git a/docs/sitemap.xml b/docs/sitemap.xml index a0427af8..a0ed39f5 100644 --- a/docs/sitemap.xml +++ b/docs/sitemap.xml @@ -52,10 +52,10 @@ https://github.com/rpahl/container/reference/Dict.html - https://github.com/rpahl/container/reference/DictS3.html + https://github.com/rpahl/container/reference/dict.table.html - https://github.com/rpahl/container/reference/dicttable.html + https://github.com/rpahl/container/reference/DictS3.html https://github.com/rpahl/container/reference/discard.html @@ -96,6 +96,9 @@ https://github.com/rpahl/container/reference/OpsReplace.html + + https://github.com/rpahl/container/reference/OrderedSet.html + https://github.com/rpahl/container/reference/peek.html @@ -136,9 +139,18 @@ https://github.com/rpahl/container/reference/update.html - https://github.com/rpahl/container/articles/Container.html + https://github.com/rpahl/container/articles/code-development.html + + + https://github.com/rpahl/container/articles/container.html + + + https://github.com/rpahl/container/articles/dict.table.html + + + https://github.com/rpahl/container/articles/parameter-list.html - https://github.com/rpahl/container/articles/overview.html + https://github.com/rpahl/container/articles/reference-semantics.html diff --git a/inst/tinytest/test_0-ContainerS3.R b/inst/tinytest/test_0-ContainerS3.R index 4bd6a8a3..4910e7ed 100644 --- a/inst/tinytest/test_0-ContainerS3.R +++ b/inst/tinytest/test_0-ContainerS3.R @@ -176,6 +176,17 @@ ee(names(container(list())), NULL) ee(names(container(1, 2, 3)), NULL) ee(names(container(a = 1, 2, x = 5)), c("a", "", "x")) +# ----------------- +# names<-.Container +# ----------------- +co = container(1, b = 2, c = 3) +names(co) = letters[1:3] +ee(names(co), letters[1:3]) +names(co)[3] = "z" +ee(names(co), c("a", "b", "z")) +names(co)[1:2] = c("x", "y") +ee(names(co), c("x", "y", "z")) + # --------------- # str.Container # --------------- diff --git a/inst/tinytest/test_0-SetR6.R b/inst/tinytest/test_0-SetR6.R index 7c0c1cdd..b531d9fa 100644 --- a/inst/tinytest/test_0-SetR6.R +++ b/inst/tinytest/test_0-SetR6.R @@ -55,7 +55,8 @@ expect_error(s$at("c"), "index 'c' not found") expect_error(s$at(as.numeric(NA)), "index must not be 'NA'") s = Set$new(a = 10, b = 1) -ee(s$at(1), Set$new(b = 1)) +ee(s$at(1), Set$new(a = 10)) + # --- # at2 @@ -283,19 +284,19 @@ ee(s$replace(1, NULL), Set$new(NULL)) # Replacing a named element preserves the name s = Set$new(a = 1, b = 2) -ee(s$replace(1, 0), Set$new(a = 0, b = 2)) +ee(s$replace(1, 0), Set$new(b = 2, a = 0)) # Replacing by new element works as expected s = Set$new(a = 1, 2, 3) ee(s$replace(1, 4), Set$new(2, 3, a = 4)) s = Set$new(1, "1") -ee(s$replace(1, 0), Set$new(0, "1")) +ee(s$replace(1, 0), Set$new("1", 0)) # Replace works on special elements of basic type s = Set$new(NULL, numeric(0), list()) -ee(s$replace(NULL, 0), Set$new(0, numeric(), list())) -ee(s$replace(numeric(0), 0), Set$new(0, list())) +ee(s$replace(NULL, 0), Set$new(numeric(), list(), 0)) +ee(s$replace(numeric(0), 0), Set$new(list(), 0)) ee(s$replace(list(), 0), Set$new(0)) # Replace works on non-basic objects @@ -303,9 +304,9 @@ S1 = Set$new(1, "1") S2 = Set$new(2, "2") Co = Container$new(NULL) s = Set$new(S1, S2, Co) -ee(s$replace(S1, 1), Set$new(1, S2, Co)) -ee(s$replace(S2, 2), Set$new(1, 2, Co)) -ee(s$replace(Co, 0), Set$new(0, 1, 2)) +ee(s$replace(S1, 1), Set$new(S2, Co, 1)) +ee(s$replace(S2, 2), Set$new(Co, 1, 2)) +ee(s$replace(Co, 0), Set$new(1, 2, 0)) # ------ # rename @@ -345,7 +346,7 @@ ee(s$replace_at(1, NULL), Set$new(NULL)) # Replacing a named element preserves the name s = Set$new(a = 1, b = 2) -ee(s$replace_at(1, 0), Set$new(a = 0, b = 2)) +ee(s$replace_at(1, 0), Set$new(b = 2, a = 0)) # Replacing by new element works as expected s = Set$new(a = 1, 2, 3) @@ -363,7 +364,7 @@ S1 = Set$new(1, "1") S2 = Set$new(2, "2") Co = Container$new(NULL) s = Set$new(co = Co, s1 = S1, s2 = S2) -ee(s$replace_at(1, 1), Set$new(co = 1, s1 = S1, s2 = S2)) +ee(s$replace_at(1, 1), Set$new(s1 = S1, s2 = S2, co = 1)) # ------ @@ -383,11 +384,10 @@ ee(s1$update(s2)$values(), list(A = 1, B = 2, C = 3, D = 4)) ee(Set$new()$update(s2), s2) # a Set can be updated by another Container object with partially unnamed elements -ee(Set$new(a = 0)$update(Container$new(2, a = 1, 1)), - Set$new(a = 1, 2)) +ee(Set$new(a = 0)$update(Container$new(2, a = 1, 1)), Set$new(2, a = 1)) ee(Set$new(a = 0)$update(Container$new(2, a = 1, 1, b = 2, x = 5, a = 3)), - Set$new(a = 3, 2, x = 5)) + Set$new(2, x = 5, a = 3)) # ------ @@ -487,7 +487,7 @@ ee(Set$new()$union(s123), s123) ee(Set$new(1, 2, 3)$union(s0), s123) ee(Set$new(1, 2)$union(s23), s123) -ee(Set$new(2, 3)$union(s12), s123) +ee(Set$new(2, 3)$union(s12), Set$new(2, 3, 1)) ee(Set$new(1, 2)$union(s1_3), s123) @@ -513,3 +513,26 @@ expect_true(s1$is_proper_subset(s12)) expect_false(s0$is_proper_subset(s0)) expect_false(s1$is_proper_subset(s1)) + +# ---------- +# OrderedSet +# ---------- +os = OrderedSet$new +s = os(2, 1) +ee(s$values(), list(1, 2)) + +ee(s$add(1)$values(), list(1, 2)) +ee(s$add(0)$values(), list(0, 1, 2)) + +# Verify sorting +ee(as.list(os(1:2, 1)), list(1, 1:2)) +ee(as.list(os(2:1, 3)), list(3, 2:1)) +ee(as.list(os(list(4), 1:2)), list(list(4), 1:2)) + +ee(as.list(os(list(), container())), list(container(), list())) +ee(as.list(os("b", "a")), list("a", "b")) + +l1 = as.list(1:6) +l2 = as.list(c(1:5, 7)) +ee(as.list(os(b = l1, a = l2)), list(a = l2, b = l1)) + diff --git a/inst/tinytest/test_0-SetS3.R b/inst/tinytest/test_0-SetS3.R index 5372c9ca..9e723ad4 100644 --- a/inst/tinytest/test_0-SetS3.R +++ b/inst/tinytest/test_0-SetS3.R @@ -11,7 +11,7 @@ ee(attr(s, "class"), c("Set", "Container", "Iterable", "R6")) # set elements can be named s <- setnew(a = 2, b = 1, 9) -ee(names(s), c("b", "a", "")) +ee(names(s), c("a", "b", "")) # Set of set is also a copy throughout s1 = setnew(1) @@ -135,3 +135,13 @@ c1$add(2) expect_true(setequal(unpack(cc), c(c1 = 1, 1, 2))) # still the same +# ---------- +# OrderedSet +# ---------- +s = setnew(2, 1, .ordered = TRUE) +expect_true(is.orderedset(s)) + +ee(as.list(s), list(1, 2)) +ee(as.list(as.orderedset(list(2, 1))), list(1, 2)) + +ee(c(s, s), s) diff --git a/inst/tinytest/test_GroupGenericMath.R b/inst/tinytest/test_GroupGenericMath.R index e054ed1d..29b8d7cf 100644 --- a/inst/tinytest/test_GroupGenericMath.R +++ b/inst/tinytest/test_GroupGenericMath.R @@ -55,12 +55,7 @@ ee = expect_equal ee(abs(setnew(-1, 1)), setnew(1, 1)) ee(exp(log(setnew(1, 2))), setnew(1, 2)) ee(cumsum(setnew(1, 2, 3)), setnew(1, 3, 6)) -ee(cumsum(setnew(3, 2, 1)), - setnew(1, 3, 6)) # first sorted then calculated ee(cumsum(setnew(two = 2, one = 1, s = setnew(one = 1, two = 2))), - setnew(one = 1, two = 3, s.one = 4, s.two = 6)) - -ee(cumsum(setnew(two = 2, one = 1, s = setnew(1, one = 1, two = 2))), - setnew(one = 1, two = 3, s1 = 4, s.two = 6)) + setnew(two = 2, one = 3, s.one = 4, s.two = 6)) diff --git a/inst/tinytest/test_Ops-arithmetic.R b/inst/tinytest/test_Ops-arithmetic.R index 9cc3e2a2..da499a7c 100644 --- a/inst/tinytest/test_Ops-arithmetic.R +++ b/inst/tinytest/test_Ops-arithmetic.R @@ -60,7 +60,7 @@ expect_equal(x + setnew(), x) expect_equal(setnew() + x, x) expect_equal(x + list(), x) expect_equal(list() + x, x) -expect_true((x + y) == (y + x)) +expect_false((x + y) == (y + x)) # x - y x <- setnew(1, 2, "1", "2") diff --git a/inst/tinytest/test_Ops-compare.R b/inst/tinytest/test_Ops-compare.R index 22baf109..464aad0a 100644 --- a/inst/tinytest/test_Ops-compare.R +++ b/inst/tinytest/test_Ops-compare.R @@ -78,7 +78,7 @@ expect_true(y >= y) s = setnew(2, 3) x = setnew(1, setnew(2, 3)) y = setnew(1, setnew(3, 2)) -expect_true(x == y) +expect_false(x == y) x = setnew(1, s) y = setnew(1, s) expect_true(x == y) @@ -92,8 +92,6 @@ expect_true(x >= y) expect_false(x < y) expect_false(x > y) -y = setnew(container(2, deque(3)), 4, 1) -expect_true(x == y) y = setnew(1, container(deque(3), 2), 4) expect_false(x == y) # order in container plays a role @@ -103,7 +101,7 @@ expect_true(x < y) y = setnew(1, container(2, deque(3))) expect_false(x == y) -expect_error(expect_true(x > y)) +expect_true(x > y) diff --git a/inst/tinytest/test_Ops-logic.R b/inst/tinytest/test_Ops-logic.R index 883bcbd7..0901f942 100644 --- a/inst/tinytest/test_Ops-logic.R +++ b/inst/tinytest/test_Ops-logic.R @@ -191,9 +191,9 @@ ee(s1 | s1, s1) ee(s1 | s12, s12) ee(s12 | s1, s12) ee(s12 | s23, s123) -ee(s23 | s12, s123) -ee(s2 | s1_3, s123) -ee(s1_3 | s123, s123) +ee(s23 | s12, setnew(2, 3, 1)) +ee(s2 | s1_3, setnew(2, 1, 3)) +ee(s1_3 | s123, setnew(1, 3, 2)) ee(s12 | s123, s123) original_sets_were_not_altered = @@ -212,16 +212,16 @@ s1 = setnew(1) ss1 = setnew(1, s1) ss2 = setnew(2, s1) res = ss1 | ss2 -ee(res, setnew(setnew(1), 1, 2)) +ee(res, setnew(1, setnew(1), 2)) s1$add(5) -has_used_copy_semantics <- res == setnew(setnew(1), 1, 2) +has_used_copy_semantics <- res == setnew(1, setnew(1), 2) expect_true(has_used_copy_semantics) # Named elements s1 = setnew(a = 1, b = 2) s2 = setnew(a = 2, c = 3) ee(s1 | s2, setnew(a = 1, b = 2, c = 3)) -ee(s2 | s1, setnew(a = 1, a = 2, c = 3)) +ee(s2 | s1, setnew(a = 2, c = 3, a = 1)) # sets combined with other objects ee(setnew(1) | list(1, 2), setnew(1, 2)) diff --git a/inst/tinytest/test_all.equal.R b/inst/tinytest/test_all.equal.R index 8885e8be..e176125f 100644 --- a/inst/tinytest/test_all.equal.R +++ b/inst/tinytest/test_all.equal.R @@ -32,16 +32,12 @@ expect_false(isTRUE(all.equal(dict(a = 1), dict(b = 1)))) d1 = dict(a = 1, b = setnew(1, 2), c = container(3, 4)) dd = dict(a = 1, b = setnew(1, 2), c = container(3, 4)) expect_true(all.equal(d1, dd)) -dd = dict(a = 1, b = setnew(2, 1), c = container(3, 4)) -expect_true(all.equal(d1, dd)) -dd = dict(a = 1, b = setnew(2, 1), c = container(3, x = 4)) +dd = dict(a = 1, b = setnew(1, 2), c = container(3, x = 4)) expect_false(isTRUE(all.equal(d1, dd))) d1 = dict(a = 1, c = container(3, y = setnew(deque(1, 2), deque(3, 4)))) dd = dict(a = 1, c = container(3, y = setnew(deque(1, 2), deque(3, 4)))) expect_true(all.equal(d1, dd)) -dd = dict(a = 1, c = container(3, y = setnew(deque(3, 4), deque(1, 2)))) -expect_true(all.equal(d1, dd)) dd = dict(a = 1, c = container(3, y = setnew(deque(1, 2), deque(4, 3)))) expect_false(isTRUE(all.equal(d1, dd))) diff --git a/inst/tinytest/test_format.R b/inst/tinytest/test_format.R index b120473a..cf891125 100644 --- a/inst/tinytest/test_format.R +++ b/inst/tinytest/test_format.R @@ -52,5 +52,5 @@ ee(f(deque(2, 3, 1)), "|2, 3, 1|") # format.Set # ---------- f = container:::format.Set -ee(f(setnew(2, 3, 1)), "{1, 2, 3}") +ee(f(setnew(2, 3, 1)), "{2, 3, 1}") diff --git a/inst/tinytest/test_replace.R b/inst/tinytest/test_replace.R index 214fca78..58201b7f 100644 --- a/inst/tinytest/test_replace.R +++ b/inst/tinytest/test_replace.R @@ -31,16 +31,16 @@ expect_true(was_changed_by_referene) # replace.Set, ref_replace.Set # ---------------------------- x = setnew(1, "z") -ee(replace(x, 1, 0), setnew(0, "z")) -ee(replace(x, "z", 0), setnew(0, 1)) +ee(replace(x, 1, 0), setnew("z", 0)) +ee(replace(x, "z", 0), setnew(1, 0)) expect_error(replace(x, old = 99, 0), "old element \\(99\\) is not in Set") x_was_not_touched = all.equal(x, setnew(1, "z")) expect_true(x_was_not_touched) -ee(ref_replace(x, 1, 0), setnew(0, "z")) -was_changed_by_referene = ee(x, setnew(0, "z")) +ee(ref_replace(x, 1, 0), setnew("z", 0)) +was_changed_by_referene = ee(x, setnew("z", 0)) expect_true(was_changed_by_referene) diff --git a/man/ContainerS3.Rd b/man/ContainerS3.Rd index 78c8b386..c0cbf4e7 100644 --- a/man/ContainerS3.Rd +++ b/man/ContainerS3.Rd @@ -43,8 +43,8 @@ or of class \link{Container} for the \code{S3} methods.} \description{ A container is a data structure with typical member functions to insert, delete and access elements from the container -object. The \link{container} can be seen as a base R \link{list} with -extended functionality. The \link[=container]{Container} class also serves as the base +object. It can be considered as a base R \link{list} with +extended functionality. The \link{Container} class also serves as the base class for \link{Deque}, \link{Set}, and \link{Dict} objects. } \details{ diff --git a/man/OrderedSet.Rd b/man/OrderedSet.Rd new file mode 100644 index 00000000..48b2b4f0 --- /dev/null +++ b/man/OrderedSet.Rd @@ -0,0 +1,138 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/0-SetR6.R +\name{OrderedSet} +\alias{OrderedSet} +\title{Ordered Set Class} +\description{ +The \link{OrderedSet} is as \link{Set} where all elements are always +ordered. +} +\details{ +The order of elements is determined sequentially as follows: +\itemize{ +\item element's length +\item whether it is an \href{is.atomic}{atomic} element +\item the element's class(es) +\item by numeric value (if applicable) +\item it's representation when printed +\item the name of the element in the \link{Set} +} +} +\examples{ +s1 = OrderedSet$new(2, 1) +s1 +} +\seealso{ +\link{Container}, \link{Set} +} +\section{Super classes}{ +\code{\link[container:Iterable]{container::Iterable}} -> \code{\link[container:Container]{container::Container}} -> \code{\link[container:Set]{container::Set}} -> \code{OrderedSet} +} +\section{Methods}{ +\subsection{Public methods}{ +\itemize{ +\item \href{#method-new}{\code{OrderedSet$new()}} +\item \href{#method-add}{\code{OrderedSet$add()}} +\item \href{#method-clone}{\code{OrderedSet$clone()}} +} +} +\if{html}{ +\out{
    Inherited methods} +\itemize{ +\item \out{}\href{../../container/html/Iterable.html#method-iter}{\code{container::Iterable$iter()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-at}{\code{container::Container$at()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-at2}{\code{container::Container$at2()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-clear}{\code{container::Container$clear()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-count}{\code{container::Container$count()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-delete}{\code{container::Container$delete()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-delete_at}{\code{container::Container$delete_at()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-discard}{\code{container::Container$discard()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-discard_at}{\code{container::Container$discard_at()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-empty}{\code{container::Container$empty()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-get_compare_fun}{\code{container::Container$get_compare_fun()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-has}{\code{container::Container$has()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-has_name}{\code{container::Container$has_name()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-is_empty}{\code{container::Container$is_empty()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-length}{\code{container::Container$length()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-names}{\code{container::Container$names()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-peek_at}{\code{container::Container$peek_at()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-peek_at2}{\code{container::Container$peek_at2()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-pop}{\code{container::Container$pop()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-print}{\code{container::Container$print()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-remove}{\code{container::Container$remove()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-rename}{\code{container::Container$rename()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-replace}{\code{container::Container$replace()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-replace_at}{\code{container::Container$replace_at()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-size}{\code{container::Container$size()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-type}{\code{container::Container$type()}}\out{} +\item \out{}\href{../../container/html/Container.html#method-update}{\code{container::Container$update()}}\out{} +\item \out{}\href{../../container/html/Set.html#method-diff}{\code{container::Set$diff()}}\out{} +\item \out{}\href{../../container/html/Set.html#method-intersect}{\code{container::Set$intersect()}}\out{} +\item \out{}\href{../../container/html/Set.html#method-is_equal}{\code{container::Set$is_equal()}}\out{} +\item \out{}\href{../../container/html/Set.html#method-is_proper_subset}{\code{container::Set$is_proper_subset()}}\out{} +\item \out{}\href{../../container/html/Set.html#method-is_subset}{\code{container::Set$is_subset()}}\out{} +\item \out{}\href{../../container/html/Set.html#method-union}{\code{container::Set$union()}}\out{} +\item \out{}\href{../../container/html/Set.html#method-values}{\code{container::Set$values()}}\out{} +} +\out{
    } +} +\if{html}{\out{
    }} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-new}{}}} +\subsection{Method \code{new()}}{ +\code{OrderedSet} constructor +\subsection{Usage}{ +\if{html}{\out{
    }}\preformatted{OrderedSet$new(...)}\if{html}{\out{
    }} +} + +\subsection{Arguments}{ +\if{html}{\out{
    }} +\describe{ +\item{\code{...}}{initial elements put into the \code{OrderedSet}} +} +\if{html}{\out{
    }} +} +\subsection{Returns}{ +returns the \code{OrderedSet} object +} +} +\if{html}{\out{
    }} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-add}{}}} +\subsection{Method \code{add()}}{ +Add element +\subsection{Usage}{ +\if{html}{\out{
    }}\preformatted{OrderedSet$add(value, name = NULL)}\if{html}{\out{
    }} +} + +\subsection{Arguments}{ +\if{html}{\out{
    }} +\describe{ +\item{\code{value}}{value of \code{ANY} type to be added to the \code{OrderedSet}.} + +\item{\code{name}}{\code{character} optional name attribute of the value.} +} +\if{html}{\out{
    }} +} +\subsection{Returns}{ +the \code{OrderedSet} object. +} +} +\if{html}{\out{
    }} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-clone}{}}} +\subsection{Method \code{clone()}}{ +The objects of this class are cloneable with this method. +\subsection{Usage}{ +\if{html}{\out{
    }}\preformatted{OrderedSet$clone(deep = FALSE)}\if{html}{\out{
    }} +} + +\subsection{Arguments}{ +\if{html}{\out{
    }} +\describe{ +\item{\code{deep}}{Whether to make a deep clone.} +} +\if{html}{\out{
    }} +} +} +} diff --git a/man/Set.Rd b/man/Set.Rd index 6d418493..6ea66b2f 100644 --- a/man/Set.Rd +++ b/man/Set.Rd @@ -4,16 +4,11 @@ \alias{Set} \title{Set Class} \description{ -The \code{\link[=Set]{Set()}} is considered and implemented as a specialized -\code{\link[=Container]{Container()}}, that is, elements are always unique in the \code{\link[=Container]{Container()}} and +The \link{Set} is considered and implemented as a specialized +\link{Container}, that is, elements are always unique in the \link{Container} and it provides typical set operations such as \code{union} and \code{intersect}. For the standard S3 interface, see \code{\link[=setnew]{setnew()}}. } -\details{ -Under the hood, elements of a set object are stored in a hash-table -and always sorted by their length and, in case of ties, by their lexicographical -representation. -} \examples{ s1 = Set$new(1, 2) s1 @@ -32,7 +27,7 @@ s1$diff(s1) s1 } \seealso{ -\code{\link[=Container]{Container()}}, \code{\link[=set]{set()}} +\link{Container}, \code{\link[=set]{set()}} } \section{Super classes}{ \code{\link[container:Iterable]{container::Iterable}} -> \code{\link[container:Container]{container::Container}} -> \code{Set} diff --git a/man/add.Rd b/man/add.Rd index ebb50784..da90d08d 100644 --- a/man/add.Rd +++ b/man/add.Rd @@ -36,8 +36,8 @@ ref_add(.x, ...) For \link{Container}, an object of class \link{Container} (or one of the respective derived classes). -For \href{dicttable}{dict.table} an object of class -\href{dicttable}{dict.table}. +For \link{dict.table} an object of class +\link{dict.table}. } \description{ Add elements to container-like objects. @@ -48,7 +48,7 @@ While \link{add} uses copy semantics \link{ref_add} works by reference. If \code{.x} is a \link{Container}, \link{Set} or \link{Deque} object, the elements being added can (but must not) be named. -If \code{.x} is a \link{Dict} or \href{dicttable}{dict.table} object, +If \code{.x} is a \link{Dict} or \link{dict.table} object, all elements \emph{must} be of the form \code{key = value}. If one of the keys already exists, an error is given. } diff --git a/man/clear.Rd b/man/clear.Rd index 09110678..2696c827 100644 --- a/man/clear.Rd +++ b/man/clear.Rd @@ -28,8 +28,8 @@ ref_clear(x) For \link{Container}, an object of class \link{Container} (or one of the respective derived classes). -For \href{dicttable}{dict.table} an object of class -\href{dicttable}{dict.table}. +For \link{dict.table} an object of class +\link{dict.table}. } \description{ Removes all elements from the container object. diff --git a/man/dequeS3.Rd b/man/dequeS3.Rd index 4a361201..804dd25b 100644 --- a/man/dequeS3.Rd +++ b/man/dequeS3.Rd @@ -24,11 +24,11 @@ or of class \code{Deque} for the \code{S3} methods.} \description{ Deques are a generalization of stacks and queues typically with methods to add, remove and access elements at both sides of the -underlying data sequence. As such, the \code{\link[=deque]{deque()}} can also be used to mimic +underlying data sequence. As such, the \link{deque} can also be used to mimic both stacks and queues. } \details{ -Methods that alter \code{Deque} objects usually come in two versions +Methods that alter \link{Deque} objects usually come in two versions providing either copy or reference semantics where the latter start with \code{'ref_'} to note the reference semantic, for example, \code{add()} and \code{ref_add()}. diff --git a/man/dicttable.Rd b/man/dict.table.Rd similarity index 89% rename from man/dicttable.Rd rename to man/dict.table.Rd index 192ee508..3cae3aad 100644 --- a/man/dicttable.Rd +++ b/man/dict.table.Rd @@ -3,8 +3,7 @@ % R/at2.R, R/clear.R, R/clone.R, R/delete_at.R, R/discard_at.R, R/has.R, % R/has_name.R, R/is_empty.R, R/peek_at.R, R/peek_at2.R, R/pop.R, R/rename.R, % R/replace_at.R, R/update.R -\name{dicttable} -\alias{dicttable} +\name{dict.table} \alias{dict.table} \alias{as.dict.table} \alias{as.dict.table.data.table} @@ -26,27 +25,31 @@ is.dict.table(x) \method{cbind}{dict.table}(x, ...) } \arguments{ -\item{...}{elements put into the \href{dicttable}{dict.table} and/or additional +\item{...}{elements put into the \link{dict.table} and/or additional arguments to be passed on.} -\item{x}{any \code{R} object or a \href{dicttable}{dict.table} object.} +\item{x}{any \code{R} object or a \link{dict.table} object.} \item{copy}{if \code{TRUE} creates a copy of the \link{data.table} object otherwise works on the passed object by reference.} } \description{ -The \href{dicttable}{dict.table} is a combination of \link{dict} and -\link{data.table} and basically can be considered a \link{data.table} with extended -functionality to manage its data columns in a stricter way. For example, -in contrast to \link{data.table}, \href{dicttable}{dict.table} does not allow -duplicated column names. -A \href{dicttable}{dict.table} object provides all \link{dict} and \link{data.table} +The \link{dict.table} is a combination of \link{dict} and +\href{https://CRAN.R-project.org/package=data.table}{data.table} +and basically can be considered a +\href{https://CRAN.R-project.org/package=data.table}{data.table} +with unique +column names and an extended set of functions to add, extract and +remove data columns with the goal to further facilitate code development +using \href{https://CRAN.R-project.org/package=data.table}{data.table}. +A \link{dict.table} object provides all \link{dict} and +\href{https://CRAN.R-project.org/package=data.table}{data.table} functions and operators at the same time. } \details{ -Methods that alter \href{dicttable}{dict.table} objects usually come in two versions +Methods that alter \link{dict.table} objects usually come in two versions providing either copy or reference semantics where the latter start with -\code{'ref_'} to note the reference semantic, for example, \link{add} and \link{ref_add}. +\code{'ref_'} to note the reference semantic, for example, \code{\link[=add]{add()}} and \code{\link[=ref_add]{ref_add()}}. \itemize{ \item \code{dict.table(...)} initializes and returns a \link{dict} object. @@ -310,5 +313,5 @@ update(dit1, dit2) update(dit2, dit1) } \seealso{ -\link{dict}, \link{data.table} +\link{dict}, \href{https://CRAN.R-project.org/package=data.table}{data.table} } diff --git a/man/dictS3.Rd b/man/dictS3.Rd index e620ee19..81e90a7d 100644 --- a/man/dictS3.Rd +++ b/man/dictS3.Rd @@ -22,10 +22,14 @@ is.dict(x) or of class \code{Dict} for the \code{S3} methods.} } \description{ -The \code{\link[=dict]{dict()}} resembles Python's dict type, and is implemented -as a specialized associative \code{\link[=Container]{Container()}} thus sharing all \link[=Container]{container()} -methods with some of them being overridden to account for the associative -key-value pair semantic. +The \link{Dict} initially was developed to resemble Python's +dict type, but by now offers both more features and flexibility, for +example, by providing both associative key-value pair as well as +positional array semantics. +It is implemented as a specialized associative \link{Container} thus sharing +all \link{Container} methods with some of them being adapted to account for +the key-value pair semantic. +All Dict elements must be named and are always sorted by their name. } \details{ Internally, all key-value pairs are stored in a hash-table and the @@ -149,5 +153,5 @@ update(d2, d1) # {a = 1, b = 2, c = 3} } \seealso{ See \code{\link[=container]{container()}} for all inherited methods. For the full class -documentation see \code{\link[=Dict]{Dict()}} and it's superclass \link[=container]{Container()}. +documentation see \link{Dict} and it's superclass \link{Container}. } diff --git a/man/setS3.Rd b/man/setS3.Rd index e6f37b93..4668b2e2 100644 --- a/man/setS3.Rd +++ b/man/setS3.Rd @@ -5,35 +5,39 @@ \alias{SetS3} \alias{setnew} \alias{as.set} +\alias{as.orderedset} \alias{is.set} -\title{Set} +\alias{is.orderedset} +\title{Set and ordered Set} \usage{ -setnew(...) +setnew(..., .ordered = FALSE) as.set(x) +as.orderedset(x) + is.set(x) + +is.orderedset(x) } \arguments{ \item{...}{initial elements put into the \code{Set}.} +\item{.ordered}{\code{logical} if \code{TRUE} all elements in the \link{Set} will be +ordered.} + \item{x}{\code{R} object of \code{ANY} type for \code{\link[=as.set]{as.set()}} and \code{\link[=is.set]{is.set()}} or of class \code{Set} for the \code{S3} methods.} } \description{ -The \code{\link[=Set]{Set()}} is considered and implemented as a specialized -\code{\link[=Container]{Container()}}, that is, \code{Set} elements are always unique. It provides +The \link{Set} is considered and implemented as a specialized +\link{Container}, that is, \code{Set} elements are always unique. It provides typical set operations such as \code{union} and \code{intersect}. } \details{ -Under the hood, elements of a set object are stored in a hash-table -and sorted by their length and, in case of ties, by their lexicographical -representation. -For a description of basic methods such as adding and removing elements, -see the help of \code{\link[=container]{container()}}. -Methods that alter \code{Set} objects usually come in two versions +Methods that alter \link{Set} objects usually come in two versions providing either copy or reference semantics where the latter start with -\code{'ref_'} to note the reference semantic, for example, \code{add()} and \code{ref_add()}. +\code{'ref_'} to note the reference semantic, for example, \code{\link[=add]{add()}} and \code{\link[=ref_add]{ref_add()}}. \itemize{ \item \code{setnew(...)} initializes and returns a \code{\link[=Set]{Set()}} object. @@ -43,11 +47,20 @@ providing either copy or reference semantics where the latter start with \item \code{as.set(x)} coerces \code{x} to a set. } +\itemize{ +\item \code{as.orderedset(x)} coerces \code{x} to an ordered set. +} + \itemize{ \item \code{is.set(x)} returns \code{TRUE} if \code{x} is of class \code{Set} and \code{FALSE} otherwise. } +\itemize{ +\item \code{is.orderedset(x)} returns \code{TRUE} if \code{x} is of class \code{OrderedSet} +and \code{FALSE} otherwise. +} + \itemize{ \item \code{x} \code{&} \code{y} performs the set intersection of x and y } @@ -65,6 +78,9 @@ names(s) as.list(s) unpack(s) # flatten recursively similar to unlist +so = setnew(2, 1, .ordered = TRUE) +print(so) +add(so, 0) # Math s = setnew(5:3, 1, 2) s @@ -95,5 +111,5 @@ s1 | s2 # {1, b = 2, b = 4} } \seealso{ See \code{\link[=container]{container()}} for all inherited methods. For the full class -documentation see \code{\link[=Set]{Set()}} and it's superclass \link[=container]{Container()}. +documentation see \link{Set} and it's superclass \link{Container}. } diff --git a/vignettes/class-diagram.png b/vignettes/class-diagram.png deleted file mode 100644 index ce50b76b30c29fe4049f8e47813c72c65a10d3c5..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 6238 zcmcIpc{r5syPsr9qUeXRL{gGa$rjRH_OhnQzJ+;B2r`_R`icFybk&bhAh=ee$PoqyiBpZ9&<>$&gG{dqpmeZTYQy5UvcogzCi7!0q@ zwM)hr%(iCKPTIkSUP*qG7z}3LVVz6oP46c$lij^VYhM2xE&0paB--~r_M82<=#+aV ziCrMBT6lRc4*4|@i|MY;lbHb*JY-(H3!xv=lf57*=rvSP`TX*64ibk-s1|v(k-{7u zPf2;=ame-b#QybQ<;%5sPD#@#{hD+7i|sT{3?`({VPSPQ`WuP?9GDQb5M&!hlFt^4 z!93hf7s6l$|BtuBg+THOC0K{XZSb#v+L$Sb7sD!{QGS?>_IR`TITLv4-A4!qh4J*V^Z4WpjQKi*F__ z{f_R9_rTW;MV4cWT#CFK$89E#k3P*%7w`4143=7IVr!QDBe7N%Gb7FlJ!#Zvf6YDQ zZw0u5fmI*}nb094!uWp;xqiD7id^iWMQkYl1V;)ucQj+Vea9FH?>wl#LJ&JFU1ecc z1QO}OXeFyW#n6R7Bw}JD473(Aoh-Y*+gx&h%fIL0$MVHzMT6D>-p;wA(5;p)1c^4d z`MQzS2oS6obW0HJ0jCv$n4*VG5K-(VC$1#$ejLMrzz;YU#(II*3xlMge4;Ob^()~w z9h}i}w1iXGGCGUZkmJNFVKsdM@K)!`Qka8e%T|driMsl}*_g(`tlrzAAbXf{%UlVH zh{7L%Gsew;>@4IM9eCb>)^j5QInSF6NkdHrdkG7X#JL80A1BXXb7E1Ab?hk13H!9X zq3QOI!MNqc!YT!EPRBXb;gF$kwFkX3>KvvuBi#tiPwXg~jJ2MIR$X^U(^_mp;9$n{ z%&^3Wx(=aqCmY4tL>sZaU;TO}h^?~a*#Tz`TkKI#Be&Z`r}9>VHG7JI@U?pHXKPW( zp2a=^=Z}RG?%s>NI9+RRgcIGQ>Y2dIdTZ9Nn$Dj#t-lg@Px*A`G6mD)uXt^+j*qJ} zh?N-tE6s^rE1#_%ASUO20UH;KiWz9FTiP^4B)O|t+ zfgwNaH;UCllk+X;EbM_W%|9cHf5%t8_dMYcK`c+sI?K3L$Y*~gEhn!rKLX?)ZG6YC zhBOW6#b-Bv6X_$FmDH3i=ck*zM=lS`HEovPn0cDaT@Bv3e~X?rox3>Ie+%9!^5>5s z>Pkp#n$p3g;L4QPZ~9F$j2Sn$vza9gm|avo9#|LHH0D{hK{fwZF0*&i(0y~l)zM$e z{SMau?HR?_PYCXL?C?m6AySeP{iTEu{Rx{spqe0Iwlr<_ktf(#rf3H~q0jDOkO^7m zE`kk84RT)5D3f9Ay+4>=$oM`#(hycBV>))6+8F-N9l>1W8uYrayk>scS)jvJ5s?eH znzY$}_sM~bj#}w&1Be#n>!w5?m!i#Sl_Zeu6X`7!#U2y#GQHks@4)05nP)hH z0qe$>yDr%$+A2U5-vQ|Lb@|m&=~cj7rRp7pe0V;UUvyU=nE^U!MpT4Oy2vY0#D*i^ zJ5!LYR2B46Y3~u|1aUZhbR{*`^F>L1M#}DMozut0TON6Z1!q7rS8S8?@W_lsI^)o( zW_iI8>4IbmA^=qYviv5F$&FxbaFb^bi&oRk8OS2R9=rbXb3R?jsMh#G6kyzDX4OP# zXTAl$lq#J4GW4q&DPwh-zHSS(htI?MKt8CsRb$-=|fRFmIynv-`s-Zp|Kg_WtE1#%`Hk zznPBQHTwxhBO9L|d3zmuO4i?#S#vAz`W(WTSKLfuU+B#%Lm1oj%h;{sx-Lj54ObV* z_PEzJaJkpUYV?DlLdR)0{sxNp zE?exO5G1aIvc zRsin2?2j`Se`nAz@|6lNP{BRY3NQs6ICpkpxr{;GHW)U{21T~nW2=GW!hb39|Jv9S zjeOd-FTQfVo0OUNkD+?$=$H6LEMAzKMBmv*AA-Jr9o8gdlw7!bIQ!aCyVhg~=X z+xI%I+f@&eb~}Fh_^l3-e)yZ5q6>wLg&@z~5MUckt#t06x-`W|-~6izd2XApKOkOe zpc4wmxcPs#;)kSuhHCTOh}D=N-75su7DM$Mc}&bUD01E#285ZrOuqa+N_G@@oK^?o zKQ)%}zpayQ;Z%1>S4+Kn%SB+RQE9Ned(F(x@Pb_g<>CWm+rwRS+KzX%u*t*ErvZFG z1~oyvKbAH*ey&dlaJ=b4p=_Zd{totuI(PO#UC3#VMV-CB<*Yjlsx0c^d8u==w;7u( z;WrD+J-(>m>qR{d;d#zIMc>?08Hi23vahdPv*df83RFEQvkeoDzFH9yU-Al_gGUKa zfr0k&mXl{sF~=-SLYlUo?tl|#xM^PmCZtbKq@5vsO+gl47!phI#1%C@l>#5M7IN0(I($vK?SU*BfW zm4;}{&+2*3^W%8VaG=@sMzH$^ocR2*mfzww9wY+6l=!P+#Eu6@Iq(U6(ohor5y(Ho z=O@^~m)lXKqbHy*0w;Z)e<|oGCpB8)UpC}tlRmqG4}xv9$;+)B-Ws30E^p`_g68QI zOCcON2zBFOH88!`YST}1fkj=Wm9Ib5KSvbdeyg9(7BPsPfA~LEV$Z1-^7ZUt#@iK7 zDE$JV_i3l0F=OYggW|uWZ?_{&i#vnAG|te7FUV0y`z|zKemco~+C$L`S6}F{Xi*A2 zERRNe>F&sAcqE_V;rA^FSBaG!;%Cb%5&v(<7^EN>?S@lFan3x@*lgNJW zrF-&ETnLbt1mcogXqA=8cdZw<9F03?FRpc1iQ9DgNfp-S$oVeJA@Qfd$CbDTl@*V9 zdk}c=ckOb{LJ(u-!vcO+$^KYRyY{K$v559NzYdNm-191kw}X}2fO6P1w-AE{l?L=c zYz_bN?IwL(q&F8)32t-?<&BdE^Z@1rSgpE?~`U~1ne3I}DoE4FxF;12~ezkN%)sf{Pp9v~$~)Xz(8@;V7P zHq`2;HjtZJSzWeqay`8l3>5x7<6vJ1=o}=5}W+=FE0nMVrv%uL#OM)&c5!vX*k`#e$gI3nD z_lDo)F?;#km*lbW8_-_S%FB1}p0CN7rxX2{C#l8b$3B@0>Z|Ly*B+-9SLS# zf;wxVv98?#R1-MR?RCi()~Mze*jlgy2}3nGzgl40(qmObCa2L!*7c`sIjGqonOv_L zZRV;$SJ8C#aeeQLr6f5&%aYWwbjN~*;58FeMn<;Og-FC6i#-vb?=0}`0R6H!G@tL| zHI(jqrR~`F7pe`Wvd#b6P-O9{#QpB>B`N(xa z)G=Aqv3n9QK)3Bg+RyJjXb=OXh@C|XFg*|&%WWvK4V`mwYb*W$hFj;gdpq#4$66PW z8&iGScAy}MqX{|x-XAKuJb-o5OS7QpLSqv9muffv328}Guei1}&65aQhnUqs!`q{# zGpnHB?VqWlEa#9~@dA%;N);z$wuP`zV!Xj;iL&{_757@lcx(fOMsd z@b-U?Izg8|R=B9*?fGPOcRy|)0nCnVDD|&&>YU>}feF~MQ4!-Y-u*uf*&M{Rs?I>7 z&UqtkCuF<68>N&09xiLqs$HZ2Lw2Wj1;BKmfrQ>zKp=&==<7_TqT4o=@tJxU#a!eT z9n7ru780u4-D29Q$dfc$_0cYhcwhN(oJPq-`Q7A|fX;kUgRE0Yjdk%VWp#Y)Y9t^<&Um-O~;(8GhFat4hV7F%ogGBry3&Yp>5F9C0Fgw%Vj#M{=+}6VfdS zdsEZf0I#o_;%al)3vyEbC+&^!)g%JfX8sjy@?w^ONb6#KbYhn#iq&hVqEE!;Wt(h& zIvFaSkjS3tqc?zrpW%LIb0_qBXkB~%V+X@z_Gw9lb)Vz{JwZ29A{I+a^E6j=OfQe~ z5xAqCm=brQysJ*^OBD!5u+8_aGje|#i$^Wx*@c?kq-ws><{oJd`OP~~gADY@p57gn z$<5dCXAkdlBbU1XM=I!6dFxNTW)G)gc)lRSLJuQfTWtCpX1AEk-r2 zw(Iu;Ae#rxd@H0qLVl+^Cf9)5{VEpMBV997=)R36+jpUTBX!qD1k0*=Lud6-3F3T7 zHy_eKN-5KVb(gLmrijmC1>c*1&JRrOUgtHzjbw0qNI&eLKYW{D^EfS9zzJGYbPn0V z;(K@CptYyyvRe!`^P69LgFOX3@anHBXyr0}qne_OqPd;m$2o)uh^7l2#ajDMfovt2 zx7I|gYGQ?Qh5oBJ$t0<0wUwhuh@8oWBOkJHCH-8?NW|1JWq`Qalc{2%$dGHC5W)dh z#%Z8FO4ZVw0vLP0$pGr;!QVifz6@?19qIOcLNozINjMolh!cWsNT^^a;@}>4rJz8b z@V%ZTr7CHZ-F*XxgM)M-LM0Mq9X% zS3GY>@{^wZ0X}%TysCe8V#JSN7{P~#dXo$8WC?-ar}HJr(>$ynEc+}v$wh$^(KFfS zAC+GD80qwRq;jX#MB@W;8Jj^TNz~jni7u5d%zdK@7H;x0zqYCzlqPml(*zZ{=R zyQ1b*DGF!ZANUeh65DK6+)j_~vND?1dl;!`d#K2BTr8g5+g>AaY2~@DiVI)&-r3&> zYt2qj#3;#|bD}ZLa@4QKNeNj!xV}DdV@aoO-oUCY7imqW*#*?-C97{Tw73s#~1i|^BD$+(uEDy}s10c7>> zJ~;FW$ZOyK)509VT8>&5IpMHgT7<4{g_Q?Al$X={#Ne%@rCVpKjXzX(A zmtA1>PjDW38G6lMDoJGD4@rUHG+w+F%#12d%|*^GW;zp{JYvILJm#w2@4`RJ&sGHM zwQ-#+I%%%^R9s61;I9TN(O3IavO&DGI=((Py98n#jcQ{PDcOZg&y74iXzgcTqRsgJ z_Byai*?HwzQCKKIVkw=u^4e0OoAmZQ19Jd@=IE zm0&O;Jyx2H6OmGS*_p3aKa*usRYEED7PwZ39(GN*l9T)9khG@=Ps!4egr|}Tafvwi zth$N9+obbCDWUUG&Wq_~unp!J-7yT)#>-iZwOo{RpEs=lD{M5hkr;oCH^T|nfe{9> zmqNmYC&Su`N0HNAu_&JIzRq%ArApGCNbmE&KDq(W25@>5a*j$rB;5|cT0Q%y5S7EU z@;m(eDf7;_gF6&al{xqbC?{USP3})N9i+wSsEs#;+j)7Xh&M4Z>TGUMP0qgZae34~ zAjMsqgXj}q9)&EP&xfsw;t`A>bKox42<>LX3p+-X$s+o@H|Z})lZwUThmde(A3jt4$)%IuG%u6m(Gi=+5Q-jWykmt%DPzAXIEfYt`5^#Y$zhp%vX zad9Q&M%%&>qT`g^RE}^k{hW9s_Ry5V3*x5BrG?!pacGp)<}Y=A9Vi;3Fh30mE zaal8(wvaSWj7WE;?-rqZckL*q$Xo2ezoe|+GArVBEbA?03LZ1BPh=lPwvF-sXU~W{ zSq8$r^V4IVHhm;v@={xwNdhB@-ETz+VSl8~jhWvn6W`@9-!xM=D(-I84Yi;atH*gx zDg-HEw3U^YdJQHh1V6F_ojw9#jF;$V-!oi*NiywG;a9G}Toc-kU=Qlnl0r#rN-ufA)&`nqMY=9-SWE%wE2&Mr`R7VXEP zHf|&zU(yqYw9RWf_CTqBuONCBbmq8*>qHjkA|+d0*)^?jcdSvL`J=XUJymXObNbZp zKjek80s{Z-Q^^gbO363ZR9&u - %\VignetteIndexEntry{Overview} - %\VignetteEngine{knitr::rmarkdown} - %\VignetteEncoding{UTF-8} ---- - -```{r knitr-setup, include = FALSE} -knitr::opts_chunk$set( - collapse = TRUE, - comment = "#>" -) -``` - -## Introduction - -This package aims at providing common container data structures with typical member functions to insert, delete and access container elements. Specifically, it comes with the types [deque](https://en.wikipedia.org/wiki/Double-ended_queue), [set](https://en.wikipedia.org/wiki/Set_(abstract_data_type)), and `dict`, an [associative container](https://en.wikipedia.org/wiki/Associative_containers) resembling Python's [dict](https://docs.python.org/3/tutorial/datastructures.html#dictionaries) type. In addition, a specialized data structure called `dict.frame` is provided, which is a `dict` containing elements with identical length. The `dict.frame` can be considered a generalized and more powerful version of the base `data.frame`. - -The backbone of this package are classes implemented using the [R6](https://CRAN.R-project.org/package=R6) framework. The focus for developing this package was to provide a concise data structure and specifically making use of inheritance and the reference semantics provided by the [R6](https://CRAN.R-project.org/package=R6) package. The basic class hierarchy is outlined in the class diagram below. - -
    -```{r out.width = '80%', echo = FALSE, fig.cap="Basic class hierarchy of the container package."} -knitr::include_graphics("class-diagram.png") -``` - -
    - -## R6 classes and member methods - -The [Container](Container.html) class as the central element serves as the base class for [Deque](Deque.html), [Set](Set.html), and [Dict](Dict.html), which inherit all methods from [Container](Container.html), with some of them being overwritten (see below). In addition, the [Container](Container.html) class inherits from the abstract *Iterable* class and therefore provides a method to create an [Iterator](Iterator.html), which can be used to iterate through the elements of any container object. - -The following table shows member methods divided by class. The top half contains all [Container](Container.html) methods, each derived by a subclass to the right unless there is a new entry in a subclass column, meaning that the method is redefined in the subclass. The bottom half contains methods unique to each subclass. Note that `Dict.frame` (right-most column) inherits all methods from both [Container](Container.html) and [Dict](Dict.html). - -```{=html} - -``` -| Container | Deque | Set | Dict | -| :--------------------------| :-------------| :--------------------| :----------------------------| -| Container\$new() | Deque\$new() | s <- Set\$new() | Dict\$new() | -| | | | | -| add(elem) | | | add(key, value) | -| clear() | | | | -| count(elem) | | | | -| delete(elem) | | | delete(key) | -| discard(elem) | | | discard(key) | -| has(elem) | | | has(key) | -| is_empty() | | | | -| replace(old, new, add = F) | | | replace(key, value, add = F) | -| values() | | | | -| | | | | -| | addleft(elem) | diff(s) | get(key) | -| | peek() | intersect(s) | peek(key, default = NULL) | -| | peekleft() | is_equal(s) | pop(key) | -| | pop() | is_subset(s) | rename(old, new) | -| | popleft() | is_proper_subset(s) | update(other) | -| | rev() | union(s) | | -| | rotate(n) | | | - - -Table: Overview of classes and member methods - -
    - -For more details visit the respective online helps (see `?Container`, `?Deque`, `?Set`, `?Dict`. Usage examples are found in the corresponding [Container](Container.html), [Deque](Deque.html), [Set](Set.html), and [Dict](Dict.html) vignettes. - - -## S3 classes and methods - -On top of the above classes and methods, a complete [S3](http://adv-r.had.co.nz/S3.html) interface is available, which might be more familiar to most typical R users. More importantly, it allows to provide operators, for example, to access elements in the dict.frame via `[[`. In the table below, standard `set` operators are already listed for the `set` class. - -| container | deque | set | dict | -| :----------------------------| :-------------------| :----------------| :------------------------------| -| co = container() | d = deque() | s = setnew() | d = dict() | -| | | | | -| add(co, elem) | | | add(d, key, val) | -| clear(co) | | | | -| delete(co, elem, right=F) | | | delete(d, key) | -| discard(co, elem, right=F) | | | discard(d, key) | -| has(co, elem) | | | has(d, key) | -| is_empty(co) | | | | -| values(co) | | | | -| | | | | -| | addleft(d, elem) | s1 - s2 | getval(d, key) | -| | count(d, elem) | s1 / s2 | keys(d) | -| | peek(d) | s1 == s2 | peek(d, key, default=NULL) | -| | peekleft(d) | s1 < s2 | pop(d, key) | -| | pop(d) | s1 > s2 | | -| | popleft(d) | s1 + s2 | rename(d, old, new) | -| | reverse(d) | | setval(d, key, val, add=FALSE)| -| | rotate(d, n=1L) | | sortkey(decr=FALSE) | - -Table: Overview of S3 classes and methods - -
    -For more details and to see the provided operators for each class again refer to the corresponding [Container](Container.html), [Deque](Deque.html), [Set](Set.html), [Dict](Dict.html), and [Dict.frame](Dict.frame) vignettes.