Skip to content

Commit

Permalink
Update docs and add OrderedSet class (#3)
Browse files Browse the repository at this point in the history
* 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
  • Loading branch information
rpahl authored Oct 23, 2021
1 parent dd2009c commit 7059c5c
Show file tree
Hide file tree
Showing 115 changed files with 3,101 additions and 923 deletions.
5 changes: 5 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ S3method("[",Container)
S3method("[<-",Container)
S3method("[[",Container)
S3method("[[<-",Container)
S3method("names<-",Container)
S3method("|",Dict)
S3method("|",Set)
S3method(Math,Container)
Expand All @@ -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)
Expand Down Expand Up @@ -128,6 +130,7 @@ export(Container)
export(Deque)
export(Dict)
export(Iterator)
export(OrderedSet)
export(Set)
export(add)
export(addleft)
Expand All @@ -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)
Expand Down Expand Up @@ -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)
Expand Down
8 changes: 7 additions & 1 deletion R/0-ContainerS3.R
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -113,5 +113,11 @@ str.Container <- function(object, ...)
}


#' @export
"names<-.Container" <- function(x, value)
{
x$rename(names(x), value)
}

# TODO: implement generic %in%

4 changes: 2 additions & 2 deletions R/0-DequeS3.R
Original file line number Diff line number Diff line change
Expand Up @@ -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()]
Expand All @@ -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
Expand Down
14 changes: 9 additions & 5 deletions R/0-DictS3.R
Original file line number Diff line number Diff line change
@@ -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.
Expand Down
92 changes: 82 additions & 10 deletions R/0-SetR6.R
Original file line number Diff line number Diff line change
@@ -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)
Expand Down Expand Up @@ -58,7 +55,6 @@ Set <- R6::R6Class("Set",

hash_value = private$.get_hash_value(value)
private$elems[[hash_value]] = elem
private$.reorder_values()

self
},
Expand Down Expand Up @@ -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
)


61 changes: 49 additions & 12 deletions R/0-SetS3.R
Original file line number Diff line number Diff line change
@@ -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)
Expand All @@ -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.
Expand All @@ -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)
Expand All @@ -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)
}
}

Loading

0 comments on commit 7059c5c

Please sign in to comment.