Skip to content
Snippets Groups Projects

Correction

Closed Ilyess Rachedi requested to merge Correction into master
Files
9
+ 299
28
library(SingleCellExperiment)
.checkDbscanObject <- function(obj, val){
clustering <- getClustering(obj)
if (ncol(clustering) == val | (class(obj) == "Dbscan")){
return(TRUE)
} else {
return(FALSE)
}
}
checkDbscanList <- function(liste){
val <- ncol(getClustering(liste[[1]]))
vec <- sapply(liste, .checkDbscanObject, val)
if (all(vec)) {
return(TRUE)
} else {
liste[!vec]
names <- sapply(liste ,getName)
names <- paste(names , collapse = "; ")
msg <- paste("The following clusterings in 'dbscanList' slot don't ",
"have the same number of cells or the Dbscan class : ",
sep="")
stop(msg, names)
}
}
.checkTsneObject <- function(obj, val){
coordinates <- getCoordinates(obj)
if (nrow(coordinates) == val | (class(obj) == "Tsne")){
return(TRUE)
} else {
return(FALSE)
}
}
checkTsneList <- function(liste){
val <- nrow(getCoordinates(liste[[1]]))
vec <- sapply(liste, .checkTsneObject, val)
if (all(vec)) {
return(TRUE)
} else {
liste[!vec]
names <- sapply(liste ,getName)
names <- paste(names , collapse = "; ")
msg <- paste("The following coordinates in 'TsneList' slot don't ",
"have the same number of cells or the Tsne class : ",
sep="")
stop(msg, names)
}
}
################################################################################
############################## scRNAseq class ##################################
################################################################################
scRNAseq <- setClass(
# Set the name for the class
"scRNAseq",
# Define the slots
slots = c(
experimentName = "character",
countMatrix = "matrix",
normalizedCountMatrix = "SingleCellExperiment",
colData = "data.frame",
species = "character",
outputDirectory = "character",
tSNEList = "list",
dbscanList = "list",
cellsSimilarityMatrix = "matrix",
clustersSimilarityMatrix = "matrix",
clusters = "SingleCellExperiment"
clustersSimiliratyOrdered = "factor"
),
prototype=list(
normalizedCountMatrix = SingleCellExperiment(),
tSNEList = list(new("Tsne")),
dbscanList = list(new("Dbscan"))
),
validity = function(object){
errors <- character()
# Make a function that can test to see if the data is consistent.
# This is not called if you have an initialize function defined!
validity = function(object)
{
if(ncol(countMatrix) < 100) {
return("Not enough cells in the count matrix")
## Test experimentName slot
experimentName = getExperimentName(object)
if (length(experimentName) == 0){
msg <- paste("\n'experimentName' slot is empty. ",
"Please fill it.\n",
sep = "")
errors <- c(errors, msg)
} else if (!is.character(experimentName) |
(grepl(" ", experimentName))){
msg <- paste("Experiment name should contain a single string ",
"describing the experiment, '",
experimentName,
"' is not correct.\n",
sep = "")
errors <- c(errors, msg)
}
# Vérifiez les types des slots
return(TRUE)
}
)
## Test countMatrix slot
countMatrix = getCountMatrix(object)
if(all(is.na(countMatrix))) {
msg <- paste("'countMatrix' slot is empty. ",
"Should be a matrix containing at leat 100 cells.\n",
sep = "")
errors <- c(errors, msg)
} else if(ncol(countMatrix) < 100) {
msg <- paste("Not enough cells in the count matrix. ",
"Should be at leat 100 cells. ",
"The current count matrix contains ",
ncol(countMatrix), " cells.\n",
sep = "")
errors <- c(errors, msg)
}
## Test normalizedCountMatrix slot
normalizedCountMatrix=getNormalizedCountMatrix(object)
if (!class(normalizedCountMatrix) == "SingleCellExperiment"){
msg <- paste("Normalized count matrix should be ",
"SingleCellExperiment, ",
"not '",
class(normalizedCountMatrix),
"'.\n",
sep = "")
errors <- c(errors, msg)
}
## Test species slot
species=getSpecies(object)
if (length(species) == 0){
msg <- paste("'species' slot is empty. ",
"It should be 'mmu' or 'human'.\n",
sep = "")
errors <- c(errors, msg)
} else if (!is.element(species, c("mmu","human"))){
msg <- paste("species should be 'mmu' or 'human'. '",
species, "' is not available.\n",
sep = "")
errors <- c(errors, msg)
}
## Test outputDirectory slot
outputDirectory=getOutputDirectory(object)
if (length(outputDirectory) == 0){
msg <- paste("'outputDirectory' slot is empty. ",
"Please fill it.\n",
sep = "")
errors <- c(errors, msg)
} else if (!is.character(outputDirectory) |
(grepl(" ", outputDirectory))){
msg <- paste("'outputDirectory' should be conform folder path, '",
species, "' is not correct.\n",
sep = "")
errors <- c(errors, msg)
}
## Test tSNEList slot
tSNEList=getTSNEList(object)
checkTsneList(tSNEList)
## Test dbscan slot
dbscanList=getDbscanList(object)
checkDbscanList(dbscanList)
## Test cellsSimilarityMatrix slot
cellsSimilarityMatrix=getCellsSimilarityMatrix(object)
if(!is.matrix(cellsSimilarityMatrix)) {
msg <- paste("'cellsSimilarityMatrix' slot should contain ",
"a matrix. ",
class(cellsSimilarityMatrix), "' is not correct.\n",
sep = "")
errors <- c(errors, msg)
}
## Test clustersSimilarityMatrix slot
clustersSimilarityMatrix=getClustersSimilarityMatrix(object)
if(!is.matrix(clustersSimilarityMatrix)) {
msg <- paste("'clustersSimilarityMatrix' slot should contain ",
"a matrix. ",
class(clustersSimilarityMatrix), "' is not correct.\n",
sep = "")
errors <- c(errors, msg)
}
## Test clustersSimiliratyOrdered slot
clustersSimiliratyOrdered=getClustersSimiliratyOrdered(object)
if(!is.factor(clustersSimiliratyOrdered)) {
msg <- paste("'clustersSimiliratyOrdered' slot should contain ",
"a factor with label of cluster ordered. ",
class(clustersSimiliratyOrdered),
"' is not correct.\n",
sep = "")
errors <- c(errors, msg)
}
## Validity return errors messages if they exist
if (length(errors) == 0) {
return(TRUE)
} else {
return(stop(errors))
}
})
################################################################################
############################### Tsne class ####################################
################################################################################
Tsne <- setClass(
# Set the name for the class
"Tsne",
# Define the slots
slots = c(
name = "character",
pc = "numeric",
perplexity = "numeric",
coordinates = "list"
)
coordinates = "matrix"
),
validity = function(object){
errors <- character()
## Test slot Name
name = getName(object)
if (!is.character(name)){
msg <- paste("Name of Tsne object'" , name , "' is incorrect. ",
"It should be a string.\n",
sep = "")
errors <- c(errors, msg)
}
## Test slot pc
pc = getPC(object)
if (!is.numeric(pc)){
msg <- paste("PC '" , pc , "' is incorrect. ",
"It should be a numeric.\n",
sep = "")
errors <- c(errors, msg)
}
## Test slot perplexity
perplexity = getPerplexity(object)
if (!is.numeric(perplexity)){
msg <- paste("Perplexity '" , perplexity , "' is incorrect. ",
"It should be a numeric.\n",
sep = "")
errors <- c(errors, msg)
}
## Test slot coordinates
coordinates = getCoordinates(object)
if (!is.matrix(coordinates)){
msg <- paste("Coordinates should be matrix",
sep = "")
errors <- c(errors, msg)
}
}
)
################################################################################
############################### Dbscan class ###################################
################################################################################
Dbscan <- setClass(
# Set the name for the class
"Dbscan",
# Define the slots
slots = c(
name = "character",
clustering = "matrix",
epsilon = "numeric",
minPoints = "numeric"
)
minPoints = "numeric",
clustering = "matrix"
),
validity = function(object){
errors <- character()
## Test slot Name
name = getName(object)
if (!is.character(name)){
msg <- paste("Name of Dbscan object '" , name , "' is incorrect. ",
"It should be a string.\n",
sep = "")
errors <- c(errors, msg)
}
## Test slot epsilon
epsilon = getEpsilon(object)
if (!is.numeric(pc)){
msg <- paste("Epsilon '" , epsilon , "' is incorrect. ",
"It should be a numeric.\n",
sep = "")
errors <- c(errors, msg)
}
## Test slot minPoints
minPoints = getMinPoints(object)
if (!is.numeric(minPoints)){
msg <- paste("minPoints '" , minPoints , "' is incorrect. ",
"It should be a numeric.\n",
sep = "")
errors <- c(errors, msg)
}
## Test slot clustering
clustering = getClustering(object)
if (!is.matrix(clustering)){
msg <- paste("Coordinates should be matrix",
sep = "")
errors <- c(errors, msg)
}
}
)
Loading