R/tuxedo.R

Defines functions createDir tophat cufflinks cuffmerge cuffdiff geneDiff isoDiff cdsDiff chooseOutDir chooseInDir

Documented in cdsDiff chooseInDir chooseOutDir createDir cuffdiff cufflinks cuffmerge geneDiff isoDiff tophat

#create a dir for each sample in the target file
createDir <- function(){
	Try(chooseInDir())
	Try(tkmessageBox(title="Folder Creation",message="Open the target file containing the dataset description.",type="ok",icon="info"))
   	Try(OpenTargetsFile())
    Try(targets <- get("Targets", env=affylmGUIenvironment))
    Try(covar <- unique(targets$Target))
    if(length(covar)>2){
	     Try(tkmessageBox(title="Covariates",message="The present implementation only support two covariates.\nPlease, edit your target to include only two experimental conditions.",type="ok",icon="error"))
         Try(return())
    }
    for( i in targets$Name){
	     Try(dir.create(i))
    }
    Try(tkmessageBox(title="Folder Creation",message="Folders for tophat runs have been created.",type="ok",icon="info"))	
}

#this function creates a configuration file to run tophat
tophat <- function(){
	#check if bowtie, tophat, cufflinks are in the path
	Try(tmp <- system("bowtie --version", intern=T))
	if(length(grep("bowtie version", tmp))==0){
		Try(cat("\nbowtie is not installed or it is not inserted in the PATH variable\n"))
		Try(return())
	}
	Try(tmp <- system("tophat --version", intern=T))
	if(length(grep("TopHat v", tmp))==0){
		Try(cat("\nTopHat is not installed or it is not inserted in the PATH variable\n"))
		Try(return())
	}
#	Try(tmp <- system("cufflinks", intern=T))
#	if(length(grep("cufflinks v", tmp))==0){
#		Try(cat("\ncufflinks is not installed or it is not inserted in the PATH variable\n"))
#		Try(return())
#	}
	#Try(require(tkWidgets) || stop("\ntkWidgets library is not installed\n"))
	##PE or SE
    Try(ttGetSeqMethod <- tktoplevel(.affylmGUIglobals$ttMain))
	Try(tkwm.deiconify(ttGetSeqMethod))
    Try(tkgrab.set(ttGetSeqMethod))
    Try(tkfocus(ttGetSeqMethod))
    Try(tkwm.title(ttGetSeqMethod,"Sequencing method"))
	Try(tkgrid(tklabel(ttGetSeqMethod,text="    ")))
	Try(ttGetSeqMethodTcl <- tclVar("PE"))
    Try(rbIQR.5 <- tkradiobutton(ttGetSeqMethod,text="PE",variable=ttGetSeqMethodTcl,value="PE",font=.affylmGUIglobals$affylmGUIfont2))
    Try(rbIQR.25<-tkradiobutton(ttGetSeqMethod,text="SE",variable=ttGetSeqMethodTcl,value="SE",font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(tklabel(ttGetSeqMethod,text="    "),rbIQR.5))
	Try(tkgrid(tklabel(ttGetSeqMethod,text="    "),rbIQR.25))
	Try(tkgrid.configure(rbIQR.5,rbIQR.25,columnspan=2,sticky="w"))
	Try(tkgrid(tklabel(ttGetSeqMethod,text="    "),tklabel(ttGetSeqMethod,text="    ")))
	Try(ReturnVal <- "")
	Try(onCancel <- function() {Try(ReturnVal <<- "");Try(tkgrab.release(ttGetSeqMethod));Try(tkdestroy(ttGetSeqMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})
	Try(onOK <- function() {Try(ReturnVal <<- tclvalue(ttGetSeqMethodTcl));Try(tkgrab.release(ttGetSeqMethod));Try(tkdestroy(ttGetSeqMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})
    Try(onHelp <- function() tkmessageBox(title="About sequencing methods", message="PE stands for pair end reads; \nSE stands for single end reads",icon="info"))
    Try(Help.but <- tkbutton(ttGetSeqMethod,text=" Help ",command=function()Try(onHelp()),font=.affylmGUIglobals$affylmGUIfont2))
	Try(OK.but     <- tkbutton(ttGetSeqMethod,text="OK",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
	Try(Cancel.but <- tkbutton(ttGetSeqMethod,text="Cancel",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(tklabel(ttGetSeqMethod,text="    "),OK.but,Cancel.but, Help.but,tklabel(ttGetSeqMethod,text="    ")))
	Try(tkgrid.configure(OK.but,sticky="e"))
	Try(tkgrid.configure(Cancel.but,sticky="w"))
	Try(tkgrid.configure(Help.but,sticky="e"))
	Try(tkgrid(tklabel(ttGetSeqMethod,text="    ")))
    Try(tkbind(ttGetSeqMethod,"<Destroy>",function() {ReturnVal <- "";Try(tkgrab.release(ttGetSeqMethod));Try(tkfocus(.affylmGUIglobals$ttMain));}))
    Try(tkbind(OK.but, "<Return>",onOK))
    Try(tkbind(Cancel.but, "<Return>",onCancel))      
    Try(tkbind(Help.but, "<Return>",onCancel)) 
	Try(tkwait.window(ttGetSeqMethod))
    Try(seqtype <- ReturnVal)
    Try(program	<- "nohup tophat")
    Try(param1 <- "--bowtie1")
    #expected inner distance in pair-end reads
    Try(ttMateInnerDist<-tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttMateInnerDist))
    Try(tkgrab.set(ttMateInnerDist))
    Try(tkfocus(ttMateInnerDist))
    Try(tkwm.title(ttMateInnerDist,"Defining the between reads distance"))
    Try(tkgrid(tklabel(ttMateInnerDist,text="    ")))
    Try(MateInnerDistnum <- "200")
    Try(Local.MateInnerDist <- tclVar(init=MateInnerDistnum))
    Try(entry.MateInnerDist <-tkentry(ttMateInnerDist,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.MateInnerDist,bg="white"))
    Try(tkgrid(tklabel(ttMateInnerDist,text="Please enter the nts between pair end reads.",font=.affylmGUIglobals$affylmGUIfont2)))
    Try(tkgrid(entry.MateInnerDist))
    onOK <- function()
    {
                     Try(MateInnerDistnum <- as.numeric(tclvalue(Local.MateInnerDist)))
                     Try(assign("MateInnerDist", as.numeric(tclvalue(Local.MateInnerDist)),affylmGUIenvironment))
			         Try(assign("MateInnerDist.available", TRUE,affylmGUIenvironment))
                     Try(tkgrab.release(ttMateInnerDist));Try(tkdestroy(ttMateInnerDist));Try(tkfocus(.affylmGUIglobals$ttMain))                        
    }
    Try(OK.but <-tkbutton(ttMateInnerDist,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(tklabel(ttMateInnerDist,text="    ")))
    Try(tkgrid(OK.but))
    Try(tkgrid.configure(OK.but))
    Try(tkgrid(tklabel(ttMateInnerDist,text="       ")))
    Try(tkfocus(entry.MateInnerDist))
    Try(tkbind(entry.MateInnerDist, "<Return>",onOK))
    Try(tkbind(ttMateInnerDist, "<Destroy>", function(){Try(tkgrab.release(ttMateInnerDist));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
    Try(tkwait.window(ttMateInnerDist))
    Try(tkfocus(.affylmGUIglobals$ttMain))
    Try(MateInnerDistnum <- get("MateInnerDist", env=affylmGUIenvironment))    
    Try(param2 <- paste("-r",MateInnerDistnum, sep=" "))
    #min anchor distance
    Try(ttGetAnchorDist <- tktoplevel(.affylmGUIglobals$ttMain))
	Try(tkwm.deiconify(ttGetAnchorDist))
    Try(tkgrab.set(ttGetAnchorDist))
    Try(tkfocus(ttGetAnchorDist))
    Try(tkwm.title(ttGetAnchorDist,"Minimal anchor distance"))
	Try(tkgrid(tklabel(ttGetAnchorDist,text="    ")))
	Try(ttGetAnchorDistTcl <- tclVar(8))
    Try(rbIQR.5 <- tkradiobutton(ttGetAnchorDist,text="12",variable=ttGetAnchorDistTcl,value=12,font=.affylmGUIglobals$affylmGUIfont2))
    Try(rbIQR.25<-tkradiobutton(ttGetAnchorDist,text="8",variable=ttGetAnchorDistTcl,value=8,font=.affylmGUIglobals$affylmGUIfont2))
    Try(rbIQR.50<-tkradiobutton(ttGetAnchorDist,text="3",variable=ttGetAnchorDistTcl,value=3,font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(tklabel(ttGetAnchorDist,text="    "),rbIQR.5))
	Try(tkgrid(tklabel(ttGetAnchorDist,text="    "),rbIQR.25))
	Try(tkgrid(tklabel(ttGetAnchorDist,text="    "),rbIQR.50))
	Try(tkgrid.configure(rbIQR.5,rbIQR.25, rbIQR.50, columnspan=2,sticky="w"))
	Try(tkgrid(tklabel(ttGetAnchorDist,text="    "),tklabel(ttGetAnchorDist,text="    ")))
	Try(ReturnVal1 <- "")
	Try(onCancel <- function() {Try(ReturnVal1 <<- "");Try(tkgrab.release(ttGetAnchorDist));Try(tkdestroy(ttGetAnchorDist));Try(tkfocus(.affylmGUIglobals$ttMain))})
	Try(onOK <- function() {Try(ReturnVal1 <<- tclvalue(ttGetAnchorDistTcl));Try(tkgrab.release(ttGetAnchorDist));Try(tkdestroy(ttGetAnchorDist));Try(tkfocus(.affylmGUIglobals$ttMain))})
    Try(onHelp <- function() tkmessageBox(title="About minimal anchor distance", message="TopHat will report junctions spanned by reads with at least this \nmany bases on each side of the junction. Note that individual spliced alignments \nmay span a junction with fewer than this many bases on one side. \nHowever, every junction involved in spliced alignments is supported by \nat least one read with this many bases on each side. \nThis must be at least 3 and the default is 8",icon="info"))
    Try(Help.but <- tkbutton(ttGetAnchorDist,text=" Help ",command=function()Try(onHelp()),font=.affylmGUIglobals$affylmGUIfont2))
	Try(OK.but     <- tkbutton(ttGetAnchorDist,text="OK",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
	Try(Cancel.but <- tkbutton(ttGetAnchorDist,text="Cancel",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(tklabel(ttGetAnchorDist,text="    "),OK.but,Cancel.but, Help.but,tklabel(ttGetAnchorDist,text="    ")))
	Try(tkgrid.configure(OK.but,sticky="e"))
	Try(tkgrid.configure(Cancel.but,sticky="w"))
	Try(tkgrid.configure(Help.but,sticky="e"))
	Try(tkgrid(tklabel(ttGetAnchorDist,text="    ")))
    Try(tkbind(ttGetAnchorDist,"<Destroy>",function() {ReturnVal1 <- "";Try(tkgrab.release(ttGetAnchorDist));Try(tkfocus(.affylmGUIglobals$ttMain));}))
    Try(tkbind(OK.but, "<Return>",onOK))
    Try(tkbind(Cancel.but, "<Return>",onCancel))      
    Try(tkbind(Help.but, "<Return>",onCancel)) 
	Try(tkwait.window(ttGetAnchorDist))
    Try(param3 <- paste("-a",ReturnVal1, sep=" "))
    Try(param4 <- "--solexa-quals")
    #setting the number of cores involverd in the run
    Try(ttCores<-tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttCores))
    Try(tkgrab.set(ttCores))
    Try(tkfocus(ttCores))
    Try(tkwm.title(ttCores,"Defining the between reads distance"))
    Try(tkgrid(tklabel(ttCores,text="    ")))
    Try(Coresnum <- "1")
    Try(Local.Cores <- tclVar(init=Coresnum))
    Try(entry.Cores <-tkentry(ttCores,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.Cores,bg="white"))
    Try(tkgrid(tklabel(ttCores,text="Please enter number of cores used for the analysis.",font=.affylmGUIglobals$affylmGUIfont2)))
    Try(tkgrid(entry.Cores))
    onOK <- function()
    {
                     Try(Cores <- as.numeric(tclvalue(Local.Cores)))
                     Try(assign("Cores", as.numeric(tclvalue(Local.Cores)),affylmGUIenvironment))
			         Try(assign("Cores.available", TRUE,affylmGUIenvironment))
                     Try(tkgrab.release(ttCores));Try(tkdestroy(ttCores));Try(tkfocus(.affylmGUIglobals$ttMain))                        
    }
    Try(OK.but <-tkbutton(ttCores,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(tklabel(ttCores,text="    ")))
    Try(tkgrid(OK.but))
    Try(tkgrid.configure(OK.but))
    Try(tkgrid(tklabel(ttCores,text="       ")))
    Try(tkfocus(entry.Cores))
    Try(tkbind(entry.Cores, "<Return>",onOK))
    Try(tkbind(ttCores, "<Destroy>", function(){Try(tkgrab.release(ttCores));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
    Try(tkwait.window(ttCores))
    Try(tkfocus(.affylmGUIglobals$ttMain))
    Try(Coresnum <- get("Cores", env=affylmGUIenvironment))    
    Try(param5 <- paste("-p",Coresnum, sep=" "))
    Try(param6 <- "--library-type fr-unstranded")
    Try(param7 <- "--no-coverage-search")#reduces time and memory usage

    #selecting outputdir
    Try(outDir <- chooseOutDir())
    Try(outDir <- paste("-o ", outDir, sep=""))
    #select the bowtie indexed genome
    Try(tkmessageBox(title="Selecting the bowtie indexed genome",message="With the next widget, please select one of the genome files indexed by bowtie\nThe program will keep only the basename.",type="ok",icon="info"))
    Try(genome <- fileBrowser())
    Try(tmp <- strsplit(genome, "\\."))
	Try(tmp <- unlist(tmp))
    if(tmp[length(tmp)]!="ebwt"){
	    Try(tkmessageBox(title="Selecting the bowtie indexed genome",message="It seems that you have selected a index file that dows not have the right ebwt extension!",type="ok",icon="error"))
	    Try(return())
    }else{
           if(tmp[length(tmp)-2] == "rev"){
	          genome <- paste(tmp[1:(length(tmp)-3)],collapse=".")             
           }else	{
		          genome <- paste(tmp[1:(length(tmp)-2)],collapse=".")
		  }	
   }
   Try(inDir <- chooseInDir())
   #select the fastq files
   if(seqtype=="PE"){
    Try(tkmessageBox(title="Selecting the R1",message="With the next widget, please select all R1 fastq files.",type="ok",icon="info"))
    Try(r1 <- fileBrowser(path=inDir))
    #Try(r1 <- strsplit(r1,'/'))
	#Try(r1 <- sapply(r1, function(x) x[length(x)]))
    Try(tkmessageBox(title="Selecting the R2",message="With the next widget, please select all R2 fastq files.",type="ok",icon="info"))
    Try(r2 <- fileBrowser(path=inDir))
    #Try(r2 <- strsplit(r2,'/'))
	#Try(r2 <- sapply(r2, function(x) x[length(x)]))
	Try(r1 <- r1[order(r1)])
	Try(r2 <- r2[order(r2)])
	Try(r1<- paste(r1, collapse=","))
	Try(r2<- paste(r2, collapse=","))
	Try(df.config <- cbind(c("program", "param1", "param2", "param3", "param4", "param5", "param6", "param7", "outDir", "genome", "inDir", "r1", "r2"),c(program, param1, param2, param3, param4, param5, param6, param7, outDir, genome, inDir, r1, r2)))
    Try(df.config)
    Try(tmp <- gsub(" ","_", date()))
	Try(tmp <- gsub(":","-", tmp))
	Try(tkmessageBox(title="tophat configuration",message=paste("TopHat configuration file is ",paste("tophat_config_",tmp,".txt", sep=""),sep=""),type="ok",icon="info"))
    Try(write.table(df.config, file = paste("tophat_config_",tmp,".txt", sep=""), sep="\t", quote=F, row.name=F, col.name=F))
    Try(config <- c(program, param1, param2, param3, param4, param5, param6, param7, outDir, genome, inDir, r1, r2))
    Try(names(config) <- c("program", "param1", "param2", "param3", "param4", "param5", "param6", "param7", "outDir", "genome", "inDir", "r1", "r2"))
    Try(config1 <- config[setdiff(seq(1,length(config)),which(names(config) %in% c("seqtype","inDir","r1","r2")))])

    Try(indir <- paste(r1, r2, sep=" "))
	Try(mycom <- paste(config1, sep="",collapse=" "))
	Try(mycom <- paste(mycom, indir, sep=" "))
	Try(cat("\nTopHat command string:\n",mycom,"\n"))
	Try(system(mycom, wait =F))
	
  }else if(	seqtype=="SE"){
	    Try(tkmessageBox(title="Selecting the fastq files to be mapped",message="With the next widget, please select all fastq files to be mapped.",type="ok",icon="info"))
	    Try(r1 <- fileBrowser(path=inDir))
	    Try(r1 <- strsplit(r1,'/'))
		Try(r1 <- sapply(r1, function(x) x[length(x)]))
		Try(r1<- paste(r1, collapse=","))
	    Try(df.config <- c(program, param1, param3, param4, param5, param6, param7, outDir, genome, inDir, r1))
	    Try(df.config <- cbind(c("program", "param1", "param3", "param4", "param5", "param6", "param7", "outDir", "genome", "inDir", "r1"),c(program, param1, param3, param4, param5, param6, outDir, genome, inDir, r1)))
	    Try(tmp <- gsub(" ","_", date()))
		Try(tmp <- gsub(":","-", tmp))
	    Try(write.table(df.config, file = paste("tophat_config_",tmp,".txt", sep=""), sep="\t", quote=F, row.name=F, col.name=F))
		#to be completed
  }
  Try(tkmessageBox(title="TopHat",message="TopHat is running in background.\nWhen finished for all samples run cuffkinks",type="ok",icon="info"))
  
	
}
########
cufflinks <- function(){
#	Try(require(tkWidgets) || stop("\ntkWidgets library is not installed\n"))
	#setting the number of cores involverd in the run
    Try(ttCores<-tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttCores))
    Try(tkgrab.set(ttCores))
    Try(tkfocus(ttCores))
    Try(tkwm.title(ttCores,"Defining the between reads distance"))
    Try(tkgrid(tklabel(ttCores,text="    ")))
    Try(Coresnum <- "1")
    Try(Local.Cores <- tclVar(init=Coresnum))
    Try(entry.Cores <-tkentry(ttCores,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.Cores,bg="white"))
    Try(tkgrid(tklabel(ttCores,text="Please enter number of cores used for the analysis.",font=.affylmGUIglobals$affylmGUIfont2)))
    Try(tkgrid(entry.Cores))
    onOK <- function()
    {
                     Try(Cores <- as.numeric(tclvalue(Local.Cores)))
                     Try(assign("Cores", as.numeric(tclvalue(Local.Cores)),affylmGUIenvironment))
			         Try(assign("Cores.available", TRUE,affylmGUIenvironment))
                     Try(tkgrab.release(ttCores));Try(tkdestroy(ttCores));Try(tkfocus(.affylmGUIglobals$ttMain))                        
    }
    Try(OK.but <-tkbutton(ttCores,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(tklabel(ttCores,text="    ")))
    Try(tkgrid(OK.but))
    Try(tkgrid.configure(OK.but))
    Try(tkgrid(tklabel(ttCores,text="       ")))
    Try(tkfocus(entry.Cores))
    Try(tkbind(entry.Cores, "<Return>",onOK))
    Try(tkbind(ttCores, "<Destroy>", function(){Try(tkgrab.release(ttCores));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
    Try(tkwait.window(ttCores))
    Try(tkfocus(.affylmGUIglobals$ttMain))
    Try(Coresnum <- get("Cores", env=affylmGUIenvironment))    
    Try(param1 <- paste("-p",Coresnum, sep=" "))
    Try(param2 <- "--library-type fr-unstranded")
    #select the genome.gtf
    Try(tkmessageBox(title="Selecting the genes.gtf",message="With the next widget, please select the genes.gtf file.",type="ok",icon="info"))
    Try(genes <- fileBrowser())
    Try(tmp <- strsplit(genes, "\\."))
	Try(tmp <- unlist(tmp))
    if(tmp[length(tmp)]!="gtf"){
	    Try(tkmessageBox(title="Selecting the genes.gtf",message="It seems that you have selected a gtf file that does not have the right gtf extension!",type="ok",icon="error"))
	    Try(return())
    }	
    Try(genes <- paste("-g ", genes, sep=""))
    #selecting inputdirs
    Try(tkmessageBox(title="Selecting folders with TopHat results",message="Select all folders containing TopHat results",type="ok",icon="info"))
	Try(inDir <- chooseInDir())
	Try(inData <- fileBrowser(path=inDir))
	 #selecting outputdir
    Try(outDir <- paste("-o ", inData, sep=""))
    Try(inData1 <- paste(inData, "accepted_hits.bam", sep=""))
    for(i in 1:length(inData)){
	    Try(mycom <- paste("nohup cufflinks -q ", param1, param2, genes, outDir[i], inData1[i]))
	    Try(cat("\nCufflinks command string:\n",mycom,"\n"))
		Try(system(mycom, wait =F))
    }
    Try(tkmessageBox(title="Cufflinks",message="Cufflinks is running in background.\nWhen finished for all samples run cuffmerge",type="ok",icon="info"))
}
########
cuffmerge <- function(){
	Try(tkmessageBox(title="Creating assemblies.txt",message="Select all folders containing cufflinks results",type="ok",icon="info"))
	Try(outDir <- chooseOutDir())
	Try(merging <- fileBrowser(path=outDir))
    Try(merging <- paste(merging, "transcripts.gtf", sep=""))
    Try(zz <- file("assemblies.txt", "w")) 
    Try(writeLines(merging, con=zz))
    Try(close(zz))
	Try(tkmessageBox(title="Creating assemblies.txt",message=paste("assemblies.txt is located in:", outDir, sep="\n"),type="ok",icon="info"))
    #select the gene.gtf
    Try(tkmessageBox(title="Selecting the genes.gtf",message="With the next widget, please select the genes.gtf file.",type="ok",icon="info"))
    Try(genes <- fileBrowser())
    Try(tmp <- strsplit(genes, "\\."))
	Try(tmp <- unlist(tmp))
    if(tmp[length(tmp)]!="gtf"){
	    Try(tkmessageBox(title="Selecting the genes.gtf",message="It seems that you have selected a gtf file that does not have the right gtf extension!",type="ok",icon="error"))
	    Try(return())
    }	
    Try(genes <- paste("-g ", genes, sep=""))
    #select the genome.fa
    Try(tkmessageBox(title="Selecting the genome.fa",message="With the next widget, please select the genome.fa file.",type="ok",icon="info"))
    Try(genome <- fileBrowser())
    Try(tmp <- strsplit(genome, "\\."))
	Try(tmp <- unlist(tmp))
    if(tmp[length(tmp)]!="fa"){
	    Try(tkmessageBox(title="Selecting the genome.fa",message="It seems that you have selected a fasta file that does not have the right fa extension!",type="ok",icon="error"))
	    Try(return())
    }	
    Try(genome <- paste("-s ", genome, sep=""))
    #setting the number of cores involverd in the run
    Try(ttCores<-tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttCores))
    Try(tkgrab.set(ttCores))
    Try(tkfocus(ttCores))
    Try(tkwm.title(ttCores,"Defining the between reads distance"))
    Try(tkgrid(tklabel(ttCores,text="    ")))
    Try(Coresnum <- "1")
    Try(Local.Cores <- tclVar(init=Coresnum))
    Try(entry.Cores <-tkentry(ttCores,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.Cores,bg="white"))
    Try(tkgrid(tklabel(ttCores,text="Please enter number of cores used for the analysis.",font=.affylmGUIglobals$affylmGUIfont2)))
    Try(tkgrid(entry.Cores))
    onOK <- function()
    {
                     Try(Cores <- as.numeric(tclvalue(Local.Cores)))
                     Try(assign("Cores", as.numeric(tclvalue(Local.Cores)),affylmGUIenvironment))
			         Try(assign("Cores.available", TRUE,affylmGUIenvironment))
                     Try(tkgrab.release(ttCores));Try(tkdestroy(ttCores));Try(tkfocus(.affylmGUIglobals$ttMain))                        
    }
    Try(OK.but <-tkbutton(ttCores,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(tklabel(ttCores,text="    ")))
    Try(tkgrid(OK.but))
    Try(tkgrid.configure(OK.but))
    Try(tkgrid(tklabel(ttCores,text="       ")))
    Try(tkfocus(entry.Cores))
    Try(tkbind(entry.Cores, "<Return>",onOK))
    Try(tkbind(ttCores, "<Destroy>", function(){Try(tkgrab.release(ttCores));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
    Try(tkwait.window(ttCores))
    Try(tkfocus(.affylmGUIglobals$ttMain))
    Try(Coresnum <- get("Cores", env=affylmGUIenvironment))    
    Try(param1 <- paste("-p",Coresnum, sep=" "))
    Try(mycom <- paste("nohup cuffmerge ", param1, genes, genome, paste(outDir, "assemblies.txt", sep="/")))
    Try(cat("\nCuffmerge command string:\n",mycom,"\n"))
	Try(system(mycom, wait =F)) 
	Try(tkmessageBox(title="Cuffmerge",message="Cuffmerge is running in background.\nWhen finished for all samples run cuffdiff",type="ok",icon="info"))
       
}
########
cuffdiff <- function(){
	Try(inDir <- chooseInDir())
	Try(myDir <- getwd())
	Try(setwd(inDir))
	Try(tkmessageBox(title="DE analysis",message="Open the target file containing the dataset description.",type="ok",icon="info"))
   	Try(OpenTargetsFile())
    Try(setwd(myDir))
    Try(targets <- get("Targets", env=affylmGUIenvironment))
    Try(covar <- unique(targets$Target))    
	#select the genome.fa
    Try(tkmessageBox(title="Selecting the genome.fa",message="With the next widget, please select the genome.fa file.",type="ok",icon="info"))
    Try(genome <- fileBrowser())
    Try(tmp <- strsplit(genome, "\\."))
	Try(tmp <- unlist(tmp))
    if(tmp[length(tmp)]!="fa"){
	    Try(tkmessageBox(title="Selecting the genome.fa",message="It seems that you have selected a fasta file that does not have the right fa extension!",type="ok",icon="error"))
	    Try(return())
    }	
	Try(genome <- paste("-b",genome, sep=" "))
	#setting the number of cores involverd in the run
    Try(ttCores<-tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttCores))
    Try(tkgrab.set(ttCores))
    Try(tkfocus(ttCores))
    Try(tkwm.title(ttCores,"Defining the between reads distance"))
    Try(tkgrid(tklabel(ttCores,text="    ")))
    Try(Coresnum <- "1")
    Try(Local.Cores <- tclVar(init=Coresnum))
    Try(entry.Cores <-tkentry(ttCores,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.Cores,bg="white"))
    Try(tkgrid(tklabel(ttCores,text="Please enter number of cores used for the analysis.",font=.affylmGUIglobals$affylmGUIfont2)))
    Try(tkgrid(entry.Cores))
    onOK <- function()
    {
                     Try(Cores <- as.numeric(tclvalue(Local.Cores)))
                     Try(assign("Cores", as.numeric(tclvalue(Local.Cores)),affylmGUIenvironment))
			         Try(assign("Cores.available", TRUE,affylmGUIenvironment))
                     Try(tkgrab.release(ttCores));Try(tkdestroy(ttCores));Try(tkfocus(.affylmGUIglobals$ttMain))                        
    }
    Try(OK.but <-tkbutton(ttCores,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(tklabel(ttCores,text="    ")))
    Try(tkgrid(OK.but))
    Try(tkgrid.configure(OK.but))
    Try(tkgrid(tklabel(ttCores,text="       ")))
    Try(tkfocus(entry.Cores))
    Try(tkbind(entry.Cores, "<Return>",onOK))
    Try(tkbind(ttCores, "<Destroy>", function(){Try(tkgrab.release(ttCores));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
    Try(tkwait.window(ttCores))
    Try(tkfocus(.affylmGUIglobals$ttMain))
    Try(Coresnum <- get("Cores", env=affylmGUIenvironment))    
    Try(param1 <- paste("-p",Coresnum, sep=" "))
    #select the merged.gtf
    Try(tkmessageBox(title="Selecting the merged.gtf",message="With the next widget, please select the merged.gtf file in the merged_asm dir.",type="ok",icon="info"))
    Try(merged <- fileBrowser())
    Try(tmp <- strsplit(merged, "\\."))
	Try(tmp <- unlist(tmp))
    if(tmp[length(tmp)]!="gtf"){
	    Try(tkmessageBox(title="Selecting the merged.gtf",message="It seems that you have selected a gtf file that does not have the right gtf extension!",type="ok",icon="error"))
	    Try(return())
    }	
    Try(merged <- paste("-u ", merged, sep=""))
    #selecting inputdirs
    Try(tkmessageBox(title="Selecting folders with TopHat results",message="Select all folders containing TopHat results",type="ok",icon="info"))
	Try(inData <- fileBrowser(path=inDir))
	Try(inData <- paste(inData, "accepted_hits.bam", sep=""))
    Try(tmp1 <- targets$Name[which(targets$Target == covar[1])])
    Try(tmp2 <- targets$Name[which(targets$Target == covar[2])])
    Try(tmpIn <- strsplit(inData, "/"))
    Try(tmpIn <- sapply(tmpIn, function(x) x[length(x)-1]))
    Try(cov1 <- inData[which(tmpIn %in% tmp1)])
    Try(cov1 <- paste(cov1, collapse=","))
    Try(cov2 <- inData[which(tmpIn %in% tmp2)])
    Try(cov2 <- paste(cov2, collapse=","))    
	Try(covar <- paste("-L",paste(covar, collapse=","),sep=" "))
	Try(mycom <- paste("nohup cuffdiff -q -o diff.out ", covar, genome, param1, merged, cov1, cov2))
	Try(cat("\nCuffdiff command string:\n",mycom,"\n"))
	Try(system(mycom, wait =F))
	Try(tkmessageBox(title="Cuffdiff",message="Cuffdiff is running in background.\nWhen finished for all samples run geneDiff, isoDiff, cdsDiff",type="ok",icon="info"))	
}
########
geneDiff <- function(){
#	Try(require(cummeRbund) || stop("Missing cummeRbund library"))
	Try(tkmessageBox(title="DE gene analysis",message="Open the target file containing the dataset description.",type="ok",icon="info"))
   	Try(OpenTargetsFile())
#    Try(setwd(myDir))
    Try(targets <- get("Targets", env=affylmGUIenvironment))
    Try(covar <- unique(targets$Target))    
	
	Try(myDir <- getwd())
#	Try(require(cummeRbund) || stop("\ncummeRbund library is missing!\n"))
	Try(tkmessageBox(title="DE gene output",message="Select the diff.out folder",type="ok",icon="info"))
    Try(diff.out <- fileBrowser())
	Try(setwd(diff.out))
	if(length(grep(".diff", dir()))==0){
		Try(tkmessageBox(title="DE output",message=paste("The folder ", getwd(),"\ndoes not seems to contain cuffdiff data."),type="ok",icon="error"))
		Try(return())
	}
	Try(cuff <- readCufflinks(dir=getwd()))
	Try(cuff)
	if(dim(genes(cuff))[1] == 0){
		Try(tkmessageBox(title="geneDiff",message="No differentially expressed genes!",type="ok",icon="info"))
		Try(setwd(myDir))	
		Try(return())
	}
	#getting diff expressed
	gene.diff<-diffData(genes(cuff))
	#def thresholds
	Try(ttIfDialog<-tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttIfDialog))
    Try(tkgrab.set(ttIfDialog))
    Try(tkfocus(ttIfDialog))
    Try(tkwm.title(ttIfDialog,"Threshold Options"))
    Try(tkgrid(tklabel(ttIfDialog,text="    ")))

    Try(frame1 <- tkframe(ttIfDialog,relief="groove",borderwidth=2))
    Try(HowManyQuestion1 <- tklabel(frame1,text="Fold Change threshold",font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(HowManyQuestion1))
    Try(tkgrid.configure(HowManyQuestion1,columnspan=2,sticky="w"))
    Try(thresholdTcl <- tclVar("1"))
    Try(I0.but  <- tkradiobutton(frame1,text="log2(FC)=2",variable=thresholdTcl,value=2,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I1.but  <- tkradiobutton(frame1,text="log2(FC)=1",variable=thresholdTcl,value=1,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I2.but  <- tkradiobutton(frame1,text="log2(FC)=0.5",variable=thresholdTcl,value=0.5,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I3.but  <- tkradiobutton(frame1,text="log2(FC)=0.1",variable=thresholdTcl,value=0.1,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I4.but  <- tkradiobutton(frame1,text="log2(FC)=none",variable=thresholdTcl,value=0,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(I0.but,sticky="w"))
    Try(tkgrid(I1.but,sticky="w"))
    Try(tkgrid(I2.but,sticky="w"))
    Try(tkgrid(I3.but,sticky="w"))
    Try(tkgrid(I4.but,sticky="w"))
    Try(tkgrid.configure(HowManyQuestion1,I0.but,I1.but,I2.but,I3.but,I4.but,sticky="w"))

    Try(frame2 <- tkframe(ttIfDialog,relief="groove",borderwidth=2))
    Try(fractionLabel <- tklabel(frame2,text="q-value threshold",font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(fractionLabel,sticky="w"))
    Try(tkgrid.configure(fractionLabel,sticky="w"))
    Try(fractionTcl <- tclVar("1"))
    Try(F1.but <- tkradiobutton(frame2,text="0.005",variable=fractionTcl,value=0.005,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F2.but <- tkradiobutton(frame2,text="0.01",variable=fractionTcl,value=0.01,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F3.but <- tkradiobutton(frame2,text="0.05",variable=fractionTcl,value=0.05,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F4.but <- tkradiobutton(frame2,text="0.1",variable=fractionTcl,value=0.1,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F5.but <- tkradiobutton(frame2,text="none",variable=fractionTcl,value=1,font=.affylmGUIglobals$affylmGUIfont2))

    Try(tkgrid(F1.but,sticky="w"))
    Try(tkgrid(F2.but,sticky="w"))
    Try(tkgrid(F3.but,sticky="w"))
    Try(tkgrid(F4.but,sticky="w"))
    Try(tkgrid(F5.but,sticky="w"))
    Try(tkgrid.configure(fractionLabel,F1.but,F2.but,F3.but,F4.but,F5.but,sticky="w"))

    Try(onOK <- function()
    {
         Try(ReturnVal1 <- as.numeric(tclvalue(thresholdTcl)))
         Try(ReturnVal2 <- as.numeric(tclvalue(fractionTcl)))
         Try(ReturnVal <<- paste(ReturnVal1, ReturnVal2, sep=";"))
         Try(tkgrab.release(ttIfDialog))
         Try(tkdestroy(ttIfDialog))
         Try(tkfocus(.affylmGUIglobals$ttMain))
    })

    Try(frame3 <- tkframe(ttIfDialog,borderwidth=2))
    Try(onCancel <- function() {Try(ReturnVal <<- ""); Try(tkgrab.release(ttIfDialog));Try(tkdestroy(ttIfDialog));Try(tkfocus(.affylmGUIglobals$ttMain))})
    Try(OK.but <-tkbutton(frame3,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
    Try(Cancel.but <-tkbutton(frame3,text=" Cancel ",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))

    Try(tkgrid(tklabel(frame3,text="    "),OK.but,Cancel.but,tklabel(frame3,text="    ")))

    Try(tkgrid(tklabel(ttIfDialog,text="    "),frame1,frame2,tklabel(ttIfDialog,text="  ")))
    Try(tkgrid(tklabel(ttIfDialog,text="    ")))
    Try(tkgrid(tklabel(ttIfDialog,text="    "),frame3,tklabel(ttIfDialog,text="  ")))
    Try(tkgrid(tklabel(ttIfDialog,text="    ")))
    Try(tkgrid.configure(frame1,frame3,sticky="w"))

    Try(tkfocus(ttIfDialog))
    Try(tkbind(ttIfDialog, "<Destroy>", function() {Try(tkgrab.release(ttIfDialog));Try(tkfocus(.affylmGUIglobals$ttMain));}))
    Try(tkwait.window(ttIfDialog))
    Try(if(ReturnVal==""){return()})
    Try(tmp<-strsplit(ReturnVal, ";"))
    Try(q.value <- as.numeric(tmp[[1]][2]))
    Try(fc <- as.numeric(tmp[[1]][1]))
    	
	Try(gene.up <- intersect(which(gene.diff$q_value <= q.value),which(gene.diff$log2_fold_change >= fc)))
	Try(up <- gene.diff[gene.up,])
	Try(myUP<-getGenes(cuff,gene.diff$gene_id[gene.up]))
	Try(fpkm.up <- fpkm(myUP))
	Try(fpkmmat.up <-cbind(fpkm.up[seq(1,dim(fpkm.up)[1], by=2),], fpkm.up[seq(2,dim(fpkm.up)[1], by=2),2:6]))
	Try(ann.up <- annotation(myUP))
	if(identical(fpkmmat.up$gene_id, ann.up$gene_id)){
	   Try(fpkmmat.up <- cbind(fpkmmat.up, 	ann.up[,4:5]))
	} else (cat("\nAnnotation and up fpkm gene_id are not identical!\n"))
	if(identical(fpkmmat.up$gene_id, up$gene_id)){
	   Try(fpkmmat.up <- cbind(fpkmmat.up, 	up[,7:10]))
	} else {Try(cat("\nup fpkm and diff gene_ids are not identical!\n"))}
	Try(fpkmmat.up <- fpkmmat.up[,c(1,12:13,2:11,14:17)])	
	Try(write.table(fpkmmat.up, "up.txt", sep="\t", row.names=FALSE))
	Try(tkmessageBox(title="DE gene output",message=paste("The number of UP modulated genes is",length(gene.up),"\nData are available in up.txt"),type="ok",icon="info"))	
	Try(gene.dw <- intersect(which(gene.diff$q_value <= q.value),which(gene.diff$log2_fold_change <= -(fc))))
	Try(dw <- gene.diff[gene.dw,])
	Try(myDW<-getGenes(cuff,gene.diff$gene_id[gene.dw]))
	Try(fpkm.dw <- fpkm(myDW))
	Try(fpkmmat.dw <-cbind(fpkm.dw[seq(1,dim(fpkm.dw)[1], by=2),], fpkm.dw[seq(2,dim(fpkm.dw)[1], by=2),2:6]))
	Try(ann.dw <- annotation(myDW))
	if(identical(fpkmmat.dw$gene_id, ann.dw$gene_id)){
	   Try(fpkmmat.dw <- cbind(fpkmmat.dw, 	ann.dw[,4:5]))
	} else (Try(cat("\nAnnotation and dw fpkm gene_id are not identical!\n")))
	if(identical(fpkmmat.dw$gene_id, dw$gene_id)){
	   Try(fpkmmat.dw <- cbind(fpkmmat.dw, 	dw[,7:10]))
	} else {Try(cat("\n dw fpkm and diff gene_ids are not identical!\n"))}
	Try(fpkmmat.dw <- fpkmmat.dw[,c(1,12:13,2:11,14:17)])
	Try(write.table(fpkmmat.dw, "dw.txt", sep="\t", row.names=FALSE))
	Try(tkmessageBox(title="DE gene output",message=paste("The number of DW modulated genes is",length(gene.dw),"\nData are available in dw.txt"),type="ok",icon="info"))	
	Try(cat("The number of UP modulated genes is ",length(gene.up),"\nData are available in up.txt\n"))
	Try(cat("The number of DW modulated genes is ", length(gene.dw),"\nData are available in dw.txt\n"))
	Try(A <- apply(gene.diff[,5:6], 1,mean))
	Try(A <- A+1)
	Try(A <- log10(A))
	Try(M <- gene.diff$log2_fold_change)
	Try(M[which(M>10)] <- 11)
	Try(M[which(M< -10)] <- -11)
	Try(plot(A,M, pch=19, cex=0.5, xlab="A", ylab="M", main=paste("Genes", paste(covar,collapse="-"))))
	Try(points(A[gene.up],M[gene.up], col="red", pch=19, cex=0.5))
	Try(points(A[gene.dw],M[gene.dw], col="red", pch=19, cex=0.5))
	Try(abline(h=1, col="red"))
	Try(abline(h=-1, col="green"))
	Try(setwd(myDir))	
}
########
isoDiff <- function(){
#	Try(require(cummeRbund) || stop("Missing cummeRbund library"))
	Try(tkmessageBox(title="DE isoforms analysis",message="Open the target file containing the dataset description.",type="ok",icon="info"))
   	Try(OpenTargetsFile())
#    Try(setwd(myDir))
    Try(targets <- get("Targets", env=affylmGUIenvironment))
    Try(covar <- unique(targets$Target))    
	
	Try(myDir <- getwd())
#	Try(require(cummeRbund) || stop("\ncummeRbund library is missing!\n"))
	Try(tkmessageBox(title="DE isoforms output",message="Select the diff.out folder",type="ok",icon="info"))
    Try(diff.out <- fileBrowser())
	Try(setwd(diff.out))
	if(length(grep(".diff", dir()))==0){
		Try(tkmessageBox(title="DE output",message=paste("The folder ", getwd(),"\ndoes not seems to contain cuffdiff data."),type="ok",icon="error"))
		Try(return())
	}
	Try(cuff <- readCufflinks(dir=getwd()))
	Try(cuff)
	if(dim(isoforms(cuff))[1] == 0){
		Try(tkmessageBox(title="isoDiff",message="No differentially expressed isoforms!",type="ok",icon="info"))
		Try(setwd(myDir))	
		Try(return())
	}
	Try(gene.diff<-diffData(isoforms(cuff)))
	#def thresholds
	Try(ttIfDialog<-tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttIfDialog))
    Try(tkgrab.set(ttIfDialog))
    Try(tkfocus(ttIfDialog))
    Try(tkwm.title(ttIfDialog,"Threshold Options"))
    Try(tkgrid(tklabel(ttIfDialog,text="    ")))

    Try(frame1 <- tkframe(ttIfDialog,relief="groove",borderwidth=2))
    Try(HowManyQuestion1 <- tklabel(frame1,text="Fold Change threshold",font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(HowManyQuestion1))
    Try(tkgrid.configure(HowManyQuestion1,columnspan=2,sticky="w"))
    Try(thresholdTcl <- tclVar("1"))
    Try(I0.but  <- tkradiobutton(frame1,text="log2(FC)=2",variable=thresholdTcl,value=2,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I1.but  <- tkradiobutton(frame1,text="log2(FC)=1",variable=thresholdTcl,value=1,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I2.but  <- tkradiobutton(frame1,text="log2(FC)=0.5",variable=thresholdTcl,value=0.5,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I3.but  <- tkradiobutton(frame1,text="log2(FC)=0.1",variable=thresholdTcl,value=0.1,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I4.but  <- tkradiobutton(frame1,text="log2(FC)=none",variable=thresholdTcl,value=0,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(I0.but,sticky="w"))
    Try(tkgrid(I1.but,sticky="w"))
    Try(tkgrid(I2.but,sticky="w"))
    Try(tkgrid(I3.but,sticky="w"))
    Try(tkgrid(I4.but,sticky="w"))
    Try(tkgrid.configure(HowManyQuestion1,I0.but,I1.but,I2.but,I3.but,I4.but,sticky="w"))

    Try(frame2 <- tkframe(ttIfDialog,relief="groove",borderwidth=2))
    Try(fractionLabel <- tklabel(frame2,text="q-value threshold",font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(fractionLabel,sticky="w"))
    Try(tkgrid.configure(fractionLabel,sticky="w"))
    Try(fractionTcl <- tclVar("1"))
    Try(F1.but <- tkradiobutton(frame2,text="0.005",variable=fractionTcl,value=0.005,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F2.but <- tkradiobutton(frame2,text="0.01",variable=fractionTcl,value=0.01,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F3.but <- tkradiobutton(frame2,text="0.05",variable=fractionTcl,value=0.05,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F4.but <- tkradiobutton(frame2,text="0.1",variable=fractionTcl,value=0.1,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F5.but <- tkradiobutton(frame2,text="none",variable=fractionTcl,value=1,font=.affylmGUIglobals$affylmGUIfont2))

    Try(tkgrid(F1.but,sticky="w"))
    Try(tkgrid(F2.but,sticky="w"))
    Try(tkgrid(F3.but,sticky="w"))
    Try(tkgrid(F4.but,sticky="w"))
    Try(tkgrid(F5.but,sticky="w"))
    Try(tkgrid.configure(fractionLabel,F1.but,F2.but,F3.but,F4.but,F5.but,sticky="w"))

    Try(onOK <- function()
    {
         Try(ReturnVal1 <- as.numeric(tclvalue(thresholdTcl)))
         Try(ReturnVal2 <- as.numeric(tclvalue(fractionTcl)))
         Try(ReturnVal <<- paste(ReturnVal1, ReturnVal2, sep=";"))
         Try(tkgrab.release(ttIfDialog))
         Try(tkdestroy(ttIfDialog))
         Try(tkfocus(.affylmGUIglobals$ttMain))
    })

    Try(frame3 <- tkframe(ttIfDialog,borderwidth=2))
    Try(onCancel <- function() {Try(ReturnVal <<- ""); Try(tkgrab.release(ttIfDialog));Try(tkdestroy(ttIfDialog));Try(tkfocus(.affylmGUIglobals$ttMain))})
    Try(OK.but <-tkbutton(frame3,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
    Try(Cancel.but <-tkbutton(frame3,text=" Cancel ",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))

    Try(tkgrid(tklabel(frame3,text="    "),OK.but,Cancel.but,tklabel(frame3,text="    ")))

    Try(tkgrid(tklabel(ttIfDialog,text="    "),frame1,frame2,tklabel(ttIfDialog,text="  ")))
    Try(tkgrid(tklabel(ttIfDialog,text="    ")))
    Try(tkgrid(tklabel(ttIfDialog,text="    "),frame3,tklabel(ttIfDialog,text="  ")))
    Try(tkgrid(tklabel(ttIfDialog,text="    ")))
    Try(tkgrid.configure(frame1,frame3,sticky="w"))

    Try(tkfocus(ttIfDialog))
    Try(tkbind(ttIfDialog, "<Destroy>", function() {Try(tkgrab.release(ttIfDialog));Try(tkfocus(.affylmGUIglobals$ttMain));}))
    Try(tkwait.window(ttIfDialog))
    Try(if(ReturnVal==""){return()})
    Try(tmp<-strsplit(ReturnVal, ";"))
    Try(q.value <- as.numeric(tmp[[1]][2]))
    Try(fc <- as.numeric(tmp[[1]][1]))	
	Try(gene.up <- intersect(which(gene.diff$q_value <= q.value),which(gene.diff$log2_fold_change >= fc)))
	Try(up <- gene.diff[gene.up,])
	Try(all.fpkm<-fpkm(isoforms(cuff)))
	Try(samples.ids <- as.character(unique(all.fpkm$sample_name)))
	if(length(samples.ids)>2){
		Try(tkmessageBox(title="DE isoforms output",message="samples ids are more then two.\n It is not supported by oneChannelGUI",type="ok",icon="info"))	
        Try(return())
	}
	Try(all1 <- all.fpkm[which(all.fpkm$sample_name==samples.ids[1]),])
	Try(all2 <- all.fpkm[which(all.fpkm$sample_name==samples.ids[2]),])
	Try(all.fpkm <- cbind(all1,all2))
	Try(fpkmmat.up <- all.fpkm[which(all.fpkm$isoform_id %in%  up$isoform_id),c(1:6,8:12)])
	Try(fpkmmat.up <- fpkmmat.up[order(fpkmmat.up$isoform_id),])
	Try(ann.all <- annotation(isoforms(cuff)))
	Try(ann.all <- ann.all[,c(1,4:7)])
	Try(up <- up[order(up$isoform_id),])
	Try(ann.up <- ann.all[which(ann.all$isoform_id %in% up$isoform_id),])
	Try(ann.up <- ann.up[order(ann.up$isoform_id),])
	Try(fpkmmat.up <- fpkmmat.up[which(fpkmmat.up$isoform_id%in%ann.up$isoform_id),])
	if(identical(fpkmmat.up$isoform_id, ann.up$isoform_id)){
	   Try(fpkmmat.up <- cbind(fpkmmat.up, 	ann.up[,2:5]))
	} else (cat("\nAnnotation and up fpkm gene_id are not identical!\n"))
	if(identical(fpkmmat.up$isoform_id, up$isoform_id)){
	   Try(fpkmmat.up <- cbind(fpkmmat.up, 	up[,7:10]))
	} else {cat("\nup fpkm and diff isoform_ids are not identical!\n")}
	Try(fpkmmat.up <- fpkmmat.up[,c(1,12:13,2:11,14:16,19)])
	Try(tkmessageBox(title="DE isoforms output",message=paste("The number of UP modulated genes is",length(gene.up),"\nData are available in upisoform.txt"),type="ok",icon="info"))	
	Try(write.table(fpkmmat.up, "upisoform.txt", sep="\t", row.names=FALSE))


	Try(gene.dw <- intersect(which(gene.diff$q_value <= q.value),which(gene.diff$log2_fold_change <= -(fc))))
	Try(dw <- gene.diff[gene.dw,])
	Try(all.fpkm<-fpkm(isoforms(cuff)))
#	Try(all1 <- all.fpkm[seq(1, dim(all.fpkm)[1], by=2),])
#	Try(all2 <- all.fpkm[seq(2, dim(all.fpkm)[1], by=2),])
    Try(all1 <- all.fpkm[which(all.fpkm$sample_name==samples.ids[1]),])
    Try(all2 <- all.fpkm[which(all.fpkm$sample_name==samples.ids[2]),])
	Try(all.fpkm <- cbind(all1,all2))
	Try(fpkmmat.dw <- all.fpkm[which(all.fpkm$isoform_id %in%  dw$isoform_id),c(1:6,8:12)])
	Try(fpkmmat.dw <- fpkmmat.dw[order(fpkmmat.dw$isoform_id),])
	Try(ann.all <- annotation(isoforms(cuff)))
	Try(ann.all <- ann.all[,c(1,4:7)])
	Try(ann.dw <- ann.all[which(ann.all$isoform_id %in% dw$isoform_id),])
	Try(ann.dw <- ann.dw[order(ann.dw$isoform_id),])
	Try(fpkmmat.dw <- fpkmmat.dw[which(fpkmmat.dw$isoform_id%in%ann.dw$isoform_id),])
	
	if(identical(fpkmmat.dw$isoform_id, ann.dw$isoform_id)){
	   Try(fpkmmat.dw <- cbind(fpkmmat.dw, 	ann.dw[,2:5]))
	} else (cat("\nAnnotation and dw fpkm gene_id are not identical!\n"))
	if(identical(fpkmmat.dw$isoform_id, dw$isoform_id)){
	   Try(fpkmmat.dw <- cbind(fpkmmat.dw, 	dw[,7:10]))
	} else {cat("\ndw fpkm and diff isoform_ids are not identical!\n")}
	fpkmmat.dw <- fpkmmat.dw[,c(1,12:13,2:11,14:16,19)]
	Try(write.table(fpkmmat.dw, "dwisoform.txt", sep="\t", row.names=FALSE))
    Try(tkmessageBox(title="DE isoforms output",message=paste("The number of DW modulated isoforms is",length(gene.dw),"\nData are available in dwisoform.txt"),type="ok",icon="info"))	
	
	Try(cat("The number of UP modulated genes is ",length(gene.up),"\nData are available in upisoform.txt\n"))
	Try(cat("The number of DW modulated genes is ", length(gene.dw),"\nData are available in dwisoform.txt\n"))
	Try(A <- apply(gene.diff[,5:6], 1,mean))
	Try(A <- A+1)
	Try(A <- log10(A))
	Try(M <- gene.diff$log2_fold_change)
	Try(M[which(M>10)] <- 11)
	M[which(M< -10)] <- -11
	Try(plot(A,M, pch=19, cex=0.5, xlab="A", ylab="M", main=paste("Isoforms", paste(covar,collapse="-"))))
	Try(points(A[gene.up],M[gene.up], col="red", pch=19, cex=0.5))
	Try(points(A[gene.dw],M[gene.dw], col="red", pch=19, cex=0.5))
	Try(abline(h=1, col="red"))
	Try(abline(h=-1, col="green"))
	Try(setwd(myDir))	
	
	
}
########
cdsDiff <- function(){
#	Try(require(cummeRbund) || stop("Missing cummeRbund library"))
	Try(tkmessageBox(title="DE CDS analysis",message="Open the target file containing the dataset description.",type="ok",icon="info"))
   	Try(OpenTargetsFile())
#    Try(setwd(myDir))
    Try(targets <- get("Targets", env=affylmGUIenvironment))
    Try(covar <- unique(targets$Target))    
	
	Try(myDir <- getwd())
#	Try(require(cummeRbund) || stop("\ncummeRbund library is missing!\n"))
	Try(tkmessageBox(title="DE CDS output",message="Select the diff.out folder",type="ok",icon="info"))
    Try(diff.out <- fileBrowser())
	Try(setwd(diff.out))
	if(length(grep(".diff", dir()))==0){
		Try(tkmessageBox(title="DE output",message=paste("The folder ", getwd(),"\ndoes not seems to contain cuffdiff data."),type="ok",icon="error"))
		Try(return())
	}
	Try(cuff <- readCufflinks(dir=getwd()))
	Try(cuff)
	if(dim(CDS(cuff))[1] == 0){
		Try(tkmessageBox(title="isoDiff",message="No differentially expressed isoforms!",type="ok",icon="info"))
		Try(setwd(myDir))	
		Try(return())
	}
	Try(gene.diff<-diffData(CDS(cuff)))
	#def thresholds
	Try(ttIfDialog<-tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttIfDialog))
    Try(tkgrab.set(ttIfDialog))
    Try(tkfocus(ttIfDialog))
    Try(tkwm.title(ttIfDialog,"Threshold Options"))
    Try(tkgrid(tklabel(ttIfDialog,text="    ")))

    Try(frame1 <- tkframe(ttIfDialog,relief="groove",borderwidth=2))
    Try(HowManyQuestion1 <- tklabel(frame1,text="Fold Change threshold",font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(HowManyQuestion1))
    Try(tkgrid.configure(HowManyQuestion1,columnspan=2,sticky="w"))
    Try(thresholdTcl <- tclVar("1"))
    Try(I0.but  <- tkradiobutton(frame1,text="log2(FC)=2",variable=thresholdTcl,value=2,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I1.but  <- tkradiobutton(frame1,text="log2(FC)=1",variable=thresholdTcl,value=1,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I2.but  <- tkradiobutton(frame1,text="log2(FC)=0.5",variable=thresholdTcl,value=0.5,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I3.but  <- tkradiobutton(frame1,text="log2(FC)=0.1",variable=thresholdTcl,value=0.1,font=.affylmGUIglobals$affylmGUIfont2))
    Try(I4.but  <- tkradiobutton(frame1,text="log2(FC)=none",variable=thresholdTcl,value=0,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(I0.but,sticky="w"))
    Try(tkgrid(I1.but,sticky="w"))
    Try(tkgrid(I2.but,sticky="w"))
    Try(tkgrid(I3.but,sticky="w"))
    Try(tkgrid(I4.but,sticky="w"))
    Try(tkgrid.configure(HowManyQuestion1,I0.but,I1.but,I2.but,I3.but,I4.but,sticky="w"))

    Try(frame2 <- tkframe(ttIfDialog,relief="groove",borderwidth=2))
    Try(fractionLabel <- tklabel(frame2,text="q-value threshold",font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(fractionLabel,sticky="w"))
    Try(tkgrid.configure(fractionLabel,sticky="w"))
    Try(fractionTcl <- tclVar("1"))
    Try(F1.but <- tkradiobutton(frame2,text="0.005",variable=fractionTcl,value=0.005,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F2.but <- tkradiobutton(frame2,text="0.01",variable=fractionTcl,value=0.01,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F3.but <- tkradiobutton(frame2,text="0.05",variable=fractionTcl,value=0.05,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F4.but <- tkradiobutton(frame2,text="0.1",variable=fractionTcl,value=0.1,font=.affylmGUIglobals$affylmGUIfont2))
    Try(F5.but <- tkradiobutton(frame2,text="none",variable=fractionTcl,value=1,font=.affylmGUIglobals$affylmGUIfont2))

    Try(tkgrid(F1.but,sticky="w"))
    Try(tkgrid(F2.but,sticky="w"))
    Try(tkgrid(F3.but,sticky="w"))
    Try(tkgrid(F4.but,sticky="w"))
    Try(tkgrid(F5.but,sticky="w"))
    Try(tkgrid.configure(fractionLabel,F1.but,F2.but,F3.but,F4.but,F5.but,sticky="w"))

    Try(onOK <- function()
    {
         Try(ReturnVal1 <- as.numeric(tclvalue(thresholdTcl)))
         Try(ReturnVal2 <- as.numeric(tclvalue(fractionTcl)))
         Try(ReturnVal <<- paste(ReturnVal1, ReturnVal2, sep=";"))
         Try(tkgrab.release(ttIfDialog))
         Try(tkdestroy(ttIfDialog))
         Try(tkfocus(.affylmGUIglobals$ttMain))
    })

    Try(frame3 <- tkframe(ttIfDialog,borderwidth=2))
    Try(onCancel <- function() {Try(ReturnVal <<- ""); Try(tkgrab.release(ttIfDialog));Try(tkdestroy(ttIfDialog));Try(tkfocus(.affylmGUIglobals$ttMain))})
    Try(OK.but <-tkbutton(frame3,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
    Try(Cancel.but <-tkbutton(frame3,text=" Cancel ",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))

    Try(tkgrid(tklabel(frame3,text="    "),OK.but,Cancel.but,tklabel(frame3,text="    ")))

    Try(tkgrid(tklabel(ttIfDialog,text="    "),frame1,frame2,tklabel(ttIfDialog,text="  ")))
    Try(tkgrid(tklabel(ttIfDialog,text="    ")))
    Try(tkgrid(tklabel(ttIfDialog,text="    "),frame3,tklabel(ttIfDialog,text="  ")))
    Try(tkgrid(tklabel(ttIfDialog,text="    ")))
    Try(tkgrid.configure(frame1,frame3,sticky="w"))

    Try(tkfocus(ttIfDialog))
    Try(tkbind(ttIfDialog, "<Destroy>", function() {Try(tkgrab.release(ttIfDialog));Try(tkfocus(.affylmGUIglobals$ttMain));}))
    Try(tkwait.window(ttIfDialog))
    Try(if(ReturnVal==""){return()})
    Try(tmp<-strsplit(ReturnVal, ";"))
    Try(q.value <- as.numeric(tmp[[1]][2]))
    Try(fc <- as.numeric(tmp[[1]][1]))	
	
	Try(gene.up <- intersect(which(gene.diff$q_value <= q.value),which(gene.diff$log2_fold_change >= fc)))
	Try(up <- gene.diff[gene.up,])
	Try(all.fpkm<-fpkm(CDS(cuff)))
	Try(all1 <- all.fpkm[seq(1, dim(all.fpkm)[1], by=2),])
	Try(all2 <- all.fpkm[seq(2, dim(all.fpkm)[1], by=2),])
	Try(all.fpkm <- cbind(all1,all2))
	Try(fpkmmat.up <- all.fpkm[which(all.fpkm$CDS_id %in%  up$CDS_id),c(1:6,8:12)])
	Try(fpkmmat.up <- fpkmmat.up[order(fpkmmat.up$CDS_id),])
	Try(ann.all <- annotation(CDS(cuff)))
	Try(ann.all <- ann.all[,c(1,4:7)])
	Try(ann.up <- ann.all[which(ann.all$CDS_id %in% up$CDS_id),])
	Try(ann.up <- ann.up[order(ann.up$CDS_id),])
	Try(fpkmmat.up <- fpkmmat.up[which(fpkmmat.up$CDS_id%in%ann.up$CDS_id),])
	
	if(identical(fpkmmat.up$CDS_id, ann.up$CDS_id)){
	   Try(fpkmmat.up <- cbind(fpkmmat.up, 	ann.up[,2:5]))
	} else (Try(cat("\nAnnotation and up fpkm gene_id are not identical!\n")))
	if(identical(fpkmmat.up$CDS_id, up$CDS_id)){
	   Try(fpkmmat.up <- cbind(fpkmmat.up, 	up[,7:10]))
	} else {Try(cat("\nup fpkm and diff gene_ids are not identical!\n"))}
	Try(fpkmmat.up <- fpkmmat.up[,c(1,12:13,2:11,14:16,19)])
	Try(write.table(fpkmmat.up, "upCDS.txt", sep="\t", row.names=FALSE))
    Try(tkmessageBox(title="DE CDSs output",message=paste("The number of UP modulated CDSs is",length(gene.up),"\nData are available in upCDS.txt"),type="ok",icon="info"))	
    

	Try(gene.dw <- intersect(which(gene.diff$q_value <= q.value),which(gene.diff$log2_fold_change <= -(fc))))
	Try(dw <- gene.diff[gene.dw,])
	Try(all.fpkm<-fpkm(CDS(cuff)))
	Try(all1 <- all.fpkm[seq(1, dim(all.fpkm)[1], by=2),])
	Try(all2 <- all.fpkm[seq(2, dim(all.fpkm)[1], by=2),])
	Try(all.fpkm <- cbind(all1,all2))
	Try(fpkmmat.dw <- all.fpkm[which(all.fpkm$CDS_id %in%  dw$CDS_id),c(1:6,8:12)])
	Try(fpkmmat.dw <- fpkmmat.dw[order(fpkmmat.dw$CDS_id),])
	Try(ann.all <- annotation(CDS(cuff)))
	Try(ann.all <- ann.all[,c(1,4:7)])
	Try(ann.dw <- ann.all[which(ann.all$CDS_id %in% dw$CDS_id),])
	Try(ann.dw <- ann.dw[order(ann.dw$CDS_id),])
	Try(fpkmmat.dw <- fpkmmat.dw[which(fpkmmat.dw$CDS_id%in%ann.dw$CDS_id),])
	if(identical(fpkmmat.dw$CDS_id, ann.dw$CDS_id)){
	   Try(fpkmmat.dw <- cbind(fpkmmat.dw, 	ann.dw[,2:5]))
	} else (Try(cat("\nAnnotation and dw fpkm gene_id are not identical!\n")))
	if(identical(fpkmmat.dw$CDS_id, dw$CDS_id)){
	   Try(fpkmmat.dw <- cbind(fpkmmat.dw, 	dw[,7:10]))
	} else {Try(cat("\ndw fpkm and diff gene_ids are not identical!\n"))}
	Try(fpkmmat.dw <- fpkmmat.dw[,c(1,12:13,2:11,14:16,19)])
	Try(write.table(fpkmmat.dw, "dwCDS.txt", sep="\t", row.names=FALSE))
    Try(tkmessageBox(title="DE CDSs output",message=paste("The number of DW modulated CDSs is",length(gene.dw),"\nData are available in dwCDS.txt"),type="ok",icon="info"))	
    
	Try(cat("The number of UP modulated genes is ",length(gene.up),"\nData are available in upCDS.txt\n"))
	Try(cat("The number of DW modulated genes is ", length(gene.dw),"\nData are available in dwCDS.txt\n"))
	Try(A <- apply(gene.diff[,5:6], 1,mean))
	Try(A <- A+1)
	Try(A <- log10(A))
	Try(M <- gene.diff$log2_fold_change)
	Try(M[which(M>10)] <- 11)
	Try(M[which(M< -10)] <- -11)
	Try(plot(A,M, pch=19, cex=0.5, xlab="A", ylab="M", main=paste("CDSs", paste(covar,collapse="-"))))
	Try(points(A[gene.up],M[gene.up], col="red", pch=19, cex=0.5))
	Try(points(A[gene.dw],M[gene.dw], col="red", pch=19, cex=0.5))
	Try(abline(h=1, col="red"))
	Try(abline(h=-1, col="green"))
	Try(setwd(myDir))	
	
	
}
########
chooseOutDir <- function(){
	Try(wd <- tclVar(getwd()))
	Try(
		if(.Platform$OS.type=="windows"){
			Try(tclvalue(wd) <- gsub("/","\\\\",tclvalue(wd)))
		}
	)
	Try(ttChooseDir <- tktoplevel(.affylmGUIglobals$ttMain))
	Try(tkwm.title(ttChooseDir,"Choose Output directory"))
	Try(tkwm.deiconify(ttChooseDir))
	Try(tkgrab.set(ttChooseDir))
	Try(tkgrid(tklabel(ttChooseDir,text="    ")))
	Try(label1 <- tklabel(ttChooseDir,text="Choose Output directory:",font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(tklabel(ttChooseDir,text="    "),label1,sticky="w"))
	Try(tkgrid.configure(label1,columnspan=3))
	Try(tkgrid(tklabel(ttChooseDir,text="    ")))
	#
	#
	Try(
		onBrowse <- function(){
			Try(if(file.exists(gsub("\\\\","/",tclvalue(wd)))) initialdir<-gsub("\\\\","/",tclvalue(wd)) else initialdir<-getwd())
			Try(dir1 <- tclvalue(tkchooseDirectory(title="Please choose the output dir for tophat data",initialdir=initialdir)))
			Try(if(nchar(dir1)>0) tclvalue(wd) <- dir1)
			Try(
				if(.Platform$OS.type=="windows"){
					Try(tclvalue(wd) <- gsub("/","\\\\",tclvalue(wd)))
				}
			)
		} #end of onBrowse <- function()
	)# end of Try
	#
	#
	Try(ReturnVal <- "")
	#
	#
	Try(
		onOK <- function(){
			Try(DirChosen <- tclvalue(wd))
			Try(tkgrab.release(ttChooseDir))
			Try(tkdestroy(ttChooseDir))
			Try(DirChosen <- gsub("\\\\","/",DirChosen))
			Try(ReturnVal <<- DirChosen)
		} #end of onOK <- function()
	)
	#
	#
	Try(
		onCancel <- function(){
			Try(tkgrab.release(ttChooseDir));
			Try(tkdestroy(ttChooseDir))
		} #end of onCancel <- function()
	) #end of try
	#
	#
	Try(Browse.but <- tkbutton(ttChooseDir,text="Browse",command=onBrowse,font=.affylmGUIglobals$affylmGUIfont2))
	Try(OK.but <- tkbutton(ttChooseDir,text="    OK		",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
	Try(Cancel.but <- tkbutton(ttChooseDir,text=" Cancel ",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))
	#
	Try(entry1 <- tkentry(ttChooseDir,textvariable=wd,width=40,font=.affylmGUIglobals$affylmGUIfont2))
	#
	Try(tkgrid(tklabel(ttChooseDir,text="    "),entry1))
	Try(tkgrid.configure(entry1,columnspan=3))
	Try(tkgrid(tklabel(ttChooseDir,text="    "),row=3,column=4))
	Try(tkgrid(Browse.but,row=3,column=5))
	Try(tkgrid(tklabel(ttChooseDir,text="    "),row=3,column=6))
	Try(tkgrid(tklabel(ttChooseDir,text="    ")))
	Try(tkgrid(tklabel(ttChooseDir,text="    "),tklabel(ttChooseDir,text="    "),OK.but,Cancel.but))
	Try(tkgrid.configure(Cancel.but,sticky="w"))
	Try(tkgrid(tklabel(ttChooseDir,text="    ")))
	#
	Try(tkfocus(entry1))
	Try(tkbind(ttChooseDir,"<Destroy>",function()tkgrab.release(ttChooseDir)))
	Try(tkbind(entry1,"<Return>",onOK))
	Try(tkwait.window(ttChooseDir))
	Try(tkfocus(.affylmGUIglobals$ttMain))
	#
	return(ReturnVal)
}
############
chooseInDir <- function(){
	Try(wd <- tclVar(getwd()))
	Try(
		if(.Platform$OS.type=="windows"){
			Try(tclvalue(wd) <- gsub("/","\\\\",tclvalue(wd)))
		}
	)
	Try(ttChooseDir <- tktoplevel(.affylmGUIglobals$ttMain))
	Try(tkwm.title(ttChooseDir,"Choose Input directory"))
	Try(tkwm.deiconify(ttChooseDir))
	Try(tkgrab.set(ttChooseDir))
	Try(tkgrid(tklabel(ttChooseDir,text="    ")))
	Try(label1 <- tklabel(ttChooseDir,text="Choose Input directory:",font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(tklabel(ttChooseDir,text="    "),label1,sticky="w"))
	Try(tkgrid.configure(label1,columnspan=3))
	Try(tkgrid(tklabel(ttChooseDir,text="    ")))
	#
	#
	Try(
		onBrowse <- function(){
			Try(if(file.exists(gsub("\\\\","/",tclvalue(wd)))) initialdir<-gsub("\\\\","/",tclvalue(wd)) else initialdir<-getwd())
			Try(dir1 <- tclvalue(tkchooseDirectory(title="Please choose the dir containing the fastq files to be analysied by TopHat",initialdir=initialdir)))
			Try(if(nchar(dir1)>0) tclvalue(wd) <- dir1)
			Try(
				if(.Platform$OS.type=="windows"){
					Try(tclvalue(wd) <- gsub("/","\\\\",tclvalue(wd)))
				}
			)
		} #end of onBrowse <- function()
	)# end of Try
	#
	#
	Try(ReturnVal <- "")
	#
	#
	Try(
		onOK <- function(){
			Try(DirChosen <- tclvalue(wd))
			Try(tkgrab.release(ttChooseDir))
			Try(tkdestroy(ttChooseDir))
			Try(DirChosen <- gsub("\\\\","/",DirChosen))
			Try(ReturnVal <<- DirChosen)
		} #end of onOK <- function()
	)
	#
	#
	Try(
		onCancel <- function(){
			Try(tkgrab.release(ttChooseDir));
			Try(tkdestroy(ttChooseDir))
		} #end of onCancel <- function()
	) #end of try
	#
	#
	Try(Browse.but <- tkbutton(ttChooseDir,text="Browse",command=onBrowse,font=.affylmGUIglobals$affylmGUIfont2))
	Try(OK.but <- tkbutton(ttChooseDir,text="    OK		",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
	Try(Cancel.but <- tkbutton(ttChooseDir,text=" Cancel ",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))
	#
	Try(entry1 <- tkentry(ttChooseDir,textvariable=wd,width=40,font=.affylmGUIglobals$affylmGUIfont2))
	#
	Try(tkgrid(tklabel(ttChooseDir,text="    "),entry1))
	Try(tkgrid.configure(entry1,columnspan=3))
	Try(tkgrid(tklabel(ttChooseDir,text="    "),row=3,column=4))
	Try(tkgrid(Browse.but,row=3,column=5))
	Try(tkgrid(tklabel(ttChooseDir,text="    "),row=3,column=6))
	Try(tkgrid(tklabel(ttChooseDir,text="    ")))
	Try(tkgrid(tklabel(ttChooseDir,text="    "),tklabel(ttChooseDir,text="    "),OK.but,Cancel.but))
	Try(tkgrid.configure(Cancel.but,sticky="w"))
	Try(tkgrid(tklabel(ttChooseDir,text="    ")))
	#
	Try(tkfocus(entry1))
	Try(tkbind(ttChooseDir,"<Destroy>",function()tkgrab.release(ttChooseDir)))
	Try(tkbind(entry1,"<Return>",onOK))
	Try(tkwait.window(ttChooseDir))
	Try(tkfocus(.affylmGUIglobals$ttMain))
	#
	return(ReturnVal)
}

Try the oneChannelGUI package in your browser

Any scripts or data that you put into this service are public.

oneChannelGUI documentation built on Nov. 17, 2017, 11:02 a.m.