Skip to content

Commit

Permalink
deprecating here
Browse files Browse the repository at this point in the history
  • Loading branch information
Melkiades committed Nov 13, 2023
1 parent 7162cb1 commit 03acf7d
Show file tree
Hide file tree
Showing 7 changed files with 61 additions and 25 deletions.
4 changes: 4 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ export("cell_footnotes<-")
export("clayout<-")
export("col_counts<-")
export("col_fnotes_here<-")
export("col_footnotes<-")
export("col_info<-")
export("col_total<-")
export("colcount_format<-")
Expand Down Expand Up @@ -64,6 +65,7 @@ export(clear_indent_mods)
export(col_counts)
export(col_exprs)
export(col_fnotes_here)
export(col_footnotes)
export(col_info)
export(col_paths)
export(col_paths_summary)
Expand Down Expand Up @@ -198,6 +200,7 @@ exportMethods("cell_footnotes<-")
exportMethods("clayout<-")
exportMethods("col_counts<-")
exportMethods("col_fnotes_here<-")
exportMethods("col_footnotes<-")
exportMethods("col_info<-")
exportMethods("col_total<-")
exportMethods("colcount_format<-")
Expand Down Expand Up @@ -228,6 +231,7 @@ exportMethods(clayout)
exportMethods(clear_indent_mods)
exportMethods(col_counts)
exportMethods(col_fnotes_here)
exportMethods(col_footnotes)
exportMethods(col_info)
exportMethods(col_total)
exportMethods(colcount_format)
Expand Down
10 changes: 5 additions & 5 deletions R/index_footnotes.R
Original file line number Diff line number Diff line change
Expand Up @@ -63,8 +63,8 @@ index_col_refs <- function(tt, cur_idx_fun) {


.index_col_refs_inner <- function(ctree, cur_idx_fun) {
col_fnotes_here(ctree) <- .reindex_one_pos(
col_fnotes_here(ctree),
col_footnotes(ctree) <- .reindex_one_pos(
col_footnotes(ctree),
cur_idx_fun
)

Expand All @@ -75,9 +75,9 @@ index_col_refs <- function(tt, cur_idx_fun) {
)
}
ctree
## cfs <- col_fnotes_here(ctree)
## cfs <- col_footnotes(ctree)
## if(length(unlist(cfs)) > 0) {
## col_fnotes_here(ctree) <- .reindex_one_pos(lapply(cfs,
## col_footnotes(ctree) <- .reindex_one_pos(lapply(cfs,
## function(refs) lapply(refs, function(refi) {
}

Expand All @@ -95,7 +95,7 @@ index_col_refs <- function(tt, cur_idx_fun) {
#' manually.
#' @export
update_ref_indexing <- function(tt) {
col_fnotes <- c(list(row_fnotes = list()), col_fnotes_here(tt))
col_fnotes <- c(list(row_fnotes = list()), col_footnotes(tt))
row_fnotes <- row_footnotes(tt)
cell_fnotes <- cell_footnotes(tt)
all_fns <- rbind(col_fnotes, cbind(row_fnotes, cell_fnotes))
Expand Down
34 changes: 27 additions & 7 deletions R/tree_accessors.R
Original file line number Diff line number Diff line change
Expand Up @@ -2877,45 +2877,65 @@ setMethod("cell_footnotes<-", "ContentRow",
definition = .cfn_set_helper
)

# Deprecated methods
#' @export
#' @rdname ref_fnotes
setGeneric("col_fnotes_here", function(obj) standardGeneric("col_fnotes_here"))
#' @export
#' @rdname ref_fnotes
setMethod("col_fnotes_here", "ANY", function(obj) {
warning("col_fnotes_here is deprecated since {rtables} version 0.6.5.9011. Please use col_footnotes instead.")
col_footnotes(obj)
})
#' @export
#' @rdname ref_fnotes
setGeneric("col_fnotes_here<-", function(obj, value) standardGeneric("col_fnotes_here<-"))
#' @export
#' @rdname int_methods
setMethod("col_fnotes_here", c("LayoutColTree"), function(obj) obj@col_footnotes)
setMethod("col_fnotes_here<-", "ANY", function(obj, value) {
warning("col_fnotes_here<- is deprecated since {rtables} version 0.6.5.9011. Please use col_footnotes<- instead.")
col_footnotes(obj) <- value
})

#' @export
#' @rdname ref_fnotes
setGeneric("col_footnotes", function(obj) standardGeneric("col_footnotes"))
#' @export
#' @rdname int_methods
setMethod("col_fnotes_here", c("LayoutColLeaf"), function(obj) obj@col_footnotes)
setMethod("col_footnotes", "LayoutColTree", function(obj) obj@col_footnotes)
#' @export
#' @rdname int_methods
setMethod("col_footnotes", "LayoutColLeaf", function(obj) obj@col_footnotes)

#' @export
#' @rdname ref_fnotes
setGeneric("col_fnotes_here<-", function(obj, value) standardGeneric("col_fnotes_here<-"))
setGeneric("col_footnotes<-", function(obj, value) standardGeneric("col_footnotes<-"))
#' @export
#' @rdname int_methods
setMethod("col_fnotes_here<-", "LayoutColTree", function(obj, value) {
setMethod("col_footnotes<-", "LayoutColTree", function(obj, value) {
obj@col_footnotes <- make_ref_value(value)
obj
})

#' @export
#' @rdname int_methods
setMethod("col_fnotes_here<-", "LayoutColLeaf", function(obj, value) {
setMethod("col_footnotes<-", "LayoutColLeaf", function(obj, value) {
obj@col_footnotes <- make_ref_value(value)
obj
})

#' @export
#' @rdname int_methods
setMethod(
"col_fnotes_here", "VTableTree",
"col_footnotes", "VTableTree",
function(obj) {
ctree <- coltree(obj)
cols <- tree_children(ctree)
while (all(sapply(cols, is, "LayoutColTree"))) {
cols <- lapply(cols, tree_children)
cols <- unlist(cols, recursive = FALSE)
}
all_col_fnotes <- lapply(cols, col_fnotes_here)
all_col_fnotes <- lapply(cols, col_footnotes)
if (is.null(unlist(all_col_fnotes))) return(NULL)

return(all_col_fnotes)
Expand Down
4 changes: 2 additions & 2 deletions R/tt_paginate.R
Original file line number Diff line number Diff line change
Expand Up @@ -444,7 +444,7 @@ setMethod(
sibpos = sibpos,
nsibs = nsibs,
leaf_indices = colnum,
col_fnotes = col_fnotes_here(ct)
col_fnotes = col_footnotes(ct)
))
}
)
Expand Down Expand Up @@ -484,7 +484,7 @@ setMethod(
sibpos = sibpos,
nsibs = nsibs,
pth = thispth,
col_fnotes = col_fnotes_here(ct)
col_fnotes = col_footnotes(ct)
))
ret <- c(thisone, ret)
}
Expand Down
2 changes: 1 addition & 1 deletion R/tt_pos_and_access.R
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,7 @@ coltree_split <- function(ctree) ctree@split

col_fnotes_at_path <- function(ctree, path, fnotes) {
if (length(path) == 0) {
col_fnotes_here(ctree) <- fnotes
col_footnotes(ctree) <- fnotes
return(ctree)
}

Expand Down
23 changes: 13 additions & 10 deletions man/int_methods.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

9 changes: 9 additions & 0 deletions man/ref_fnotes.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit 03acf7d

Please sign in to comment.