Skip to content

Commit

Permalink
Optimized functions
Browse files Browse the repository at this point in the history
  • Loading branch information
Jakob Russel committed Mar 13, 2017
1 parent 5fe0d6a commit 60c0be2
Show file tree
Hide file tree
Showing 10 changed files with 37 additions and 66 deletions.
42 changes: 21 additions & 21 deletions R/co_agg.R
Original file line number Diff line number Diff line change
Expand Up @@ -94,47 +94,51 @@ co_agg.default <- function(imgs,channels,size,npixel,dstep=1,pwidth,zstep,freec=
ch2_t[ch2_t > 0] <- 1} else stop("Kernel smooth has to be odd integers in all directions")
}

# Sum channels
sumch <- ch1_t+ch2_t

# Densities of channels
d1 <- length(which(ch1_t == 1))/length(ch1_t)
d2 <- length(which(ch2_t == 1))/length(ch2_t)
d12 <- length(which(sumch > 0))/length(sumch)

# Addresses in array (pixels)
side <- dim(ch1_t)[1]
address_array <- array(1:(side*side*dim(ch1_t)[3]),
c(side, side, dim(ch1_t)[3]))

# Coordinates of pixels in channel1 (pixels)
ch1_add <- data.frame(which(ch1_t == 1, T))
ch1_add <- data.frame(which(ch1_t > 0, T))
colnames(ch1_add) <- c("x", "y", "z")

# Coordinates of pixels in channel2 (pixels)
ch2_add <- data.frame(which(ch2_t == 1, T))
ch2_add <- data.frame(which(ch2_t > 0, T))
colnames(ch2_add) <- c("x", "y", "z")

# Coordinates of all pixels (pixels)
ch_add <- data.frame(which(ch1_t == 1 | ch1_t == 0, T))
colnames(ch_add) <- c("x", "y", "z")
# Coordinates of pixels in either channel (pixels)
ch_sum <- data.frame(which(sumch > 0, T))
colnames(ch_sum) <- c("x", "y", "z")

# Randomly sample pixels (pixels)
these <- sample(1:dim(ch_add)[1], size = npixel)
these <- sample(1:dim(ch_sum)[1], size = npixel)

# Get their addresses
ch_pix <- ch_add[these,]
ch_pix <- ch_sum[these,]

# Matrix to collect results
hits <- matrix(NA, length(ds), npixel)
totals <- matrix(NA, length(ds), npixel)

# Loop through pixels
for(j in 1:npixel){

# Focal pixel position
p <- ch_pix[j,]
# Does the focal pixel have a colour?

# What colour is the focal pixel
test1 <- ch1_add[ch1_add$x == p$x & ch1_add$y == p$y & ch1_add$z == p$z,]
test2 <- ch2_add[ch2_add$x == p$x & ch2_add$y == p$y & ch2_add$z == p$z,]

# Coordinates of the box (pixels)
xrange <- c(p$x-(size/pwidth), p$x+(size/pwidth))
yrange <- c(p$y-(size/pwidth), p$y+(size/pwidth))
Expand Down Expand Up @@ -181,14 +185,10 @@ co_agg.default <- function(imgs,channels,size,npixel,dstep=1,pwidth,zstep,freec=
}

# Hits
if((nrow(test1)+nrow(test2))==0) {hits[,j] <- 0} else {

for(l in 1:(length(ds))){
if(nrow(test1)>0 & nrow(test2)==0) hits[l,j] <- length(which(id2[positions[[l]]]==1))
if(nrow(test2)>0 & nrow(test1)==0) hits[l,j] <- length(which(id1[positions[[l]]]==1))
if(nrow(test1)>0 & nrow(test2)>0) hits[l,j] <- length(which(id1[positions[[l]]]==1))+length(which(id2[positions[[l]]]==1))
}

for(l in 1:(length(ds))){
if(nrow(test1)==1 && nrow(test2)==0) hits[l,j] <- length(which(id2[positions[[l]]]==1))
if(nrow(test2)==1 && nrow(test1)==0) hits[l,j] <- length(which(id1[positions[[l]]]==1))
if(nrow(test1)==1 && nrow(test2)==1) hits[l,j] <- length(which(id1[positions[[l]]]==1))+length(which(id2[positions[[l]]]==1))
}

}
Expand All @@ -199,8 +199,8 @@ co_agg.default <- function(imgs,channels,size,npixel,dstep=1,pwidth,zstep,freec=

# Calculate probability and co-aggregation
Prop <- hits.sum/totals.sum
CA <- Prop/(2*d1*d2)
CA <- Prop/(2*(d1*d2/d12))

theseCC <- cbind(gsub(channels[1],"",sub(".*/", "", ch1_files[i])),ds, CA)
theseCC <- as.data.frame(theseCC)
colnames(theseCC) <- c("Img", "Distance", "CA")
Expand Down
42 changes: 10 additions & 32 deletions R/cross_ratio.R
Original file line number Diff line number Diff line change
Expand Up @@ -99,37 +99,25 @@ cross_ratio.default <- function(imgs,focal.channel,target.channels,size,npixel,d
ch.f <- medianFilter(ch.f,kern.s)
ch.f[ch.f > 0] <- 1} else stop("Kernel smooth has to be odd integers in all directions")
}

# Densities of channels
d1 <- length(which(ch.t1 == 1))/length(ch.t1)
d2 <- length(which(ch.t2 == 1))/length(ch.t2)

# Addresses in array (pixels)
side <- dim(ch.t1)[1]
address_array <- array(1:(side*side*dim(ch.t1)[3]),
c(side, side, dim(ch.t1)[3]))

# Coordinates of pixels in channel1 (pixels)
ch1_add <- data.frame(which(ch.t1 == 1, T))
colnames(ch1_add) <- c("x", "y", "z")

# Coordinates of pixels in channel2 (pixels)
ch2_add <- data.frame(which(ch.t2 == 1, T))
colnames(ch2_add) <- c("x", "y", "z")

# Coordinates of pixels in focal channel (pixels)
chf_add <- data.frame(which(ch.f == 1, T))
colnames(chf_add) <- c("x", "y", "z")

# Coordinates of all pixels (pixels)
ch_add <- data.frame(which(ch.t1 == 1 | ch.t1 == 0, T))
colnames(ch_add) <- c("x", "y", "z")


# Randomly sample pixels (pixels)
these <- sample(1:dim(ch_add)[1], size = npixel)
these <- sample(1:dim(chf_add)[1], size = npixel)

# Get their addresses
ch_pix <- ch_add[these,]
ch_pix <- chf_add[these,]

# Matrix to collect results
hits1 <- matrix(NA, length(ds), npixel)
Expand All @@ -141,11 +129,6 @@ cross_ratio.default <- function(imgs,focal.channel,target.channels,size,npixel,d
# Focal pixel position
p <- ch_pix[j,]

# Does the focal pixel have a colour?
test1 <- ch1_add[ch1_add$x == p$x & ch1_add$y == p$y & ch1_add$z == p$z,]
test2 <- ch2_add[ch2_add$x == p$x & ch2_add$y == p$y & ch2_add$z == p$z,]
testf <- chf_add[chf_add$x == p$x & chf_add$y == p$y & chf_add$z == p$z,]

# Coordinates of the box (pixels)
xrange <- c(p$x-(size/pwidth), p$x+(size/pwidth))
yrange <- c(p$y-(size/pwidth), p$y+(size/pwidth))
Expand Down Expand Up @@ -187,16 +170,11 @@ cross_ratio.default <- function(imgs,focal.channel,target.channels,size,npixel,d
}

# Count hits
if(nrow(testf)==0) {
for(l in 1:(length(ds))){
hits1[l,j] <- length(which(id1[positions[[l]]]==1))
hits2[l,j] <- length(which(id2[positions[[l]]]==1))
}
} else {
hits1[,j] <- 0
hits2[,j] <- 0
for(l in 1:(length(ds))){
hits1[l,j] <- length(which(id1[positions[[l]]]==1))
hits2[l,j] <- length(which(id2[positions[[l]]]==1))

}

}

# Sum hits for all pixels
Expand All @@ -206,7 +184,7 @@ cross_ratio.default <- function(imgs,focal.channel,target.channels,size,npixel,d
# Calculate ratio and cross-ratio
Ratio <- hits1.sum/hits2.sum
CR <- Ratio/(d1/d2)

theseCR <- cbind(gsub(target.channels[1],"",sub(".*/", "", ch.t1_files[i])),ds, CR)
theseCR <- as.data.frame(theseCR)
colnames(theseCR) <- c("Img","Distance", "CR")
Expand Down
6 changes: 1 addition & 5 deletions R/occupancy.R
Original file line number Diff line number Diff line change
Expand Up @@ -103,14 +103,10 @@ occupancy.default <- function(imgs,focal.channel,target.channel,size,npixel,dste
address_array <- array(1:(side*side*dim(ch.f)[3]),
c(side, side, dim(ch.f)[3]))

# Coordinates of pixels in channel1 (pixels)
# Coordinates of pixels in focal channel (pixels)
chf_add <- data.frame(which(ch.f == 1, T))
colnames(chf_add) <- c("x", "y", "z")

# Coordinates of pixels in channel2 (pixels)
cht_add <- data.frame(which(ch.t == 1, T))
colnames(cht_add) <- c("x", "y", "z")

# Randomly sample pixels (pixels)
these <- sample(1:dim(chf_add)[1], size = npixel)

Expand Down
13 changes: 5 additions & 8 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -172,10 +172,9 @@ of both zstep and pwidth
## [1] 0.0 1.5 3.0 4.5 6.0 7.5 9.0 10.5 12.0 13.5 15.0 16.5 18.0 19.5
## [15] 21.0 22.5 24.0 25.5 27.0 28.5 30.0

Ok. lets try 21 microns then. As an example we pick 200 random pixels
(should be higher for actual analysis), and we run the whole thing 5
times to see how picking random pixels affect the variability of the
result
Ok. lets try 21 microns then. As an example we pick 200 random pixels,
and we run the whole thing 5 times to see how picking random pixels
affect the variability of the result

mycc <- co_agg(imgs=myimg,channels=c("xan","ste"),size=21,npixel=200,dstep=1,pwidth=0.75,zstep=0.25,R=5)

Expand Down Expand Up @@ -210,9 +209,7 @@ expected from random chance

We can also quantify how much space a channel (target) occupy at certain
distances from another channel (focal). This is similar to
co-aggregation, although this is directed. With set number of random
pixels, `occupancy` is more precise than the `co_agg`, especially in
images with low fill.
co-aggregation, although this is directed.

Lets run it until 21 microns. As an example we pick 200 random pixels,
and we run the whole thing 5 times to see how picking random pixels
Expand Down Expand Up @@ -291,7 +288,7 @@ expected given random chance. A cross-ratio above 1 at some distance
means that target channel 1 is more likely to be found than target
channel 2 at that distance.

mycr <- cross_ratio(imgs=myimg,focal.channel="pan",target.channels=c("xan","ste"),size=21,npixel=200,dstep=1,pwidth=0.75,zstep=0.25,R=5)
mycr <- cross_ratio(imgs=myimg,focal.channel="mic",target.channels=c("xan","pan"),size=21,npixel=200,dstep=1,pwidth=0.75,zstep=0.25,R=5)

##
|
Expand Down
Binary file modified README_files/figure-markdown_strict/unnamed-chunk-10-1.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file not shown.
Binary file modified README_files/figure-markdown_strict/unnamed-chunk-12-1.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file not shown.
Binary file modified README_files/figure-markdown_strict/unnamed-chunk-16-1.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file not shown.

0 comments on commit 60c0be2

Please sign in to comment.