Skip to content

Commit

Permalink
deprecate array w/ warning for narray pkg
Browse files Browse the repository at this point in the history
  • Loading branch information
mschubert committed Feb 14, 2018
1 parent a23c075 commit 0fca5b6
Show file tree
Hide file tree
Showing 6 changed files with 10 additions and 16 deletions.
2 changes: 1 addition & 1 deletion array/__init__.r
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,4 @@
for (n in ls(.pkg))
assign(n, .pkg[[n]])

#warning("'array' module is deprecated. Use 'narray' package instead.")
warning("'array' module is deprecated. Use 'narray' package instead.")
3 changes: 1 addition & 2 deletions data_frame/assemble.r
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
import('../base/operators')
.ar = import('../array')

#' Creates a data.frame from named vectors
#'
Expand All @@ -13,7 +12,7 @@ assemble = function(...) {

myclasses = sapply(l., class)

re = as.data.frame(.ar$stack(l., along=2), stringsAsFactors=FALSE)
re = as.data.frame(narray::stack(l., along=2), stringsAsFactors=FALSE)
for (i in seq_along(re)) {
cc = myclasses[names(re)[i]]
if (cc == "factor")
Expand Down
3 changes: 1 addition & 2 deletions plot/matrix.r
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
.b = import('../base')
.ar = import('../array')

#' Cluster the rows and columns, order factor levels to respect that
#'
Expand All @@ -10,7 +9,7 @@
#' @param size A size c(rows,cols) to limit the result clustering to
#' @param fill Fill array if data.frame does not have all values
cluster = function(df, formula, cols=TRUE, rows=TRUE, size=NULL, fill=NA) {
mat = .ar$construct(data=df, formula=formula, fun.aggregate=mean)
mat = narray::construct(data=df, formula=formula, fun.aggregate=mean)
indep_vars = all.vars(formula[[3]])
rname = indep_vars[1] #FIXME: ar$construct should order by std. axis ordering
cname = indep_vars[2] # order: 1,2 && remove t()
Expand Down
5 changes: 2 additions & 3 deletions process/idmap/gene.r
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
library(dplyr)
.b = import('../../base')
.io = import('../../io')
.ar = import('../../array')
.guess_id_type = import('./guess_id_type')$guess_id_type
.gene_table = import('../../seq/gene_table')$gene_table

Expand Down Expand Up @@ -31,7 +30,7 @@ gene.character = function(obj, to, from=.guess_id_type(obj),
.b$match(obj, from=df$from, to=df$to)
}

gene.default = function(obj, to, from=.guess_id_type(.ar$dimnames(obj, along=1)),
gene.default = function(obj, to, from=.guess_id_type(narray::dimnames(obj, along=1)),
dset="hsapiens_gene_ensembl", summarize=mean) {
if (to %in% c("hgnc_symbol", "mgi_symbol"))
to = "external_gene_name"
Expand All @@ -48,7 +47,7 @@ gene.default = function(obj, to, from=.guess_id_type(.ar$dimnames(obj, along=1))
names(obj) = sub("\\.[0-9]+$", "", dimnames(obj)[[1]])
}

.ar$summarize(obj, along=1, from=df$from, to=df$to, FUN=summarize)
narray::translate(obj, along=1, from=df$from, to=df$to, FUN=summarize)
}

gene.ExpressionSet = function(obj, to, from=.guess_id_type(rownames(exprs(obj))),
Expand Down
7 changes: 3 additions & 4 deletions process/idmap/probeset.r
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
library(dplyr)
.b = import('../../base')
.ar = import('../../array')
.guess_id_type = import('./guess_id_type')$guess_id_type
.probeset_table = import('../../seq/probeset_table')$probeset_table

Expand All @@ -26,21 +25,21 @@ probeset.numeric = function(obj, to, from=.guess_id_type(names(obj)), summarize=
lookup = probeset_table()[[from]]
df = na.omit(data.frame(from=lookup$probe_id, to=lookup[[to]]))
df = df[!duplicated(df),]
.ar$summarize(obj, along=1, from=df$from, to=df$to, FUN=summarize)
narray::translate(obj, along=1, from=df$from, to=df$to, FUN=summarize)
}

probeset.matrix = function(obj, to, from=.guess_id_type(rownames(obj)), summarize=mean) {
lookup = probeset_table()[[from]]
df = na.omit(data.frame(from=lookup$probe_id, to=lookup[[to]]))
df = df[!duplicated(df),]
.ar$summarize(obj, along=1, from=df$from, to=df$to, FUN=summarize)
narray::translate(obj, along=1, from=df$from, to=df$to, FUN=summarize)
}

probeset.ExpressionSet = function(obj, to, from=.guess_id_type(rownames(exprs(obj))), summarize=mean) {
lookup = probeset_table()[[from]]
df = na.omit(data.frame(from=lookup$probe_id, to=lookup[[to]]))
df = df[!duplicated(df),]
exprs(obj) = .ar$summarize(exprs(obj), along=1, from=df$from, to=df$to, FUN=summarize)
exprs(obj) = narray::translate(exprs(obj), along=1, from=df$from, to=df$to, FUN=summarize)
obj
}

Expand Down
6 changes: 2 additions & 4 deletions stats/batch.r
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
.ar = import('../array')

merge = function(method, X, batch, covariate=NULL) {
if (method == "combat")
combat(X, batch, covariate)
Expand Down Expand Up @@ -32,14 +30,14 @@ none = function(X, batch=NA) {

.list2mat = function(ll) {
if (is.list(ll))
.ar$stack(ll, along=2)
narray::stack(ll, along=2)
else
ll
}

.mat2list = function(X, subsets) {
if (is.matrix(X))
.ar$split(X, along=2, subsets=subsets)
narray::split(X, along=2, subsets=subsets)
else
X
}

0 comments on commit 0fca5b6

Please sign in to comment.