Skip to content

Commit

Permalink
using light and heavy label variables. Fixing bugs.
Browse files Browse the repository at this point in the history
  • Loading branch information
wolski committed Aug 16, 2016
1 parent 02c2c9f commit f2bf101
Showing 1 changed file with 83 additions and 46 deletions.
129 changes: 83 additions & 46 deletions R/SRMService.R
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,9 @@
#' data <-allData[allData$pool==pool,]
#' head(data)
#' srms <- SRMService(data,qvalue=0.05)
#' SRMService$methods()
#' srms$maxNAHeavy()
#' SRMService$fields()
#' head(srms$piw)
#'
#' srms$plotQValues()
Expand All @@ -51,49 +54,50 @@
#'
#' srms$getNrNAs()
#' srms$getNrNAs(light=TRUE)
#' srms$maxNAHeavy
#' srms$maxNALight
#'
#' srms$maxNAHeavy()
#' srms$maxNALight()
#' srms$maxNAHeavy(80)
#' srms$maxNALight(80)
#' srms$plotCommonTransitions()
#' srms$getLHLog2FoldChange()
#' srms$setMaxNAHeavy(30)
#' srms$setMaxNALight(40)
#' srms$plotCommonTransitions(light=TRUE)
#' tmp <-srms$getLHLog2FoldChange(maxNA = 20)
#' srms$maxNAFC()
#' resH <- srms$plotCommonTransitions()
#' dim(resH)
#' resL <-srms$plotCommonTransitions(light=TRUE)
#' dim(resL)
#' resAll <- srms$getMatchingIntensities()
#' dim(resAll$light)
#'
#' colnames(srms$piw)
#' tmpH <- srms$getTransitionIntensities()
#' dim(tmpH)
#' stopifnot(max(apply(tmpH, 1, function(x){sum(is.na(x))}))<=30)
#' tmpL <- srms$getTransitionIntensities(light=TRUE)
#' dim(tmpL)
#' stopifnot(max(apply(tmpL, 1, function(x){sum(is.na(x))}))<=40)
#' x<-srms$getMatchingIntensities()
#' names(x)
#' dim(x$light)
#' dim(x$heavy)
#'
SRMService <- setRefClass("SRMService",
fields = list( data = "data.frame",
dataq = "data.frame",
qValueThreshold = "numeric",
maxNAHeavy = "numeric",
maxNALight = "numeric",
MaxNAHeavy = "numeric",
MaxNALight = "numeric",
MaxNAFC = "numeric",
piw = "data.frame",
int = "data.frame",
lightLabel = "character",
heavyLable = "character"
heavyLabel = "character"


),methods = list(
initialize = function(data,
qvalue = 0.05
){
.self$lightLabel = "light"
.self$heavyLable = "heavy"
.self$heavyLabel = "heavy"

stopifnot(getRequiredColumns() %in% colnames(data))
.self$data <- data[,getRequiredColumns()]
.self$maxNAHeavy <- length(unique(.self$data$Replicate.Name))
.self$maxNALight <- length(unique(.self$data$Replicate.Name))
.self$MaxNAHeavy <- length(unique(.self$data$Replicate.Name))
.self$MaxNALight <- .self$MaxNAHeavy
.self$MaxNAFC <- .self$MaxNAHeavy
setQ(qvalue)
},
setQ = function(qvalue = 0.05){
Expand All @@ -103,26 +107,30 @@ SRMService <- setRefClass("SRMService",
.self$dataq$Area[.self$dataq$annotation_QValue > .self$qValueThreshold] <- NA
.makePivotData()
},
qValueHist=function(){
hist(.self$data$annotation_QValue, main="q Values")
abline(v = .self$qValueThreshold, col=2)
},
.mergeHL=function(piwdata){
library(reshape2)
" make sure that to every light you have also an heavy transition "
d2 <- reshape2::melt(piwdata, id.vars= colnames(piwdata)[1:6], variable.name = 'Replicate.Name',value.name='Area')
dl <- d2[d2$Isotope.Label == .self$lightLabel,]
dh <- d2[d2$Isotope.Label == .self$heavyLable,]
dh <- d2[d2$Isotope.Label == .self$heavyLabel,]

dl <- subset(dl, select = colnames(dl)!="Isotope.Label")
dh <- subset(dh, select = colnames(dh)!="Isotope.Label")

.reportMissing(dl,dh)

colnames(dl)[colnames(dl) == "Area"] <- "light"
colnames(dh)[colnames(dh) == "Area"] <- "heavy"
colnames(dl)[colnames(dl) == "Area"] <- .self$lightLabel
colnames(dh)[colnames(dh) == "Area"] <- .self$heavyLabel


fixedData <- merge(dl,dh)
tmp <-melt(fixedData, id.vars = colnames(fixedData)[1:6],variable.name = "Isotope.Label",value.name = "Area" )
return(tmp)
}
}
,.makePivotData = function(){
message("pivoting data")
.self$piw <- SRMService::piwotPiw(.self$dataq)
Expand All @@ -145,25 +153,44 @@ SRMService <- setRefClass("SRMService",
},
getNrNAs = function(light = FALSE){
"show nr of NA's for heavy (defalt) or light transitions"
isolable <- ifelse(light, "light", "heavy")
nas <- subset(.self$piw,Isotope.Label==isolable)$nrNA
hist(nas, main=isolable)
abline(v=ifelse(light, .self$maxNALight, .self$maxNAHeavy), col=2)
isolabel <- if(light){ .self$lightLabel} else {.self$heavyLabel}
nas <- subset(.self$piw,Isotope.Label==isolabel)$nrNA
plot(table(nas), main=isolabel)
abline(v=ifelse(light, .self$MaxNALight, .self$MaxNAHeavy), col=2)
invisible(nas)
},
setMaxNAHeavy = function(max=0){
maxNAHeavy = function(max){
"set maximum of na's heavy row"
.self$maxNAHeavy = max
if(!missing(max)){
.self$MaxNAHeavy = max
}else{
return(.self$MaxNAHeavy)
}
},
setMaxNALight = function(max=0){
maxNALight = function(max){
"set maximum of na's in light row"
.self$maxNALight = max
if(!missing(max)){
.self$MaxNALight = max
}else{
return(.self$MaxNALight)
}
},
maxNAFC = function(max){
if(!missing(max)){
.self$MaxNAFC = max
}else{
return(.self$MaxNAFC)
}
},
getTransitionIntensities=function(light=FALSE){
getTransitionIntensities=function(maxNA,light=FALSE){
"get matrix with intensities, where nr of NAs in row < maxNA"
idx <- .self$piw$nrNA <= ifelse(light,.self$maxNALight, .self$maxNAHeavy)

int_ <- subset(.self$int, .self$piw$Isotope.Label==ifelse(light, "light", "heavy")
if(!missing(maxNA)){
idx <- .self$piw$nrNA <= maxNA
}else{
idx <- .self$piw$nrNA <= ifelse(light,.self$MaxNALight, .self$MaxNAHeavy)
}
int_ <- subset(.self$int,
.self$piw$Isotope.Label==ifelse(light,.self$lightLabel, .self$heavyLabel)
& idx
)
return(int_)
Expand All @@ -184,31 +211,41 @@ SRMService <- setRefClass("SRMService",
"Shows transitions which occure in heavy and light"
int_ <- getMatchingIntensities()
int_ <- if(light){ int_$light}else{int_$heavy}
main <- paste(if(light){.self$lightLabel} else {.self$heavyLabel}, "Intensity")
imageWithLabels(log2(t((int_))),col = quantable::getRedScale(),
main="heavy Int",marLeft=c(5,15,3,3),marRight = c(5,0,3,3))
main=main,marLeft=c(5,15,3,3),marRight = c(5,0,3,3))
invisible(int_)
},
getLHLog2FoldChange = function(plot=TRUE){

getLHLog2FoldChange = function(maxNA, plot=TRUE){
int_<-getMatchingIntensities()
stopifnot(colnames( int_$light) == colnames(int_$heavy))
stopifnot(rownames( int_$light) == rownames(int_$heavy))

logfc <-(log2(( int_$light )) - log2((int_$heavy)) )
if(missing(maxNA)){
maxNA <- .self$MaxNAFC
}
logfc <- subset(logfc , maxNA >= apply(logfc ,1, function(x){sum(is.na(x))}))

if(plot){
imageWithLabels(t(logfc), main="log2(L/H)", col= getBlueWhiteRed(), marLeft=c(5,15,3,3),marRight = c(5,0,3,3))
invisible(logfc)
}
else{
return(logfc)
imageWithLabels(t(logfc), main=
paste("log2(",.self$lightLabel, "/", .self$heavyLabel, ")"),
col= getBlueWhiteRed(),
marLeft=c(5,15,3,3),
marRight = c(5,0,3,3))
}
invisible(logfc)

},

plotTransition = function(light = FALSE){
int_ <- .self$getTransitionIntensities(light=light)
quantable::imageWithLabels( t(as.matrix(log2( int_ ) )) , col = quantable::getRedScale(),
main=ifelse(light, "ligth", "heavy"),marLeft=c(5,15,3,3),marRight = c(5,0,3,3))
quantable::imageWithLabels( t(as.matrix(log2( int_ ) )) ,
col = quantable::getRedScale(),
main=ifelse(light, .self$lightLabel,.self$heavyLabel),
marLeft=c(5,15,3,3),
marRight = c(5,0,3,3))
invisible(int_)
}

)
Expand Down

0 comments on commit f2bf101

Please sign in to comment.