Skip to content

Commit

Permalink
New version 0.1.8: include a third protein color for a protein in the…
Browse files Browse the repository at this point in the history
… cytosol and finde the outline of the cell
  • Loading branch information
buddekai committed Jan 11, 2021
1 parent f95eadb commit a86f0ff
Show file tree
Hide file tree
Showing 5 changed files with 137 additions and 10 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Package: cellPixels
Type: Package
Title: Detect neclei and count pixels within and outside these
Version: 0.1.7
Version: 0.1.8
Author: c(person("Kai", "Budde", email = "kai.budde@uni-rostock.de",
role = c("aut", "cre"))
Maintainer: Kai Budde <kai.budde@uni-rostock.de>
Expand Down
131 changes: 125 additions & 6 deletions R/cellPixels.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@
#' @param nucleus_color A character (color (layer) of nuclei)
#' @param protein_in_nuc_color A character (color (layer) of protein
#' expected in nucleus)
#' @param protein_in_cytosol_color A character (color (layer) of protein
#' expected in cytosol)
#' @param number_size_factor A number (factor to resize numbers for
#' numbering nuclei)
#' @param bit_depth A number (bit depth of the original czi image)
Expand All @@ -20,6 +22,7 @@
cellPixels <- function(input_dir = NULL,
nucleus_color = "blue",
protein_in_nuc_color = "none",
protein_in_cytosol_color = "none",
number_size_factor = 0.2,
bit_depth = NULL,
number_of_pixels_at_border_to_disregard = 3) {
Expand Down Expand Up @@ -86,8 +89,10 @@ cellPixels <- function(input_dir = NULL,
"dimension_x" = rep(NA, number_of_czis),
"dimension_y" = rep(NA, number_of_czis),
"number_of_nuclei" = rep(NA, number_of_czis),
"color_of_second_proteins_in_nuclei" = rep(NA, number_of_czis),
"color_of_second_protein_in_nuclei" = rep(NA, number_of_czis),
"number_of_nuclei_with_second_protein" = rep(NA, number_of_czis),
"color_of_third_protein_in_cytosol" = rep(NA, number_of_czis),
"number_of_cells_with_third_protein" = rep(NA, number_of_czis),
"intensity_sum_red_full" = rep(NA, number_of_czis),
"intensity_sum_green_full" = rep(NA, number_of_czis),
"intensity_sum_blue_full" = rep(NA, number_of_czis),
Expand Down Expand Up @@ -362,7 +367,7 @@ cellPixels <- function(input_dir = NULL,
# barplot(table(nmask)[-1])

table_nmask <- table(nmask)
nuc_min_size <- 0.05*stats::median(table_nmask[-1])
nuc_min_size <- 0.1*stats::median(table_nmask[-1])

# remove objects that are smaller than min_nuc_size
to_be_removed <- as.integer(names(which(table_nmask < nuc_min_size)))
Expand Down Expand Up @@ -472,8 +477,14 @@ cellPixels <- function(input_dir = NULL,
Image_protein_in_nuc <- EBImage::gblur(Image_protein_in_nuc, sigma = 7)
#display(Image_protein_in_nuc)


# Mask the proteins within the nucleus
pmask <- EBImage::thresh(Image_protein_in_nuc, w=15, h=15, offset=0.07)
if(grepl(pattern = "_20x_", file_names[i])){
# Smaller moving rectangle if the magnification is 20x (instead of 40x)
pmask <- EBImage::thresh(Image_protein_in_nuc, w=15, h=15, offset=0.07)
}else{
pmask <- EBImage::thresh(Image_protein_in_nuc, w=35, h=35, offset=0.07)
}

# Morphological opening to remove objects smaller than the structuring element
pmask <- EBImage::opening(pmask, EBImage::makeBrush(5, shape='disc'))
Expand Down Expand Up @@ -510,6 +521,95 @@ cellPixels <- function(input_dir = NULL,

}

# Count the number of cells that contain a third colored protein ------

if(!is.null(protein_in_cytosol_color) & protein_in_cytosol_color != "none"){


# Save only color layer of the second protein colored
image_protein_in_cytosol <- getLayer(
image = image_loaded, layer = protein_in_cytosol_color)

Image_protein_in_cytosol <- EBImage::Image(image_protein_in_cytosol)
rm(image_protein_in_cytosol)
#display(Image_protein_in_cytosol)

# Blur the image
Image_protein_in_cytosol <- EBImage::gblur(Image_protein_in_cytosol, sigma = 5)
#display(Image_protein_in_nuc)

# Mask the proteins within the cytosol
if(grepl(pattern = "_20x_", file_names[i])){
# Smaller moving rectangle if the magnification is 20x (instead of 40x)
cytosolmask <- EBImage::thresh(Image_protein_in_cytosol, w=100, h=100, offset=0.01)
}else{
cytosolmask <- EBImage::thresh(Image_protein_in_cytosol, w=200, h=200, offset=0.01)
}

#display(cytosolmask)

# Morphological opening to remove objects smaller than the structuring element
cytosolmask <- EBImage::opening(cytosolmask, EBImage::makeBrush(5, shape='disc'))
# Fill holes
cytosolmask <- EBImage::fillHull(cytosolmask)
#display(cytosolmask)

# Keep only those cell bodies that contain a nucleus
cytosolmask <- EBImage::bwlabel(cytosolmask)
no_of_cytosols <- max(cytosolmask)

# Go through every stained cytosol and check for nucleus
for(j in 1:no_of_cytosols){
collocation_found <- max((cytosolmask==j)*nmask)
if(collocation_found == 0){
cytosolmask[cytosolmask==j] <- 0
}
rm(j)
}

cytosolmask <- EBImage::bwlabel(cytosolmask)
no_of_cytosols <- max(cytosolmask)

# Combine nmask and cytosolmask and count the resulting cell bodies
# (nuclei that are within the stained proteins in the cytosol)
n_c_mask <- nmask_watershed*(!cytosolmask==0)
#display(n_c_mask)

table_n_c_mask <- table(n_c_mask)

# Count number of cells containing staining for protein
cell_with_proteins_No <- length(names(table_n_c_mask))-1
#display(n_c_mask)


# remove objects that are smaller than min_nuc_size
to_be_removed <- as.integer(names(which(table_n_c_mask < nuc_min_size)))
if(length(to_be_removed) > 0){
for(j in 1:length(to_be_removed)){
EBImage::imageData(n_c_mask)[
EBImage::imageData(n_c_mask) == to_be_removed[j]] <- 0
}
rm(j)
}

# Add border of cytosols with proteins and save file
Image_cytosol_numbers_proteins <- Image_nuclei_numbers
EBImage::colorMode(Image_cytosol_numbers_proteins) <- "color"

Image_cytosol_numbers_proteins <- EBImage::paintObjects(
x = cytosolmask,
tgt = Image_cytosol_numbers_proteins,
opac = c(1),
col=c('#FFFF00'))

#display(Image_cytosol_numbers_proteins)

# Display the number of cells with proteins
print(paste("Number of cells that contain other colored proteins: ",
cell_with_proteins_No, sep=""))

}



# -------------------------------------------------------------------- #
Expand All @@ -522,10 +622,15 @@ cellPixels <- function(input_dir = NULL,
df_results[i,"dimension_y"] <- dim(image_loaded)[1]
df_results[i,"number_of_nuclei"] <- nucNo
if(!is.null(protein_in_nuc_color) & protein_in_nuc_color != "none"){
df_results[i,"color_of_second_proteins_in_nuclei"] <- protein_in_nuc_color
df_results[i,"color_of_second_protein_in_nuclei"] <- protein_in_nuc_color
df_results[i,"number_of_nuclei_with_second_protein"] <- nuc_with_proteins_No
}

if(!is.null(protein_in_cytosol_color) & protein_in_cytosol_color != "none"){
"color_of_third_protein_in_cytosol" <- protein_in_cytosol_color
"number_of_cells_with_third_protein" <- cell_with_proteins_No
}

df_results[i,"intensity_sum_red_full"] <- sum(image_loaded[,,1])
df_results[i,"intensity_sum_green_full"] <- sum(image_loaded[,,2])
df_results[i,"intensity_sum_blue_full"] <- sum(image_loaded[,,3])
Expand Down Expand Up @@ -598,7 +703,19 @@ cellPixels <- function(input_dir = NULL,
tiff::writeTIFF(what = Image_nuclei_numbers_proteins,
where = paste(output_dir,
image_name_wo_czi,
"_nuclei_numbers_proteins.tif",
"_nuclei_numbers_proteins1_nuc.tif",
sep = ""),
bits.per.sample = 8L, compression = "none",
reduce = TRUE)
}

# Images with marked nuclei and borders around the third protein in
# cell bodies (proteins in cytosol)
if(!is.null(protein_in_cytosol_color) & protein_in_cytosol_color != "none"){
tiff::writeTIFF(what = Image_cytosol_numbers_proteins,
where = paste(output_dir,
image_name_wo_czi,
"_nuclei_numbers_proteins2_cell.tif",
sep = ""),
bits.per.sample = 8L, compression = "none",
reduce = TRUE)
Expand Down Expand Up @@ -629,7 +746,9 @@ cellPixels <- function(input_dir = NULL,
"nucleus_color","number_of_czis",
"number_of_pixels_at_border_to_disregard",
"number_size_factor", "output_dir",
"protein_in_nuc_color", ".old.options")
"protein_in_cytosol_color",
"protein_in_nuc_color",
".old.options")

remove_variables <- list_of_variables[
!(list_of_variables %in% keep_variables)]
Expand Down
1 change: 1 addition & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ The package need at least R 4.0.0.
It uses the R packages "reticulate" to load and use python packages (this will install miniconda when first used),
"EBImage" for finding nuclei and contrast enhancement as well as "tiff" for saving the results in the tif format.
We are using the python package "czifile" to directly work with the microscopy image format czi.
Important: Because this pacakge makes use of a python package which is being installed on-the-fly, you need internet connection.


## Code for using the R package
Expand Down
9 changes: 6 additions & 3 deletions inst/testscriptDevelop.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@
# Test Package: 'Ctrl + Shift + T'


# TODO: Im Namen sollte ersichtlich sein, welche Farbe gesucht und markiert wurde.

# Delete everything in the environment
rm(list = ls())
# close all open plots in RStudio
Expand All @@ -16,7 +18,7 @@ graphics.off()
# >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>

# Directory of the images
input_dir <- "test3/"
input_dir <- "test4/"

# <<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<

Expand All @@ -38,7 +40,7 @@ require(devtools)
require(reticulate)

# Check package
check()
#check()

# Document package
document()
Expand All @@ -50,7 +52,8 @@ load_all()

df_results <- cellPixels(input_dir = input_dir,
nucleus_color = "blue",
protein_in_nuc_color = "none",
protein_in_nuc_color = "red",
protein_in_cytosol_color = "green",
number_size_factor = 0.2)

save(df_results, file=paste(input_dir, "output/df_results.Rda", sep=""))
4 changes: 4 additions & 0 deletions man/cellPixels.Rd

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

0 comments on commit a86f0ff

Please sign in to comment.