Skip to content

Commit

Permalink
Support character vectors for i and j indexing
Browse files Browse the repository at this point in the history
Closes #34.
  • Loading branch information
agrueneberg committed Feb 6, 2017
1 parent f1114fd commit 09fa9d5
Showing 1 changed file with 28 additions and 6 deletions.
34 changes: 28 additions & 6 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -173,6 +173,17 @@ chunkedApply <- function(X, MARGIN, FUN, i = seq_len(nrow(X)), j = seq_len(ncol(
if (!length(dim(X))) {
stop("dim(X) must have a positive length")
}
# Convert index types
if (is.logical(i)) {
i <- which(i)
} else if (is.character(i)) {
i <- match(i, rownames(X))
}
if (is.logical(j)) {
j <- which(j)
} else if (is.character(j)) {
j <- match(j, colnames(X))
}
d <- c(length(i), length(j))
if (is.null(bufferSize) && is.null(nBuffers)) {
bufferSize <- d[MARGIN]
Expand Down Expand Up @@ -370,13 +381,16 @@ getGi <- function(x, scales = NULL, centers = NULL, scaleCol = TRUE, centerCol =
nX <- nrow(x)
pX <- ncol(x)

# Convert boolean to integer index (it leads to a more efficient subsetting
# than booleans)
# Convert index types
if (is.logical(i)) {
i <- which(i)
} else if (is.character(i)) {
i <- match(i, rownames(x))
}
if (is.logical(j)) {
j <- which(j)
} else if (is.character(j)) {
j <- match(j, colnames(x))
}

n <- length(i)
Expand Down Expand Up @@ -472,16 +486,21 @@ getGij <- function(x, i1, i2, scales, centers, scaleCol = TRUE, centerCol = TRUE
nX <- nrow(x)
pX <- ncol(x)

# Convert boolean to integer index (it leads to a more efficient subsetting
# than booleans)
# Convert index types
if (is.logical(i1)) {
i1 <- which(i1)
} else if (is.character(i1)) {
i1 <- match(i1, rownames(x))
}
if (is.logical(i2)) {
i2 <- which(i2)
} else if (is.character(i2)) {
i2 <- match(i2, rownames(x))
}
if (is.logical(j)) {
j <- which(j)
} else if (is.character(j)) {
j <- match(j, colnames(x))
}

n1 <- length(i1)
Expand Down Expand Up @@ -605,13 +624,16 @@ getG.symDMatrix <- function(X, nBlocks = 5, blockSize = NULL, centers = NULL, sc
nX <- nrow(X)
pX <- ncol(X)

# Convert boolean to integer index (it leads to a more efficient subsetting
# than booleans)
# Convert index types
if (is.logical(i)) {
i <- which(i)
} else if (is.character(i)) {
i <- match(i, rownames(X))
}
if (is.logical(j)) {
j <- which(j)
} else if (is.character(j)) {
j <- match(j, colnames(X))
}

n <- length(i)
Expand Down

0 comments on commit 09fa9d5

Please sign in to comment.