R/exonmenu.R

Defines functions saveFiltered erankProdAltSplFilter crosshybFilter simFilter gettingEG mapPSR mappingPSR runningJetta nternalLoop cosie cosieWrapper resize gettingOneEG

Documented in cosieWrapper crosshybFilter erankProdAltSplFilter runningJetta simFilter

#set of functions, directly/indirectly involved, in oneChannelGUI exonmenu
#oneChannelGUI AptMidas runs the Affymetrix APT MiDAS program to detect putative alternative splicing, works at exon level only
           #contains libraryFilesDir present in filemenu.R
           #         .aptDir present in filemenu.R
#oneChannelGUI spliceIndex calculates the spliceIndex, the SI calculation without any filter is too long.
#oneChannelGUI erankProdAltSpl calculates p-values by RankProd for the rpesence of differentially expressed exons, work on the SI or raw exon-level intensities
#oneChannelGUI inspecting.splice.index plots on a PDF file the behaviour of SI, i.e. evaluates graphically the rpesence of alternative splcing, at gene level on a set of transcripts derived for  some filtering procedure
#oneChannelGUI inspecting.one.splice.index 
#oneChannelGUI  midasFilter filters gene/exon level data by MiDAS p-values
#oneChannelGUI  erankProdAltSplFilter  filters gene/exon level data by RankProd p-values (to be made it will use the association of core gene/exon level ids present in data)
#RETIRED oneChannelGUI  crosshybFilter this filter uses crooshyb or xhyb data to remove cross hybridizing exon probe sets see their help for more info
#oneChannelGUI  simFilter this function filters gene/exon data on the basis of the absolute SI mean/min difference
#RETIRED oneChannelGUI  consistentFilter this function filters gene/exon data on the basis of p-value below a user define value common between midas and RP and on the basis of a SI mean average difference
#oneChannelGUI  consistentFilters this function filters gene/exon data on the basis of multiple options
#RETIRED embedded in EG2probeset oneChannelGUI acc2probeset this function creat a file where acc are associated to a set of glevel exon probe sets
#oneChannelGUI EG2probeset this function associate Entrez gene id to glevel exon array probe sets
#RETIRED oneChannelGUI mapping2ensembl this function will associate exon level data to exons of ensembl genes using the exon probe sets target sequence present on RRE
#RETIRED oneChannelGUI exonsSpecific2as this function associates to the gene exons to the various alternative isoforms
#RETIRED oneChannelGUI splicingIsoformSpecific this function selecte the exons from mapping2ensembl which are signifcantly spliced and isoform specific
#oneChannelGUI mapping2RefSeq This function uses RRE database to associate differentially expressed exon-level ids to NCBI gene exons
#oneChannelGUI .eprobesetsOnmRNA internal function for blast output reformatting
#oneChannelGUI mapping2exon This function retireve gene structure from RRE and map on exon the exon-level probe set associated to a spliced transcript detected by mapping2RefSeq
#oneChannelGUI retrievePSRseq This function retrieve and save exon level probe slection regions associated to a list of specific exon-probe sets
#oneChannelGUI runningJetta This function detect alternative splicing events using the jetta library. Further info at 
#oneChannelGUI variantSI    This function filters ASE exon-ids on the basis of variant exons annotaiton available in oneChannelGUI and produces a table taht cam be visualized on genom browser
#oneChannelGUI plotVariantSI interface to UCSC browser
#oneChannelGUI makeBED15 creating a file to be uploaded on the UCSC genome browser.
#RETIRED oneChannelGUI cosieWrapper produced a corrected exon and gene-level signal from sequence driven effect data are realted to hg18 and never updated
#              .cosie adapted from the article of Gaidatzis Nucleic Acids Research, 2009, 1–10
#Alternative splcing detection with Limma. Analysis is done on signal intensities not on SI
#oneChannelGUI limmaExons fit the limma model derived from Shah and Pallas work BMC Bioinformatics. 2009 Jan 20;10:26.
#oneChannelGUI exonContrasts defines the contrasts and make ebayes
#              embeds: .rawpCheckExons  check the raw p-value distribution to see if BH correction method can be applyed
#                      .exonTopTable extract p-values of regularized t-test
#oneChannelGUI exonTopTableExtract   a filter function to extract spliced exons on the basis of limma regularized t-test p values
#oneChannelGUI genomePlot using GenomeGraphs to generate and high quality immage of a splicing event
#oneChannelGUI retrievePSRseq1gid  retrieve PSR give a gene-level id
################################################################################
#graphical interface to APT midas for alternative splicing detection
"AptMidas" <- function(){
          #error if no data are loaded
          Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
          if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
          }    
          #########################
     Try(cosie.Available <- get("cosie.Available",affylmGUIenvironment))
     if(cosie.Available){
              Try(tkmessageBox(title="Exons analysis",message="COSIE available!	Since COSIE model was applied to exon-level dataMiDAS cannot be run. \nPlease, use instead Limma available in Exon Menu.",type="ok",icon="info"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
    
     }
     #loading gene/exon data
     Try(NormalizedAffyData.Available <- get("NormalizedAffyData.Available", env=affylmGUIenvironment))
     Try(exonAffyData.Available <- get("exonAffyData.Available", env=affylmGUIenvironment))

     if(NormalizedAffyData.Available & exonAffyData.Available){
         Try(Targets <- get("Targets",envir=affylmGUIenvironment))
         Try(libDir.Available <- get("libDir.Available", env=affylmGUIenvironment))
         #check if the library data for exon analysis has been set
         if (libDir.Available){ 
                                 Try(whichLib <- get("whichLib", env=affylmGUIenvironment)) 
                                 Try(libDir <- get("libDir", env=affylmGUIenvironment))
                                 Try(content.libDir <- dir(libDir))
                                 #Try(libDir <- paste(libDir, "/", sep=""))
                                 Try(exonlib.name <- paste(libDir, content.libDir[intersect(grep('.mps$',content.libDir), intersect(grep(whichLib[[1]][1],content.libDir), grep(whichLib[[1]][2],content.libDir)))], sep=""))
         } else {
         #select the directory in which are present the library data for expression console analysis
                                 Try(libDir <- "")
                                 Try(libDir <- libraryFilesDir())
                                 if(libDir != ""){
                                                     Try(libDir <- paste(libDir, "/", sep=""))
                                                     Try(content.libDir <- dir(libDir))
                                                     if(length(grep(tmp[[1]][1],content.libDir)) == 0){
                                                            Try(tkmessageBox(title="Gene/exon libraries Dir",message=paste("The selected folder does not contain ", tmp[[1]][1], " library files!\n Download them from Affymetrix web site!", sep=""),icon="error"))
                                                            Try(return())
                                                     }
                                                     Try(ctrl.name <- paste(libDir, content.libDir[intersect(grep(tmp[[1]][1],content.libDir), grep('controls.ps$',content.libDir))], sep=""))
                                                     Try(ctrl <- read.table(ctrl.name, sep="\t", header=T, as.is=T))
                                                     Try(exonlib.name <- paste(libDir, content.libDir[intersect(grep('.mps$',content.libDir), intersect(grep(tmp[[1]][1],content.libDir), grep(tmp[[1]][2],content.libDir)))], sep=""))
                                                     Try(exonlib <- read.table(exonlib.name, sep="\t", header=T, as.is=T))
                                                     Try(ctrl.exonlib <- list("controls"=ctrl, "exon.library"=exonlib))
                                                     Try(assign("libDir.Available",TRUE,affylmGUIenvironment))
                                                     Try(assign("libDir", tt ,affylmGUIenvironment))#locate here the library files as a list of data.frames
                                                     Try(assign("exprConsoleLibs.Available",TRUE,affylmGUIenvironment))
                                                     Try(assign("exprConsoleLibs", ctrl.exonlib ,affylmGUIenvironment))
                                                     Try(cat(""))
                                                  } else {
                                                           Try(tkmessageBox(title="Gene/exon libraries Dir",message="You have not defined the directory where gene/exon libraries are installed!",icon="error"))
			                                                     return()
                                                    }
  
         }
         #check id APT library is installed
         Try(aptDir.Available <- get("aptDir.Available", env=affylmGUIenvironment))
         if(aptDir.Available){ 
                               Try(aptDir <- get("aptDir", env=affylmGUIenvironment)) 
         } else{
                               Try(whereApt <- "")
                               Try(whereApt <- .aptDir())
                               if(whereApt != ""){
                               #APT dir
                               if(length(grep("apt-probeset-summarize", dir(paste(whereApt, "/bin", sep="")))) == 0){
                                                  Try(tkmessageBox(title="APT tools dir ",message="You have not correctly defined the main folder where APT tools are located!",icon="error"))
                                                  Try(return())
                               } 
                               Try(assign("aptDir.Available",TRUE,affylmGUIenvironment))
                               Try(assign("aptDir", whereApt ,affylmGUIenvironment))
                                                                
               }
         }                                           
         Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
         Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
         
         #defining the temp file containing target info for apt
         Try(tempTarget <- tempfile(pattern = "target", tmpdir = getwd()))
         Try(tempTarget <- sub( "\\\\","/",tempTarget)) #changing double backslach with slash
         Try(write.table(Targets[,2:3], tempTarget, sep="\t", row.names =F, col.names = c("cel_files", "group_id"))) 

         #defining the file with the gene level data
         Try(tempGlevel <- tempfile(pattern = "glevels", tmpdir = getwd()))
         Try(tempGlevel <- sub( "\\\\","/",tempGlevel)) #changing double backslach with slash
         Try(gTmp<- as.data.frame(exprs(NormalizedAffyData)))
         Try(gTmp <- cbind(as.character(rownames(gTmp)), gTmp))
         Try(colnames(gTmp)[1] <- "probeset_id")
         Try(write.table(gTmp, tempGlevel, sep="\t", row.names=F))
  
         #defining the file with the exon level data
         Try(tempElevel <- tempfile(pattern = "elevels", tmpdir = getwd()))
         Try(tempElevel <- sub( "\\\\","/",tempElevel)) #changing double backslach with slash
         Try(eTmp<- as.data.frame(exprs(exonAffyData)))
         Try(eTmp <- cbind(as.character(rownames(eTmp)), eTmp))
         Try(colnames(eTmp)[1] <- "probeset_id")
         Try(write.table(eTmp, tempElevel, sep="\t", row.names=F))

          
          #defining the out dir
         Try(tempMidas <- tempfile(pattern = "outMidas", tmpdir = getwd()))#creating a temp outfile
         Try(tempMidas <- sub( "\\\\","/",tempMidas)) #changing double backslach with slash
         
         #Try(cat("\n",paste(aptDir,"/bin/apt-midas ", " --cel-files ", tempTarget, " -g ", tempGlevel, " -e ", tempElevel, " -m ", exonlib.name, " -o ",tempMidas, sep=""),"\n"))

         Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
         Try(cat("\nMidas alternative splice analysis started........\n"))
         Try(system(paste(aptDir,"/bin/apt-midas "," --cel-files ", tempTarget, " -g ", tempGlevel, " -e ", tempElevel, " -m ", exonlib.name, " -n " , " -o ",tempMidas, " --no-logtrans",sep=""), wait = T))
         Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
         Try(cat("....saving MiDAS p-values\n"))
         #check if all files will produce an header of 16 rows
         Try(midas.p <- read.table(paste(tempMidas, "/midas.pvalues.txt", sep=""), header=T, skip=16, as.is=T))
         assign("midas.p" , midas.p, affylmGUIenvironment)
         assign("midas.p.Available" , TRUE, affylmGUIenvironment)
         Try(tkdelete(.affylmGUIglobals$mainTree,"AptMidas.Status"))
         Try(tkinsert(.affylmGUIglobals$mainTree,"end","AptMidas","AptMidas.Status" ,text="Available",font=.affylmGUIglobals$affylmGUIfontTree))
         #col 1 exon probe ids, col 2 gene probe ids
#        Try(cat("....saving Splice Index values\n"))
#        Try(spliceIdx <- read.table(paste(tempMidas, "/midas.normalized.txt", sep=""), header=T, skip=16, as.is=T))
#        Try(which.duplicated <- duplicated(spliceIdx[,1]))
#        Try(spliceIdx <- spliceIdx[!which.duplicated,])
#        Try(assign("spliceIndexData",spliceIdx,affylmGUIenvironment))
        #the first two columns are exon probe set ids and transcript ids 
#        Try(assign("spliceIndexData.Available",TRUE,affylmGUIenvironment))
#        Try(tkdelete(.affylmGUIglobals$mainTree,"spliceIndex.Status"))            
#        Try(tkinsert(.affylmGUIglobals$mainTree,"end","spliceIndex","spliceIndex.Status" ,text="Available",font=.affylmGUIglobals$affylmGUIfontTree))
        Try(cat("....Midas alternative splice analysis ended\n"))
        Try(hist(affylmGUIenvironment$midas.p[,3], main="MiDAS Splice Index p-values"))
 
        Try(tkmessageBox(title="APT MiDAS",message="The histogram of MiDAS p-values is shown in the main R window."))
         
   }
}
################################################################################

#Genomewide analysis of mRNA processing in yeast using splicing-specific microarrays, Clark,
#T, Sugnet, C, Ares, M. Science 2002 May 3;296(5569):907-10
#converting exon expression data in splice index
"spliceIndex" <- function(){
     Try(cat("\nSplice Index calculation started ......\n It takes some time, be patient!\n"))
     Try(ptm <- proc.time())
     #error if no data are loaded
     Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
     if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
    }    
    #########################
    Try(cosie.Available <- get("cosie.Available",affylmGUIenvironment))
    if(cosie.Available){
              Try(tkmessageBox(title="Exons analysis",message="COSIE available!	Since COSIE model was applied to exon-level data. \nSplice Index was generated by COSIE.",type="ok",icon="info"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
    
    }
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
    #start also present in cosieWrapper
    Try(exprConsoleLibs <- get("exprConsoleLibs", env=affylmGUIenvironment))
    Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
    Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment) )
    Try(spliceIdx <- NULL)#splice index
    Try(spliceIdxIds <- NULL)#exon and gene ids
    
    Try(exon.counts <- 0)
    for (i in 1: dim(exprs(NormalizedAffyData))[1]){
             #catching oexon info related to a specific gene probeset_id
             Try(geneExonsIds <- as.vector(unlist(strsplit(exprConsoleLibs$exon.library$"probeset_list"[
                            which(as.character(exprConsoleLibs$exon.library$"probeset_id")==
                            featureNames(NormalizedAffyData)[i])], split=" "))))
             Try(exon.counts <- exon.counts +  length(geneExonsIds))
             Try(geneExons <- exprs(exonAffyData[which(featureNames(exonAffyData)%in%geneExonsIds),]))
             Try(gene.exprs <- as.vector(unlist(exprs(NormalizedAffyData[featureNames(NormalizedAffyData)[i],]))))
             Try(gene.exprs <- matrix(rep(gene.exprs, dim(geneExons)[1]), ncol=dim(geneExons)[2], byrow = TRUE))
             Try(spliceIdx <- rbind(spliceIdx, (geneExons -  gene.exprs)))#this is an exon matrix
             #adding exon and gene ids to be identical in structure to the midas normalized expr output
             Try(geneGeneIds <- rep(featureNames(NormalizedAffyData)[i], length(geneExonsIds)))
             Try(tmpIds <- cbind(geneExonsIds, geneGeneIds))
             Try(spliceIdxIds <- rbind(spliceIdxIds, tmpIds))
             
              
    }        
    Try(spliceIdxIds <- spliceIdxIds[which(spliceIdxIds[,1]%in%dimnames(spliceIdx)[[1]]),])
    Try(spliceIdxIds <- spliceIdxIds[order(spliceIdxIds[,1]),])
    Try(spliceIdx <- spliceIdx[order(dimnames(spliceIdx)[[1]]),])
    if(identical(dimnames(spliceIdx)[[1]], spliceIdxIds[,1])){
              Try(spliceIdx <- data.frame(spliceIdxIds, spliceIdx))
    } else {
              Try(tkmessageBox(title="Exons analysis",message="Splice Index calculation.\nInternal error 888, please contact the oneChannelGUI package maintainer!",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())

    }
    #endo also present in cosieWrapper 
    Try(assign("spliceIndexData",spliceIdx,affylmGUIenvironment))
    Try(assign("spliceIndexData.Available",TRUE,affylmGUIenvironment))
    Try(tkdelete(.affylmGUIglobals$mainTree,"spliceIndex.Status"))            
    Try(tkinsert(.affylmGUIglobals$mainTree,"end","spliceIndex","spliceIndex.Status" ,text="Available",font=.affylmGUIglobals$affylmGUIfontTree))
    Try(cat("\n Analyzed exons ", exon.counts, "\n"))
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
    Try(usedtime <- proc.time() - ptm)
    Try(cat("\nUsed CPU time (min) ",usedtime[3]/60,"\n"))
     Try(cat("\nSplice Index calculation ended\n")) 
}
################################################################################

#detecting splice index using rank product tool
#works at exon level
"erankProdAltSpl" <-function(){
   Try(ptm <- proc.time())
 #  require(RankProd) || stop("library RankProd could not be found !")
   #error if no data are loaded
   Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
   if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
  }    
  #########################
  #selecting the starting material SI or raw exon intensities
  Try(ttCompMethod <- tktoplevel(.affylmGUIglobals$ttMain))
  Try(tkwm.deiconify(ttCompMethod))
  Try(tkgrab.set(ttCompMethod))
  Try(tkfocus(ttCompMethod))
  Try(tkwm.title(ttCompMethod,"Exon level Rank Product analysis: Splice Index or raw intensity?"))
	
 Try(tkgrid(tklabel(ttCompMethod,text="    ")))
 Try(ttCompMethodTcl <- tclVar("raw"))
 Try(rbPS <- tkradiobutton(ttCompMethod,text="Raw exon-level log2(intensity)",variable=ttCompMethodTcl,value="raw",font=.affylmGUIglobals$affylmGUIfont2))
 Try(rbEG<-tkradiobutton(ttCompMethod,text="Splice Index",variable=ttCompMethodTcl,value="si",font=.affylmGUIglobals$affylmGUIfont2))
  
  Try(tkgrid(tklabel(ttCompMethod,text="    "),rbPS))
  Try(tkgrid(tklabel(ttCompMethod,text="    "),rbEG))
  Try(cosie.Available <- get("cosie.Available",affylmGUIenvironment))
  Try(if(cosie.Available==TRUE)
  {
    Try(tkconfigure(rbEG,state="disabled"))
  })
  
  Try(tkgrid.configure(rbPS,rbEG,columnspan=2,sticky="w"))
  Try(tkgrid(tklabel(ttCompMethod,text="    "),tklabel(ttCompMethod,text="    ")))
  Try(CompVal <- "")
  Try(onCancel <- function() {Try(CompVal <<- "");Try(tkgrab.release(ttCompMethod));Try(tkdestroy(ttCompMethod));Try(tkfocus(.affylmGUIglobals$ttMain)); Try(return())})
  Try(onOK <- function() {Try(CompVal <<- tclvalue(ttCompMethodTcl));Try(tkgrab.release(ttCompMethod));Try(tkdestroy(ttCompMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})

Try(OK.but     <- tkbutton(ttCompMethod,text="OK",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
Try(Cancel.but <- tkbutton(ttCompMethod,text="Cancel",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))

Try(tkgrid(tklabel(ttCompMethod,text="    "),OK.but,Cancel.but,tklabel(ttCompMethod,text="    ")))
Try(tkgrid.configure(OK.but,sticky="e"))
Try(tkgrid.configure(Cancel.but,sticky="w"))
Try(tkgrid(tklabel(ttCompMethod,text="    ")))

Try(tkbind(ttCompMethod,"<Destroy>",function() {CompVal <- "";Try(tkgrab.release(ttCompMethod));Try(tkfocus(.affylmGUIglobals$ttMain));}))
Try(tkbind(OK.but, "<Return>",onOK))
Try(tkbind(Cancel.but, "<Return>",onCancel))      
Try(tkwait.window(ttCompMethod))
        
  
  #########################

          Try(targets <-  affylmGUIenvironment$Targets$Target)
          Try(targets <- strsplit(targets, "_"))
          Try(targets <- t(as.data.frame(targets)))
          if(dim(targets)[2]==1){
              Try(target.unique <- unique(targets[,1]))
              Try(cl <- rep(0,dim(targets)[1]))
              Try(cl[which(targets[,1]==target.unique[2])] <- 1)
              Try(origin <- rep(1,dim(targets)[1]))
          } else if(dim(targets)[2]==2){
               Try(target.unique <- unique(targets[,1]))
               Try(cl <- rep(0,dim(targets)[1]))
               Try(cl[which(targets[,1]==target.unique[2])] <- 1)
               Try(origin <- as.numeric(targets[,2]))
          } else{
             Try(tkmessageBox(title="Alternative splicing detection by RankProd analysis",message="The target file is not in the right format!\nCovariates should be linked to their origin (a number) by an underscore.\nIf the origin is only one it is not mandatory to indicate it"))
             return()
          }  

   if(length(target.unique) == 2){
   ##defining the number of permutations##################
   Try(ReturnVal <<- "")
   Try(ttIfDialog<-tktoplevel(.affylmGUIglobals$ttMain))
   Try(tkwm.deiconify(ttIfDialog))
   Try(tkgrab.set(ttIfDialog))
   Try(tkfocus(ttIfDialog))
   Try(tkwm.title(ttIfDialog,"RP permutations"))
   Try(tkgrid(tklabel(ttIfDialog,text="    ")))
   
   Try(frame1 <- tkframe(ttIfDialog,relief="groove",borderwidth=2))
   Try(HowManyQuestion1 <- tklabel(frame1,text="Select the Number of permutations",font=.affylmGUIglobals$affylmGUIfont2))
   Try(tkgrid(HowManyQuestion1))
   Try(tkgrid.configure(HowManyQuestion1,columnspan=2,sticky="w"))
   Try(thresholdTcl <- tclVar("100"))
   Try(I1.but  <- tkradiobutton(frame1,text="100",variable=thresholdTcl,value="100",font=.affylmGUIglobals$affylmGUIfont2))
   Try(I2.but  <- tkradiobutton(frame1,text="250",variable=thresholdTcl,value="250",font=.affylmGUIglobals$affylmGUIfont2))
   Try(I3.but  <- tkradiobutton(frame1,text="500",variable=thresholdTcl,value="500",font=.affylmGUIglobals$affylmGUIfont2))
   Try(I4.but  <- tkradiobutton(frame1,text="1000",variable=thresholdTcl,value="1000",font=.affylmGUIglobals$affylmGUIfont2))
           
   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,I1.but,I2.but,I3.but,I4.but,sticky="w"))

   Try(onOK <- function()
   {
       Try(ReturnVal <<- as.character(tclvalue(thresholdTcl)))
       Try(tkgrab.release(ttIfDialog))
       Try(tkdestroy(ttIfDialog))
       Try(tkfocus(.affylmGUIglobals$ttMain))
   })

   Try(frame3 <- tkframe(ttIfDialog,borderwidth=2))
   Try(onCancel <- function() {
       Try(tkgrab.release(ttIfDialog))
       Try(tkdestroy(ttIfDialog))
       Try(tkfocus(.affylmGUIglobals$ttMain))
       Try(return())
   })
   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,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))
#######################################################
   
   
   
      if(CompVal=="si"){
              Try(spliceIndexData.Available <- get("spliceIndexData.Available", env=affylmGUIenvironment) )
              if(spliceIndexData.Available){
                   Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment) )#is amatrix
                   Try(spliceIndexData.ids <- spliceIndexData[,1:2])
                   Try(spliceIndexData.ids <- paste(as.character(spliceIndexData[,1]),as.character(spliceIndexData[,2]), sep="|"))
                   Try(rownames(spliceIndexData) <- spliceIndexData.ids)
                   Try(spliceIndexData <- spliceIndexData[,3:dim(spliceIndexData)[2]])

                   Try(mean.class1 <- apply(spliceIndexData[,which(cl==0)], 1, mean))
                   Try(mean.class2 <- apply(spliceIndexData[,which(cl==1)], 1, mean))
                   Try(deltaSI <- mean.class2 - mean.class1)
                   Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
                   #Try(outTableAltSpl <- NULL)
                   if(dim(targets)[2]==1){   
                                 Try(RP.out <- RP(spliceIndexData, cl, num.perm = as.numeric(ReturnVal), logged = TRUE, na.rm = FALSE, plot = FALSE, rand = 1234567))#gene.names = rownames(spliceIndexData)
                   }     else if(dim(targets)[2]==2){
                                 Try(RP.out <- RPadvance(spliceIndexData, cl, origin, num.perm = as.numeric(ReturnVal), logged = TRUE, na.rm = FALSE, plot = FALSE, rand = 1234567, ))#gene.names = rownames(spliceIndexData)
                   }
                   
                  Try(outTableAltSpl <- cbind(rownames(spliceIndexData), RP.out$pval[1], RP.out$pval[2], deltaSI)) #false positive predictions (pfp)  i.e. FDR
                  Try(names(outTableAltSpl) <- c("exon_transcript_id", "p-val class1 < class2", "p-val class1 > class2", "deltaSI"))
                  Try(assign("AltSplRP.e.p" , outTableAltSpl, affylmGUIenvironment))
                  Try(assign("AltSplRP.e.Available" , TRUE, affylmGUIenvironment))
                  Try(outTableAltSpl <- get("AltSplRP.e.p", affylmGUIenvironment))
                  Try(tkdelete(.affylmGUIglobals$mainTree,"AltSplRP.e.Status")) 
                  Try(tkinsert(.affylmGUIglobals$mainTree,"end","AltSplRP","AltSplRP.e.Status" ,text="Available (SI based)",font=.affylmGUIglobals$affylmGUIfontTree))
                  par(mfrow=c(1,3))
                  Try(hist(outTableAltSpl[,2], main=names(outTableAltSpl)[2], xlab=""))
                  Try(hist(outTableAltSpl[,3], main=names(outTableAltSpl)[3], xlab=""))
                  Try(hist(outTableAltSpl[,4], main=names(outTableAltSpl)[4], xlab=""))
                  Try(tkmessageBox(title="RP alternative splicing detection on SI",message="RP alternative splicing detection is finished.\nResults can be exported with the Export function in the exon menu.\nHistograms of results are available in the main R window."))
                  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
            }else {
                   Try(tkmessageBox(title="Alternative splicing detection by RankProd analysis",message="Splice Index was not yet calculated"))
            }
        } else if(CompVal=="raw"){
              Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment) )
              Try(spliceIndexData <- exprs(exonAffyData))

              Try(mean.class1 <- apply(spliceIndexData[,which(cl==0)], 1, mean))
              Try(mean.class2 <- apply(spliceIndexData[,which(cl==1)], 1, mean))
              Try(deltaSI <- mean.class2 - mean.class1)
              Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
                   #Try(outTableAltSpl <- NULL)
              if(dim(targets)[2]==1){   
              Try(RP.out <- RP(spliceIndexData, cl, num.perm = 100, logged = TRUE, na.rm = FALSE, plot = FALSE, rand = 1234567))#gene.names = rownames(spliceIndexData)
              }else if(dim(targets)[2]==2){
                                 Try(RP.out <- RPadvance(spliceIndexData, cl, origin, num.perm = 100, logged = TRUE, na.rm = FALSE, plot = FALSE, rand = 1234567, ))#gene.names = rownames(spliceIndexData)
              }
                   
              Try(outTableAltSpl <- cbind(rownames(spliceIndexData), RP.out$pval[1], RP.out$pval[2], deltaSI)) #false positive predictions (pfp)  i.e. FDR
              Try(names(outTableAltSpl) <- c("exon_transcript_id", "p-val class1 < class2", "p-val class1 > class2", "deltaIntensity"))
              Try(assign("AltSplRP.e.p" , outTableAltSpl, affylmGUIenvironment))
              Try(assign("AltSplRP.e.Available" , TRUE, affylmGUIenvironment))
              Try(outTableAltSpl <- get("AltSplRP.e.p", affylmGUIenvironment))
              Try(tkdelete(.affylmGUIglobals$mainTree,"AltSplRP.e.Status")) 
              Try(tkinsert(.affylmGUIglobals$mainTree,"end","AltSplRP","AltSplRP.e.Status" ,text="Available (Intensity based)",font=.affylmGUIglobals$affylmGUIfontTree))
              par(mfrow=c(1,3))
              Try(hist(outTableAltSpl[,2], main=names(outTableAltSpl)[2], xlab=""))
              Try(hist(outTableAltSpl[,3], main=names(outTableAltSpl)[3], xlab=""))
              Try(hist(outTableAltSpl[,4], main=names(outTableAltSpl)[4], xlab=""))
              Try(tkmessageBox(title="RP alternative splicing detection on exon-level intensity",message="RP alternative splicing detectin is finished.\nResults can be exported with the Export function in the exon menu.\nHistograms of results are available in the main R window."))
              Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
          }  
  }else {
                    #groups definition
                    Try(tkmessageBox(title="Alternative splicing detection by RankProd analysis",message="One/Multi class unpaired case analysis not implemented, yet."))
       }
       Try(usedtime <- proc.time() - ptm)
       Try(cat("\nUsed CPU time (min) ",usedtime[3]/60,"\n"))        
}
################################################################################

#the part related to model selection should be refined actually the selection of value related to se and R-squared anre not sufficiently nice

"inspecting.splice.index" <-function(){
  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
  Try(tkmessageBox(title="Exons analysis",message="P-value threshold is set by default to 0.05.",type="ok",icon="info"))
				    	
  #error if no data are loaded
  Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
  if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
  }    
  Try(spliceIndexData.Available <- get("spliceIndexData.Available", env=affylmGUIenvironment) )
  Try(midas.p.Available <- get("midas.p.Available", env=affylmGUIenvironment))
  Try(AltSplRP.e.Available <- get("AltSplRP.e.Available", env=affylmGUIenvironment))
  Try(AltSplLimma.Available <- get("AltSplLimma.Available", env=affylmGUIenvironment))                  
  if((spliceIndexData.Available & midas.p.Available) | (spliceIndexData.Available & AltSplLimma.Available)){
                   Try(Targets <- get("Targets", env=affylmGUIenvironment) )
                   Try(targets.unique <- unique(Targets$Target))
                   if(length(targets.unique)!=2){
                         Try(tkmessageBox(title="Inspecting exon profiles", message="This analysis can be applied \nonly to two groups experiments!",type="ok",icon="error"))
                         Try(return())
                   }
                   Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment) )
                   Try(exprConsoleLibs <- get("exprConsoleLibs", env=affylmGUIenvironment))
                   Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
 #####################################################################################################################
 #selecting the file containing the gene probe sets to be investigated at exon level and the output name
                  Try(tkmessageBox(title="Inspecting exon profiles", message="Open the file containing the list of gene-level probe sets\n to be inspected for the presence of alernative splicing.",type="ok",icon="info"))
                  Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
                        if(!nchar(tempFileName))
                        {
                           tkfocus(.affylmGUIglobals$ttMain)
                           return()
                        }
                        Try(mySel<-read.table(tempFileName, sep="\t", header=F, as.is=TRUE))
                        if(dim(mySel)[2]==1){
                              Try(mySel <- as.character(unlist(mySel[,1])))
                              Try(tempFileName <- as.character(unlist(strsplit(tempFileName[[1]], "/"))))
                              Try(tempFileName <- tempFileName[length(tempFileName)])
                              Try(tempFileName <- sub(".txt", "", tempFileName))
                              Try(assign("FileNameText",paste("alt.sp.out.",tempFileName,".pdf", sep=""),affylmGUIenvironment))
                        } else Try(tkmessageBox(title="Inspecting exon profiles",message=paste("File should contain\nonly a column with\nAffymetrix ids")))  

########################################################################################################################################
                   Try(FileNameText <- get("FileNameText", affylmGUIenvironment))
                   pdf(FileNameText)
                   Try(selected.altsplg <- NULL)
                   for (i in 1: length(mySel)){
                   #catching oexon info related to a specific gene probeset_id
                              Try(geneExonsIds <- as.vector(unlist(strsplit(exprConsoleLibs$exon.library$"probeset_list"[
                                     which(as.character(exprConsoleLibs$exon.library$"probeset_id")==
                                     mySel[i])], split=" "))))
#                              #transposed the exon matrix
                              Try(geneExons <- spliceIndexData[which(as.character(spliceIndexData[,1])%in%geneExonsIds),])#transpose becasue I need to add the labels
                              Try(rownames(geneExons) <- as.character(geneExons[,1]))
                              Try(geneExons <- geneExons[,3:dim(geneExons)[2]])
                              ##p.value calculation for exons
                              #adding MiDAS p-values                              
                              if(midas.p.Available){
                                    Try(midas.p <- get("midas.p", env=affylmGUIenvironment))
                                    Try(tmp <- midas.p[which(midas.p[,1]%in%geneExonsIds),c(1,3)])
                                    Try(geneExonsMiDAS <- -log10(as.numeric(tmp[,2])))
                                    Try(names(geneExonsMiDAS) <- as.character(tmp[,1]))
                                    Try(geneExonsMiDAS <- geneExonsMiDAS[order(names(geneExonsMiDAS))])
                              }
                              #plotting limma
                              if(AltSplLimma.Available){
                                    Try(limma.df <- get("AltSplLimma", env=affylmGUIenvironment))
                                    Try(tmp <- limma.df[which(limma.df[,1]%in%geneExonsIds),c(1,5)])
                                    Try(geneExonsLimma <- -log10(as.numeric(tmp[,2])))
                                    Try(names(geneExonsLimma) <- as.character(tmp[,1]))
                                    Try(geneExonsLimma <- geneExonsLimma[order(names(geneExonsLimma))])
                                    Try(tmp.myylim<- as.numeric(geneExonsLimma))
                                    Try(tmp.myylim <- tmp.myylim[which(tmp.myylim!="Inf")])
                                    Try(myylim <- max(tmp.myylim))
                                    Try(geneExonsLimma[which(geneExonsLimma=="Inf")] <-  myylim)

                                    par(mfrow=c(1,2))
                                    Try(plot(seq(1,dim(geneExons)[1]),geneExonsLimma, xlab="exon index", ylab="-log10(p-value)", pch=19,main=paste("Limma results for ",featureNames(NormalizedAffyData)[i],"\nglevel probe set", sep="")))
                                    Try(abline(h=-log10(0.05), lty=2))
                                    Try(exonlegend <- paste(seq(1,length(geneExonsLimma)), names(geneExonsLimma)))
                                    Try(exonlegend <- c("exon idx exon id", exonlegend))
                                    Try(legend(1, myylim, legend= exonlegend, cex=0.5))
                                    
                                    #mapping common alt splicing in common between MiDAS rank prod
                                    Try(whichLimma <- names(geneExonsLimma)[which(geneExonsLimma >= -log10(0.05))])
                                    if(length(whichLimma)>0){
                                        Try(altcommon1 <- paste(whichLimma,collapse = "|")) 
                                        Try(myalt <- paste(mySel[i], altcommon1, sep = "|"))
                                    } else {Try(myalt <- mySel[i])}
                                    Try(selected.altsplg <- c(selected.altsplg, myalt))
                              }
                              if(AltSplRP.e.Available & midas.p.Available){
                                    Try(AltSplRP.e.p <- get("AltSplRP.e.p", env=affylmGUIenvironment))
                                    Try(myEids <- strsplit(as.character(AltSplRP.e.p[,1]), "\\|"))
                                    Try(myEids <- sapply(myEids, function(x)x[1]))
                                    Try(AltSplRP.e.p[,1] <- myEids)
                                    Try(tmp <- AltSplRP.e.p[which(AltSplRP.e.p[,1]%in%geneExonsIds),c(1,2)])# "p-val class1 < class2" 
                                    Try(geneExonsRP1 <- -log10(as.numeric(tmp[,2])))
                                    Try(names(geneExonsRP1) <- as.character(tmp[,1]))
                                    Try(geneExonsRP1 <- geneExonsRP1[order(names(geneExonsRP1))])
                                    Try(tmp <- AltSplRP.e.p[which(AltSplRP.e.p[,1]%in%geneExonsIds),c(c(1,3))])#  "p-val class1 > class2"
                                    Try(geneExonsRP2 <- -log10(as.numeric(tmp[,2])))
                                    Try(names(geneExonsRP2) <- as.character(tmp[,1]))
                                    Try(geneExonsRP2 <- geneExonsRP2[order(names(geneExonsRP2))])
                                    par(mfrow=c(1,2))
                                    #mapping common alt splicing in common between MiDAS rank prod
                                    Try(whichMiDAS <- names(geneExonsMiDAS)[which(geneExonsMiDAS >= -log10(0.05))])
                                    Try(whichRP1 <- names(geneExonsRP1)[which(geneExonsRP1 >= -log10(0.05))])
                                    Try(whichRP2 <- names(geneExonsRP2)[which(geneExonsRP2 >= -log10(0.05))])
                                    Try(altcommon <- intersect(whichMiDAS, union(whichRP1, whichRP2)))
                                    if(length(altcommon)>0){
                                        Try(altcommon1 <- paste(altcommon,collapse = "|")) 
                                        Try(myalt <- paste(mySel[i], altcommon1, sep = "|"))
                                    } else {Try(myalt <- mySel[i])}
                                    Try(selected.altsplg <- c(selected.altsplg, myalt))
                                    #############################################################
                                    #changing inf with max value -log(pvalue)
                                    Try(tmp.myylim<- as.numeric(c(geneExonsMiDAS, geneExonsRP1, geneExonsRP2)))
                                    Try(tmp.myylim <- tmp.myylim[which(tmp.myylim!="Inf")])
                                    Try(myylim <- max(tmp.myylim))
                                    Try(geneExonsMiDAS[which(geneExonsMiDAS=="Inf")] <-  myylim)
                                    Try(geneExonsRP1[which(geneExonsRP1=="Inf")] <-  myylim)
                                    Try(geneExonsRP2[which(geneExonsRP2=="Inf")] <-  myylim)
                                    
                                    Try(plot(seq(1,length(geneExonsMiDAS)),geneExonsMiDAS, xlab="exon index", ylab="-log10(p-value)", ylim=c(0,myylim),pch=19,main=paste("MiDAS/RP results for ",featureNames(NormalizedAffyData)[i],"\nglevel probe set", sep="")))
                                    Try(abline(h=-log10(0.05), lty=2))
                                    Try(points(seq(1,length(geneExonsRP1)),geneExonsRP1, pch=24, bg="red"))
                                    Try(points(seq(1,length(geneExonsRP2)),geneExonsRP2, pch=25, bg="green"))
                                    Try(abline(v=which(names(geneExonsMiDAS)%in%altcommon), lty=2, col="yellow"))
                                    Try(exonlegend <- paste(seq(1,length(geneExonsMiDAS)), names(geneExonsMiDAS)))
                                    Try(exonlegend <- c("exon idx exon id", exonlegend))
                                    Try(legend(1, myylim, legend= exonlegend, cex=0.5))
                                    
                                    #Try(plot(geneExonsMiDAS, geneExonsRP1, pch=24, bg="red", xlab="MiDAS", ylab="RP", xlim=c(0,myylim), ylim=c(0,myylim), main="Consistency between MiDAS and RP results")) 
                                    #Try(points(geneExonsMiDAS, geneExonsRP2, pch=25, bg="green"))
                                    #Try(abline(h=-log2(0.05), lty=2))
                                    #Try(abline(v=-log2(0.05), lty=2))
                              } 
                              #defining  SI behaviour
                              Try(geneExons <- t(geneExons))#transpose becasue I need to add the labels
                              
                              Try(exonIndexLablesExons <- NULL)
                              Try(for(j in 1: dim(geneExons)[2]){
                                        exonIndexLablesExons    <-  c(exonIndexLablesExons, rep(j,dim(geneExons)[1]))
                                  }
                              )    
                             
                              Try(exonIndex <-  seq(1,dim(geneExons)[2]))#this is needed since geneExons are going to be transformed in a vector
                              Try(exonIndexLablesSamples <-  rep(Targets$Target,dim(geneExons)[2]))

                              Try(geneExons <- as.numeric(unlist(geneExons)))  #when unlisting data are unlisted on a column base!
                              if( length(geneExons) > 2 & length(targets.unique)==2){
                                      #defining the index vector for model plotting
                                           Try(index.1 <- NULL)
                                           Try(index.2 <- NULL)
                                           Try(for(j in 1: length(exonIndex)){
                                                  index.1 <-  c(index.1, intersect(which(exonIndexLablesExons==j), 
                                                                  which(exonIndexLablesSamples==targets.unique[1])))
                                                  index.2 <-  c(index.2, intersect(which(exonIndexLablesExons==j), 
                                                                  which(exonIndexLablesSamples==targets.unique[2])))
                                               }
                                           )
                                           Try(plot(exonIndexLablesExons, geneExons, type="n", xlab="Exon index", ylab="Splice Index", 
                                                           main=paste("SI behaviour in ",featureNames(NormalizedAffyData)[i],"\nglevel probe set", sep="")))
                                           Try(points(exonIndexLablesExons[index.1], geneExons[index.1], pch=19, col="black", cex=0.7))
                                           Try(points(exonIndexLablesExons[index.2], geneExons[index.2], pch=19, col="red", cex=0.7))
                                           if(AltSplRP.e.Available){
                                                Try(abline(v=which(names(geneExonsMiDAS)%in%altcommon), lty=2, col="yellow"))
                                           }
                                           ##############.............
                                      #     Try(lm.geneExons <- lm(geneExons[index.1] ~ exonIndexLablesExons[index.1]))
                                      #     Try(abline(lm.geneExons, lty=2, col="black"))
                                      #     Try(lm.geneExons <- lm(geneExons[index.2] ~ exonIndexLablesExons[index.2]))
                                      #     Try(abline(lm.geneExons, lty=2, col="red"))
                                      #     Try(legend(0,max(geneExons), legend=targets.unique,pch=19, col=c("black","red")))
                                      #     
                                      #     Try(plot(geneExons1,geneExonsPval,cex=0.5,xlab="Average mean Splice Index", 
                                      #               ylab="Significance of splicing events\n-log2(p-value)", main=targets.unique[1]))                
                                      #     Try(abline(h=-log2(Pval),lty=2, col="green"))
                                      #     Try(text(geneExons1[intersect(which(geneExonsPval >= -log2(Pval)), which(geneExonsFC >= threshold))],
                                      #                geneExonsPval[intersect(which(geneExonsPval >= -log2(Pval)), which(geneExonsFC >= threshold))],
                                      #                labels=c(as.character(intersect(which(geneExonsPval >= -log2(Pval)), which(geneExonsFC >= threshold)))))
                                      #     )
                                      #    
                                      #     Try(plot(geneExons2,geneExonsPval,cex=0.5,xlab="Average mean Splice Index", 
                                      #               ylab="Significance of splicing events\n-log2(p-value)", main=targets.unique[2]))                
                                      #     Try(abline(h=-log2(Pval),lty=2, col="green"))
                                      #     Try(text(geneExons2[intersect(which(geneExonsPval >= -log2(Pval)), which(geneExonsFC >= threshold))],
                                      #                geneExonsPval[intersect(which(geneExonsPval >= -log2(Pval)), which(geneExonsFC >= threshold))],
                                      #                labels=c(as.character(intersect(which(geneExonsPval >= -log2(Pval)), which(geneExonsFC >= threshold)))))
                                      #     )     
                              } else {Try(plot(seq(1,2), seq(1,2), type="n", xlab="Exon index", ylab="Splice Index", 
                                                           main=paste("No plot available, \nthere are less than 3 exons in ",featureNames(NormalizedAffyData)[i],"\nglevel probe set", sep="")))
                              }
                            }
                   Try(selected.altsplg <- as.data.frame(selected.altsplg))
                   Try(names(selected.altsplg) <- "glevel id|exon level ids ") 
                   Try(write.table(selected.altsplg, file=paste(FileNameText, ".txt", sep=""), sep="\t", row.names=F))          
                   Try(dev.off())
                   Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                   Try(tkmessageBox(title="Inspecting exon profiles",message=paste("Plots and ids of spliced exons are saved respectively in ", FileNameText, paste(FileNameText, ".txt", sep="") , sep=" ") , type="ok", icon="info")) 
    } else {
                   Try(tkmessageBox(title="Inspecting exon profiles",message="Splice Index was not yet calculated"))
    }
    Try(assign("detected.splicing", selected.altsplg, env=affylmGUIenvironment))
    Try(assign("detected.splicing.Available" , TRUE, affylmGUIenvironment))
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))  
}
################################################################################
"inspecting.one.splice.index" <-function(){
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
      Try(tkmessageBox(title="Exons analysis",message="P-value threshold is set by default to 0.05.",type="ok",icon="info"))
    #error if no data are loaded
    Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
    if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
    }    
    Try(spliceIndexData.Available <- get("spliceIndexData.Available", env=affylmGUIenvironment) )
    if(spliceIndexData.Available){
                   Try(Targets <- get("Targets", env=affylmGUIenvironment) )
                   Try(targets.unique <- unique(Targets$Target))
                   if(length(targets.unique)!=2){
                         Try(tkmessageBox(title="Inspecting exon profiles", message="This analysis can be applied \nonly to two groups experiments!",type="ok",icon="error"))
                         Try(return())
                   }
                   Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment) )
                   Try(exprConsoleLibs <- get("exprConsoleLibs", env=affylmGUIenvironment))
                   Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
                    Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
                   Try(midas.p.Available <- get("midas.p.Available", env=affylmGUIenvironment))
                   Try(AltSplRP.e.Available <- get("AltSplRP.e.Available", env=affylmGUIenvironment))
                   Try(AltSplLimma.Available <- get("AltSplLimma.Available", env=affylmGUIenvironment))                  
 #####################################################################################################################
                     Try(selected.altsplg <- NULL)
                   
                     Try(EG2probeset.available <- get("EG2probeset.available", affylmGUIenvironment))
                     if(EG2probeset.available){
                               eg <- get("EG2probeset", affylmGUIenvironment)
                     } else {eg <- .gettingEG()}
                     
                     Try(ttGetProbesetName<-tktoplevel(.affylmGUIglobals$ttMain))
                     Try(tkwm.deiconify(ttGetProbesetName))
                     Try(tkgrab.set(ttGetProbesetName))
                     Try(tkfocus(ttGetProbesetName))
                     Try(tkwm.title(ttGetProbesetName,"Gene-level probe set"))
                     Try(tkgrid(tklabel(ttGetProbesetName,text="    ")))
                     Try(ProbesetNameText <- "")
                     Try(Local.ProbesetName <- tclVar(init=ProbesetNameText))
                     Try(entry.ProbesetName <-tkentry(ttGetProbesetName,width="10",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.ProbesetName,bg="white"))
                     Try(tkgrid(tklabel(ttGetProbesetName,text="Please enter the gene-level probe set or EG or ACC to be used for splicing visualization.",font=.affylmGUIglobals$affylmGUIfont2)))
                     Try(tkgrid(entry.ProbesetName))
                     onOK <- function()
                     {
                         Try(ProbesetNameText <- tclvalue(Local.ProbesetName))
                         if(nchar(ProbesetNameText)==0)
                           ProbesetNameText <- "Unselected"
                         Try(assign("ProbesetNameText",ProbesetNameText,affylmGUIenvironment))
                         Try(tclvalue(.affylmGUIglobals$ProbesetNameTcl) <- ProbesetNameText)
                         Try(tkgrab.release(ttGetProbesetName));Try(tkdestroy(ttGetProbesetName));Try(tkfocus(.affylmGUIglobals$ttMain))
                     }
                     Try(OK.but <-tkbutton(ttGetProbesetName,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
                     Try(tkgrid(tklabel(ttGetProbesetName,text="    ")))
                     Try(tkgrid(OK.but))
                     Try(tkgrid.configure(OK.but))
                     Try(tkgrid(tklabel(ttGetProbesetName,text="       ")))
                     Try(tkfocus(entry.ProbesetName))
                     Try(tkbind(entry.ProbesetName, "<Return>",onOK))
                     Try(tkbind(ttGetProbesetName, "<Destroy>", function(){Try(tkgrab.release(ttGetProbesetName));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
                     Try(tkwait.window(ttGetProbesetName))
                     Try(tkfocus(.affylmGUIglobals$ttMain))
                   #########################
                   #defining if I am running an analysis starting from probe set, acc or eg
                   Try(mySel <- NULL)
                   Try(mySel.tmp <- get("ProbesetNameText", env=affylmGUIenvironment) )
                   Try(mySel1 <- as.character(eg$PROBESETID[which(as.character(eg$PROBESETID) == mySel.tmp)]))
                   Try(mySel2 <- as.character(eg$PROBESETID[which(as.character(eg$ACC) == mySel.tmp)]))
                   Try(mySel3 <- as.character(eg$PROBESETID[which(as.character(eg$EG) == mySel.tmp)]))
                   if(length(mySel1) > 0) {
                        mySel <-  mySel1
                   } else if(length(mySel2) > 0) {
                        mySel <-  mySel2
                   } else if(length(mySel3) > 0) {
                        mySel <-  mySel3
                   }
                   if(length(mySel) == 0){
                               Try(tkmessageBox(title="Exons analysis",message="Non of the available identifier, gene-level probe set/ACC/EG,\nwas found within the data available in Normalized Affy Data",icon="error"))
				    	                 Try(tkfocus(.affylmGUIglobals$ttMain))
                               Try(return())
                   }
                   Try(geneExonsIds <- as.vector(unlist(strsplit(exprConsoleLibs$exon.library$"probeset_list"[
                                    which(as.character(exprConsoleLibs$exon.library$"probeset_id")==
                                    mySel)], split=" "))))
#                  #transposed the exon matrix extracting the raw intensity data
                   Try(geneExons <- spliceIndexData[which(as.character(spliceIndexData[,1])%in%geneExonsIds),])#transpose becasue I need to add the labels
                   Try(rownames(geneExons) <- as.character(geneExons[,1]))
                   Try(geneExons <- geneExons[,3:dim(geneExons)[2]])
                   Try(geneExonsRaw <- exprs(exonAffyData[which(featureNames(exonAffyData)%in%geneExonsIds),]))
                   
                   #p.value calculation for exons
                    #adding MiDAS p-values                              
                    if(midas.p.Available){
                                    Try(midas.p <- get("midas.p", env=affylmGUIenvironment))
                                    Try(tmp <- midas.p[which(midas.p[,1]%in%geneExonsIds),c(1,3)])
                                    Try(geneExonsMiDAS <- -log2(as.numeric(tmp[,2])))
                                    Try(names(geneExonsMiDAS) <- as.character(tmp[,1]))
                                    #ordering by exon id 
                                    Try(geneExonsMiDAS <- geneExonsMiDAS[order(names(geneExonsMiDAS))])
                    }
                    #plotting limma
                    if(AltSplLimma.Available){
                                    Try(limma.df <- get("AltSplLimma", env=affylmGUIenvironment))
                                    Try(tmp <- limma.df[which(limma.df[,1]%in%geneExonsIds),c(1,5)])
                                    Try(geneExonsLimma <- -log10(as.numeric(tmp[,2])))
                                    Try(names(geneExonsLimma) <- as.character(tmp[,1]))
                                    Try(geneExonsLimma <- geneExonsLimma[order(names(geneExonsLimma))])
                                    Try(tmp.myylim<- as.numeric(geneExonsLimma))
                                    Try(tmp.myylim <- tmp.myylim[which(tmp.myylim!="Inf")])
                                    Try(myylim <- max(tmp.myylim))
                                    Try(geneExonsLimma[which(geneExonsLimma=="Inf")] <-  myylim)

                                    par(mfrow=c(1,2))
                                    Try(plot(seq(1,length(geneExonsLimma)),geneExonsLimma, xlab="exon index", ylab="-log10(p-value)", pch=19,main=paste("Limma results for ",mySel,"\nglevel probe set", sep="")))
                                    Try(abline(h=-log10(0.05), lty=2))
                                    Try(exonlegend <- paste(seq(1,length(geneExonsLimma)), names(geneExonsLimma)))
                                    Try(exonlegend <- c("exon idx exon id", exonlegend))
                                    Try(legend(1, myylim, legend= exonlegend, cex=0.5))
                                    
                                    #mapping common alt splicing in common between MiDAS rank prod
                                    Try(whichLimma <- names(geneExonsLimma)[which(geneExonsLimma >= -log10(0.05))])
                                    if(length(whichLimma)>0){
                                        Try(altcommon1 <- paste(whichLimma,collapse = "|")) 
                                        Try(myalt <- paste(mySel, altcommon1, sep = "|"))
                                    } else {Try(myalt <- mySel)}
                                    Try(selected.altsplg <- c(selected.altsplg, myalt))
                    }
                    if(AltSplRP.e.Available & midas.p.Available){
                                    Try(AltSplRP.e.p <- get("AltSplRP.e.p", env=affylmGUIenvironment))
                                    Try(myEids <- strsplit(as.character(AltSplRP.e.p[,1]), "\\|"))
                                    Try(myEids <- sapply(myEids, function(x)x[1]))
                                    Try(AltSplRP.e.p[,1] <- myEids)
                                    Try(tmp <- AltSplRP.e.p[which(AltSplRP.e.p[,1]%in%geneExonsIds),c(1,2)])# "p-val class1 < class2" 
                                    Try(geneExonsRP1 <- -log2(as.numeric(tmp[,2])))
                                    Try(names(geneExonsRP1) <- as.character(tmp[,1]))
                                    Try(geneExonsRP1 <- geneExonsRP1[order(names(geneExonsRP1))])
                                    Try(tmp <- AltSplRP.e.p[which(AltSplRP.e.p[,1]%in%geneExonsIds),c(c(1,3))])#  "p-val class1 > class2"
                                    Try(geneExonsRP2 <- -log2(as.numeric(tmp[,2])))
                                    Try(names(geneExonsRP2) <- as.character(tmp[,1]))
                                    Try(geneExonsRP2 <- geneExonsRP2[order(names(geneExonsRP2))])
                                    par(mfrow=c(1,2))
                                    # par(mfrow=c(2,2))
                                    #mapping common alt splicing in common between MiDAS rank prod
                                    Try(whichMiDAS <- names(geneExonsMiDAS)[which(geneExonsMiDAS >= -log2(0.05))])
                                    Try(whichRP1 <- names(geneExonsRP1)[which(geneExonsRP1 >= -log2(0.05))])
                                    Try(whichRP2 <- names(geneExonsRP2)[which(geneExonsRP2 >= -log2(0.05))])
                                    Try(altcommon <- intersect(whichMiDAS, union(whichRP1, whichRP2)))
                                    if(length(altcommon)>0){
                                        Try(altcommon1 <- paste(altcommon,collapse = "|"))
                                        Try(myalt <- paste(mySel, altcommon1, sep = "|"))
                                    } else {Try(myalt <- mySel)}
                                    Try(selected.altsplg <- c(selected.altsplg, myalt))
                                    #############################################################
                                    #changing inf with max value -log(pvalue)
                                    Try(tmp.myylim<- as.numeric(c(geneExonsMiDAS, geneExonsRP1, geneExonsRP2)))
                                    Try(tmp.myylim <- tmp.myylim[which(tmp.myylim!="Inf")])
                                    Try(myylim <- max(tmp.myylim))
                                    Try(geneExonsMiDAS[which(geneExonsMiDAS=="Inf")] <-  myylim)
                                    Try(geneExonsRP1[which(geneExonsRP1=="Inf")] <-  myylim)
                                    Try(geneExonsRP2[which(geneExonsRP2=="Inf")] <-  myylim)
                                    
                                    Try(plot(seq(1,length(geneExonsMiDAS)),geneExonsMiDAS, xlab="exon index", ylab="-log2(p-value)", ylim=c(0,myylim),pch=19,main=paste("MiDAS/RP results for ",mySel,"\nglevel probe set", sep="")))
                                    Try(abline(h=-log2(0.05), lty=2))
                                    Try(points(seq(1,length(geneExonsRP1)),geneExonsRP1, pch=24, bg="red"))
                                    Try(points(seq(1,length(geneExonsRP2)),geneExonsRP2, pch=25, bg="green"))
                                    Try(abline(v=which(names(geneExonsMiDAS)%in%altcommon), lty=2, col="yellow"))
                                    Try(exonlegend <- paste(seq(1,length(geneExonsMiDAS)), names(geneExonsMiDAS)))
                                    Try(exonlegend <- c("exon idx exon id", exonlegend))
                                    Try(legend(1, myylim, legend= exonlegend, cex=0.5))

                                    #Try(plot(geneExonsMiDAS, geneExonsRP1, pch=24, bg="red", xlab="MiDAS", ylab="RP", xlim=c(0,myylim), ylim=c(0,myylim), main="Consistency between MiDAS and RP results")) 
                                    #Try(points(geneExonsMiDAS, geneExonsRP2, pch=25, bg="green"))
                                    #Try(abline(h=-log2(0.05), lty=2))
                                    #Try(abline(v=-log2(0.05), lty=2))
                              }
                              
                              #defining  SI behaviour
                              Try(geneExons <- t(geneExons))#transpose becasue I need to add the labels
                              
                              Try(exonIndexLablesExons <- NULL)
                              Try(for(j in 1: dim(geneExons)[2]){
                                        exonIndexLablesExons    <-  c(exonIndexLablesExons, rep(j,dim(geneExons)[1]))
                                  }
                              )    
                             
                              Try(exonIndex <-  seq(1,dim(geneExons)[2]))#this is needed since geneExons are going to be transformed in a vector
                              Try(exonIndexLablesSamples <-  rep(Targets$Target,dim(geneExons)[2]))

                              Try(geneExons <- as.numeric(unlist(geneExons)))  #when unlisting data are unlisted on a column base!
                              if( length(geneExons) > 2 & length(targets.unique)==2){
                                      #defining the index vector for model plotting
                                           Try(index.1 <- NULL)
                                           Try(index.2 <- NULL)
                                           Try(for(j in 1: length(exonIndex)){
                                                  index.1 <-  c(index.1, intersect(which(exonIndexLablesExons==j), 
                                                                  which(exonIndexLablesSamples==targets.unique[1])))
                                                  index.2 <-  c(index.2, intersect(which(exonIndexLablesExons==j), 
                                                                  which(exonIndexLablesSamples==targets.unique[2])))
                                               }
                                           )
                                           #plotting SI
                                           Try(plot(exonIndexLablesExons, geneExons, type="n", xlab="Exon index", ylab="Splice Index", 
                                                           main=paste("SI behaviour in ",mySel,"\nglevel probe set", sep="")))
                                           Try(points(exonIndexLablesExons[index.1], geneExons[index.1], pch=19, col="black", cex=0.7))
                                           Try(points(exonIndexLablesExons[index.2], geneExons[index.2], pch=19, col="red", cex=0.7))
                                           if(AltSplRP.e.Available){
                                                Try(abline(v=which(names(geneExonsMiDAS)%in%altcommon), lty=2, col="yellow"))
                                           }
                                           #Plotting raw expression
                                         #  Try(plot(exonIndexLablesExons, geneExonsRaw, type="n", xlab="Exon index", ylab="Exon level log2(Intensity)", 
                                         #                  main=paste("log2(intensity) behaviour in ",mySel,"\nglevel probe set", sep="")))
                                         #  Try(points(exonIndexLablesExons[index.1], geneExonsRaw[index.1], pch=19, col="black", cex=0.7))
                                         #  Try(points(exonIndexLablesExons[index.2], geneExonsRaw[index.2], pch=19, col="red", cex=0.7))
                                           if(AltSplRP.e.Available){
                                                Try(abline(v=which(names(geneExonsMiDAS)%in%altcommon), lty=2, col="yellow"))
                                           }
                              } else {Try(plot(seq(1,2), seq(1,2), type="n", xlab="Exon index", ylab="Splice Index", 
                                                           main=paste("No plot available, \nthere are less than 3 exons in ",mySel,"\nglevel probe set", sep="")))
                   }
                   Try(selected.altsplg <- as.data.frame(selected.altsplg))
                   Try(names(selected.altsplg) <- "glevel id|exon level ids ")
                   Try(cat("\n"))
                   Try(print(table(selected.altsplg)))
                   Try(cat("\n"))
                   Try(cat("\n"))
       }
        Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow")) 
}
################################################################################
.saveFiltered <- function(mylist)
       {
               Try(tkmessageBox(title="Exons analysis",message="Saving significantly alternatively spliced exon probesets.",type="ok",icon="info"))
               Try(FileName <- tclvalue(tkgetSaveFile(initialfile=paste("Filtered.exons",".txt",sep=""),filetypes="{{Tab-Delimited Text Files} {.txt}} {{All files} *}")))
               Try(if(!nchar(FileName))
               return())
               Try(writeLines(as.character(mylist),con=FileName))
       }
      
# Expression data are filtered on the basis of a list exported by IPA Ingenuity
"midasFilter"<-function(){
      #error if no data are loaded
      Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
      if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
      }    
      #########################

     Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
     Try(midas.p.Available <- get("midas.p.Available", env=affylmGUIenvironment))
#     Try(exonAffyData.Available <- get("exonAffyData.Available", env=affylmGUIenvironment))
     Try(spliceIndexData.Available <- get("spliceIndexData.Available", env=affylmGUIenvironment))
     
     if(midas.p.Available & spliceIndexData.Available){
            #assigning midas threshold graphical menu
                 Try(ttGetMidas<-tktoplevel(.affylmGUIglobals$ttMain))
                 Try(tkwm.deiconify(ttGetMidas))
                 Try(tkgrab.set(ttGetMidas))
                 Try(tkfocus(ttGetMidas))
                 Try(tkwm.title(ttGetMidas,"Assigning MiDAS threshold"))
                 Try(tkgrid(tklabel(ttGetMidas,text="    ")))
                 Try(Midasnum <- "0.05")
                 Try(Local.Midas <- tclVar(init=Midasnum))
                 Try(entry.Midas <-tkentry(ttGetMidas,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.Midas,bg="white"))
                 Try(tkgrid(tklabel(ttGetMidas,text="Please enter a p-value threshold.",font=.affylmGUIglobals$affylmGUIfont2)))
                 Try(tkgrid(entry.Midas))
                 onOK <- function()
                 {
                     Try(Midasnum <- as.numeric(tclvalue(Local.Midas)))
                     Try(assign("Midasnum",Midasnum,affylmGUIenvironment))
                     Try(tclvalue(.affylmGUIglobals$MidasnumTcl) <- Midasnum)
                     Try(tkgrab.release(ttGetMidas));Try(tkdestroy(ttGetMidas));Try(tkfocus(.affylmGUIglobals$ttMain))                        
                 }
                 Try(OK.but <-tkbutton(ttGetMidas,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
                 Try(tkgrid(tklabel(ttGetMidas,text="    ")))
                 Try(tkgrid(OK.but))
                 Try(tkgrid.configure(OK.but))
                 Try(tkgrid(tklabel(ttGetMidas,text="       ")))
                 Try(tkfocus(entry.Midas))
                 Try(tkbind(entry.Midas, "<Return>",onOK))
                 Try(tkbind(ttGetMidas, "<Destroy>", function(){Try(tkgrab.release(ttGetMidas));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
                 Try(tkwait.window(ttGetMidas))
                 Try(tkfocus(.affylmGUIglobals$ttMain))
                                                                   
                 Try(midas.p <- get("midas.p", env=affylmGUIenvironment))
                 Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment))
                 Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
                 Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
                 Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                 Try(Midasnum <- as.numeric(get("Midasnum", env= affylmGUIenvironment)))
                 Try(which <- midas.p[which(midas.p[,3] <= Midasnum),2])
                 Try(which <- unique(which))
                 #saving the list of exon significant
                 Try(which.exon <- midas.p[which(midas.p[,3] <= Midasnum),1])
                 Try(.saveFiltered(which.exon))
                 Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData)%in%as.character(which)),])
                 Try(assign("NormalizedAffyData",NormalizedAffyData,affylmGUIenvironment))
                 Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%featureNames(NormalizedAffyData)),3]) #in the list obtained from NetAffx there are all the probe set ids and I have to subset only those related to the exon library loaded with the data set
                 Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
                 Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
                 Try(exonAffyData <- exonAffyData[which(featureNames(exonAffyData)%in%x.lib.subset),])
                 Try(assign("exonAffyData",exonAffyData,affylmGUIenvironment))
                 Try(spliceIndexData <- spliceIndexData[which(spliceIndexData[,1]%in%x.lib.subset),])
                 Try(assign("spliceIndexData",spliceIndexData,affylmGUIenvironment))
                
                 Try(info.dataset<-paste("Genes= ", dim(exprs(NormalizedAffyData))[1],"\n",
                                         "Exons= ", dim(exprs(exonAffyData))[1],"\n",
                                         "SI= ",    dim(spliceIndexData)[1],"\n",
                                         "Samples= ", dim(exprs(NormalizedAffyData))[2],"\n",
                                         "Annotation library= ", .annotation(NormalizedAffyData),"\n", sep=""))
                Try(tkmessageBox(title="Summary of MiDAS putative alternative splicing events",message=info.dataset))
                Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
               #######################################################
            
     } else if(midas.p.Available){
                 #assigning midas threshold graphical menu
                 Try(ttGetMidas<-tktoplevel(.affylmGUIglobals$ttMain))
                 Try(tkwm.deiconify(ttGetMidas))
                 Try(tkgrab.set(ttGetMidas))
                 Try(tkfocus(ttGetMidas))
                 Try(tkwm.title(ttGetMidas,"Assigning MiDAS threshold"))
                 Try(tkgrid(tklabel(ttGetMidas,text="    ")))
                 Try(Midasnum <- "0.05")
                 Try(Local.Midas <- tclVar(init=Midasnum))
                 Try(entry.Midas <-tkentry(ttGetMidas,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.Midas,bg="white"))
                 Try(tkgrid(tklabel(ttGetMidas,text="Please enter a p-value threshold.",font=.affylmGUIglobals$affylmGUIfont2)))
                 Try(tkgrid(entry.Midas))
                 onOK <- function()
                 {
                     Try(Midasnum <- as.numeric(tclvalue(Local.Midas)))
                     Try(assign("Midasnum",Midasnum,affylmGUIenvironment))
                     Try(tclvalue(.affylmGUIglobals$MidasnumTcl) <- Midasnum)
                     Try(tkgrab.release(ttGetMidas));Try(tkdestroy(ttGetMidas));Try(tkfocus(.affylmGUIglobals$ttMain))                        
                 }
                 Try(OK.but <-tkbutton(ttGetMidas,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
                 Try(tkgrid(tklabel(ttGetMidas,text="    ")))
                 Try(tkgrid(OK.but))
                 Try(tkgrid.configure(OK.but))
                 Try(tkgrid(tklabel(ttGetMidas,text="       ")))
                 Try(tkfocus(entry.Midas))
                 Try(tkbind(entry.Midas, "<Return>",onOK))
                 Try(tkbind(ttGetMidas, "<Destroy>", function(){Try(tkgrab.release(ttGetMidas));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
                 Try(tkwait.window(ttGetMidas))
                 Try(tkfocus(.affylmGUIglobals$ttMain))
                                                                   
                 Try(midas.p <- get("midas.p", env=affylmGUIenvironment))
                 Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
                 Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
                 Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                 Try(Midasnum <- as.numeric(get("Midasnum", env= affylmGUIenvironment)))
                 Try(which <- midas.p[which(midas.p[,3] <= Midasnum),2])
                 Try(which <- unique(which))
                 #saving the list of exon significant
                 Try(which.exon <- midas.p[which(midas.p[,3] <= Midasnum),1])
                 Try(.saveFiltered(which.exon))
                 Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData)%in%as.character(which)),])
                 Try(assign("NormalizedAffyData",NormalizedAffyData,affylmGUIenvironment))
                 Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%featureNames(NormalizedAffyData)),3]) #in the list obtained from NetAffx there are all the probe set ids and I have to subset only those related to the exon library loaded with the data set
                 Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
                 Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
                 Try(exonAffyData <- exonAffyData[which(featureNames(exonAffyData)%in%x.lib.subset),])
                 Try(assign("exonAffyData",exonAffyData,affylmGUIenvironment))
                 
                 Try(info.dataset<-paste("Genes= ", dim(exprs(NormalizedAffyData))[1],"\n",
                                         "Exons= ", dim(exprs(exonAffyData))[1],"\n",
                                         "SI= \n",
                                         "Samples= ", dim(exprs(NormalizedAffyData))[2],"\n",
                                         "Annotation library= ", .annotation(NormalizedAffyData),"\n", sep=""))
                Try(tkmessageBox(title="Summary of MiDAS putative alternative splicing events",message=info.dataset))
                Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
               #######################################################

    } else {
              Try(tkmessageBox(title="Exons analysis",message="MiDAS p-values are not available\nYou need to calculate them before using this function.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
    } 

}
################################################################################

erankProdAltSplFilter <- function(){
     #error if no data are loaded
     Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
     if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
     }    
     Try(spliceIndexData.Available <- get("spliceIndexData.Available", env=affylmGUIenvironment))
     Try(AltSplRP.e.Available <- get("AltSplRP.e.Available", env=affylmGUIenvironment))

     if(!spliceIndexData.Available){
              Try(tkmessageBox(title="Exons analysis",message="Splice Index is not available\nYou need to calculate it before using this function.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
    }
    if(!AltSplRP.e.Available){
              Try(tkmessageBox(title="Exons analysis",message="RP alternative splicing detection is not available\nYou need to calculate it before using this function.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
    } 
    Try(AltSplRP.e.p <- get("AltSplRP.e.p", env=affylmGUIenvironment))
                #assigning midas threshold graphical menu
                 Try(ttGetAltSplRP<-tktoplevel(.affylmGUIglobals$ttMain))
                 Try(tkwm.deiconify(ttGetAltSplRP))
                 Try(tkgrab.set(ttGetAltSplRP))
                 Try(tkfocus(ttGetAltSplRP))
                 Try(tkwm.title(ttGetAltSplRP,"Assigning RP threshold"))
                 Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
                 Try(AltSplRPnum <- "0.05")
                 Try(Local.AltSplRP <- tclVar(init=AltSplRPnum))
                 Try(entry.AltSplRP <-tkentry(ttGetAltSplRP,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.AltSplRP,bg="white"))
                 Try(tkgrid(tklabel(ttGetAltSplRP,text="Please enter a p-value threshold.",font=.affylmGUIglobals$affylmGUIfont2)))
                 Try(tkgrid(entry.AltSplRP))
                 onOK <- function()
                 {
                     Try(Midasnum <- as.numeric(tclvalue(Local.AltSplRP)))
                     Try(assign("AltSplRPnum",AltSplRPnum,affylmGUIenvironment))
                     Try(tclvalue(.affylmGUIglobals$AltSplRPnumTcl) <- AltSplRPnum)
                     Try(tkgrab.release(ttGetAltSplRP));Try(tkdestroy(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain))                        
                 }
                 Try(OK.but <-tkbutton(ttGetAltSplRP,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
                 Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
                 Try(tkgrid(OK.but))
                 Try(tkgrid.configure(OK.but))
                 Try(tkgrid(tklabel(ttGetAltSplRP,text="       ")))
                 Try(tkfocus(entry.AltSplRP))
                 Try(tkbind(entry.AltSplRP, "<Return>",onOK))
                 Try(tkbind(ttGetAltSplRP, "<Destroy>", function(){Try(tkgrab.release(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
                 Try(tkwait.window(ttGetAltSplRP))
                 Try(tkfocus(.affylmGUIglobals$ttMain))
                                                                   
                 Try(AltSplRP.e.p <- get("AltSplRP.e.p", env=affylmGUIenvironment))
                 Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment))
                 Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
                 Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
                 Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                 Try(AltSplRPnum <- as.numeric(get("AltSplRPnum", env= affylmGUIenvironment)))
                 Try(which1 <- AltSplRP.e.p[which(AltSplRP.e.p[,2] <= AltSplRPnum),1])
                 Try(which2 <- AltSplRP.e.p[which(AltSplRP.e.p[,3] <= AltSplRPnum),1])
                 Try(which <- unique(c(as.character(which1),as.character(which2)))) #all detected exons
                 #Try(which <- strsplit(which, "\\|"))#first exon inds second transcript id
                 #Try(which1 <- sapply(which, function(x){x[1]}))#exon ids
                 #saving the list of exon significant
                 Try(.saveFiltered(which))#filtered exons
                 #Try(which2 <- sapply(which, function(x){x[2]}))#gene ids
                 #combining exon and gene probe sets since in RP only exons are available
                 Try(x.exonid <-as.character(x.lib[,3]))
                 Try(x.exonid <- paste(x.lib[,1], x.exonid)) 
                 g.to.e<- function(x){
                        tmp <- as.character(unlist(strsplit(x, " ")))
                        tmp <- paste(tmp[1], tmp[2:length(tmp)], sep=".")
                 }
                 Try(g.e.out <- as.vector(unlist(sapply(x.exonid, g.to.e))))
                 Try(g.e.out <- strsplit(g.e.out, "\\."))
                 Try(g.out <- sapply(g.e.out, function(x) x[1]))
                 Try(e.out <- sapply(g.e.out, function(x) x[2]))
                 Try(g.e.df <- cbind(g.out, e.out))
                 Try(g.e.df.which <- g.e.df[which(g.e.df[,2] %in% which),])
                 Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData)%in% g.e.df.which[,1]),])
                 Try(assign("NormalizedAffyData",NormalizedAffyData,affylmGUIenvironment))

                 Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%featureNames(NormalizedAffyData)),3]) #in the list obtained from NetAffx there are all the probe set ids and I have to subset only those related to the exon library loaded with the data set
                 Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
                 Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
                 Try(exonAffyData <- exonAffyData[which(featureNames(exonAffyData)%in%x.lib.subset),])
                 Try(assign("exonAffyData",exonAffyData,affylmGUIenvironment))
                 Try(spliceIndexData <- spliceIndexData[which(spliceIndexData[,1]%in%x.lib.subset),])
                 Try(assign("spliceIndexData",spliceIndexData,affylmGUIenvironment))
                 
                 Try(info.dataset<-paste("Genes= ", dim(exprs(NormalizedAffyData))[1],"\n",
                                         "Exons= ", dim(exprs(exonAffyData))[1],"\n",
                                         "SI= ",    dim(spliceIndexData)[1],"\n",
                                         "Samples= ", dim(exprs(NormalizedAffyData))[2],"\n",
                                         "Annotation library= ", .annotation(NormalizedAffyData),"\n", sep=""))
                Try(tkmessageBox(title="Summary of RP putative alternative splicing events",message=info.dataset))
                                  par(mfrow=c(1,3))
                  Try(hist(AltSplRP.e.p[,2], main=names(AltSplRP.e.p)[2]))
                  Try(hist(AltSplRP.e.p[,3], main=names(AltSplRP.e.p)[3]))
                  Try(hist(AltSplRP.e.p[,4], main=names(AltSplRP.e.p)[4]))
                 Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
               #######################################################
  
}


################################################################################
#This function does not work anymore since the structure of the exonleve database is changed It has to be removed completely form this release
crosshybFilter <- function(){
    
          #error if no data are loaded
          Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
          if(whichArrayPlatform !="EXON"){
              Try(tkmessageBox(title="Filtering",message="No exon arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
          }    
        	##makning the menu for selecting Type of cross hyb filter
            Try(ttGetHybFilterMethod <- tktoplevel(.affylmGUIglobals$ttMain))
	      Try(tkwm.deiconify(ttGetHybFilterMethod))
            Try(tkgrab.set(ttGetHybFilterMethod))
            Try(tkfocus(ttGetHybFilterMethod))
            Try(tkwm.title(ttGetHybFilterMethod,"Cross hybridization filter"))
	
 	      Try(tkgrid(tklabel(ttGetHybFilterMethod,text="    ")))
	      Try(ttGetHybFilterMethodTcl <- tclVar("23"))
            Try(rbXHYB <- tkradiobutton(ttGetHybFilterMethod,text="XHYB (TRUE)",variable=ttGetHybFilterMethodTcl,value="TRUE",font=.affylmGUIglobals$affylmGUIfont2))
            Try(rbCHYB2<-tkradiobutton(ttGetHybFilterMethod,text="CROSS HYB = similar",variable=ttGetHybFilterMethodTcl,value="2",font=.affylmGUIglobals$affylmGUIfont2))
            Try(rbCHYB3<-tkradiobutton(ttGetHybFilterMethod,text="CROSS HYB = mixed",variable=ttGetHybFilterMethodTcl,value="3",font=.affylmGUIglobals$affylmGUIfont2))
            Try(rbCHYB23<-tkradiobutton(ttGetHybFilterMethod,text="CROSS HYB = similar and mixed",variable=ttGetHybFilterMethodTcl,value="23",font=.affylmGUIglobals$affylmGUIfont2))

	      Try(tkgrid(tklabel(ttGetHybFilterMethod,text="    "),rbXHYB))
	      Try(tkgrid(tklabel(ttGetHybFilterMethod,text="    "),rbCHYB2))
	      Try(tkgrid(tklabel(ttGetHybFilterMethod,text="    "),rbCHYB3))
	      Try(tkgrid(tklabel(ttGetHybFilterMethod,text="    "),rbCHYB23))
	      Try(tkgrid.configure(rbXHYB,rbCHYB2,rbCHYB3,rbCHYB23,columnspan=2,sticky="w"))
	      Try(tkgrid(tklabel(ttGetHybFilterMethod,text="    "),tklabel(ttGetHybFilterMethod,text="    ")))
	      Try(ReturnVal <- "")
	      Try(onCancel <- function() {Try(ReturnVal <<- "");Try(tkgrab.release(ttGetHybFilterMethod));Try(tkdestroy(ttGetHybFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})
	      Try(onOK <- function() {Try(ReturnVal <<- tclvalue(ttGetHybFilterMethodTcl));Try(tkgrab.release(ttGetHybFilterMethod));Try(tkdestroy(ttGetHybFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})
        Try(onHelp <- function() tkmessageBox(title="Cross hybridization exon probe set filtering",
                 message="Cross hybridizing exon probe sets can be removed using the XHYB annotation or the CROSSHYB annotation.
                           \nSimilar: All the probes in the probe set perfectly match more than one sequence in the putatively transcribed array design content.
                           \nMixed: The probes in the probe set either perfectly match or partially match more than one sequence in the putatively transcribed array design content.
                           \nThe filter removes all the gene/exon level probe sets belonging to the selected item",
                 icon="info"))
        Try(Help.but <- tkbutton(ttGetHybFilterMethod,text=" Help ",command=function()Try(onHelp()),font=.affylmGUIglobals$affylmGUIfont2))
	      Try(OK.but     <- tkbutton(ttGetHybFilterMethod,text="OK",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
	      Try(Cancel.but <- tkbutton(ttGetHybFilterMethod,text="Cancel",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))

	      Try(tkgrid(tklabel(ttGetHybFilterMethod,text="    "),OK.but,Cancel.but, Help.but,tklabel(ttGetHybFilterMethod,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(ttGetHybFilterMethod,text="    ")))

	      Try(tkbind(ttGetHybFilterMethod,"<Destroy>",function() {ReturnVal <- "";Try(tkgrab.release(ttGetHybFilterMethod));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(ttGetHybFilterMethod))
	      if(ReturnVal==""){
                              Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                              return()
        } else if (ReturnVal=="2"){
                  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
                  #extracting the library
                  Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))

                  if(whichLib[[1]][1] == "HuEx"){
                 #    require(HuExExonProbesetLocation) || stop("\nMissing HuExExonProbesetLocation package\n")
                     data(HuExExonProbesetLocation)
                     exonannlib<- get("HuExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  if(whichLib[[1]][1] == "MoEx"){
                 #    require(MoExExonProbesetLocation) || stop("\nMissing MoExExonProbesetLocation package\n")
                     data(MoExExonProbesetLocation)
                     exonannlib<- get("MoExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  if(whichLib[[1]][1] == "RaEx"){
                 #    require(RaExExonProbesetLocation) || stop("\nMissing RaExExonProbesetLocation package\n")
                     data(RaExExonProbesetLocation)
                     exonannlib<- get("RaExExonProbesetLocation",envir=.GlobalEnv)
                  }

                  Try(x <- get("NormalizedAffyData",envir=affylmGUIenvironment))
                  Try(which <- unique(as.character(exonannlib[which(exonannlib$CROSSHYBTYPE!=2),2])))
                  par(mfrow=c(1,2))
                  Try(text<-paste("Unfiltered probes= ", dim(exprs(x))[1], sep=""))
                  Try(hist(as.matrix(exprs(x)), breaks=100, main=text))
                  Try(assign("NormalizedAffyData", x[which(featureNames(x)%in%which),],  envir=affylmGUIenvironment))
                  Try(NormalizedAffyData <- get("NormalizedAffyData", envir=affylmGUIenvironment)) 
                  Try(text<-paste("Filtered probes= ", dim(exprs(NormalizedAffyData))[1], "\nwithout similar crosshyb type",sep=""))
                  Try(hist(as.matrix(exprs(x[which(featureNames(x)%in%which),])), breaks=100, main=text))
#                  Try(assign("NormalizedAffyData", x[which(featureNames(x)%in%which),],  envir=affylmGUIenvironment))
                  Try(x.exon <- get("exonAffyData",envir=affylmGUIenvironment))
                  ####temporary saving unfiltered data
                  Try(tempUnfiltered <- tempfile(pattern = "unfiltered", tmpdir = ""))
                  Try(tempUnfiltered <- sub( "\\\\","",tempUnfiltered)) 
                  Try(tempUnfiltered <- paste(tempUnfiltered, ".rda", sep=""))
                  Try(assign("unfilteredData.location", tempUnfiltered, envir=affylmGUIenvironment))
                  Try(save(x, x.exon, file=tempUnfiltered))
                  ####temporary saving unfiltered data
                  Try(x <- x[which(featureNames(x)%in%which),])
                  tkdelete(.affylmGUIglobals$mainTree,"NormalizedAffyData.Status")
                  tkinsert(.affylmGUIglobals$mainTree,"end","NormalizedAffyData","NormalizedAffyData.Status" ,text="Available wo similar",font=.affylmGUIglobals$affylmGUIfontTree)
                  Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                  Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%as.numeric(featureNames(x))),3])
                  Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
                  Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
                  Try(assign("exonAffyData", x.exon[which(featureNames(x.exon)%in%x.lib.subset),], envir=affylmGUIenvironment))
                  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
        } else if (ReturnVal=="3"){
                  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
                  #extracting the library
                  Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))
                  if(whichLib[[1]][1] == "HuEx"){
               #      require(HuExExonProbesetLocation) || stop("\nMissing HuExExonProbesetLocation package\n")
                     data(HuExExonProbesetLocation)
                     exonannlib<- get("HuExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  if(whichLib[[1]][1] == "MoEx"){
                  #   require(MoExExonProbesetLocation) || stop("\nMissing MoExExonProbesetLocation package\n")
                     data(MoExExonProbesetLocation)
                     exonannlib<- get("MoExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  if(whichLib[[1]][1] == "RaEx"){
                #     require(RaExExonProbesetLocation) || stop("\nMissing RaExExonProbesetLocation package\n")
                     data(RaExExonProbesetLocation)
                     exonannlib<- get("RaExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  Try(x <- get("NormalizedAffyData",envir=affylmGUIenvironment))
                  Try(which <- unique(as.character(exonannlib[which(exonannlib$CROSSHYBTYPE!=3),2])))
                  par(mfrow=c(1,2))
                  Try(text<-paste("Unfiltered probes= ", dim(exprs(x))[1], sep=""))
                  Try(hist(as.matrix(exprs(x)), breaks=100, main=text))
                  Try(assign("NormalizedAffyData", x[which(featureNames(x)%in%which),],  envir=affylmGUIenvironment))
                  Try(NormalizedAffyData <- get("NormalizedAffyData", envir=affylmGUIenvironment)) 
                  Try(text<-paste("Filtered probes= ", dim(exprs(NormalizedAffyData))[1], "\nwithout mixed crosshyb type",sep=""))
                  Try(hist(as.matrix(exprs(x[which(featureNames(x)%in%which),])), breaks=100, main=text))
#                  Try(assign("NormalizedAffyData", x[which(featureNames(x)%in%which),],  envir=affylmGUIenvironment))
                  Try(x.exon <- get("exonAffyData",envir=affylmGUIenvironment))
                  ####temporary saving unfiltered data
                  Try(tempUnfiltered <- tempfile(pattern = "unfiltered", tmpdir = ""))
                  Try(tempUnfiltered <- sub( "\\\\","",tempUnfiltered)) 
                  Try(tempUnfiltered <- paste(tempUnfiltered, ".rda", sep=""))
                  Try(assign("unfilteredData.location", tempUnfiltered, envir=affylmGUIenvironment))
                  Try(save(x, x.exon, file=tempUnfiltered))
                  ####temporary saving unfiltered data
                  Try(x <- x[which(featureNames(x)%in%which),])
                  tkdelete(.affylmGUIglobals$mainTree,"NormalizedAffyData.Status")
                  tkinsert(.affylmGUIglobals$mainTree,"end","NormalizedAffyData","NormalizedAffyData.Status" ,text="Available wo mixed",font=.affylmGUIglobals$affylmGUIfontTree)
                  Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                  Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%as.numeric(featureNames(x))),3])
                  Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
                  Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
                  Try(assign("exonAffyData", x.exon[which(featureNames(x.exon)%in%x.lib.subset),], envir=affylmGUIenvironment))
                  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
        } else if (ReturnVal=="23"){
                  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
                  #extracting the library
                  Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))
                  if(whichLib[[1]][1] == "HuEx"){
              #       require(HuExExonProbesetLocation) || stop("\nMissing HuExExonProbesetLocation package\n")
                     data(HuExExonProbesetLocation)
                     exonannlib<- get("HuExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  if(whichLib[[1]][1] == "MoEx"){
               #      require(MoExExonProbesetLocation) || stop("\nMissing MoExExonProbesetLocation package\n")
                     data(MoExExonProbesetLocation)
                     exonannlib<- get("MoExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  if(whichLib[[1]][1] == "RaEx"){
                #     require(RaExExonProbesetLocation) || stop("\nMissing RaExExonProbesetLocation package\n")
                     data(RaExExonProbesetLocation)
                     exonannlib<- get("RaExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  Try(x <- get("NormalizedAffyData",envir=affylmGUIenvironment))
                  Try(which <- unique(as.character(exonannlib[which(exonannlib$CROSSHYBTYPE==1),2])))
                  par(mfrow=c(1,2))
                  Try(text<-paste("Unfiltered probes= ", dim(exprs(x))[1], sep=""))
                  Try(hist(as.matrix(exprs(x)), breaks=100, main=text))
                  Try(assign("NormalizedAffyData", x[which(featureNames(x)%in%which),],  envir=affylmGUIenvironment))
                  Try(NormalizedAffyData <- get("NormalizedAffyData", envir=affylmGUIenvironment)) 
                  Try(text<-paste("Filtered probes= ", dim(exprs(NormalizedAffyData))[1], "\nwithout mixed/similar crosshyb types",sep=""))
                  Try(hist(as.matrix(exprs(x[which(featureNames(x)%in%which),])), breaks=100, main=text))
#                  Try(assign("NormalizedAffyData", x[which(featureNames(x)%in%which),],  envir=affylmGUIenvironment))
                  Try(x.exon <- get("exonAffyData",envir=affylmGUIenvironment))
                  ####temporary saving unfiltered data
                  Try(tempUnfiltered <- tempfile(pattern = "unfiltered", tmpdir = ""))
                  Try(tempUnfiltered <- sub( "\\\\","",tempUnfiltered)) 
                  Try(tempUnfiltered <- paste(tempUnfiltered, ".rda", sep=""))
                  Try(assign("unfilteredData.location", tempUnfiltered, envir=affylmGUIenvironment))
                  Try(save(x, x.exon, file=tempUnfiltered))
                  ####temporary saving unfiltered data
                  Try(x <- x[which(featureNames(x)%in%which),])
                  tkdelete(.affylmGUIglobals$mainTree,"NormalizedAffyData.Status")
                  tkinsert(.affylmGUIglobals$mainTree,"end","NormalizedAffyData","NormalizedAffyData.Status" ,text="Available wo mixed/similar",font=.affylmGUIglobals$affylmGUIfontTree)
                  Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                  Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%as.numeric(featureNames(x))),3])
                  Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
                  Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
                  Try(assign("exonAffyData", x.exon[which(featureNames(x.exon)%in%x.lib.subset),], envir=affylmGUIenvironment))
                  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
        } else if (ReturnVal=="TRUE"){
                  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
                  #extracting the library
                  Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))
                  if(whichLib[[1]][1] == "HuEx"){
                #     require(HuExExonProbesetLocation) || stop("\nMissing HuExExonProbesetLocation package\n")
                     data(HuExExonProbesetLocation)
                     exonannlib<- get("HuExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  if(whichLib[[1]][1] == "MoEx"){
               #      require(MoExExonProbesetLocation) || stop("\nMissing MoExExonProbesetLocation package\n")
                     data(MoExExonProbesetLocation)
                     exonannlib<- get("MoExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  if(whichLib[[1]][1] == "RaEx"){
              #       require(RaExExonProbesetLocation) || stop("\nMissing RaExExonProbesetLocation package\n")
                     data(RaExExonProbesetLocation)
                     exonannlib<- get("RaExExonProbesetLocation",envir=.GlobalEnv)
                  }
                  Try(x <- get("NormalizedAffyData",envir=affylmGUIenvironment))
                  Try(which1 <- unique(as.character(exonannlib[which(exonannlib$XHYB=="TRUE"),2])))
                  Try(which2 <- unique(as.character(exonannlib[is.na(exonannlib$XHYB),2])))
                  Try(which <- setdiff(featureNames(x),c(which1, which2)))
                  par(mfrow=c(1,2))
                  Try(text<-paste("Unfiltered probes= ", dim(exprs(x))[1], sep=""))
                  Try(hist(as.matrix(exprs(x)), breaks=100, main=text))
                  Try(assign("NormalizedAffyData", x[which(featureNames(x)%in%which),],  envir=affylmGUIenvironment))
                  Try(NormalizedAffyData <- get("NormalizedAffyData", envir=affylmGUIenvironment)) 
                  Try(text<-paste("Filtered probes= ", dim(exprs(NormalizedAffyData))[1], "\nwithout xhyb type",sep=""))
                  Try(hist(as.matrix(exprs(x[which(featureNames(x)%in%which),])), breaks=100, main=text))
#                  Try(assign("NormalizedAffyData", x[which(featureNames(x)%in%which),],  envir=affylmGUIenvironment))
                  Try(x.exon <- get("exonAffyData",envir=affylmGUIenvironment))
                  ####temporary saving unfiltered data
                  Try(tempUnfiltered <- tempfile(pattern = "unfiltered", tmpdir = ""))
                  Try(tempUnfiltered <- sub( "\\\\","",tempUnfiltered)) 
                  Try(tempUnfiltered <- paste(tempUnfiltered, ".rda", sep=""))
                  Try(assign("unfilteredData.location", tempUnfiltered, envir=affylmGUIenvironment))
                  Try(save(x, x.exon, file=tempUnfiltered))
                  ####temporary saving unfiltered data
                  Try(x <- x[which(featureNames(x)%in%which),])
                  tkdelete(.affylmGUIglobals$mainTree,"NormalizedAffyData.Status")
                  tkinsert(.affylmGUIglobals$mainTree,"end","NormalizedAffyData","NormalizedAffyData.Status" ,text="Available wo xhyb",font=.affylmGUIglobals$affylmGUIfontTree)
                  Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                  Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%as.numeric(featureNames(x))),3])
                  Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
                  Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
                  Try(assign("exonAffyData", x.exon[which(featureNames(x.exon)%in%x.lib.subset),], envir=affylmGUIenvironment))
                  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
        }



}

################################################################################
simFilter <- function(){
          #error if no data are loaded
          Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
          if(whichArrayPlatform !="EXON"){
              Try(tkmessageBox(title="Filtering by SI mean/min difference",message="No exon arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
          }    
        	##makning the menu for selecting the amount of average SI mean difference
          Try(targets <-  affylmGUIenvironment$Targets$Target)
          Try(target.unique <- unique(targets))
          Try(cl <- rep(0,length(targets)))

          if(length(target.unique) == 2){
                 #groups definition
                 Try(tkmessageBox(title="Filtering by SI mean/min difference",message="Two-Class case analysis will be performed."))
                 Try(cl[which(targets==target.unique[2])] <- 1)
                 Try(spliceIndexData.Available <- get("spliceIndexData.Available", env=affylmGUIenvironment))
                 if(spliceIndexData.Available){
                        
                        Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
                        Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment))
                        Try(cl <- as.numeric(c("NA","NA",cl)))
                        #selecting mean ir min
                        Try(mbVal <- tkmessageBox(title="Filtering by SI mean/min difference",
                                                  message="Do you want to use a SI min difference filter? \nIf you answer no a SI mean difference filter will be applyed",
                                                  icon="question",type="yesno",default="yes"))
                        Try(if(tclvalue(mbVal)=="yes"){
                                      min.c <- apply(spliceIndexData[,which(cl==0)], 1, min)
                                      min.t <- apply(spliceIndexData[,which(cl==1)], 1, min)
                                      max.c <- apply(spliceIndexData[,which(cl==0)], 1, max)
                                      max.t <- apply(spliceIndexData[,which(cl==1)], 1, max)
                                      minmax <- data.frame(min.c, min.t, max.c, max.t)
                                      .deltaMin <- function(x){ if(x[3]<x[4]){abs(x[3]-x[2])} else{abs(x[4]-x[1])}} #if max.c<max.t |max.c-min.t| else |max.t-min.c| 
                                      amsi <- apply(minmax, 1, .deltaMin)
                                      amsi <- data.frame(spliceIndexData[,1:2], as.numeric(amsi))
                                      names(amsi) <- c("elevel","glevel", "deltaSI")
               
                            } else{
                                   mean.c <- apply(spliceIndexData[,which(cl==0)], 1, mean)
                                   mean.t <- apply(spliceIndexData[,which(cl==1)], 1, mean)
                                   amsi <- abs(mean.t - mean.c)
                                   amsi <- data.frame(spliceIndexData[,1:2], as.numeric(amsi))
                                   names(amsi) <- c("elevel","glevel", "deltaSI")
                            }
                        )
                        ######################Selecting fc threshold
                       Try(ttThresholdFC<-tktoplevel(.affylmGUIglobals$ttMain))
                       Try(tkwm.deiconify(ttThresholdFC))
                       Try(tkgrab.set(ttThresholdFC))
                       Try(tkfocus(ttThresholdFC))
                       Try(tkwm.title(ttThresholdFC,"|deltaSI| threshold"))
                       Try(tkgrid(tklabel(ttThresholdFC,text="    ")))
                       Try(ThresholdFC <- "0.5")
                       Try(Local.FileName <- tclVar(init=ThresholdFC))
                       Try(entry.FileName <-tkentry(ttThresholdFC,width="10",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.FileName,bg="white"))
                       Try(tkgrid(tklabel(ttThresholdFC,text="Please, enter the absolute SI mean/min difference \nof your choice.",font=.affylmGUIglobals$affylmGUIfont2)))
                       Try(tkgrid(entry.FileName))
                       onOK <- function()
                       {
                             Try(ThresholdFC <- tclvalue(Local.FileName))
                             if(nchar(ThresholdFC)==0)
                                 Try(ThresholdFC <- 0)
                             Try(assign("ThresholdFC",ThresholdFC,affylmGUIenvironment))
                             Try(tclvalue(.affylmGUIglobals$ThresholdFCTcl) <- ThresholdFC)
                             Try(tkgrab.release(ttThresholdFC));Try(tkdestroy(ttThresholdFC));Try(tkfocus(.affylmGUIglobals$ttMain))
                       }
                       Try(OK.but <-tkbutton(ttThresholdFC,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
                       Try(tkgrid(tklabel(ttThresholdFC,text="    ")))
                       Try(tkgrid(OK.but))
                       Try(tkgrid.configure(OK.but))
                       Try(tkgrid(tklabel(ttThresholdFC,text="       ")))
                       Try(tkfocus(entry.FileName))
                       Try(tkbind(entry.FileName, "<Return>",onOK))
                       Try(tkbind(ttThresholdFC, "<Destroy>", function(){Try(tkgrab.release(ttThresholdFC));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
                       Try(tkwait.window(ttThresholdFC))
                       Try(tkfocus(.affylmGUIglobals$ttMain))
                                           
                       Try(fold.change <- as.numeric(affylmGUIenvironment$ThresholdFC))
                       Try(selGlevel <- amsi[which(amsi[,3] >= fold.change),2])
                       Try(selElevel <- amsi[which(amsi[,3] >= fold.change),1])
                       #saving the list of exon significant
                       Try(.saveFiltered(selElevel))
                           Try( x <- get("NormalizedAffyData",envir=affylmGUIenvironment))
                           Try(x.exon <- get("exonAffyData",envir=affylmGUIenvironment))
                            ####temporary saving unfiltered data
                            Try(tempUnfiltered <- tempfile(pattern = "unfiltered", tmpdir = "") )
                            Try(tempUnfiltered <- sub( "\\\\","",tempUnfiltered)) 
                            Try(tempUnfiltered <- paste(tempUnfiltered, ".rda", sep=""))
                            Try(assign("unfilteredData.location", tempUnfiltered, envir=affylmGUIenvironment))
                            Try(save(x, x.exon, file=tempUnfiltered))
                            ####temporary saving unfiltered data
                           Try(x <- x[which(featureNames(x)%in%selGlevel),])#subset of probe set to be used to extract exon data
                           Try(assign("NormalizedAffyData", x, envir=affylmGUIenvironment))
                           Try(tkdelete(.affylmGUIglobals$mainTree,"NormalizedAffyData.Status"))
                           Try(tkinsert(.affylmGUIglobals$mainTree,"end","NormalizedAffyData","NormalizedAffyData.Status" ,text="Available from SI mean diff. filter.",font=.affylmGUIglobals$affylmGUIfontTree))
                           Try( x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                           Try( x.lib.subset <- x.lib[which(x.lib[,1]%in%as.numeric(featureNames(x))),3])
                           Try( x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
                           Try( x.lib.subset<-as.vector(unlist(x.lib.subset)))
                           Try( affylmGUIenvironment$exonAffyData <- x.exon[which(featureNames(x.exon)%in%x.lib.subset),])
                           Try(showDataset()) 
                       Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                 } else {
                         Try(tkmessageBox(title="Filtering by SI mean difference",message="Splice Index values are not available. Use the APT MiDAS function in exon menu.",type="ok",icon="error"))
				    	           Try(tkfocus(.affylmGUIglobals$ttMain))
                         Try(return())
                 }
                 
          } else {
                         Try(tkmessageBox(title="Filtering by SI mean difference",message="This function works only for a two-class case.",type="ok",icon="error"))
				    	           Try(tkfocus(.affylmGUIglobals$ttMain))
                         Try(return())
          }
}

################################################################################
#"acc2probeset" <- function(){
#   Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
#   Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
#   if(whichArrayPlatform == "EXON"){
#        Try(NormalizedAffyData.Available <- get("NormalizedAffyData.Available",envir=affylmGUIenvironment))
#        if(NormalizedAffyData.Available){
#           Try(NormalizedAffyData <- get("NormalizedAffyData",envir=affylmGUIenvironment))
#        } else {            
#           Try(tkmessageBox(title="EXON arrays: linking ACC to glevel probe sets",message="Normalized data set is not loaded!"))
#           return()
#        }
#        Try(id <- featureNames(NormalizedAffyData))
#        Try(whichLib <- get("whichLib", envir=affylmGUIenvironment)) 
#        Try(annlibloc <- grep(paste("^",whichLib[[1]][1],sep=""), as.vector(unlist(data(package="oneChannelGUI"))), ignore.case = T))
#        Try(annlibname <- as.vector(unlist(data(package="oneChannelGUI")))[annlibloc])
#        Try(data(list=annlibname,package="oneChannelGUI"))
#        Try(exonannlib<- get(annlibname,envir=.GlobalEnv))
#        Try(acc <- as.character(exonannlib$ACC[which(as.character(exonannlib$PROBESETID)%in%id)]))
#        Try(probeset <- as.character(exonannlib$PROBESETID[which(as.character(exonannlib$PROBESETID)%in%id)]))#needed to have the same orientation of probe set ids and acc
#        Try(names(acc) <- probeset)
#        #saving the filtered subset
#       .saveacc2id <- function()
#       {
#               Try(FileName <- tclvalue(tkgetSaveFile(initialfile=paste("acc2probesetids",".xls",sep=""),filetypes="{{Tab-Delimited Text Files} {.txt .xls}} {{All files} *}")))
#               Try(if(!nchar(FileName))
#               return())
#               Try(write.table(acc,file=FileName,quote=FALSE, sep="\t", row.names=T, col.names=F))
#       }
#      Try(mbVal <- tkmessageBox(title="EXON arrays: linking ACC to glevel probe sets",
#                message="Save the ACC associated to EXON arrays gene-level probe sets present in Normalized Affy Data.",
#                icon="question",type="yesno",default="yes"))
#                try(if(tclvalue(mbVal)=="yes") .saveacc2id())
#   } else {            
#           Try(tkmessageBox(title="EXON arrays: linking ACC to glevel probe sets",message="Exon arrays are not loaded!"))
#           return()
#        }
#   Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
#}                                                                                
################################################################################

"EG2probeset" <- function(){
   Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
   Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
   if(whichArrayPlatform == "EXON" || whichArrayPlatform == "LARGE"){
        Try(NormalizedAffyData.Available <- get("NormalizedAffyData.Available",envir=affylmGUIenvironment))
        if(NormalizedAffyData.Available){
           Try(eg <- .gettingEG())
        } else {            
           Try(tkmessageBox(title="EXON arrays: linking ACC and EG to glevel probe sets",message="Normalized data set is not loaded!"))
           return()
        }
        ############################################
        #saving the filtered subset
       .saveeg2id <- function()
       {
               Try(FileName <- tclvalue(tkgetSaveFile(initialfile=paste("EG2probesetids",".xls",sep=""),filetypes="{{Tab-Delimited Text Files} {.txt .xls}} {{All files} *}")))
               Try(if(!nchar(FileName))
               return())
               Try(write.table(eg,file=FileName,quote=FALSE, sep="\t", row.names=F, col.names=T))
       }
             
      OpenAFile <- function(FileName) {
         Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
               if(!nchar(tempFileName))
               {
                  tkfocus(.affylmGUIglobals$ttMain)
                  return()
               }
         mySel<-read.table(tempFileName, sep="\t", header=T, as.is=TRUE)
         return(mySel)
      }


      Try(mbVal <- tkmessageBox(title="EXON arrays: linking EG and ACC to glevel probe sets",
                message="Save the EG and ACC associated to EXON arrays gene-level probe sets present in Normalized Affy Data.\nIf you answer No you will be asked to select a file containing the list of Probeset IDs to be used for the association to EGs on the first column",
                icon="question",type="yesno",default="yes"))
                Try(if(tclvalue(mbVal)=="yes") .saveeg2id())
                Try(if(tclvalue(mbVal)=="no") {
                                                    mySel <- OpenAFile()
                                                    ids <- as.character(mySel[,1])
                                                    test <- intersect(as.character(eg[,1]), ids)
                                                    if(length(test) == 0){
                                                            Try(tkmessageBox(title="EXON arrays: linking ACC and EG to glevel probe sets",message="The first column of the file does not contain probeset ids!"))
                                                            Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                                                            Try(return())
                                                    }
                                                    sub.eg <- eg[which(as.character(eg[,1]) %in% ids),]
                                                    sub.eg <- sub.eg[order(sub.eg[,1]),]
                                                    mySel <- mySel[which(as.character(mySel[,1]) %in% as.character(sub.eg[,1])),]
                                                    mySel <- mySel[order(mySel[,1]),]
                                                    if (is.vector(mySel)) mySel <- as.data.frame(mySel)
                                                    if(identical(as.character(sub.eg[, 1]), as.character(mySel[, 1]))){
                                                            mySel <- cbind(sub.eg, mySel[,2:dim(mySel)[2]])
                                                            Try(FileName <- tclvalue(tkgetSaveFile(initialfile=paste("EG2probesetids",".xls",sep=""),filetypes="{{Tab-Delimited Text Files} {.txt .xls}} {{All files} *}")))
                                                            Try(if(!nchar(FileName))
                                                                  return())
                                                            Try(write.table(mySel,file=FileName,quote=FALSE, sep="\t", row.names=F, col.names=T))
                                                    } else {
                                                            Try(tkmessageBox(title="EXON arrays: linking ACC and EG to glevel probe sets",message="A correct alignment is missing between gene-level probeset ids and EGs.\nIt is possible that the loaded file contains multiple entries for some fo the gene-level probesets!"))
                                                            Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                                                            Try(return())
                                                    
                                                    }
                                              }
                )
        
   } else {            
           Try(tkmessageBox(title="EXON arrays: linking EG to glevel probe sets",message="Exon arrays are not loaded!"))
           return()
        }
   Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}
#internal function
############################################
.gettingEG <- function(){
     #   require(annotate, quietly = TRUE) || stop("\nneed data package: annotate\n")
        Try(NormalizedAffyData <- get("NormalizedAffyData",envir=affylmGUIenvironment))
        tmpExann <- .annotation(NormalizedAffyData)
        if(tmpExann == ""){
          Try(whichLib <- get("whichLib", envir=affylmGUIenvironment))
        }else{Try(whichLib <- list(c(tmpExann, "core")))}
        Try(tmpExann <- "")
                    Try(if(whichLib[[1]][1]=="HuEx"){
                            #require(humanLLMappings) || stop("library humanLLMappings could not be found !")
                            #lib <- "humanLLMappings"
                        #    require(org.Hs.eg.db, quietly = TRUE) || stop("\nneed data package: org.Hs.eg.db\n")
                            lib = "org.Hs.eg.db"
                    })
                    Try(if(whichLib[[1]][1]=="MoEx"){
                            #require(mouseLLMappings) || stop("library mouseLLMappings could not be found !")
                            #lib <- "mouseLLMappings"
                       #     require(org.Mm.eg.db, quietly = TRUE) || stop("\nneed data package: org.Mm.eg.db\n")
                            lib = "org.Mm.eg.db"
                   })
                    Try(if(whichLib[[1]][1]=="RaEx"){
                            #require(ratLLMappings) || stop("library ratLLMappings could not be found !")
                            #lib <- "ratLLMappings"
                       #     require(org.Rn.eg.db, quietly = TRUE) || stop("\nneed data package: org.Rn.eg.db\n")
                            lib = "org.Rn.eg.db"
                   })
        #Try(annlibloc <- grep(paste("^",whichLib[[1]][1],sep=""), as.vector(unlist(data(package="oneChannelGUI"))), ignore.case = T))
        #Try(annlibname <- as.vector(unlist(data(package="oneChannelGUI")))[annlibloc])
        #Try(data(list=annlibname,package="oneChannelGUI"))
        #Try(exonannlib<- get(annlibname,envir=.GlobalEnv))
        if(whichLib[[1]][1] == "HuEx"){
             Try(libDirLocation <- get("libDirLocation", envir=affylmGUIenvironment))
             Try(load(paste(libDirLocation, "huex.annotation.rda", sep="/")))
             Try(exonannlib <- huex.annotation)
             Try(rm(huex.annotation))
        }else if(whichLib[[1]][1] == "MoEx"){
             Try(libDirLocation <- get("libDirLocation", envir=affylmGUIenvironment))
             Try(load(paste(libDirLocation, "moex.annotation.rda", sep="/")))
             Try(exonannlib <- moex.annotation)
             Try(rm(moex.annotation))
        }else if(whichLib[[1]][1] == "RaEx"){
             Try(libDirLocation <- get("libDirLocation", envir=affylmGUIenvironment))
             Try(load(paste(libDirLocation, "raex.annotation.rda", sep="/")))
             Try(exonannlib <- raex.annotation)
             Try(rm(raex.annotation))
        }
   
        
        Try(genelist <- featureNames(NormalizedAffyData))#normalizeAffyData in x
        Try(acc <- as.character(exonannlib$ACC[which(as.character(exonannlib$PROBESETID)%in%genelist)])) #defining the universe of ll
        Try(probesets <- as.character(exonannlib$PROBESETID[which(as.character(exonannlib$PROBESETID)%in%genelist)])) #defining the universe of ll
        Try(names(acc) <- probesets)
        Try(acc <- acc[acc!=""])
        Try(acc <- acc[!is.na(acc)])
#        getDataEnv <- function(name, lib) {
#        	    get(paste(lib, name, sep = ""), mode = "environment")
#    	  }
        #Try(lltoacc <- mget(acc, env=getDataEnv("ACCNUM2LL", lib), ifnotfound=NA))#LL ids
        #extracting EGs
        Try(lltoacc <- as.character(unlist(lookUp(as.character(acc), lib, "ACCNUM2EG"))))
       Try(if(length(acc) == length(lltoacc)){
                   eg <- data.frame(names(acc), acc, lltoacc) 
                   names(eg) <- c("PROBESETID", "ACC", "EG")
                   toberemoved <- which(is.na(eg$EG))
                   eg <- eg[setdiff(seq(1,dim(eg)[1]),toberemoved),]
                   symbol <- toupper(as.character(unlist(lookUp(as.character(eg$EG), lib, "SYMBOL"))))
                   eg <- cbind(eg, symbol)
                   names(eg) <- c("PROBESETID", "ACC", "EG", "SYMBOL") 
                   assign("EG2probeset.available", TRUE, affylmGUIenvironment)
                   assign("EG2probeset", eg, affylmGUIenvironment)
                   return(eg) 
        } else {Try(tkmessageBox(title="Entres Gene ID and ACC to glevel probe sets: internal error 500, please communicate this error to the oneChannelGUI mantainer!"))
           return()
        })
}
                                                                                
################################################################################
".consistentFilter" <- function(){
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
    #error if no data are loaded
    Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
    if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
    }    
    Try(midas.p.Available <- get("midas.p.Available", env=affylmGUIenvironment))
    Try(AltSplRP.e.Available <- get("AltSplRP.e.Available", env=affylmGUIenvironment))
    if(midas.p.Available & AltSplRP.e.Available){
          Try(AltSplRP.e.p <- get("AltSplRP.e.p", env=affylmGUIenvironment))
          Try(myEids <- strsplit(as.character(AltSplRP.e.p[,1]), "\\|"))
          Try(myEids <- sapply(myEids, function(x)x[1]))
          Try(AltSplRP.e.p[,1] <- myEids)
          Try(midas.p <- get("midas.p", env=affylmGUIenvironment))
          Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment))
          Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
          Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
          #######################################################
          #assigning a p-value threshold to be use for the filter 
          #assigning midas threshold graphical menu
          Try(ttGetAltSplRP<-tktoplevel(.affylmGUIglobals$ttMain))
          Try(tkwm.deiconify(ttGetAltSplRP))
          Try(tkgrab.set(ttGetAltSplRP))
          Try(tkfocus(ttGetAltSplRP))
          Try(tkwm.title(ttGetAltSplRP,"Assigning p-value threshold"))
          Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
          Try(AltSplRPnum <- "0.05")
          Try(Local.AltSplRP <- tclVar(init=AltSplRPnum))
          Try(entry.AltSplRP <-tkentry(ttGetAltSplRP,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.AltSplRP,bg="white"))
          Try(tkgrid(tklabel(ttGetAltSplRP,text="Please enter a p-value threshold.",font=.affylmGUIglobals$affylmGUIfont2)))
          Try(tkgrid(entry.AltSplRP))
          onOK <- function()
          {
                Try(Midasnum <- as.numeric(tclvalue(Local.AltSplRP)))
                Try(assign("consistentP",AltSplRPnum,affylmGUIenvironment))
                Try(tclvalue(.affylmGUIglobals$AltSplRPnumTcl) <- AltSplRPnum)
                Try(tkgrab.release(ttGetAltSplRP));Try(tkdestroy(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain))                        
          }
          Try(OK.but <-tkbutton(ttGetAltSplRP,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
          Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
          Try(tkgrid(OK.but))
          Try(tkgrid.configure(OK.but))
          Try(tkgrid(tklabel(ttGetAltSplRP,text="       ")))
          Try(tkfocus(entry.AltSplRP))
          Try(tkbind(entry.AltSplRP, "<Return>",onOK))
          Try(tkbind(ttGetAltSplRP, "<Destroy>", function(){Try(tkgrab.release(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
          Try(tkwait.window(ttGetAltSplRP))
          Try(tkfocus(.affylmGUIglobals$ttMain))
#########################################################################
          Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
          Try(AltSplRPnum <- as.numeric(get("consistentP", env= affylmGUIenvironment)))
          Try(which1 <- AltSplRP.e.p[which(AltSplRP.e.p[,2] <= AltSplRPnum),1])
          Try(which2 <- AltSplRP.e.p[which(AltSplRP.e.p[,3] <= AltSplRPnum),1])
          Try(which <- unique(c(as.character(which1),as.character(which2))))#exons in RP

          Try(which3 <- midas.p[which(midas.p[,3] <= AltSplRPnum),2])#gene ids
          Try(which3 <- unique(which3))
          Try(which4 <- midas.p[which(midas.p[,3] <= AltSplRPnum),1])#exon ids
          Try(consistentExons <- intersect(which, which4))
          
          ######################Selecting fc threshold
          Try(targets <-  affylmGUIenvironment$Targets$Target)
          Try(target.unique <- unique(targets))
          Try(cl <- rep(0,length(targets)))
          if(length(target.unique) == 2){
                 #groups definition
                 Try(tkmessageBox(title="Filtering by SI mean difference",message="Two-Class case analysis will be performed."))
                 Try(cl[which(targets==target.unique[2])] <- 1)
                 Try(cl <- as.numeric(c("NA","NA",cl)))
                 Try(mean.c <- apply(spliceIndexData[,which(cl==0)], 1, mean))
                 Try(mean.t <- apply(spliceIndexData[,which(cl==1)], 1, mean))
                 Try(amsi <- abs(mean.t - mean.c))
          } else {
                         Try(tkmessageBox(title="Filtering by SI mean difference",message="This function works only for a two-class case.",type="ok",icon="error"))
				    	           Try(tkfocus(.affylmGUIglobals$ttMain))
                         Try(return())
          }
          
          Try(ttThresholdFC<-tktoplevel(.affylmGUIglobals$ttMain))
          Try(tkwm.deiconify(ttThresholdFC))
          Try(tkgrab.set(ttThresholdFC))
          Try(tkfocus(ttThresholdFC))
          Try(tkwm.title(ttThresholdFC,"|Delta SI| threshold"))
          Try(tkgrid(tklabel(ttThresholdFC,text="    ")))
          Try(ThresholdFC <- "1")
          Try(Local.FileName <- tclVar(init=ThresholdFC))
          Try(entry.FileName <-tkentry(ttThresholdFC,width="10",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.FileName,bg="white"))
          Try(tkgrid(tklabel(ttThresholdFC,text="Please, enter the absolute SI mean difference \nof your choice.",font=.affylmGUIglobals$affylmGUIfont2)))
          Try(tkgrid(entry.FileName))
          onOK <- function()
          {
                  Try(ThresholdFC <- tclvalue(Local.FileName))
                  if(nchar(ThresholdFC)==0)
                        Try(ThresholdFC <- 0)
                  Try(assign("ThresholdFC",ThresholdFC,affylmGUIenvironment))
                  Try(tclvalue(.affylmGUIglobals$ThresholdFCTcl) <- ThresholdFC)
                  Try(tkgrab.release(ttThresholdFC));Try(tkdestroy(ttThresholdFC));Try(tkfocus(.affylmGUIglobals$ttMain))
          }
          Try(OK.but <- tkbutton(ttThresholdFC,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
          Try(tkgrid(tklabel(ttThresholdFC,text="    ")))
          Try(tkgrid(OK.but))
          Try(tkgrid.configure(OK.but))
          Try(tkgrid(tklabel(ttThresholdFC,text="       ")))
          Try(tkfocus(entry.FileName))
          Try(tkbind(entry.FileName, "<Return>",onOK))
          Try(tkbind(ttThresholdFC, "<Destroy>", function(){Try(tkgrab.release(ttThresholdFC));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
          Try(tkwait.window(ttThresholdFC))
          Try(tkfocus(.affylmGUIglobals$ttMain))
                                           
          Try(fold.change <- as.numeric(affylmGUIenvironment$ThresholdFC))
          Try(selElevel <- spliceIndexData[which(amsi >= fold.change),1])
          ################################################################
          Try(consistentExons <- intersect(as.character(consistentExons) , as.character(selElevel)))
          #saving the list of exon significant
          Try(.saveFiltered(consistentExons))
          
          Try(consistentGenes <- midas.p[which(midas.p[,1] %in% consistentExons),2])
          Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData)%in%as.character(consistentGenes)),])
          Try(assign("NormalizedAffyData",NormalizedAffyData,affylmGUIenvironment))
          Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%featureNames(NormalizedAffyData)),3]) #in the list obtained from NetAffx there are all the probe set ids and I have to subset only those related to the exon library loaded with the data set
          Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
          Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
          Try(exonAffyData <- exonAffyData[which(featureNames(exonAffyData)%in%x.lib.subset),])
          Try(assign("exonAffyData",exonAffyData,affylmGUIenvironment))
          Try(spliceIndexData <- spliceIndexData[which(spliceIndexData[,1]%in%x.lib.subset),])
          Try(assign("spliceIndexData",spliceIndexData,affylmGUIenvironment))
          Try(info.dataset<-paste("Genes= ", dim(exprs(NormalizedAffyData))[1],"\n",
                                         "Exons= ", dim(exprs(exonAffyData))[1],"\n",
                                         "SI= ",    dim(spliceIndexData)[1],"\n",
                                         "Samples= ", dim(exprs(NormalizedAffyData))[2],"\n",
                                         "Annotation library= ", .annotation(NormalizedAffyData),"\n", sep=""))
    } else{
            Try(tkmessageBox(title="Consistent splicing events: to run this filter both midas and rank product p-values are needed!"))
            return()
    }
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}
################################################################################
"consistentFilters" <- function(){
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
    #error if no data are loaded
    Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
    if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())
    }    
    #select the filter combination
    Try(ttIfDialog<-tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttIfDialog))
    Try(tkgrab.set(ttIfDialog))
    Try(tkfocus(ttIfDialog))
    Try(tkwm.title(ttIfDialog,"Combining Filters"))
    Try(tkgrid(tklabel(ttIfDialog,text="    ")))
    Try(frame1 <- tkframe(ttIfDialog,relief="groove",borderwidth=2))
    Try(HowManyQuestion1 <- tklabel(frame1,text="Select the filters combination",font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(HowManyQuestion1))
    Try(tkgrid.configure(HowManyQuestion1,columnspan=2,sticky="w"))
    Try(thresholdTcl <- tclVar("midas.rp"))
    Try(I1.but  <- tkradiobutton(frame1,text="MiDAS and RP",variable=thresholdTcl,value="midas.rp",font=.affylmGUIglobals$affylmGUIfont2))
    Try(I2.but  <- tkradiobutton(frame1,text="MiDAS and delta SI",variable=thresholdTcl,value="midas.si",font=.affylmGUIglobals$affylmGUIfont2))
    Try(I3.but  <- tkradiobutton(frame1,text="RP and delta SI",variable=thresholdTcl,value="rp.si",font=.affylmGUIglobals$affylmGUIfont2))
    Try(I4.but  <- tkradiobutton(frame1,text="RP, MiDAS and delta SI",variable=thresholdTcl,value="midas.rp.si",font=.affylmGUIglobals$affylmGUIfont2))
    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,I1.but,I2.but,I3.but, I4.but,sticky="w"))
    Try(onOK <- function()
    {
        Try(ReturnFilter <<- as.character(tclvalue(thresholdTcl)))
        Try(tkgrab.release(ttIfDialog))
        Try(tkdestroy(ttIfDialog))
        Try(tkfocus(.affylmGUIglobals$ttMain))
    })
    Try(frame3 <- tkframe(ttIfDialog,borderwidth=2))
    Try(onCancel <- function() {
        Try(tkgrab.release(ttIfDialog))
        Try(tkdestroy(ttIfDialog))
        Try(tkfocus(.affylmGUIglobals$ttMain))
        Try(return())
    })
    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,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))
    if(ReturnFilter == "midas.rp"){
          Try(midas.p.Available <- get("midas.p.Available", env=affylmGUIenvironment))
          Try(AltSplRP.e.Available <- get("AltSplRP.e.Available", env=affylmGUIenvironment))
          if(midas.p.Available & AltSplRP.e.Available){
               Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment))
               Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
               Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
               Try(midas.p <- get("midas.p", env=affylmGUIenvironment))
               Try(AltSplRP.e.p <- get("AltSplRP.e.p", env=affylmGUIenvironment))
               #######################################################
               #assigning a p-value threshold to be use for the filter 
               #assigning midas threshold graphical menu
               Try(ttGetAltSplRP<-tktoplevel(.affylmGUIglobals$ttMain))
               Try(tkwm.deiconify(ttGetAltSplRP))
               Try(tkgrab.set(ttGetAltSplRP))
               Try(tkfocus(ttGetAltSplRP))
               Try(tkwm.title(ttGetAltSplRP,"Assigning p-value threshold"))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
               Try(AltSplRPnum <- "0.05")
               Try(Local.AltSplRP <- tclVar(init=AltSplRPnum))
               Try(entry.AltSplRP <-tkentry(ttGetAltSplRP,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.AltSplRP,bg="white"))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="Please enter a p-value threshold.",font=.affylmGUIglobals$affylmGUIfont2)))
               Try(tkgrid(entry.AltSplRP))
               onOK <- function()
               {
                     Try(AltSplRPnum <- as.numeric(tclvalue(Local.AltSplRP)))
                     Try(assign("consistentP",AltSplRPnum,affylmGUIenvironment))
                     Try(tclvalue(.affylmGUIglobals$AltSplRPnumTcl) <- as.numeric(tclvalue(Local.AltSplRP)))
                     Try(tkgrab.release(ttGetAltSplRP));Try(tkdestroy(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain))                        
               }
               Try(OK.but <-tkbutton(ttGetAltSplRP,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
               Try(tkgrid(OK.but))
               Try(tkgrid.configure(OK.but))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="       ")))
               Try(tkfocus(entry.AltSplRP))
               Try(tkbind(entry.AltSplRP, "<Return>",onOK))
               Try(tkbind(ttGetAltSplRP, "<Destroy>", function(){Try(tkgrab.release(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
               Try(tkwait.window(ttGetAltSplRP))
               Try(tkfocus(.affylmGUIglobals$ttMain))
               #########################################################################
               Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
               Try(AltSplRPnum <- as.numeric(get("consistentP", env= affylmGUIenvironment)))
               Try(which1 <- AltSplRP.e.p[which(AltSplRP.e.p[,2] <= AltSplRPnum),1])
               Try(which2 <- AltSplRP.e.p[which(AltSplRP.e.p[,3] <= AltSplRPnum),1])
               Try(which <- unique(c(as.character(which1),as.character(which2)))) #exons in RP
               
               Try(which3 <- midas.p[which(midas.p[,3] <= AltSplRPnum),2])#gene ids
               Try(which3 <- unique(which3))
               Try(which4 <- midas.p[which(midas.p[,3] <= AltSplRPnum),1])#exon ids
               Try(consistentExons <- intersect(which, which4))
               #saving the list of exon significant
               Try(.saveFiltered(consistentExons))
               
               Try(consistentGenes <- midas.p[which(midas.p[,1] %in% consistentExons),2])
               Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData)%in%as.character(consistentGenes)),])
               Try(assign("NormalizedAffyData",NormalizedAffyData,affylmGUIenvironment))
               Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%featureNames(NormalizedAffyData)),3]) #in the list obtained from NetAffx there are all the probe set ids and I have to subset only those related to the exon library loaded with the data set
               Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
               Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
               Try(exonAffyData <- exonAffyData[which(featureNames(exonAffyData)%in%x.lib.subset),])
               Try(assign("exonAffyData",exonAffyData,affylmGUIenvironment))
               Try(spliceIndexData <- spliceIndexData[which(spliceIndexData[,1]%in%x.lib.subset),])
               Try(assign("spliceIndexData",spliceIndexData,affylmGUIenvironment))
               Try(info.dataset<-paste("Genes= ", dim(exprs(NormalizedAffyData))[1],"\n",
                                         "Exons= ", dim(exprs(exonAffyData))[1],"\n",
                                         "SI= ",    dim(spliceIndexData)[1],"\n",
                                         "Samples= ", dim(exprs(NormalizedAffyData))[2],"\n",
                                         "Annotation library= ", .annotation(NormalizedAffyData),"\n", sep="")
               )
               Try(tkmessageBox(title="Combining Filters result",message=info.dataset,type="ok",icon="info"))
				    	     Try(tkfocus(.affylmGUIglobals$ttMain))
				    	     Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                   Try(return())
          } else{
                   Try(missedData <- "")
                   if(!midas.p.Available){ 
                            Try(missedData <- paste(missedData, "\nMiDAS p-values are missed!", sep=""))
                   }
                   if(!AltSplRP.e.Available){ 
                            Try(missedData <- paste(missedData, "\nRank Product p-values are missed!", sep=""))
                   }
                   Try(tkmessageBox(title="Combining Filters",message=paste(missedData, "\nPlease, calculate the missed item and run again this filter.",  sep=""),type="ok",icon="error"))
				    	     Try(tkfocus(.affylmGUIglobals$ttMain))
				    	     Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                   Try(return())
          }
    
    }
    if(ReturnFilter == "midas.si"){
          Try(midas.p.Available <- get("midas.p.Available", env=affylmGUIenvironment))
          Try(spliceIndexData.Available <- get("spliceIndexData.Available", env=affylmGUIenvironment))
          if(midas.p.Available & spliceIndexData.Available){
               Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment))
               Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
               Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
               Try(midas.p <- get("midas.p", env=affylmGUIenvironment))
               #######################################################
               #assigning a p-value threshold to be use for the filter 
               #assigning midas threshold graphical menu
               Try(ttGetAltSplRP<-tktoplevel(.affylmGUIglobals$ttMain))
               Try(tkwm.deiconify(ttGetAltSplRP))
               Try(tkgrab.set(ttGetAltSplRP))
               Try(tkfocus(ttGetAltSplRP))
               Try(tkwm.title(ttGetAltSplRP,"Assigning p-value threshold"))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
               Try(AltSplRPnum <- "0.05")
               Try(Local.AltSplRP <- tclVar(init=AltSplRPnum))
               Try(entry.AltSplRP <-tkentry(ttGetAltSplRP,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.AltSplRP,bg="white"))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="Please enter a p-value threshold.",font=.affylmGUIglobals$affylmGUIfont2)))
               Try(tkgrid(entry.AltSplRP))
               onOK <- function()
               {
                     Try(AltSplRPnum <- as.numeric(tclvalue(Local.AltSplRP)))
                     Try(assign("consistentP",AltSplRPnum,affylmGUIenvironment))
                     Try(tclvalue(.affylmGUIglobals$AltSplRPnumTcl) <- as.numeric(tclvalue(Local.AltSplRP)))
                     Try(tkgrab.release(ttGetAltSplRP));Try(tkdestroy(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain))                        
               }
               Try(OK.but <-tkbutton(ttGetAltSplRP,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
               Try(tkgrid(OK.but))
               Try(tkgrid.configure(OK.but))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="       ")))
               Try(tkfocus(entry.AltSplRP))
               Try(tkbind(entry.AltSplRP, "<Return>",onOK))
               Try(tkbind(ttGetAltSplRP, "<Destroy>", function(){Try(tkgrab.release(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
               Try(tkwait.window(ttGetAltSplRP))
               Try(tkfocus(.affylmGUIglobals$ttMain))
               
               Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
               #Try(which3 <- midas.p[which(midas.p[,3] <= AltSplRPnum),2])#gene ids
               #   Try(which3 <- unique(which3))
               Try(AltSplRPnum <- as.numeric(get("consistentP", affylmGUIenvironment)))
               Try(which4 <- midas.p[which(midas.p[,3] <= AltSplRPnum),1])#exon ids
               ######################Selecting delaSIthreshold
               Try(targets <-  affylmGUIenvironment$Targets$Target)
               Try(target.unique <- unique(targets))
               Try(cl <- rep(0,length(targets)))
               if(length(target.unique) == 2){
                      #groups definition
                      Try(tkmessageBox(title="Filtering by SI mean/min difference",message="Two-Class case analysis will be performed."))
                      Try(cl[which(targets==target.unique[2])] <- 1)
                      Try(cl <- as.numeric(c("NA","NA",cl)))
                      Try(mean.c <- apply(spliceIndexData[,which(cl==0)], 1, mean))
                      Try(mean.t <- apply(spliceIndexData[,which(cl==1)], 1, mean))
                      Try(amsi <- abs(mean.t - mean.c))
               } else {
                         Try(tkmessageBox(title="Filtering by SI mean/min difference",message="This function works only for a two-class case.",type="ok",icon="error"))
				    	           Try(tkfocus(.affylmGUIglobals$ttMain))
				    	           Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                         Try(return())
               }
               Try(ttThresholdFC<-tktoplevel(.affylmGUIglobals$ttMain))
               Try(tkwm.deiconify(ttThresholdFC))
               Try(tkgrab.set(ttThresholdFC))
               Try(tkfocus(ttThresholdFC))
               Try(tkwm.title(ttThresholdFC,"|Delta SI| threshold"))
               Try(tkgrid(tklabel(ttThresholdFC,text="    ")))
               Try(ThresholdFC <- "1")
               Try(Local.FileName <- tclVar(init=ThresholdFC))
               Try(entry.FileName <-tkentry(ttThresholdFC,width="10",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.FileName,bg="white"))
               Try(tkgrid(tklabel(ttThresholdFC,text="Please, enter the absolute SI mean/min difference \nof your choice.",font=.affylmGUIglobals$affylmGUIfont2)))
               Try(tkgrid(entry.FileName))
               onOK <- function()
               {
                  Try(ThresholdFC <- tclvalue(Local.FileName))
                  if(nchar(ThresholdFC)==0)
                        Try(ThresholdFC <- 0)
                  Try(assign("ThresholdFC",ThresholdFC,affylmGUIenvironment))
                  Try(tclvalue(.affylmGUIglobals$ThresholdFCTcl) <- ThresholdFC)
                  Try(tkgrab.release(ttThresholdFC));Try(tkdestroy(ttThresholdFC));Try(tkfocus(.affylmGUIglobals$ttMain))
               }
               Try(OK.but <- tkbutton(ttThresholdFC,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
               Try(tkgrid(tklabel(ttThresholdFC,text="    ")))
               Try(tkgrid(OK.but))
               Try(tkgrid.configure(OK.but))
               Try(tkgrid(tklabel(ttThresholdFC,text="       ")))
               Try(tkfocus(entry.FileName))
               Try(tkbind(entry.FileName, "<Return>",onOK))
               Try(tkbind(ttThresholdFC, "<Destroy>", function(){Try(tkgrab.release(ttThresholdFC));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
               Try(tkwait.window(ttThresholdFC))
               Try(tkfocus(.affylmGUIglobals$ttMain))
               Try(fold.change <- as.numeric(get("ThresholdFC", affylmGUIenvironment)))
               ###############################################################
               #selecting mean ir min
               Try(mbVal <- tkmessageBox(title="Filtering by SI mean/min difference",
                                           message="Do you want to use a SI min difference filter? \nIf you answer no a SI mean difference filter will be applyed",
                                           icon="question",type="yesno",default="yes"))
               Try(if(tclvalue(mbVal)=="yes"){
                          min.c <- apply(spliceIndexData[,which(cl==0)], 1, min)
                          min.t <- apply(spliceIndexData[,which(cl==1)], 1, min)
                          max.c <- apply(spliceIndexData[,which(cl==0)], 1, max)
                          max.t <- apply(spliceIndexData[,which(cl==1)], 1, max)
                          minmax <- data.frame(min.c, min.t, max.c, max.t)
                          .deltaMin <- function(x){ if(x[3]<x[4]){abs(x[3]-x[2])} else{abs(x[4]-x[1])}} #if max.c<max.t |max.c-min.t| else |max.t-min.c| 
                          amsi <- apply(minmax, 1, .deltaMin)
                          amsi <- data.frame(spliceIndexData[,1], spliceIndexData[,2], as.numeric(amsi))
                          names(amsi) <- c("elevel", "glevel", "deltaSI")
                 } else{
                          mean.c <- apply(spliceIndexData[,which(cl==0)], 1, mean)
                          mean.t <- apply(spliceIndexData[,which(cl==1)], 1, mean)
                          amsi <- abs(mean.t - mean.c)
                          amsi <- data.frame(spliceIndexData[,1], spliceIndexData[,2], as.numeric(amsi))
                          names(amsi) <- c("elevel", "glevel", "deltaSI")
                    }
               )
               Try(selGElevel <- amsi[which(amsi[,3] >= fold.change),])
               ################################################################
               Try(consistentExons <- intersect(as.character(which4) , as.character(selGElevel[,1]))) #common exons ids
               #saving the list of exon significant
               Try(.saveFiltered(consistentExons))
               
               Try(consistentGene <- selGElevel[which(selGElevel[,1] %in% consistentExons),2])#common gene ids  
               Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData) %in% as.character(consistentGene)),])
               Try(assign("NormalizedAffyData",NormalizedAffyData,affylmGUIenvironment))
               Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%featureNames(NormalizedAffyData)),3]) #in the list obtained from NetAffx there are all the probe set ids and I have to subset only those related to the exon library loaded with the data set
               Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
               Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
               Try(exonAffyData <- exonAffyData[which(featureNames(exonAffyData)%in%x.lib.subset),])
               Try(assign("exonAffyData",exonAffyData,affylmGUIenvironment))
               Try(spliceIndexData <- spliceIndexData[which(spliceIndexData[,1]%in%x.lib.subset),])
               Try(assign("spliceIndexData",spliceIndexData,affylmGUIenvironment))
               Try(info.dataset<-paste("Genes= ", dim(exprs(NormalizedAffyData))[1],"\n",
                                         "Exons= ", dim(exprs(exonAffyData))[1],"\n",
                                         "SI= ",    dim(spliceIndexData)[1],"\n",
                                         "Samples= ", dim(exprs(NormalizedAffyData))[2],"\n",
                                         "Annotation library= ", .annotation(NormalizedAffyData),"\n", sep="")
               )
               Try(tkmessageBox(title="Combining Filters result",message=info.dataset,type="ok",icon="info"))
				    	     Try(tkfocus(.affylmGUIglobals$ttMain))
				    	     Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                   Try(return())
          } else{
                   Try(missedData <- "")
                   if(!midas.p.Available){ 
                            Try(missedData <- paste(missedData, "\nMiDAS p-values are missed!", sep=""))
                   }
                   if(!spliceIndexData.Available){ 
                            Try(missedData <- paste(missedData, "\nSplice Indexes are missed!", sep=""))
                   }
                   Try(tkmessageBox(title="Combining Filters",message=paste(missedData, "\nPlease, calculate the missed item and run again this filter.",  sep=""),type="ok",icon="error"))
				    	     Try(tkfocus(.affylmGUIglobals$ttMain))
				    	     Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                   Try(return())
           }
          }
          if(ReturnFilter == "rp.si"){
            Try(AltSplRP.e.Available <- get("AltSplRP.e.Available", env=affylmGUIenvironment))
            if(AltSplRP.e.Available){
               Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment))
               Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
               Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
               Try(AltSplRP.e.p <- get("AltSplRP.e.p", env=affylmGUIenvironment))
               #######################################################
               #assigning a p-value threshold to be use for the filter 
               #assigning midas threshold graphical menu
               Try(ttGetAltSplRP<-tktoplevel(.affylmGUIglobals$ttMain))
               Try(tkwm.deiconify(ttGetAltSplRP))
               Try(tkgrab.set(ttGetAltSplRP))
               Try(tkfocus(ttGetAltSplRP))
               Try(tkwm.title(ttGetAltSplRP,"Assigning p-value threshold"))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
               Try(AltSplRPnum <- "0.05")
               Try(Local.AltSplRP <- tclVar(init=AltSplRPnum))
               Try(entry.AltSplRP <-tkentry(ttGetAltSplRP,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.AltSplRP,bg="white"))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="Please enter a p-value threshold.",font=.affylmGUIglobals$affylmGUIfont2)))
               Try(tkgrid(entry.AltSplRP))
               onOK <- function()
               {
                     Try(AltSplRPnum <- as.numeric(tclvalue(Local.AltSplRP)))
                     Try(assign("consistentP",AltSplRPnum,affylmGUIenvironment))
                     Try(tclvalue(.affylmGUIglobals$AltSplRPnumTcl) <- as.numeric(tclvalue(Local.AltSplRP)))
                     Try(tkgrab.release(ttGetAltSplRP));Try(tkdestroy(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain))                        
               }
               Try(OK.but <-tkbutton(ttGetAltSplRP,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
               Try(tkgrid(OK.but))
               Try(tkgrid.configure(OK.but))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="       ")))
               Try(tkfocus(entry.AltSplRP))
               Try(tkbind(entry.AltSplRP, "<Return>",onOK))
               Try(tkbind(ttGetAltSplRP, "<Destroy>", function(){Try(tkgrab.release(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
               Try(tkwait.window(ttGetAltSplRP))
               Try(tkfocus(.affylmGUIglobals$ttMain))

               Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
               #Try(which3 <- midas.p[which(midas.p[,3] <= AltSplRPnum),2])#gene ids
               #   Try(which3 <- unique(which3))
               Try(AltSplRPnum <- as.numeric(get("consistentP", affylmGUIenvironment)))
               Try(which1 <- AltSplRP.e.p[which(AltSplRP.e.p[,2] <= AltSplRPnum),1])
               Try(which2 <- AltSplRP.e.p[which(AltSplRP.e.p[,3] <= AltSplRPnum),1])
               Try(which <- unique(c(as.character(which1),as.character(which2)))) #exons in RP
               ######################Selecting delaSIthreshold
               Try(targets <-  affylmGUIenvironment$Targets$Target)
               Try(target.unique <- unique(targets))
               Try(cl <- rep(0,length(targets)))
               if(length(target.unique) == 2){
                      #groups definition
                      Try(tkmessageBox(title="Filtering by SI mean/min difference",message="Two-Class case analysis will be performed."))
                      Try(cl[which(targets==target.unique[2])] <- 1)
                      Try(cl <- as.numeric(c("NA","NA",cl)))
                      Try(mean.c <- apply(spliceIndexData[,which(cl==0)], 1, mean))
                      Try(mean.t <- apply(spliceIndexData[,which(cl==1)], 1, mean))
                      Try(amsi <- abs(mean.t - mean.c))
               } else {
                         Try(tkmessageBox(title="Filtering by SI mean/min difference",message="This function works only for a two-class case.",type="ok",icon="error"))
				    	           Try(tkfocus(.affylmGUIglobals$ttMain))
				    	           Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                         Try(return())
               }
               Try(ttThresholdFC<-tktoplevel(.affylmGUIglobals$ttMain))
               Try(tkwm.deiconify(ttThresholdFC))
               Try(tkgrab.set(ttThresholdFC))
               Try(tkfocus(ttThresholdFC))
               Try(tkwm.title(ttThresholdFC,"|Delta SI| threshold"))
               Try(tkgrid(tklabel(ttThresholdFC,text="    ")))
               Try(ThresholdFC <- "1")
               Try(Local.FileName <- tclVar(init=ThresholdFC))
               Try(entry.FileName <-tkentry(ttThresholdFC,width="10",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.FileName,bg="white"))
               Try(tkgrid(tklabel(ttThresholdFC,text="Please, enter the absolute SI mean/min difference \nof your choice.",font=.affylmGUIglobals$affylmGUIfont2)))
               Try(tkgrid(entry.FileName))
               onOK <- function()
               {
                  Try(ThresholdFC <- tclvalue(Local.FileName))
                  if(nchar(ThresholdFC)==0)
                        Try(ThresholdFC <- 0)
                  Try(assign("ThresholdFC",ThresholdFC,affylmGUIenvironment))
                  Try(tclvalue(.affylmGUIglobals$ThresholdFCTcl) <- ThresholdFC)
                  Try(tkgrab.release(ttThresholdFC));Try(tkdestroy(ttThresholdFC));Try(tkfocus(.affylmGUIglobals$ttMain))
               }
               Try(OK.but <- tkbutton(ttThresholdFC,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
               Try(tkgrid(tklabel(ttThresholdFC,text="    ")))
               Try(tkgrid(OK.but))
               Try(tkgrid.configure(OK.but))
               Try(tkgrid(tklabel(ttThresholdFC,text="       ")))
               Try(tkfocus(entry.FileName))
               Try(tkbind(entry.FileName, "<Return>",onOK))
               Try(tkbind(ttThresholdFC, "<Destroy>", function(){Try(tkgrab.release(ttThresholdFC));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
               Try(tkwait.window(ttThresholdFC))
               Try(tkfocus(.affylmGUIglobals$ttMain))
               Try(fold.change <- as.numeric(get("ThresholdFC", affylmGUIenvironment)))
               ###############################################################
               #selecting mean ir min
               Try(mbVal <- tkmessageBox(title="Filtering by SI mean/min difference",
                                           message="Do you want to use a SI min difference filter? \nIf you answer no a SI mean difference filter will be applyed",
                                           icon="question",type="yesno",default="yes"))
               Try(if(tclvalue(mbVal)=="yes"){
                          min.c <- apply(spliceIndexData[,which(cl==0)], 1, min)
                          min.t <- apply(spliceIndexData[,which(cl==1)], 1, min)
                          max.c <- apply(spliceIndexData[,which(cl==0)], 1, max)
                          max.t <- apply(spliceIndexData[,which(cl==1)], 1, max)
                          minmax <- data.frame(min.c, min.t, max.c, max.t)
                          .deltaMin <- function(x){ if(x[3]<x[4]){abs(x[3]-x[2])} else{abs(x[4]-x[1])}} #if max.c<max.t |max.c-min.t| else |max.t-min.c| 
                          amsi <- apply(minmax, 1, .deltaMin)
                          amsi <- data.frame(spliceIndexData[,1], spliceIndexData[,2], as.numeric(amsi))
                          names(amsi) <- c("elevel", "glevel", "deltaSI")
                 } else{
                          mean.c <- apply(spliceIndexData[,which(cl==0)], 1, mean)
                          mean.t <- apply(spliceIndexData[,which(cl==1)], 1, mean)
                          amsi <- abs(mean.t - mean.c)
                          amsi <- data.frame(spliceIndexData[,1], spliceIndexData[,2], as.numeric(amsi))
                          names(amsi) <- c("elevel", "glevel", "deltaSI")
                    }
               )
               Try(selGElevel <- amsi[which(amsi[,3] >= fold.change),])
               ################################################################
               Try(consistentExons <- intersect(as.character(which) , as.character(selGElevel[,1]))) #common exons ids rp set which
               #saving the list of exon significant
               Try(.saveFiltered(consistentExons))
               
               Try(consistentGene <- selGElevel[which(selGElevel[,1] %in% consistentExons),2])#common gene ids  
               Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData) %in% as.character(consistentGene)),])
               Try(assign("NormalizedAffyData",NormalizedAffyData,affylmGUIenvironment))
               Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%featureNames(NormalizedAffyData)),3]) #in the list obtained from NetAffx there are all the probe set ids and I have to subset only those related to the exon library loaded with the data set
               Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
               Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
               Try(exonAffyData <- exonAffyData[which(featureNames(exonAffyData)%in%x.lib.subset),])
               Try(assign("exonAffyData",exonAffyData,affylmGUIenvironment))
               Try(spliceIndexData <- spliceIndexData[which(spliceIndexData[,1]%in%x.lib.subset),])
               Try(assign("spliceIndexData",spliceIndexData,affylmGUIenvironment))
               Try(info.dataset<-paste("Genes= ", dim(exprs(NormalizedAffyData))[1],"\n",
                                         "Exons= ", dim(exprs(exonAffyData))[1],"\n",
                                         "SI= ",    dim(spliceIndexData)[1],"\n",
                                         "Samples= ", dim(exprs(NormalizedAffyData))[2],"\n",
                                         "Annotation library= ", .annotation(NormalizedAffyData),"\n", sep="")
               )
               Try(tkmessageBox(title="Combining Filters result",message=info.dataset,type="ok",icon="info"))
				    	     Try(tkfocus(.affylmGUIglobals$ttMain))
				    	     Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                   Try(return())
          } else{
                   Try(missedData <- "")
                   if(!midas.p.Available){ 
                            Try(missedData <- paste(missedData, "\nMiDAS p-values are missed!", sep=""))
                   }
                   if(!spliceIndexData.Available){ 
                            Try(missedData <- paste(missedData, "\nSplice Indexes are missed!", sep=""))
                   }
                   Try(tkmessageBox(title="Combining Filters",message=paste(missedData, "\nPlease, calculate the missed item and run again this filter.",  sep=""),type="ok",icon="error"))
				    	     Try(tkfocus(.affylmGUIglobals$ttMain))
				    	     Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                   Try(return())
          }
       }
       if(ReturnFilter == "midas.rp.si"){
          Try(midas.p.Available <- get("midas.p.Available", env=affylmGUIenvironment))
          Try(AltSplRP.e.Available <- get("AltSplRP.e.Available", env=affylmGUIenvironment))
          if(midas.p.Available & AltSplRP.e.Available){
               Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment))
               Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
               Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
               Try(midas.p <- get("midas.p", env=affylmGUIenvironment))
               Try(AltSplRP.e.p <- get("AltSplRP.e.p", env=affylmGUIenvironment))
               #######################################################
               #assigning a p-value threshold to be use for the filter 
               #assigning midas threshold graphical menu
               Try(ttGetAltSplRP<-tktoplevel(.affylmGUIglobals$ttMain))
               Try(tkwm.deiconify(ttGetAltSplRP))
               Try(tkgrab.set(ttGetAltSplRP))
               Try(tkfocus(ttGetAltSplRP))
               Try(tkwm.title(ttGetAltSplRP,"Assigning p-value threshold"))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
               Try(AltSplRPnum <- "0.05")
               Try(Local.AltSplRP <- tclVar(init=AltSplRPnum))
               Try(entry.AltSplRP <-tkentry(ttGetAltSplRP,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.AltSplRP,bg="white"))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="Please enter a p-value threshold.",font=.affylmGUIglobals$affylmGUIfont2)))
               Try(tkgrid(entry.AltSplRP))
               onOK <- function()
               {
                     Try(AltSplRPnum <- as.numeric(tclvalue(Local.AltSplRP)))
                     Try(assign("consistentP",AltSplRPnum,affylmGUIenvironment))
                     Try(tclvalue(.affylmGUIglobals$AltSplRPnumTcl) <- as.numeric(tclvalue(Local.AltSplRP)))
                     Try(tkgrab.release(ttGetAltSplRP));Try(tkdestroy(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain))                        
               }
               Try(OK.but <-tkbutton(ttGetAltSplRP,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="    ")))
               Try(tkgrid(OK.but))
               Try(tkgrid.configure(OK.but))
               Try(tkgrid(tklabel(ttGetAltSplRP,text="       ")))
               Try(tkfocus(entry.AltSplRP))
               Try(tkbind(entry.AltSplRP, "<Return>",onOK))
               Try(tkbind(ttGetAltSplRP, "<Destroy>", function(){Try(tkgrab.release(ttGetAltSplRP));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
               Try(tkwait.window(ttGetAltSplRP))
               Try(tkfocus(.affylmGUIglobals$ttMain))
               #########################################################################
               Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
               Try(AltSplRPnum <- as.numeric(get("consistentP", env= affylmGUIenvironment)))
               Try(which1 <- AltSplRP.e.p[which(AltSplRP.e.p[,2] <= AltSplRPnum),1])
               Try(which2 <- AltSplRP.e.p[which(AltSplRP.e.p[,3] <= AltSplRPnum),1])
               Try(which <- unique(c(as.character(which1),as.character(which2))))
               Try(which <- strsplit(which, "\\|"))#first exon inds second transcript id

               Try(which3 <- midas.p[which(midas.p[,3] <= AltSplRPnum),2])#gene ids
               Try(which3 <- unique(which3))
               Try(which4 <- midas.p[which(midas.p[,3] <= AltSplRPnum),1])#exon ids
               Try(consistentExons <- intersect(which, which4))
               ######################Selecting delaSIthreshold
               Try(targets <-  affylmGUIenvironment$Targets$Target)
               Try(target.unique <- unique(targets))
               Try(cl <- rep(0,length(targets)))
               if(length(target.unique) == 2){
                      #groups definition
                      Try(tkmessageBox(title="Filtering by SI mean/min difference",message="Two-Class case analysis will be performed."))
                      Try(cl[which(targets==target.unique[2])] <- 1)
                      Try(cl <- as.numeric(c("NA","NA",cl)))
                      Try(mean.c <- apply(spliceIndexData[,which(cl==0)], 1, mean))
                      Try(mean.t <- apply(spliceIndexData[,which(cl==1)], 1, mean))
                      Try(amsi <- abs(mean.t - mean.c))
               } else {
                         Try(tkmessageBox(title="Filtering by SI mean/min difference",message="This function works only for a two-class case.",type="ok",icon="error"))
				    	           Try(tkfocus(.affylmGUIglobals$ttMain))
				    	           Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                         Try(return())
               }
               Try(ttThresholdFC<-tktoplevel(.affylmGUIglobals$ttMain))
               Try(tkwm.deiconify(ttThresholdFC))
               Try(tkgrab.set(ttThresholdFC))
               Try(tkfocus(ttThresholdFC))
               Try(tkwm.title(ttThresholdFC,"|Delta SI| threshold"))
               Try(tkgrid(tklabel(ttThresholdFC,text="    ")))
               Try(ThresholdFC <- "1")
               Try(Local.FileName <- tclVar(init=ThresholdFC))
               Try(entry.FileName <-tkentry(ttThresholdFC,width="10",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.FileName,bg="white"))
               Try(tkgrid(tklabel(ttThresholdFC,text="Please, enter the absolute SI mean/min difference \nof your choice.",font=.affylmGUIglobals$affylmGUIfont2)))
               Try(tkgrid(entry.FileName))
               onOK <- function()
               {
                  Try(ThresholdFC <- tclvalue(Local.FileName))
                  if(nchar(ThresholdFC)==0)
                        Try(ThresholdFC <- 0)
                  Try(assign("ThresholdFC",ThresholdFC,affylmGUIenvironment))
                  Try(tclvalue(.affylmGUIglobals$ThresholdFCTcl) <- ThresholdFC)
                  Try(tkgrab.release(ttThresholdFC));Try(tkdestroy(ttThresholdFC));Try(tkfocus(.affylmGUIglobals$ttMain))
               }
               Try(OK.but <- tkbutton(ttThresholdFC,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
               Try(tkgrid(tklabel(ttThresholdFC,text="    ")))
               Try(tkgrid(OK.but))
               Try(tkgrid.configure(OK.but))
               Try(tkgrid(tklabel(ttThresholdFC,text="       ")))
               Try(tkfocus(entry.FileName))
               Try(tkbind(entry.FileName, "<Return>",onOK))
               Try(tkbind(ttThresholdFC, "<Destroy>", function(){Try(tkgrab.release(ttThresholdFC));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
               Try(tkwait.window(ttThresholdFC))
               Try(tkfocus(.affylmGUIglobals$ttMain))
               Try(fold.change <- as.numeric(get("ThresholdFC", affylmGUIenvironment)))
               ###############################################################
               #selecting mean ir min
               Try(mbVal <- tkmessageBox(title="Filtering by SI mean/min difference",
                                           message="Do you want to use a SI min difference filter? \nIf you answer no a SI mean difference filter will be applyed",
                                           icon="question",type="yesno",default="yes"))
               Try(if(tclvalue(mbVal)=="yes"){
                          min.c <- apply(spliceIndexData[,which(cl==0)], 1, min)
                          min.t <- apply(spliceIndexData[,which(cl==1)], 1, min)
                          max.c <- apply(spliceIndexData[,which(cl==0)], 1, max)
                          max.t <- apply(spliceIndexData[,which(cl==1)], 1, max)
                          minmax <- data.frame(min.c, min.t, max.c, max.t)
                          .deltaMin <- function(x){ if(x[3]<x[4]){abs(x[3]-x[2])} else{abs(x[4]-x[1])}} #if max.c<max.t |max.c-min.t| else |max.t-min.c| 
                          amsi <- apply(minmax, 1, .deltaMin)
                          amsi <- data.frame(spliceIndexData[,1], spliceIndexData[,2], as.numeric(amsi))
                          names(amsi) <- c("elevel", "glevel", "deltaSI")
                 } else{
                          mean.c <- apply(spliceIndexData[,which(cl==0)], 1, mean)
                          mean.t <- apply(spliceIndexData[,which(cl==1)], 1, mean)
                          amsi <- abs(mean.t - mean.c)
                          amsi <- data.frame(spliceIndexData[,1], spliceIndexData[,2], as.numeric(amsi))
                          names(amsi) <- c("elevel", "glevel", "deltaSI")
                    }
               )
               Try(selGElevel <- amsi[which(amsi[,3] >= fold.change),])
               ################################################################
               Try(consistentExons <- intersect(as.character(consistentExons) , as.character(selGElevel[,1]))) #common exons ids rp set which1
               #saving the list of exon significant
               Try(.saveFiltered(consistentExons))
               
               Try(consistentGenes <- selGElevel[which(selGElevel[,1] %in% consistentExons),2])#common gene ids  
               Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData)%in%as.character(consistentGenes)),])
               Try(assign("NormalizedAffyData",NormalizedAffyData,affylmGUIenvironment))
               Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%featureNames(NormalizedAffyData)),3]) #in the list obtained from NetAffx there are all the probe set ids and I have to subset only those related to the exon library loaded with the data set
               Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
               Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
               Try(exonAffyData <- exonAffyData[which(featureNames(exonAffyData)%in%x.lib.subset),])
               Try(assign("exonAffyData",exonAffyData,affylmGUIenvironment))
               Try(spliceIndexData <- spliceIndexData[which(spliceIndexData[,1]%in%x.lib.subset),])
               Try(assign("spliceIndexData",spliceIndexData,affylmGUIenvironment))
               Try(info.dataset<-paste("Genes= ", dim(exprs(NormalizedAffyData))[1],"\n",
                                         "Exons= ", dim(exprs(exonAffyData))[1],"\n",
                                         "SI= ",    dim(spliceIndexData)[1],"\n",
                                         "Samples= ", dim(exprs(NormalizedAffyData))[2],"\n",
                                         "Annotation library= ", .annotation(NormalizedAffyData),"\n", sep="")
               )
               Try(tkmessageBox(title="Combining Filters result",message=info.dataset,type="ok",icon="info"))
				    	     Try(tkfocus(.affylmGUIglobals$ttMain))
				    	     Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                   Try(return())
          } else{
                   Try(missedData <- "")
                   if(!midas.p.Available){ 
                            Try(missedData <- paste(missedData, "\nMiDAS p-values are missed!", sep=""))
                   }
                   if(!AltSplRP.e.Available){ 
                            Try(missedData <- paste(missedData, "\nRank Product p-values are missed!", sep=""))
                   }
                   Try(tkmessageBox(title="Combining Filters",message=paste(missedData, "\nPlease, calculate the missed item and run again this filter.",  sep=""),type="ok",icon="error"))
				    	     Try(tkfocus(.affylmGUIglobals$ttMain))
				    	     Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                   Try(return())
          }
    
    }


    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}
################################################################################
"mapping2ensembl" <- function(){
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
    Try(cat("\nStarting probeset mapping to ENSEMBL exons\n"))
    #error if no data are loaded
    Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
    if(whichArrayPlatform !="EXON"){
              Try(tkmessageBox(title="Mapping to ENSEMBL",message="No exon arrays are loaded. This function only apply to Affymetrix EXON arrays.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())
    }
    Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
    Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))
    Try(cat("\nCombining statistical and expression data\n"))
    if(whichLib[[1]][1] == "HuEx"){
    #    require(HuExExonProbesetLocation) || stop("\nMissing HuExExonProbesetLocation package\n")
        data(HuExExonProbesetLocation)
        crosshybhuex.annotation<- get("HuExExonProbesetLocation",envir=.GlobalEnv)
        Try(exon.ann <- crosshybhuex.annotation[which(as.character(crosshybhuex.annotation$GPROBESETID)%in%featureNames(NormalizedAffyData)),c(1:3,5:8)])
    }
    if(whichLib[[1]][1] == "MoEx"){
    #    require(MoExExonProbesetLocation) || stop("\nMissing MoExExonProbesetLocation package\n")
        data(MoExExonProbesetLocation)
        crosshybmoex.annotation<- get("MoExExonProbesetLocation",envir=.GlobalEnv)
        Try(exon.ann <- crosshybmoex.annotation[which(as.character(crosshybmoex.annotation$GPROBESETID)%in%featureNames(NormalizedAffyData)),c(1:3,5:8)])
    }
    if(whichLib[[1]][1] == "RaEx"){
     #   require(RaExExonProbesetLocation) || stop("\nMissing RaExExonProbesetLocation package\n")
        data(RaExExonProbesetLocation)
        crosshybraex.annotation<- get("RaExExonProbesetLocation",envir=.GlobalEnv)
        Try(exon.ann <- crosshybraex.annotation[which(as.character(crosshybraex.annotation$GPROBESETID)%in%featureNames(NormalizedAffyData)),c(1:3,5:8)])
    }
    Try(spliceIndexData.Available <- get("spliceIndexData.Available",  env=affylmGUIenvironment))
    if(!spliceIndexData.Available){
              Try(tkmessageBox(title="Mapping to ENSEMBL",message="No Splice Index is available. Please calculate it and run this function again.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())

    }
    Try(spliceIndexData <- get("spliceIndexData",  env=affylmGUIenvironment))
    Try(tmp.si <- spliceIndexData[which(as.character(spliceIndexData$geneExonsIds)%in%as.character(exon.ann$EPROBESETID)),])
    Try(tmp.si <- tmp.si[order(as.character(tmp.si$geneExonsIds)),])
    Try(exon.ann <- exon.ann[which(as.character(exon.ann$EPROBESETID)%in%as.character(tmp.si$geneExonsIds)),])
    Try(exon.ann <- exon.ann[order(as.character(exon.ann$EPROBESETID)),])
    if(!identical(as.character(exon.ann$EPROBESETID), as.character(tmp.si$geneExonsIds))){
              Try(tkmessageBox(title="Mapping to ENSEMBL",message="Internal error 501. Comunicate it to package mantainer!",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())
    }
    #attaching SI values
    Try(exon.ann <- cbind(exon.ann, tmp.si[,3:dim(tmp.si)[2]]))
    #attaching an empty midas.p column
    Try(exon.ann <- cbind(exon.ann, "midas.p"=rep(NA, dim(exon.ann)[1])))
    #attaching an empty rp column
    Try(exon.ann <- cbind(exon.ann, "rp.p1"=rep(NA, dim(exon.ann)[1])))
    Try(exon.ann <- cbind(exon.ann, "rp.p2"=rep(NA, dim(exon.ann)[1])))
    #attaching deltaSI
    Try(exon.ann <- cbind(exon.ann, "deltaSI"=rep(NA, dim(exon.ann)[1])))
    #getting midas.p
    Try(midas.p.Available <- get("midas.p.Available",  env=affylmGUIenvironment))
    if(midas.p.Available){
      Try(midas.p <- get("midas.p",  env=affylmGUIenvironment))
      Try(tmp.p <- midas.p[which(as.character(midas.p[,1])%in%as.character(exon.ann$EPROBESETID)),])
      Try(tmp.p <- tmp.p[order(tmp.p[,1]),])
      if(!identical(as.character(exon.ann$EPROBESETID), as.character(tmp.p[,1]))){
              Try(tkmessageBox(title="Mapping to ENSEMBL",message="Internal error 502. Comunicate it to package mantainer!",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())
      }
      Try(exon.ann$midas.p <- tmp.p[,3])
    }
    #gettong rp exon p
    Try(AltSplRP.e.Available <- get("AltSplRP.e.Available",  env=affylmGUIenvironment))
    if(AltSplRP.e.Available){
      Try(AltSplRP.e.p <- get("AltSplRP.e.p",  env=affylmGUIenvironment))
      Try(tmp.ids <- strsplit(as.character(AltSplRP.e.p[,1]), '\\|'))
      Try(tmp.ids <- sapply(tmp.ids, function(x){x[1]}))
      Try(AltSplRP.e.p[,1] <- tmp.ids)
      Try(tmp.p <- AltSplRP.e.p[which(as.character(AltSplRP.e.p[,1])%in%as.character(exon.ann$EPROBESETID)),])
      Try(tmp.p <- tmp.p[order(tmp.p[,1]),])
      if(!identical(as.character(exon.ann$EPROBESETID), as.character(tmp.p[,1]))){
              Try(tkmessageBox(title="Mapping to ENSEMBL",message="Internal error 502. Comunicate it to package mantainer!",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())
      }
      Try(exon.ann$rp.p1 <- tmp.p[,2])
      Try(exon.ann$rp.p2 <- tmp.p[,3])
      Try(exon.ann$deltaSI <- tmp.p$deltaSI)

    }
    Try(cat("\nRetrieving e-level target sequences from RRE database\n"))
    #retrieving from RRE the target sequences for EPROBESETID
    #defining a temporary file tu save the exon-level target sequences downloaded by RRE
    tempSeq <- tempfile(pattern = "RRE", tmpdir = "")
    tempSeq <- sub( "\\\\","",tempSeq)
    tempSeq <- sub( "/","",tempSeq)
    workingDir <- getwd()
    workingDir <- sub( "/$","",workingDir)  
    tempSeq <- paste(workingDir, "/", tempSeq, ".seq", sep="")
                            
    if(length(exon.ann$EPROBESETID) <= 1000){
        Try(query1 <- "http://www6.unito.it/RRE/Query/probeSet.php?glist=")
        Try(query2 <- paste(exon.ann$EPROBESETID, collapse=","))
        if(whichLib[[1]][1] =="HuEx"){
           Try(query3 <- "&organism=Human&sep=,&Start=no&Stop=no")
        }
        if(whichLib[[1]][1] =="MoEx"){
           Try(query3 <- "&organism=Mouse&sep=,&Start=no&Stop=no")
        }
        if(whichLib[[1]][1] =="RaEx"){
           Try(query3 <- "&organism=Rat&sep=,&Start=no&Stop=no")
        }
        Try(query.all <- paste(query1, query2, query3, collapse=""))
        Try(query.all <- gsub(" ", "", query.all))
        Try(download.file(query.all, tempSeq, mode="w"))
    } else{
      Try(steps <- seq(1, length(exon.ann$EPROBESETID), by=1000))
      Try(stepsi <- steps)
      Try(stepsj <- c(steps[2:length(steps)] - 1, length(exon.ann$EPROBESETID)))
      Try(query1 <- "http://www6.unito.it/RRE/Query/probeSet.php?glist=")
      if(whichLib[[1]][1] =="HuEx"){
              Try(query3 <- "&organism=Human&sep=,&Start=no&Stop=no")
      }
      if(whichLib[[1]][1] =="MoEx"){
              Try(query3 <- "&organism=Mouse&sep=,&Start=no&Stop=no")
      }
      if(whichLib[[1]][1] =="RaEx"){
              Try(query3 <- "&organism=Rat&sep=,&Start=no&Stop=no")
      }
      for(i in 1:length(stepsi)){
       #       Try(require(stats))
              Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
              Try(query2 <- paste(exon.ann$EPROBESETID[stepsi[i]:stepsj[i]], collapse=","))
              Try(query.all <- paste(query1, query2, query3, collapse=""))
              Try(query.all <- gsub(" ", "", query.all))
              Try(download.file(query.all, tempSeq, mode="a"))
      }
        
    }
    Try(e.seq <- read.table(tempSeq, sep="\t", header=F, as.is=T, fill=T))
    #select only the info of interest
    Try(e.seq <- e.seq[which(as.character(e.seq[,2])%in%as.character(exon.ann$EPROBESETID)),c(2,8)])
    #I have taken only part of the data set so now elevel ids are in position 1 of e.seq
    Try(e.seq <- e.seq[order(e.seq[,1]),])
    if(!identical(as.character(exon.ann$EPROBESETID), as.character(e.seq[,1]))){
              Try(tkmessageBox(title="Mapping to ENSEMBL",message="Internal error 503. Comunicate it to package mantainer!",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())
    }
    Try(exon.ann <- cbind(exon.ann, "etarget.seq"=rep("-", dim(exon.ann)[1])))
    Try(exon.ann$etarget.seq <- as.character(unlist(e.seq[,2])))
    #retrieving exon seq from ensembl
    Try(cat("\nMapping g-level ids to EGs and retrieving exons sequence from ensembl\n"))
 #   require(biomaRt) || stop("library biomaRt could not be found !")
    Try(ensembl <- useMart('ensembl'))
    Try(eg <- .gettingEG())
    if(whichLib[[1]][1]=="HuEx"){
              ensembl <- useDataset('hsapiens_gene_ensembl', mart=ensembl)
    }
    if(whichLib[[1]][1]=="MoEx"){
           ensembl <- useDataset('mmusculus_gene_ensembl', mart=ensembl)
    }
	  if(whichLib[[1]][1]=="RaEx"){
           ensembl <- useDataset('rnorvegicus_gene_ensembl', mart=ensembl)
    }
    Try(emblExons <- getSequence(id=as.character(eg[,3]), type="entrezgene", seqType="gene_exon",  mart = ensembl))
    #TO BE CHECKED
    #The assumption is that the extraction of exon seqs from embl is ordered by exon position 1,2,3 if + strand or 3,2,1 if - strand
    Try(emblExons <- cbind(emblExons, "exon.idx"=seq(1, dim(emblExons)[1])))
    Try(emblExons <- emblExons[order(emblExons$entrezgene),])
    for(i in unique(emblExons$entrezgene)){
            Try(tmp.idx <- emblExons[which(emblExons$entrezgene == i),3])
            Try(tmp.idx <- seq(1, length(tmp.idx)))
            Try(emblExons[which(emblExons$entrezgene == i),3] <- tmp.idx)
    }  
    #checking the consistency between the retrieved sequences and the egs available
    Try(eg.tobekept <- intersect(unique(eg[,3]),unique(emblExons[,2])))
    Try(glevelids <- as.character(eg[which(as.character(eg[,3])%in%eg.tobekept),1]))
    Try(exon.ann <- exon.ann[which(as.character(exon.ann$GPROBESETID)%in%glevelids),])
    #Try(exon.ann <- cbind(exon.ann, "idx"=rep(NA, dim(exon.ann)[1])))
    tmp.idx <- NULL
    Try(cat("\nCombining oneChannelGUI and ensembl data\n"))
    #embl.ann <- list()
    embl.ann <- NULL
    z <- 1
    Try(embl.ann.names <- c(names(emblExons)[c(2,3,1)], names(exon.ann)))
    for(i in 1: length(exon.ann$etarget.seq)){
    #     #cat("\n",i)
          Try(tmp.idx <- grep(as.character(exon.ann$etarget.seq[i]), emblExons[,1]))#select the index of exon on embl exon matching the target seq of elevel probeset
         if(length(tmp.idx)>= 1){
            for(j in 1:length(tmp.idx)){
              embl.tmp <- paste(emblExons[tmp.idx[j],c(2,3,1)], collapse=",")
              exon.tmp <- paste(exon.ann[i,], collapse=",")
              tmp.ann <-  paste(embl.tmp, exon.tmp, sep=",")
              embl.ann[z] <- tmp.ann
              z <- z+1      
            }
         } 
         #else{
         #    fake.embl <- rep(NA,dim(emblExons)[2])
         #    fake.embl <- paste(fake.embl, collapse=",")
         #    exon.tmp <- paste(exon.ann[i,], collapse=",")
         #    tmp.ann <-  paste(fake.embl, exon.tmp, sep=",")
         #    embl.ann[z] <- tmp.ann
         #    z <- z+1
         #}
    }
    Try(embl.ann <- strsplit(embl.ann, ","))
    Try(embl.ann <- as.data.frame(embl.ann))
    Try(embl.ann <- t(embl.ann))
    Try(dimnames(embl.ann)[[2]] <- embl.ann.names)
    Try(dimnames(embl.ann)[[1]] <- seq(1, dim(embl.ann)[1]))
    #ordering exons
    cat("\nOrdering exons\n")
    Try(embl.ann.ordered <- NULL)
    Try(tmp.ann <- NULL)
    for(i in unique(embl.ann[,1])){
              #selecting exons associated to eg
              Try(tmp.ann <- embl.ann[which(embl.ann[,1]==i),])
              #ordering exons by exon idx (the sorting associated to the e-level target seq does not give similar results)
              Try(tmp.ann <- tmp.ann[order(as.numeric(tmp.ann[,2])),])
              Try(embl.ann.ordered <- rbind(embl.ann.ordered,tmp.ann)) 
    }
    
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
    assign("mapping2ensembl" , embl.ann.ordered, affylmGUIenvironment)
    assign("mapping2ensembl.Available" , TRUE, affylmGUIenvironment)
    Try(exonsSpecific2as())
    Try(cat("\nEnding probeset mapping to ENSEMBL exons\n"))
    return()
}
################################################################################
"exonsSpecific2as" <- function(){
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
    Try(cat("\nStarting definition of conserved and isoform specific exons\n")) 
    #error if no data are loaded
    Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
    if(whichArrayPlatform !="EXON"){
              Try(tkmessageBox(title="Defining exons characteristics of alternative spliced isoforms",message="Mapping to ENSEMBL fuction was not run, yet!",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())
    }
    Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))
#    require(biomaRt) || stop("library biomaRt could not be found !")
    Try(ensembl <- useMart('ensembl'))
    if(whichLib[[1]][1]=="HuEx"){
              ensembl <- useDataset('hsapiens_gene_ensembl', mart=ensembl)
    }
    if(whichLib[[1]][1]=="MoEx"){
           ensembl <- useDataset('mmusculus_gene_ensembl', mart=ensembl)
    }
	  if(whichLib[[1]][1]=="RaEx"){
           ensembl <- useDataset('rnorvegicus_gene_ensembl', mart=ensembl)
    }

    Try(mapping2ensembl.Available <- get("mapping2ensembl.Available",  env=affylmGUIenvironment))
    if(!mapping2ensembl.Available){
              Try(tkmessageBox(title="Defining exons characteristics of alternative spliced isoforms",message="Mapping to ENSEMBL fuction was not run, yet!",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())

    }
    Try(mapping2ensembl <- get("mapping2ensembl",  env=affylmGUIenvironment))
    Try(conserved.exons <- rep(NA, dim(mapping2ensembl)[1]))
    Try(mapping2ensembl <- cbind(mapping2ensembl, conserved.exons))
    Try(egs <- unique(mapping2ensembl[,1]))
    Try(all.transcripts <- list())
    Try(cat("\n"))
    for(z in egs){
      Try(cat("."))
      ###qui c'e' il problema
        Try(emblInfo <- getBM(attributes = c('external_gene_id','entrezgene','ensembl_gene_id','ensembl_transcript_id'), filters = 'entrezgene', values = z, mart = ensembl)) 
        Try(for(n in 1:10) mad(runif(100000)))#to wait a bit      
        Try(emblGeneExons <- NULL)
        Try(emblGeneExons <- getSequence(id=emblInfo$entrezgene[1], type="entrezgene", seqType="gene_exon",  mart = ensembl))
        transcripts <- NULL
        for(j in 1: dim(emblInfo)[1]){
           Try(for(n in 1:10) mad(runif(100000)))#to wait a bit
           ###qui c'e' il problema
           Try(emblIsoformExons <- getSequence(id=emblInfo$ensembl_transcript_id[j], type="ensembl_transcript_id", seqType="gene_exon",  mart = ensembl))
           if(dim(emblGeneExons)[1] >0){
             Try(present <- rep(0, dim(emblGeneExons)[1]))
             for(i in 1: dim(emblGeneExons)[1]){
                Try(present[i] <- length(grep(emblGeneExons$gene_exon[i], emblIsoformExons$gene_exon)))
             }
             Try(transcripts <- cbind(transcripts, present))
           }   
        }
        if(dim(transcripts)[1] >0){
          Try(colnames(transcripts) <- emblInfo$ensembl_transcript_id)
          Try(rownames(transcripts) <- seq(1,dim(transcripts)[1]))
          Try(conserved.e <- apply(transcripts, 1, function(x){signif(sum(x)/length(x),digits=1)}))
          Try(transcripts <- cbind(transcripts, conserved.e))
          for(i in rownames(transcripts)){
            Try(mapping2ensembl[intersect(which(mapping2ensembl[,1]==z), which(mapping2ensembl[,2]==i)),dim(mapping2ensembl)[2]] <- transcripts[rownames(transcripts)==i,dim(transcripts)[2]])
          }
          Try(all.transcripts[[z]] <- transcripts)
       }   
     }
     Try(cat("\n"))
     assign("exonsSpecific2as" , all.transcripts, affylmGUIenvironment)
     assign("exonsSpecific2as.Available" , TRUE, affylmGUIenvironment)
     assign("mapping2ensembl" , mapping2ensembl, affylmGUIenvironment)
   	 Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
   	 Try(cat("\nEnding definition of conserved and isoform specific exons\n"))
     return()
}
################################################################################
"mapping2RefSeq" <- function(){
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
    #selecting the file containing the gene probe sets to be investigated at exon level and the output name
#    Try(detected.splicing.Available <- get("detected.splicing.Available",envir=affylmGUIenvironment))
#    if(!detected.splicing.Available){
#              Try(tkmessageBox(title="Mapping Alternatively spliced exons on NCBI genes",message="To run this function, Inspecting Splice Index function needs to be run first!",type="ok",icon="error"))
#				    	Try(tkfocus(.affylmGUIglobals$ttMain))
#				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
#             Try(return())
#   }
#    Try(detected.splicing <- get("detected.splicing",envir=affylmGUIenvironment))
#    Try(detected.splicing <- as.character(unlist(detected.splicing)))
#    extract.eprobeset <- function(x){
#                     x.tmp <- as.vector(unlist(strsplit(x, "\\|")))
#                     x.tmp <- x.tmp[2:length(x.tmp)]
#                     return(x.tmp)
#    }
#    Try(eprobesetid <- sapply(detected.splicing, extract.eprobeset))
 #####################################################################################################################
 #selecting the file containing the gene probe sets to be investigated at exon level and the output name
                  Try(tkmessageBox(title="Mapping exon probe sets to refseq", message="Open the file containing the list of exon-level probe sets\n to be mapped on refseq.",type="ok",icon="info"))
                  Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
                        if(!nchar(tempFileName))
                        {
                           tkfocus(.affylmGUIglobals$ttMain)
                           return()
                        }
                        Try(mySel<-read.table(tempFileName, sep="\t", header=F, as.is=TRUE))
                        if(dim(mySel)[2]==1){
                              Try(mySel <- as.character(unlist(mySel[,1])))
                              Try(tempFileName <- as.character(unlist(strsplit(tempFileName[[1]], "/"))))
                              Try(tempFileName <- tempFileName[length(tempFileName)])
                              Try(tempFileName <- sub(".txt", "", tempFileName))
                              Try(assign("FileNameText",tempFileName,affylmGUIenvironment))
                        } else Try(tkmessageBox(title="Mapping exon probe sets to refseq",message=paste("File should contain\nonly a column with\nexon-level probe set ids")))  

########################################################################################################################################

    Try(eprobesetid <- mySel)
    Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))   
    Try(cat("\nRetrieving e-level target sequences from RRE database\n"))
    #retrieving from RRE the target sequences for EPROBESETID
    #defining a temporary file tu save the exon-level target sequences downloaded by RRE
    tempSeq <- tempfile(pattern = "RRE", tmpdir = "")
    tempSeq <- sub( "\\\\","",tempSeq)
    tempSeq <- sub( "/","",tempSeq)
    workingDir <- getwd()
    workingDir <- sub( "/$","",workingDir)  
    tempSeq <- paste(workingDir, "/", tempSeq, ".fa", sep="")
                            
    if(length(eprobesetid) <= 1000){
        Try(query1 <- "http://www6.unito.it/RRE/Query/probeSet.php?glist=")
        Try(query2 <- paste(eprobesetid, collapse=","))
        if(whichLib[[1]][1] =="HuEx"){
           Try(query3 <- "&organism=Human&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        if(whichLib[[1]][1] =="MoEx"){
           Try(query3 <- "&organism=Mouse&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        if(whichLib[[1]][1] =="RaEx"){
           Try(query3 <- "&organism=Rat&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        Try(query.all <- paste(query1, query2, query3, collapse=""))
        Try(query.all <- gsub(" ", "", query.all))
        Try(download.file(query.all, tempSeq, mode="w"))
    } else{
      Try(steps <- seq(1, length(eprobesetid), by=1000))
      Try(stepsi <- steps)
      Try(stepsj <- c(steps[2:length(steps)] - 1, length(eprobesetid)))
      Try(query1 <- "http://www6.unito.it/RRE/Query/probeSet.php?glist=")
      if(whichLib[[1]][1] =="HuEx"){
              Try(query3 <- "&organism=Human&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      if(whichLib[[1]][1] =="MoEx"){
              Try(query3 <- "&organism=Mouse&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      if(whichLib[[1]][1] =="RaEx"){
              Try(query3 <- "&organism=Rat&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      for(i in 1:length(stepsi)){
       #       Try(require(stats))
              Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
              Try(query2 <- paste(eprobesetid[stepsi[i]:stepsj[i]], collapse=","))
              Try(query.all <- paste(query1, query2, query3, collapse=""))
              Try(query.all <- gsub(" ", "", query.all))
              Try(download.file(query.all, tempSeq, mode="a"))
      }
   }
   ##require(Biostrings) || stop("library Biostrings could not be found !")
#   require(annotate) || stop("library annotate could not be found !")
   #load exon probe sets target seq
   #tempSeq <- "RRE62a149c2.seq"
   #Try(eps.seq <- read.DNAStringSet(tempSeq, "fasta"))
   #Try(eps.seq <- readFASTA(tempSeq, strip.desc=TRUE))
   #running blast
   cat("\nStarting blastn mapping of exon-level PSR to RefSeq\n")
   cat("\nBe patient!\n")
   Try(aptDir <- get("aptDir",envir=affylmGUIenvironment))
   if(is.na(aptDir)) {
          Try(tkmessageBox(title="apt tool dir is not defined!",message= , type="ok", icon="error")) 
          return()
   }
   Try(blastDir <- paste(aptDir, "/blast", sep=""))
   if(whichLib[[1]][1] =="HuEx"){
      if(length(which(dir(blastDir) == "human.rna.fna.nin")) == 0){
             Try(formatCommand <- paste(blastDir,"/bin/formatdb -i ", blastDir, "/human.rna.fna ", "-p F -o T", sep="")) 
             Try(system(formatCommand, wait = T))
             Try(cat("\nHuman RefSeq blast lib is formatted\n"))
      }
      Try(blastCommand <- paste(blastDir,"/bin/blastall -p blastn -d ", blastDir, "/human.rna.fna -i ", tempSeq, " -S 1 -E 1000 -e 0.0001 -m 0 -v 1 -b 1 -o ", tempSeq, ".out",sep="")) 
      Try(system(blastCommand, wait = T))
      Try(cat("\nMapping on RefSeq ended.\n", tempSeq, ".out is ready for analysis", "\n", sep=""))
   }
   if(whichLib[[1]][1] =="MoEx"){
      if(length(which(dir(blastDir) == "mouse.rna.fna.nin")) == 0){
             Try(formatCommand <- paste(blastDir,"/bin/formatdb -i ", blastDir, "/mouse.rna.fna ", "-p F -o T", sep="")) 
             Try(system(formatCommand, wait = T))
             Try(cat("\nMouse RefSeq blast lib is formatted\n"))
      }
      Try(blastCommand <- paste(blastDir,"/bin/blastall -p blastn -d ", blastDir, "/mouse.rna.fna -i ", tempSeq, " -S 1 -E 1000 -e 0.0001 -m 0 -v 1 -b 1 -o ", tempSeq, ".out",sep="")) 
      Try(system(blastCommand, wait = T))
      Try(cat("\nMapping on RefSeq ended. Now, ", tempSeq, ".out is ready for analysis", "\n", sep=""))
   }
   if(whichLib[[1]][1] =="RaEx"){
     if(length(which(dir(blastDir) == "rat.rna.fna.nin")) == 0){
             Try(formatCommand <- paste(blastDir,"/bin/formatdb -i ", blastDir, "/rat.rna.fna ", "-p F -o T", sep="")) 
             Try(system(formatCommand, wait = T))
             Try(cat("\nRat RefSeq blast lib is formatted\n", tempSeq, ".out is ready for analysis", "\n", sep=""))
      }

      Try(blastCommand <- paste(blastDir,"/bin/blastall -p blastn -d ", blastDir, "/rat.rna.fna -i ", tempSeq, " -S 1 -E 1000 -e 0.0001 -m 0 -v 1 -b 1 -o ", tempSeq, ".out",sep="")) 
      Try(system(blastCommand, wait = T))
      Try(cat("\nMapping on RefSeq ended. Now ", tempSeq, ".out is ready for analysis", "\n", sep=""))
   }
   blastReformatted <- .eprobesetsOnmRNA(paste(tempSeq, ".out", sep=""))
   Try(FileNameText <- get("FileNameText", affylmGUIenvironment)) 
   Try(writeLines(blastReformatted$summary, paste("eps2rs.1ststep", FileNameText, ".tmp", sep="")))
   #extracting refseqs associated to the EG where ASE is found
   if(whichLib[[1]][1] =="HuEx"){
    #       require(org.Hs.eg.db) || stop("library org.Hs.eg.db could not be found !")
           cat("\nBe patient! Loading Hs refseq data\n")
           Try(rs.seq <- read.DNAStringSet(paste(blastDir, "/human.rna.fna", sep=""), "fasta"))#load refseq
   }
   if(whichLib[[1]][1] =="MoEx"){
    #       require(org.Mm.eg.db) || stop("library org.Mm.eg.db could not be found !")
           cat("\nBe patient! Loading Mm refseq data\n")
           Try(rs.seq <- read.DNAStringSet(paste(blastDir, "/mouse.rna.fna", sep=""), "fasta"))
   }
   if(whichLib[[1]][1] =="RaEx"){
   #        require(org.Rn.eg.db) || stop("library org.Rn.eg.db could not be found !")
           cat("\nBe patient! Loading Rn refseq data\n")
           Try(rs.seq <- read.DNAStringSet(paste(blastDir, "/rat.rna.fna", sep=""), "fasta"))
   }
   
   #refseq, length refseq start PRS on refseq exon-level id
  Try(eps.seq <- read.DNAStringSet(tempSeq, "fasta"))#load psr
  #function to map psr to refseq
  map2rs <- function(x, psr=eps.seq){ 
   if(!is.na(x)){
    Try(x.tmp <- unlist(strsplit(x, " ")))
    Try(x.tmp1 <- unlist(strsplit(x.tmp[1], "\\.")))
    Try(eg <- as.character(unlist(lookUp(x.tmp1[1], "org.Hs.eg", "REFSEQ2EG"))))
    if(!is.na(eg)){
        Try(eg.rs <-  as.character(unlist(lookUp(eg, "org.Hs.eg", "REFSEQ"))))
    
        #as.character(eps.seq[[grep(x.tmp[4], names(eps.seq))]])
#        Try(write.XStringSet(eps.seq[grep(x.tmp[4], names(eps.seq))], file="query.fa", format="fasta", width=80)) #write the PSR to be use as blast on the ref seqs associated to the eg
        #extracting the refseq seq associated to the eg of ase
        eg.rsq <- paste(eg.rs, ".", sep="")
        getting.rs <- function(eg.rsq, rs.seq) return(grep(eg.rsq, names(rs.seq)))
        eg.rss <- sapply(eg.rsq, getting.rs, rs.seq=rs.seq)
        eg.rss <- as.numeric(unlist(eg.rss))
#        Try(write.XStringSet(rs.seq[eg.rss], file="subject.fa", format="fasta", width=80))
#        Try(formatCommand <- paste(blastDir,"/bin/formatdb -i ", getwd(), "/subject.fa ", "-p F -o T", sep=""))
#        Try(system(formatCommand))
#        Try(blastCommand <- paste(blastDir,"/bin/blastall -p blastn -d ", getwd(), "/subject.fa -i ", getwd(),"/query.fa", " -S 1 -E 1000 -e 0.0001 -m 0 -v 1 -b 1 -o ", "query.out",sep="")) 
#        Try(system(blastCommand, wait = T))
#        cat(x.tmp1[1],"\n")
#        Try(outReformatted <- .eprobesetsOnmRNA("query.out"))
         query.seq <- eps.seq[grep(x.tmp[4], names(eps.seq))]
         subject.seq <- rs.seq[eg.rss]
         tmp.seq <- as.character(query.seq)
         sbj.seq <- as.character(subject.seq)
         scores <- sapply(sbj.seq, function(x, q.seq){ 
                                   score.tmp <- countPattern(q.seq , DNAString(x), max.mismatch=3)
                                   return(score.tmp)
                             }, q.seq=tmp.seq)

        if(sum(scores) >=  length(eg.rss)){
               return(paste(c("eprobesetid=", x.tmp[4], "conservative=",x.tmp1[1], "EG=",eg, "RefSeqs=",eg.rs), sep="",collapse=" "))
        }else if(sum(scores) <  length(eg.rss)){
              return(paste(c("eprobesetid=", x.tmp[4], "isoform specific=",x.tmp1[1], "EG=",eg, "RefSeqs=",eg.rs), sep="", collapse=" "))
        }
     } else return(NA)
   } else return(NA)
  } 
  Try(mapped <- sapply(blastReformatted$summary, map2rs, psr=eps.seq))
  Try(FileNameText <- get("FileNameText", affylmGUIenvironment))
  Try(tkmessageBox(title="mapping exon-level probesets to RefSeqs",message=paste("Mapping results are summarized in ", paste("eps2rs.", FileNameText, ".txt", sep="") , sep=" ") , type="ok", icon="info")) 
  Try(writeLines(mapped, paste("eps2rs.", FileNameText, ".txt", sep="")))  
  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow")) 
}

".eprobesetsOnmRNA" <- function(file){

    blast <- readLines(file)
    #reformattig blast
    blast <- blast[which(nchar(blast) > 0)]
    cleaup1 <- function(x){
           if(length(grep("subject.fa |BLASTN|Reference|Jinghui|Gapped|programs|Database|sequences|Searching|Score|Sequences|>ref|Strand|letters|Query: |\\|$", x)) == 1) return(0) else return(1)
    }
    tmp <- sapply(blast, cleaup1)
    blast1 <- names(tmp[which(tmp == 1)])
    cleaup2 <- function(x){
           if(length(grep("[0-9A-Za-z]" ,x )) == 1) return(1) else return(0)
    }
    tmp <- sapply(blast1, cleaup2)
    blast2 <- names(tmp[which(tmp == 1)])

    #calculating location on the mRNA
    whereQ <- function(x){
              if(length(grep("Query=", x)) == 1) return(1) else return(0)  
    }
    tmp <- sapply(blast2, whereQ)
    tmp <- as.vector(tmp)
    locationQ <- which(tmp == 1)
    report <- NULL
    summary <- NULL
    j <- 1
    if(length(locationQ) > 1){
      if(blast2[locationQ[length(locationQ)]+1] == " ***** No hits found ******"){
             locationQ <- locationQ[1:(length(locationQ) -1)]
      }
      for( i in locationQ[1:(length(locationQ) - 1)]){
      cat(i,"\n")
           mrna.loc <- grep("^ref", blast2[i:length(blast2)])
           mrna.loc1 <- i + mrna.loc[1] - 1
           #if(!is.na(mrna.loc[2])){
               mrna.loc2 <- i + mrna.loc[2] - 1
               mrna.size.loc <- grep("Length", blast2[mrna.loc1:mrna.loc2])
               mrna.size.loc <- i + mrna.size.loc[1]
               identity.loc <- grep("Identities", blast2[mrna.loc1:mrna.loc2])
               identity.loc <- i + identity.loc[1] 
           #} else{
           #    mrna.loc2 <- length(blast2)
           #    mrna.size.loc <- grep("Length", blast2[mrna.loc1:mrna.loc2])#
           #    mrna.size.loc <- i + mrna.size.loc[1]
           #    identity.loc <- grep("Identities", blast2[mrna.loc1:mrna.loc2])
           #    identity.loc <- i + identity.loc[1] 
           #} 
           if(blast2[i+1] == " ***** No hits found ******"){
                  locationE <- NA
                  eom <- NA
           } else if(length(mrna.size.loc[1]) == 1 & (length(grep("100%", blast2[identity.loc])) == 1 | 
                                                      length(grep("99%", blast2[identity.loc])) == 1) |
                                                      length(grep("98%", blast2[identity.loc])) == 1 |
                                                      length(grep("97%", blast2[identity.loc])) == 1 |
                                                      length(grep("96%", blast2[identity.loc])) == 1 |
                                                      length(grep("95%", blast2[identity.loc])) == 1){
                  #mrna.loc <- grep("^ref", blast2[i:(i+20)])
                  mrna <- as.vector(unlist(strsplit(blast2[mrna.loc1], "\\|")))
                  mrna <- mrna[2]
                  etarget.tmp <- as.vector(unlist(strsplit(blast2[i], ":")))
                  etarget.tmp <- as.vector(unlist(strsplit(etarget.tmp[[2]], ";")))
                  mrna.size <- as.vector(unlist(strsplit(blast2[mrna.size.loc], " = ")))
                  mrna.size <- as.numeric(mrna.size[length(mrna.size)])
                  if( length(grep("Identities", blast2[identity.loc])) == 1){
                       etarget.mrna <- as.vector(unlist(strsplit(blast2[identity.loc + 1], " ")))
                       etarget.mrna <-  as.numeric(etarget.mrna[2])
                  } else {
                          etarget.mrna <- as.vector(unlist(strsplit(blast2[identity.loc], " ")))
                          etarget.mrna <-  as.numeric(etarget.mrna[2])
                  }
                  locationE <-  etarget.mrna/mrna.size
                  eom <- paste(mrna, mrna.size, etarget.mrna, etarget.tmp[1], collapse =" ") #refseq, length refseq, initialial position on refseq of etarget, etarget ID
           } else{
                  locationE <- NA
                  eom <- NA
           }
           report[j] <- locationE   #represent the position of the eterget in percentage with respspect to the mRNA length
           summary[j] <- eom
           j <- j+1
     }
    } 
    i <- locationQ[length(locationQ)]
    cat(i,"\n")
    mrna.loc <- grep("^ref", blast2[i:length(blast2)])
    mrna.loc1 <- i + mrna.loc - 1
    mrna.loc2 <- length(blast2)
    mrna.size.loc <- grep("Length", blast2[mrna.loc1:mrna.loc2])
    mrna.size.loc <- i + mrna.size.loc[1]
    identity.loc <- grep("Identities", blast2[mrna.loc1:mrna.loc2])
    identity.loc <- i + identity.loc[1] 
            
    if(blast2[i+1] == " ***** No hits found ******"){
                  locationE <- NA
                  eom <- NA
    } else if(length(mrna.size.loc[1]) == 1 & length(grep("100%", blast2[identity.loc])) == 1){
                  #mrna.loc <- grep("^ref", blast2[i:(i+20)])
                  mrna <- as.vector(unlist(strsplit(blast2[mrna.loc1], "\\|")))
                  mrna <- mrna[2]
                  etarget.tmp <- as.vector(unlist(strsplit(blast2[i], ":")))
                  etarget.tmp <- as.vector(unlist(strsplit(etarget.tmp[[2]], ";")))
                  mrna.size <- as.vector(unlist(strsplit(blast2[mrna.size.loc], " = ")))
                  mrna.size <- as.numeric(mrna.size[length(mrna.size)])
                  if( length(grep("Identities", blast2[identity.loc])) == 1){
                       etarget.mrna <- as.vector(unlist(strsplit(blast2[identity.loc + 1], " ")))
                       etarget.mrna <-  as.numeric(etarget.mrna[2])
                  } else {
                          etarget.mrna <- as.vector(unlist(strsplit(blast2[identity.loc], " ")))
                          etarget.mrna <-  as.numeric(etarget.mrna[2])
                  }
                  locationE <-  etarget.mrna/mrna.size
                  eom <- paste(mrna, mrna.size, etarget.mrna, etarget.tmp[1], collapse =" ") #refseq, length refseq, initialial position on refseq of etarget, etarget ID
    } else{
                  locationE <- NA
                  eom <- NA
    }
    report[j] <- locationE   #represent the position of the eterget in percentage with respspect to the mRNA length
    summary[j] <- eom
    out <- list("report"=report, "summary"=summary)
    return(out)
}
################################################################################

"mapping2exon" <- function(){
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
#selecting the file containing the output from mapping2RefSeq
    Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
    if(whichArrayPlatform !="EXON"){
              Try(tkmessageBox(title="Associate exon-level probesets to exons",message="Mapping e-level probesets to exons fuction apply only to EXON Affymetrix Genechips\n",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())
    }
    Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))

    Try(tkmessageBox(title="Associate exon-level probesets to exons", message="Open the file containing the complete or partial output generated by \nMapping exon level probe sets to Reference Sequences function.\nThis txt filename starts with eps2rs",type="ok",icon="info"))
    Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
    if(!nchar(tempFileName))
    {
         tkfocus(.affylmGUIglobals$ttMain)
         return()
    }
    Try(mySel<-readLines(tempFileName))
    epsExtract <- function(x){
        tmp <- strsplit(x,"eprobesetid= ")
        tmp <- strsplit(tmp[[1]][2]," ")
        return(tmp[[1]][1])

    }
    Try(eprobesetid <- sapply(mySel, epsExtract))
    Try(eprobesetid <- unique(as.numeric(eprobesetid[!is.na(eprobesetid)])))
    Try(cat("\nRetrieving e-level target sequences from RRE database\n"))
    #retrieving from RRE the target sequences for EPROBESETID
    #defining a temporary file tu save the exon-level target sequences downloaded by RRE
    tempSeq <- tempfile(pattern = "RRE", tmpdir = "")
    tempSeq <- sub( "\\\\","",tempSeq)
    tempSeq <- sub( "/","",tempSeq)
    workingDir <- getwd()
    workingDir <- sub( "/$","",workingDir)  
    tempSeq <- paste(workingDir, "/", tempSeq, ".fa", sep="")
                            
    if(length(eprobesetid) <= 1000){
        Try(query1 <- "http://www6.unito.it/RRE/Query/probeSet.php?glist=")
        Try(query2 <- paste(eprobesetid, collapse=","))
        if(whichLib[[1]][1] =="HuEx"){
           Try(query3 <- "&organism=Human&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        if(whichLib[[1]][1] =="MoEx"){
           Try(query3 <- "&organism=Mouse&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        if(whichLib[[1]][1] =="RaEx"){
           Try(query3 <- "&organism=Rat&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        Try(query.all <- paste(query1, query2, query3, collapse=""))
        Try(query.all <- gsub(" ", "", query.all))
        Try(download.file(query.all, tempSeq, mode="w"))
    } else{
      Try(steps <- seq(1, length(eprobesetid), by=1000))
      Try(stepsi <- steps)
      Try(stepsj <- c(steps[2:length(steps)] - 1, length(eprobesetid)))
      Try(query1 <- "http://www6.unito.it/RRE/Query/probeSet.php?glist=")
      if(whichLib[[1]][1] =="HuEx"){
              Try(query3 <- "&organism=Human&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      if(whichLib[[1]][1] =="MoEx"){
              Try(query3 <- "&organism=Mouse&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      if(whichLib[[1]][1] =="RaEx"){
              Try(query3 <- "&organism=Rat&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      for(i in 1:length(stepsi)){
        #      Try(require(stats))
              Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
              Try(query2 <- paste(eprobesetid[stepsi[i]:stepsj[i]], collapse=","))
              Try(query.all <- paste(query1, query2, query3, collapse=""))
              Try(query.all <- gsub(" ", "", query.all))
              Try(download.file(query.all, tempSeq, mode="a"))
      }
   }
   

egExtract <- function(x){
        tmp <- strsplit(x,"EG= ")
        tmp <- strsplit(tmp[[1]][2]," ")
        return(tmp[[1]][1])

}
Try(eg <- sapply(mySel, egExtract))
Try(eg <- unique(as.numeric(eg[!is.na(eg)])))
    Try(cat("\nRetrieving exons sequences from RRE database\n"))
    #retrieving from RRE the gene exons
    #defining a temporary file tu save the exon sequences downloaded by RRE
    tempSeqeg <- tempfile(pattern = "RREeg", tmpdir = "")
    tempSeqeg <- sub( "\\\\","",tempSeqeg)
    tempSeqeg <- sub( "/","",tempSeqeg)
    workingDir <- getwd()
    workingDir <- sub( "/$","",workingDir)  
    tempSeqeg <- paste(workingDir, "/", tempSeqeg, ".fa", sep="")
                            
    if(length(eg) <= 1000){
        Try(query1 <- "http://www6.unito.it/RRE/Query/httpIE.php?genelist=")
        Try(query2 <- paste(eg, collapse=","))
        if(whichLib[[1]][1] =="HuEx"){
           Try(query3 <- "&coding=ALL&organism=Human&sep=,")
        }
        if(whichLib[[1]][1] =="MoEx"){
           Try(query3 <- "&coding=ALL&organism=Mouse&sep=,")
        }
        if(whichLib[[1]][1] =="RaEx"){
           Try(query3 <- "&coding=ALL&organism=Rat&sep=,")
        }
        Try(query.all <- paste(query1, query2, query3, collapse=""))
        Try(query.all <- gsub(" ", "", query.all))
        Try(download.file(query.all, tempSeqeg, mode="w"))
    } else{
      Try(steps <- seq(1, length(eg), by=1000))
      Try(stepsi <- steps)
      Try(stepsj <- c(steps[2:length(steps)] - 1, length(eg)))
      Try(query1 <- "http://http://www6.unito.it/RRE/Query/httpIE.php?genelist=")
      if(whichLib[[1]][1] =="HuEx"){
              Try(query3 <- "&coding=ALL&organism=Human&sep=,")
      }
      if(whichLib[[1]][1] =="MoEx"){
              Try(query3 <- "&coding=ALL&organism=Mouse&sep=,")
      }
      if(whichLib[[1]][1] =="RaEx"){
              Try(query3 <- "&coding=ALL&organism=Rat&sep=,")
      }
      for(i in 1:length(stepsi)){
        #      Try(require(stats))
              Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
              Try(query2 <- paste(eg[stepsi[i]:stepsj[i]], collapse=","))
              Try(query.all <- paste(query1, query2, query3, collapse=""))
              Try(query.all <- gsub(" ", "", query.all))
              Try(download.file(query.all, tempSeqeg, mode="a"))
      }
   }
   
   epsegExtract <- function(x){
        tmp <- strsplit(x,"eprobesetid= ")
        tmp <- strsplit(tmp[[1]][2]," ")
        tmp1 <- strsplit(x,"EG= ")
        tmp1 <- strsplit(tmp1[[1]][2]," ")
        if(!is.na(tmp[[1]][1])){
           return(paste(c(tmp[[1]][1], tmp1[[1]][1]), collapse="."))
        }  else return(NA)
   }
  Try(eps.eg <- sapply(mySel, epsegExtract))
  Try(eps.eg <- as.character(eps.eg[!is.na(eps.eg)])) 
   #require(Biostrings) || stop("library Biostrings could not be found !")
#   require(annotate) || stop("library annotate could not be found !")
   Try(eps.seq <- read.DNAStringSet(tempSeq, "fasta"))#read exon-level target seq
   Try(exs.seq <- read.DNAStringSet(tempSeqeg, "fasta"))#read RRE exons 
  
   cat("Wait.")
   Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
   cat(".")
   Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
   cat(".")
   Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
   cat(".")
   Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
   cat(".")
   Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
   cat(".\n")
  
  Try(mapped.psr <- lapply(eps.eg, .mappingPSR, eps.seq=eps.seq, exs.seq=exs.seq))
  Try(mapped.psr <- mapped.psr[which(mapped.psr != "NULL")])
  Try(mapped.psr1 <- unlist(mapped.psr))
  lfas <- list()
  for( i in 1:length(mapped.psr1)){
        lfa <- list("desc"= names(mapped.psr1)[i], "seq"=as.character(mapped.psr1[i]))
        lfas[[i]] <- lfa
  }
  
  Try(fname <- strsplit(tempFileName, "\\/"))
  Try(fname <- unlist(fname))
  Try(fname <- fname[length(fname)])
  Try(fname <- paste("PRS.and.exon.from.", fname,".fa", sep=""))
  Try(writeFASTA(lfas, fname))
  Try(tkmessageBox(title="Associate exon-level probesets to exons",message=paste("eprobeset and EXON sequences are in", fname, sep=" "),type="ok",icon="info"))
  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}

.mapPSR <- function(j, eps.loc, eps.seq, exs.seq){
            tmp.seq <- as.character(eps.seq[eps.loc]) 
            #if(length(tmp.seq) > 500){
            #       tmp.seq <- subXString(tmp.seq, start=1,length=500)
            #}
            #score.tmp <- score(pairwiseAlignment(tmp.seq , DNAString(as.character(exs.seq[j])), type="local"))
            score.tmp <- countPattern(tmp.seq , DNAString(as.character(exs.seq[j])), max.mismatch=3)
            return(score.tmp)
   }
   
.mappingPSR <- function(i, eps.seq, exs.seq){
            #eps2ex <- list()
            eps2ex.tmp <- NULL
            ideg <- as.character(unlist(strsplit(i,"\\.")))
            eps.loc <- grep(paste(":",ideg[1], ";", sep=""), names(eps.seq))
            eg.locs <- grep(ideg[2], names(exs.seq))
            #scores <- NULL
            if(length(eg.locs) > 0){
              scores  <- sapply(eg.locs, .mapPSR, eps.loc=eps.loc, eps.seq=eps.seq, exs.seq=exs.seq)
              if(length(which(scores == max(scores))) == 1){
                 exs.seq.tmp <- as.character(exs.seq[eg.locs[which(scores == max(scores))]])
                 eps.seq.tmp <- as.character(eps.seq[eps.loc])
                 eps2ex.tmp <- list(as.character(eps.seq.tmp), as.character(exs.seq.tmp))
                 names(eps2ex.tmp)[1] <- names(eps.seq)[eps.loc]
                 names(eps2ex.tmp)[2] <- names(exs.seq)[eg.locs[which(scores == max(scores))]]
              }else {
                 cat("\nMore that one match for", names(eps.seq)[eps.loc], ".\nMapping discarded\n")
                 eps.seq.tmp <- as.character(eps.seq[eps.loc])
                 eps2ex.tmp <- list(as.character(eps.seq.tmp), NA)
                 names(eps2ex.tmp)[1] <- names(eps.seq)[eps.loc]
                 names(eps2ex.tmp)[2] <- NA
              }
           }
           return(eps2ex.tmp)
   }
   



################################################################################
"retrievePSRseq" <- function(){
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
 #selecting the file containing the gene probe sets to be investigated at exon level and the output name
                  Try(tkmessageBox(title="Mapping exon probe sets to refseq", message="Open the file containing the list of exon-level probe sets\n to be used to retrieve PSRs.",type="ok",icon="info"))
                  Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
                        if(!nchar(tempFileName))
                        {
                           tkfocus(.affylmGUIglobals$ttMain)
                           return()
                        }
                        Try(mySel<-read.table(tempFileName, sep="\t", header=F, as.is=TRUE))
                        if(dim(mySel)[2]==1){
                              Try(mySel <- as.character(unlist(mySel[,1])))
                              Try(tempFileName <- as.character(unlist(strsplit(tempFileName[[1]], "/"))))
                              Try(tempFileName <- tempFileName[length(tempFileName)])
                              Try(tempFileName <- sub(".txt", "", tempFileName))
                              Try(assign("FileNameText",tempFileName,affylmGUIenvironment))
                        } else Try(tkmessageBox(title="Mapping exon probe sets to refseq",message=paste("File should contain\nonly a column with\nexon-level probe set ids")))  

########################################################################################################################################

    Try(eprobesetid <- mySel)
    Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))   
    Try(cat("\nRetrieving e-level target sequences from RRE database\n"))
    #retrieving from RRE the target sequences for EPROBESETID
    #defining a temporary file tu save the exon-level target sequences downloaded by RRE
    tempSeq <- tempfile(pattern = "RRE", tmpdir = "")
    tempSeq <- sub( "\\\\","",tempSeq)
    tempSeq <- sub( "/","",tempSeq)
    workingDir <- getwd()
    workingDir <- sub( "/$","",workingDir)  
    tempSeq <- paste(workingDir, "/", tempSeq, ".fa", sep="")
                            
    if(length(eprobesetid) <= 1000){
        Try(query1 <- "http://www6.unito.it/RRE/Query/probeSet.php?glist=")
        Try(query2 <- paste(eprobesetid, collapse=","))
        if(whichLib[[1]][1] =="HuEx"){
           Try(query3 <- "&organism=Human&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        if(whichLib[[1]][1] =="MoEx"){
           Try(query3 <- "&organism=Mouse&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        if(whichLib[[1]][1] =="RaEx"){
           Try(query3 <- "&organism=Rat&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        Try(query.all <- paste(query1, query2, query3, collapse=""))
        Try(query.all <- gsub(" ", "", query.all))
        Try(download.file(query.all, tempSeq, mode="w"))
    } else{
      Try(steps <- seq(1, length(eprobesetid), by=1000))
      Try(stepsi <- steps)
      Try(stepsj <- c(steps[2:length(steps)] - 1, length(eprobesetid)))
      Try(query1 <- "http://www6.unito.it/RRE/Query/probeSet.php?glist=")
      if(whichLib[[1]][1] =="HuEx"){
              Try(query3 <- "&organism=Human&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      if(whichLib[[1]][1] =="MoEx"){
              Try(query3 <- "&organism=Mouse&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      if(whichLib[[1]][1] =="RaEx"){
              Try(query3 <- "&organism=Rat&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      for(i in 1:length(stepsi)){
         #     Try(require(stats))
              Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
              Try(query2 <- paste(eprobesetid[stepsi[i]:stepsj[i]], collapse=","))
              Try(query.all <- paste(query1, query2, query3, collapse=""))
              Try(query.all <- gsub(" ", "", query.all))
              Try(download.file(query.all, tempSeq, mode="a"))
      }
   }
   #see the file
   Try(readORnot <- tclvalue(tkmessageBox(title="Retrieving PSR",message=paste("File", tempSeq, "contains Probe Selection Regions of the exon-level probesets.\nDoyou want to see it?", sep=" "),type="yesno",icon="question")))
   if (readORnot=="yes"){
     ttToptableTable <- tktoplevel(.affylmGUIglobals$ttMain)
     tkwm.title(ttToptableTable,"Selected PSR")
     xscr <-tkscrollbar(ttToptableTable, repeatinterval=5,orient="horizontal", command=function(...)tkxview(txt,...))
     scr <- tkscrollbar(ttToptableTable, repeatinterval=5, command=function(...)tkyview(txt,...))
     txt <- tktext(ttToptableTable, bg="white", font="courier",xscrollcommand=function(...)tkset(xscr,...), yscrollcommand=function(...)tkset(scr,...),wrap="none",width=100)
     tkpack(scr, side="right", fill="y")
     tkpack(xscr, side="bottom", fill="x")
     tkpack(txt, side="left", fill="both", expand="yes")

     chn <- tclvalue(tclopen(tempSeq))
     tkinsert(txt, "end", tclvalue(tclread( chn)))
     tclclose( chn)
     tkconfigure(txt, state="disabled")
     tkmark.set(txt,"insert","0.0")
     tkfocus(txt)
                    
     topMenu2 <- tkmenu(ttToptableTable)
     tkconfigure(ttToptableTable, menu=topMenu2)
     fileMenu2 <- tkmenu(topMenu2, tearoff=FALSE)
     tkadd(fileMenu2, "command", label="Close", command=function() tkdestroy(ttToptableTable)) # ) # ,font=affylmGUIfontMenu)
     tkadd(topMenu2, "cascade", label="File", menu=fileMenu2) # ,font=affylmGUIfontMenu)
   } else {
         Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
         Try(return())
   }            
}
################################################################################
################################################################################
#It returns a  mads object:
#MetaProbesetId: ID for Gene or TC
#ProbesetId: tested probeset ID
#ConnectedProbesetId: connected probeset in inclusion/exclusion relations
#AlternativeSplicingType: alternative or constitutive
#StructureType: indication of inclusion and exclusion
#ProbsetLevel: probeset level, core, extended or full
#NumProbes: number of summairzed probes to get probeset level MADS p-value (DABG uses all probes)
#MADS_PVpos: MADS p-value for class1 < class2, a probeset is over-expressed on class2
#MADS_PVneg: MADS p-value for class1 > class2, a probeset is over-expressed on class1
#DABG_Class1: geometric mean of DABG p-values of class 1 samples
#DABG_Class2: geometric mean of DABG p-values of class 2 samples
#DABG_XXXX: DABG p-value of sample XXXX 

runningJetta <- function(){
  #in this way jetta is not detected ducring check and build
  pkg <- "jetta"
  require(pkg, character.only=TRUE) || if(.Platform$OS.type == "windows") {
                                        jettalib <- system.file("affylibs/jetta.libs/jetta_0.0.1.zip",package="oneChannelGUI")
                                        install.packages(pkgs=jettalib, repos = NULL)
                                       }  else {
                                                  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                                                  stop(paste("library jetta not implemented for", .Platform$OS.type))
                                       }
  whichLib     <- get("whichLib" , envir=affylmGUIenvironment)
  if(whichLib[[1]][1] == "RaEx"){
          Try(tkmessageBox(title="Gene/Exon libraries Dir",message="Rat exon arrays are not supported by Jetta"))
          Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
          Try(return())
  }
  libDir <- get("libDir", affylmGUIenvironment)
  jettaDir <- paste(libDir, "jetta.libs/", sep="")
  content.jettaDir <- dir(jettaDir)
  if(length(grep(whichLib[[1]][1],content.jettaDir)) == 0){
          Try(tkmessageBox(title="Gene/Exon libraries Dir",message=paste("The selected folder does not contain ", tmp[[1]][1], " library files!\n Download them using the function provided in the general tools!", sep=""),icon="error"))
          Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
          Try(return())
  }
  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
  genelib.name <- paste(jettaDir, content.jettaDir[intersect(grep('\\.mps$',content.jettaDir), intersect(grep(whichLib[[1]][1],content.jettaDir), grep(whichLib[[1]][2],content.jettaDir)))], sep="")                                                                         
  
  Try(clf.name <- paste(jettaDir, content.jettaDir[intersect(grep(whichLib[[1]][1],content.jettaDir), grep('.clf$',content.jettaDir))], sep=""))
  Try(pgf.name <- paste(jettaDir, content.jettaDir[intersect(grep(whichLib[[1]][1],content.jettaDir), grep('.pgf$',content.jettaDir))], sep=""))
   ##making the menu for signal calculation parameters
  Try(ttjettaDialog<-tktoplevel(.affylmGUIglobals$ttMain))
  Try(tkwm.deiconify(ttjettaDialog))
  Try(tkgrab.set(ttjettaDialog))
  Try(tkfocus(ttjettaDialog))
  Try(tkwm.title(ttjettaDialog,"Jetta Parameters"))
  Try(tkgrid(tklabel(ttjettaDialog,text="    ")))

  Try(frame1 <- tkframe(ttjettaDialog,relief="groove",borderwidth=2))
  Try(HowManyQuestion1 <- tklabel(frame1,text=
  "BackgroundCorrectionMethod",font=.affylmGUIglobals$affylmGUIfont2))
  Try(tkgrid(HowManyQuestion1))
  Try(tkgrid.configure(HowManyQuestion1,columnspan=2,sticky="w"))
  #c("mediangc", "mat", "none")
  Try(bgTcl <- tclVar("mediangc"))
	Try(q1.but			<- tkradiobutton(frame1,text="Median GC",variable=bgTcl,value="mediangc",font=.affylmGUIglobals$affylmGUIfont2))
	Try(q2.but	 <- tkradiobutton(frame1,text="Mat",variable=bgTcl,value="mat",font=.affylmGUIglobals$affylmGUIfont2))
	Try(q3.but		<- tkradiobutton(frame1,text="None",variable=bgTcl,value="none",font=.affylmGUIglobals$affylmGUIfont2))
	
	Try(tkgrid(q1.but,sticky="w"))
	Try(tkgrid(q2.but,sticky="w"))
	Try(tkgrid(q3.but,sticky="w"))
	Try(tkgrid.configure(HowManyQuestion1,q1.but,q2.but,q3.but,sticky="w"))
  # c("median_scaling", "quantile", "none")
	Try(frame2 <- tkframe(ttjettaDialog,relief="groove",borderwidth=2))
	Try(alfaLabel <- tklabel(frame2,text="NormalizationMethod",font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(alfaLabel,sticky="w"))
	Try(tkgrid.configure(alfaLabel,sticky="w"))

  Try(normTcl <- tclVar("quantile"))

	Try(a1.but <- tkradiobutton(frame2,text="Quantile",variable=normTcl,value="quantile",font=.affylmGUIglobals$affylmGUIfont2))
	Try(a2.but <- tkradiobutton(frame2,text="median Scaling",variable=normTcl,value="median_scaling",font=.affylmGUIglobals$affylmGUIfont2))
	Try(a3.but <- tkradiobutton(frame2,text="None",variable=normTcl,value="none",font=.affylmGUIglobals$affylmGUIfont2))
	
	Try(tkgrid(a1.but,sticky="w"))
	Try(tkgrid(a2.but,sticky="w"))
	Try(tkgrid(a3.but,sticky="w"))
	#TruncateProcessedSignal = c("zero", "one", "none")
  Try(frame3 <- tkframe(ttjettaDialog,relief="groove",borderwidth=2))
	Try(r2Label <- tklabel(frame3,text="TruncateProcessedSignal",font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(r2Label,sticky="w"))
	Try(tkgrid.configure(r2Label,sticky="w"))

  Try(tpsTcl <- tclVar("one"))
	Try(r1.but <- tkradiobutton(frame3,text="0",variable=tpsTcl,value="zero",font=.affylmGUIglobals$affylmGUIfont2))
	Try(r2.but	 <- tkradiobutton(frame3,text="1"  ,variable=tpsTcl,value="one"  ,font=.affylmGUIglobals$affylmGUIfont2))
	Try(r3.but	 <- tkradiobutton(frame3,text="none"  ,variable=tpsTcl,value="none"  ,font=.affylmGUIglobals$affylmGUIfont2))
	
	Try(tkgrid(r1.but,sticky="w"))
	Try(tkgrid(r2.but	,sticky="w"))
	Try(tkgrid(r3.but	,sticky="w"))
    
  #SummarizationMethod = c("liwong", "probe_selection", "median_polish")
  Try(frame4 <- tkframe(ttjettaDialog,relief="groove",borderwidth=2))
	Try(sumMt <- tklabel(frame4,text="SummarizationTarget",font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(sumMt,sticky="w"))
	Try(tkgrid.configure(sumMt,sticky="w"))

  Try(summtTcl <- tclVar("median_polish"))
	Try(summt1.but <- tkradiobutton(frame4,text="liwong",variable=summtTcl,value="liwong",font=.affylmGUIglobals$affylmGUIfont2))
	Try(summt2.but	 <- tkradiobutton(frame4,text="probe_selection"  ,variable=summtTcl,value="probe_selection"  ,font=.affylmGUIglobals$affylmGUIfont2))
	Try(summt3.but	 <- tkradiobutton(frame4,text="median_polish"  ,variable=summtTcl,value="median_polish"  ,font=.affylmGUIglobals$affylmGUIfont2))
	
	Try(tkgrid(summt1.but,sticky="w"))
	Try(tkgrid(summt2.but	,sticky="w"))
	Try(tkgrid(summt3.but	,sticky="w"))
	
	Try(Abort <- 1)
  jetta.param <- list()
   
	Try(onOK <- function()
	{
			Try(jetta.param[[1]] <<- tclvalue(bgTcl))
			Try(tkgrab.release(ttjettaDialog))
			Try(tkdestroy(ttjettaDialog))
			Try(tkfocus(.affylmGUIglobals$ttMain))
			Try(jetta.param[[2]]	<<- tclvalue(normTcl))
			Try(jetta.param[[3]]	<<- tclvalue(tpsTcl))
			Try(jetta.param[[4]]	<<- tclvalue(summtTcl))
			Try(assign("jetta.param", jetta.param, affylmGUIenvironment)) 
			Try(Abort					<<- 0)
	})
	Try(frame5 <- tkframe(ttjettaDialog,borderwidth=2))
	Try(onCancel <- function() {Try(tkgrab.release(ttjettaDialog));Try(tkdestroy(ttjettaDialog));Try(tkfocus(.affylmGUIglobals$ttMain));Abort <<- 1})
	Try(OK.but <-tkbutton(frame5,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
	Try(Cancel.but <-tkbutton(frame5,text=" Cancel ",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))
	
	Try(tkgrid(tklabel(frame5,text="    "),OK.but,Cancel.but,tklabel(frame5,text="    ")))

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

	Try(tkfocus(ttjettaDialog))
	Try(tkbind(ttjettaDialog, "<Destroy>", function() {Try(tkgrab.release(ttjettaDialog));Try(tkfocus(.affylmGUIglobals$ttMain));}))
	Try(tkwait.window(ttjettaDialog))

	Try(if(Abort==1) return())
  Try(jetta.param <- get("jetta.param", affylmGUIenvironment))
  
  #defining the  MADSSampleClass
  Try(Targets <- get("Targets",envir=affylmGUIenvironment))
  cels <- dir()[grep("\\.CEL$", dir())]
  target.unique <- unique(Targets$Target)
  if(length(target.unique) > 2){
                 Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                 Try(tkmessageBox(title="Jetta alternative splicing analysis",message="Jetta Alternative splicing analysis is only implemented for two groups"))
                 Try(return())
  }
  sample.class <- rep(0,dim(Targets)[1]) 
  for(i in 1:dim(Targets)[1]){
      if(Targets$Target[grep(cels[i], Targets$FileName)] ==  target.unique[1]){
              sample.class[i] <- -1
      } else if(Targets$Target[grep(cels[i], Targets$FileName)] ==  target.unique[2]){
              sample.class[i] <- 1
      }
  }
  
  #Filtering
  ##making the menu for selecting Filtering parameters
  Try(ttfilterDialog<-tktoplevel(.affylmGUIglobals$ttMain))
  Try(tkwm.deiconify(ttfilterDialog))
  Try(tkgrab.set(ttfilterDialog))
  Try(tkfocus(ttfilterDialog))
  Try(tkwm.title(ttfilterDialog,"Jetta Filtering Parameters"))
  Try(tkgrid(tklabel(ttfilterDialog,text="    ")))

  Try(frame1 <- tkframe(ttfilterDialog,relief="groove",borderwidth=2))
  Try(HowManyQuestion1 <- tklabel(frame1,text="MADS filtering cutoff for high probe intensity",font=.affylmGUIglobals$affylmGUIfont2))
  Try(tkgrid(HowManyQuestion1))
  Try(tkgrid.configure(HowManyQuestion1,columnspan=2,sticky="w"))
  #MADS filtering cutoff for high probe intensity, -1 doesn't use this filtering. 
  Try(intensityTcl <- tclVar("0.9"))
	Try(q1.but			<- tkradiobutton(frame1,text="No filtering",variable=intensityTcl,value="-1",font=.affylmGUIglobals$affylmGUIfont2))
	Try(q2.but	 <- tkradiobutton(frame1,text="0.2",variable=intensityTcl,value="0.2",font=.affylmGUIglobals$affylmGUIfont2))
	Try(q3.but	 <- tkradiobutton(frame1,text="0.3",variable=intensityTcl,value="0.3",font=.affylmGUIglobals$affylmGUIfont2))
  Try(q4.but	 <- tkradiobutton(frame1,text="0.4",variable=intensityTcl,value="0.4",font=.affylmGUIglobals$affylmGUIfont2))
	Try(q5.but	 <- tkradiobutton(frame1,text="0.5",variable=intensityTcl,value="0.5",font=.affylmGUIglobals$affylmGUIfont2))
	Try(q6.but	 <- tkradiobutton(frame1,text="0.6",variable=intensityTcl,value="0.6",font=.affylmGUIglobals$affylmGUIfont2))
	Try(q7.but	 <- tkradiobutton(frame1,text="0.7",variable=intensityTcl,value="0.7",font=.affylmGUIglobals$affylmGUIfont2))
	Try(q8.but	 <- tkradiobutton(frame1,text="0.8",variable=intensityTcl,value="0.8",font=.affylmGUIglobals$affylmGUIfont2))
	Try(q9.but	 <- tkradiobutton(frame1,text="0.9",variable=intensityTcl,value="0.9",font=.affylmGUIglobals$affylmGUIfont2))
	
  Try(tkgrid(q1.but,sticky="w"))
	Try(tkgrid(q2.but,sticky="w"))
	Try(tkgrid(q3.but,sticky="w"))
	Try(tkgrid(q4.but,sticky="w"))
	Try(tkgrid(q5.but,sticky="w"))
	Try(tkgrid(q6.but,sticky="w"))
	Try(tkgrid(q7.but,sticky="w"))
	Try(tkgrid(q8.but,sticky="w"))
	Try(tkgrid(q9.but,sticky="w"))
	Try(tkgrid.configure(HowManyQuestion1,q1.but,q2.but,q3.but,q4.but,q5.but,q6.but,q7.but,q8.but,q9.but,sticky="w"))
  # MADS filtering cutoff for low expression genes, -1 doesn't use this filtering. 
	Try(frame2 <- tkframe(ttfilterDialog,relief="groove",borderwidth=2))
	Try(lowLabel <- tklabel(frame2,text="MADS filtering cutoff for low expression genes",font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(lowLabel,sticky="w"))
	Try(tkgrid.configure(lowLabel,sticky="w"))

  Try(lowTcl <- tclVar("500"))
	Try(a1.but <- tkradiobutton(frame2,text="No filtering",variable=lowTcl,value="-1",font=.affylmGUIglobals$affylmGUIfont2))
	Try(a2.but <- tkradiobutton(frame2,text="log2(32)=5",variable=lowTcl,value="32",font=.affylmGUIglobals$affylmGUIfont2))
	Try(a3.but <- tkradiobutton(frame2,text="log2(64)=6",variable=lowTcl,value="64",font=.affylmGUIglobals$affylmGUIfont2))
	Try(a4.but <- tkradiobutton(frame2,text="log2(128)=7",variable=lowTcl,value="128",font=.affylmGUIglobals$affylmGUIfont2))
	Try(a5.but <- tkradiobutton(frame2,text="log2(256)=8",variable=lowTcl,value="256",font=.affylmGUIglobals$affylmGUIfont2))
	Try(a6.but <- tkradiobutton(frame2,text="log2(512)=9",variable=lowTcl,value="512",font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(a1.but,sticky="w"))
	Try(tkgrid(a2.but,sticky="w"))
	Try(tkgrid(a3.but,sticky="w"))
	Try(tkgrid(a4.but,sticky="w"))
	Try(tkgrid(a5.but,sticky="w"))
	Try(tkgrid(a6.but,sticky="w"))
	
	#MADS filtering cutoff for significantly changed genes
  Try(frame3 <- tkframe(ttfilterDialog,relief="groove",borderwidth=2))
	Try(fcLabel <- tklabel(frame3,text="MADS filtering cutoff for significantly changed genes",font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(fcLabel,sticky="w"))
	Try(tkgrid.configure(fcLabel,sticky="w"))
  Try(fcTcl <- tclVar("2"))
	Try(r1.but <- tkradiobutton(frame3,text="No filtering",variable=fcTcl,value="-1",font=.affylmGUIglobals$affylmGUIfont2))
	Try(r2.but	 <- tkradiobutton(frame3,text="log2(2)=1"  ,variable=fcTcl,value="2"  ,font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(r1.but,sticky="w"))
	Try(tkgrid(r2.but	,sticky="w"))
    
  #MADS filtering cutoff for cross hybridized probes, -1 doesn't use this filtering.
  Try(frame4 <- tkframe(ttfilterDialog,relief="groove",borderwidth=2))
	Try(crossMt <- tklabel(frame4,text="MADS filtering cutoff for cross hybridized probes.",font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(crossMt,sticky="w"))
	Try(tkgrid.configure(crossMt,sticky="w"))

  Try(crossTcl <- tclVar("0.55"))
	Try(summt1.but <- tkradiobutton(frame4,text="No filtering",variable=crossTcl,value="-1",font=.affylmGUIglobals$affylmGUIfont2))
	Try(summt2.but	 <- tkradiobutton(frame4,text="0.30"  ,variable=crossTcl,value="0.30"  ,font=.affylmGUIglobals$affylmGUIfont2))
	Try(summt3.but	 <- tkradiobutton(frame4,text="0.55"  ,variable=crossTcl,value="0.55"  ,font=.affylmGUIglobals$affylmGUIfont2))
	Try(summt4.but	 <- tkradiobutton(frame4,text="0.75"  ,variable=crossTcl,value="0.75"  ,font=.affylmGUIglobals$affylmGUIfont2))
	Try(summt5.but	 <- tkradiobutton(frame4,text="0.90"  ,variable=crossTcl,value="0.90"  ,font=.affylmGUIglobals$affylmGUIfont2))
	Try(tkgrid(summt1.but,sticky="w"))
	Try(tkgrid(summt2.but	,sticky="w"))
	Try(tkgrid(summt3.but	,sticky="w"))
	Try(tkgrid(summt4.but	,sticky="w"))
	Try(tkgrid(summt5.but	,sticky="w"))

	Try(Abort <- 1)
   
	Try(onOK <- function()
	{
			Try(jetta.param[[5]] <<- tclvalue(intensityTcl))
			Try(tkgrab.release(ttfilterDialog))
			Try(tkdestroy(ttfilterDialog))
			Try(tkfocus(.affylmGUIglobals$ttMain))
			Try(jetta.param[[6]]	<<- tclvalue(lowTcl))
			Try(jetta.param[[7]]	<<- tclvalue(fcTcl))
			Try(jetta.param[[8]]	<<- tclvalue(crossTcl))
			Try(assign("jetta.param", jetta.param, affylmGUIenvironment)) 
			Try(Abort					<<- 0)
	})
	Try(frame5 <- tkframe(ttfilterDialog,borderwidth=2))
	Try(onCancel <- function() {Try(tkgrab.release(ttfilterDialog));Try(tkdestroy(ttfilterDialog));Try(tkfocus(.affylmGUIglobals$ttMain));Abort <<- 1})
	Try(OK.but <-tkbutton(frame5,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
	Try(Cancel.but <-tkbutton(frame5,text=" Cancel ",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))
	
	Try(tkgrid(tklabel(frame5,text="    "),OK.but,Cancel.but,tklabel(frame5,text="    ")))

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

	Try(tkfocus(ttfilterDialog))
	Try(tkbind(ttfilterDialog, "<Destroy>", function() {Try(tkgrab.release(ttfilterDialog));Try(tkfocus(.affylmGUIglobals$ttMain));}))
	Try(tkwait.window(ttfilterDialog))

	Try(if(Abort==1) return())
  Try(jetta.param <- get("jetta.param", affylmGUIenvironment))

  #Cross-hybridized probe filtering
  if(jetta.param[[8]] != -1 ){
    if(whichLib[[1]][1] == "HuEx" &&  whichLib[[1]][2] == "core"){
        Try(crosshyb.name <- paste(jettaDir, "huex_cross_hyb.reduced.txt", sep=""))
    } else if(whichLib[[1]][1] == "MoEx" &&  whichLib[[1]][2] == "core"){
        Try(crosshyb.name <- paste(jettaDir, "moex_cross_hyb.reduced.txt",sep=""))
    } else     crosshyb.name <-""
   }
  cat("\nCalculating the effects of MADS filters on gene-level data\n")
  mads.param <- jetta.do.mads(getwd(), clf.name, pgf.name, MetaProbesetFile = genelib.name, BackgroundCorrectionMethod = jetta.param[[1]], NormalizationMethod = jetta.param[[2]], TruncateProcessedSignal = jetta.param[[3]], SummarizationTarget = "mps", SummarizationMethod = jetta.param[[4]], MADSPrecomputedCrossHybCorr = crosshyb.name, MADSCutoffHigh = jetta.param[[5]], MADSCutoffExpression = jetta.param[[6]], MADSCutoffFoldChange = jetta.param[[7]], MADSCutoffCrossHybCorr = jetta.param[[8]], MADSSampleClass = sample.class)
  g.expr = jetta.read.expression(mads.param)
  mads <- jetta.read.mads.output(mads.param)
  assign("mads.Available", TRUE, affylmGUIenvironment)
  assign("mads", mads, affylmGUIenvironment)
  assign("g.expr", g.expr, affylmGUIenvironment)
  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
 }
################################################################################
"variantSI" <- function(){
          Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
          #error if no data are loaded
          Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
          if(whichArrayPlatform !="EXON"){
              Try(tkmessageBox(title="Associating deltaSI to variant exons",message="No exon arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())
          }
          Try(tkmessageBox(title="Associating deltaSI to variant exons",message="Open the file containing the list of spliced exon-level probesets\n This file is generated applying any of the filters present in exon menu.",type="ok",icon="info"))
          Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
          if(!nchar(tempFileName))
          {
                     tkfocus(.affylmGUIglobals$ttMain)
                     return()
          }
          Try(mySel<-read.table(tempFileName, sep="\t", header=F, as.is=TRUE))
          if(dim(mySel)[2]==1){
                    Try(mySel <- as.character(unlist(mySel[,1])))
                    Try(tempFileName <- as.character(unlist(strsplit(tempFileName[[1]], "/"))))
                    Try(tempFileName <- tempFileName[length(tempFileName)])
                    Try(tempFileName <- sub(".txt", "", tempFileName))
                    Try(tempFileName <- paste("variant.exons.",tempFileName,".txt", sep=""))
          } else Try(tkmessageBox(title="Associating deltaSI to variant exons",message=paste("File should contain\nonly a column with\nAffymetrix exon-level ids")))  
          #USARE MYSEL PER FILTRARE GLI SPLICE INDEX
          Try(targets <-  affylmGUIenvironment$Targets$Target)
          Try(target.unique <- unique(targets))
          Try(cl <- rep(0,length(targets)))

          if(length(target.unique) == 2){
                 #groups definition
                 Try(tkmessageBox(title="Associating deltaSI to variant exons",message="Two-Class case analysis will be performed."))
                 Try(cl[which(targets==target.unique[2])] <- 1)
                 Try(spliceIndexData.Available <- get("spliceIndexData.Available", env=affylmGUIenvironment))
                 if(spliceIndexData.Available){
                        Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment))
                        Try(cl <- c(NA,NA,cl))
                        #selecting mean ir min
                        Try(mbVal <- tkmessageBox(title="Associating deltaSI to variant exons",
                                                  message="Do you want to use a SI min difference filter? \nIf you answer no a SI mean difference filter will be applyed",
                                                  icon="question",type="yesno",default="yes"))
                        Try(if(tclvalue(mbVal)=="yes"){
                                      min.c <- apply(spliceIndexData[,which(cl==0)], 1, min)
                                      min.t <- apply(spliceIndexData[,which(cl==1)], 1, min)
                                      max.c <- apply(spliceIndexData[,which(cl==0)], 1, max)
                                      max.t <- apply(spliceIndexData[,which(cl==1)], 1, max)
                                      minmax <- data.frame(min.c, min.t, max.c, max.t)
                                      .deltaMin <- function(x){ if(x[3]<x[4]){abs(x[3]-x[2])} else{abs(x[4]-x[1])}} #if max.c<max.t |max.c-min.t| else |max.t-min.c| 
                                      amsi <- apply(minmax, 1, .deltaMin)
                                      amsi <- data.frame(spliceIndexData[,1:2], as.numeric(amsi))
                                      names(amsi) <- c("elevel","glevel", "deltaSI")
               
                            } else{
                                   mean.c <- apply(spliceIndexData[,which(cl==0)], 1, mean)
                                   mean.t <- apply(spliceIndexData[,which(cl==1)], 1, mean)
                                   amsi <- abs(mean.t - mean.c)
                                   amsi <- data.frame(spliceIndexData[,1:2], as.numeric(amsi))
                                   names(amsi) <- c("elevel","glevel", "deltaSI")
                            }
                        )
                        Try(amsi <- amsi[which(as.character(amsi[,1])%in%mySel),])
                        Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))
                        Try(cat("\nCombining deltaSI with variant exon location\n"))
                        if(whichLib[[1]][1] == "HuEx"){
                                 # Try(data("huex.variantexons",package="oneChannelGUI"))
                                 # Try(exonannlib<- get("huex.variantexons",envir=.GlobalEnv))
                                 Try(libDirLocation <- get("libDirLocation", envir=affylmGUIenvironment))
                                 Try(load(paste(libDirLocation, "huex.variantexons.rda", sep="/")))
                                 Try(exonannlib <- huex.variantexons)
                                 Try(rm(huex.variantexons))
                        }
                        if(whichLib[[1]][1] == "MoEx"){
                                #  Try(data("moex.variantexons",package="oneChannelGUI"))
                                #  Try(exonannlib<- get("moex.variantexons",envir=.GlobalEnv))
                                 Try(libDirLocation <- get("libDirLocation", envir=affylmGUIenvironment))
                                 Try(load(paste(libDirLocation, "moex.variantexons.rda", sep="/")))
                                 Try(exonannlib <- moex.variantexons)
                                 Try(rm(moex.variantexons))
                        }
                        if(whichLib[[1]][1] == "RaEx"){
                               #   Try(data("raex.variantexons",package="oneChannelGUI"))
                               #   Try(exonannlib<- get("raex.variantexons",envir=.GlobalEnv))
                               Try(libDirLocation <- get("libDirLocation", envir=affylmGUIenvironment))
                               Try(load(paste(libDirLocation, "raex.variantexons.rda", sep="/")))
                               Try(exonannlib <- raex.variantexons)
                               Try(rm(raex.variantexons))
                        }
                        #exon.ann is a matrix
                        Try(exon.ann <- exonannlib[which(as.character(exonannlib[,1])%in%as.character(amsi$elevel)),])
                        Try(tmp.genome<- strsplit(exon.ann[,dim(exon.ann)[2]], "="))
                        Try(tmp.genome <- sapply(tmp.genome, function(x){x[length(x)]}))
                        Try(exon.ann[,dim(exon.ann)[2]] <- tmp.genome)
                        Try(exon.ann <- exon.ann[order(as.character(exon.ann[,1])),])
                        Try(amsi <- amsi[which(as.character(amsi$elevel) %in% as.character(exon.ann[,1])),])
                        Try(amsi <- amsi[order(as.character(amsi$elevel)),])
                        Try(out <- .internalLoop(amsi, exon.ann))
                        Try(exon.ann <- cbind(out$exon.gid, exon.ann, out$exon.fc))
                        Try(dimnames(exon.ann)[[2]][1] <- "geneLevelID")
                        Try(dimnames(exon.ann)[[2]][which(dimnames(exon.ann)[[2]]== "affyname")] <- "exonLevelID")
                        Try(dimnames(exon.ann)[[2]][dim(exon.ann)[2]] <- "deltaSI")                        
                        Try(tkmessageBox(title="Associating deltaSI to variant exons",message=paste("The table associating spliced exon-level probesets to variant exons is ",tempFileName, sep="")))
                        Try(write.table(exon.ann, tempFileName, sep="\t", row.names=F))
                        Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                        return()
                 }else {
                        Try(tkmessageBox(title="Associating deltaSI to variant exons",message="SI is needed. Please calculate it!"))
                        Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
                        return()
                }
       }else {
              Try(tkmessageBox(title="Associating deltaSI to variant exons",message="Only two groups analysis is permitted."))
              Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              return()
       }                        

}
#associating deltaSI and geneleveID to exon.ann containing variant exons
.internalLoop <- function(amsi,exon.ann){
                        exon.fc <- rep(0, dim(exon.ann)[1])#deltaSI
                        exon.gid <- rep(NA, dim(exon.ann)[1]) #genelevel id

                        for(amsi.id in as.character(amsi$elevel)){
                               exon.fc[which(exon.ann == amsi.id)] <-  amsi$deltaSI[which(as.character(amsi$elevel) == amsi.id)]
                               exon.gid[which(exon.ann == amsi.id)] <-  as.character(amsi$glevel[which(as.character(amsi$elevel) == amsi.id)])
                        }
                        out <- list("exon.fc" =  exon.fc, "exon.gid" =  exon.gid)                        
}
################################################################################
#this function uses the output of variantSI to generate an output for the UCSC browser
"plotVariantSI" <- function(){
#    require(rtracklayer) || stop("\nMissing rtracklayer library\n")
    #require(IRanges) || stop("\nMissing IRanges library\n")
    Try(tkmessageBox(title="Plotting variant exons on UCSC browser",message="Open the file containing the variant exon detected with the exon menu option:\n Associating alternative spliced exon-level probe set to variant exons.",type="ok",icon="info"))
    Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
    if(!nchar(tempFileName))
    {
                tkfocus(.affylmGUIglobals$ttMain)
                return()
    }
    Try(mySel<-read.table(tempFileName, sep="\t", header=T, as.is=TRUE))
    Try(mychrs <- unique(as.character(mySel[,which(names(mySel) == "chr")])))
    #selecting the Chr to be plotted 
    Try(ttcolExtract<-tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttcolExtract))
    Try(tkgrab.set(ttcolExtract))
    Try(tkfocus(ttcolExtract))
    Try(tkwm.title(ttcolExtract,"Defining the chromosome to be plotted"))
    Try(tkgrid(tklabel(ttcolExtract,text="    ")))
    Try(colnum <- "")
    Try(Local.colExtract <- tclVar(init=colnum))
    Try(entry.colExtract <-tkentry(ttcolExtract,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.colExtract,bg="white"))
    Try(tkgrid(tklabel(ttcolExtract,text=paste("Please enter chromosome to be plotted:\n", paste(mychrs,collapse=" ")),font=.affylmGUIglobals$affylmGUIfont2)))
    Try(tkgrid(entry.colExtract))
    onOK <- function()
    {
        Try(chrnum <- as.numeric(tclvalue(Local.colExtract)))
        Try(assign("chrnum", as.character(tclvalue(Local.colExtract)),affylmGUIenvironment))
        Try(tkgrab.release(ttcolExtract));Try(tkdestroy(ttcolExtract));Try(tkfocus(.affylmGUIglobals$ttMain))                        
    }
    Try(OK.but <-tkbutton(ttcolExtract,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(tklabel(ttcolExtract,text="    ")))
    Try(tkgrid(OK.but))
    Try(tkgrid.configure(OK.but))
    Try(tkgrid(tklabel(ttcolExtract,text="       ")))
    Try(tkfocus(entry.colExtract))
    Try(tkbind(entry.colExtract, "<Return>",onOK))
    Try(tkbind(ttcolExtract, "<Destroy>", function(){Try(tkgrab.release(ttcolExtract));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
    Try(tkwait.window(ttcolExtract))
    Try(tkfocus(.affylmGUIglobals$ttMain))
    Try(chrnum <- get("chrnum", affylmGUIenvironment))
    if(length(grep(chrnum, mychrs)) == 0){
                         Try(tkmessageBox(title="Chromosome selection",message="You have selected a chromosome not present in this data set!"))
                         return()
    }
    Try(chrpos <- which(names(mySel) == "chr"))
    Try(vsp <- mySel[which(mySel[,chrpos] ==  chrnum ),7:14])
    Try(names(vsp) <- c("name","start","end","width","strand","chr","genome","deltaSI"))
    Try(vsp$deltaSI <- rep(0, dim(vsp)[1]))
    Try(psr <- mySel[which(mySel[,chrpos] ==  chrnum ),c(2:6, 12:14)])
    Try(bed15params <- cbind(rep(1, dim(psr)[1]), rep(0, dim(psr)[1])))
    Try(psr <- cbind(psr[,1:dim(psr)[2] - 1], bed15params, psr[,dim(psr)[2]]))
    Try(names(psr) <- c("name","start","end","width","strand","chr","genome","expCount","expIds","expScores"))
    Try(tmp.n <- paste(psr$name, signif(psr$expScores,2), sep="_"))
    Try(psr$name <- tmp.n)
    #Try(targets <- rbind(vsp, psr))
    Try(targets <- psr)
    Try(targetRanges <- IRanges(targets$start, targets$end))
    Try(targetTrack <- GenomicData(targetRanges, targets[, c("strand","name", "expCount", "expIds", "expScores")], chrom = targets$chr, genome = "hg18"))
    Try(session <- browserSession("UCSC"))
    Try(track(session, "targets") <- targetTrack)
#    Try(view <- browserView(session, range(targetTrack), pack = "targets", dense="Affy Exon...",hide = c("Base Position", "RefSeq Genes", "MGC Genes", "Spliced ESTs", "Conservation", "SNPs (130)", "SNP Arrays")))
    Try(view <- browserView(session, range(targetTrack), pack = "targets"))

}
################################################################################
#this function creates a bed15 version file to be loaded on UCSC browser
"makeBED15" <- function(){
    Try(tkmessageBox(title="Creating a BED15 for UCSC browser",message="Open the file containing the variant exon detected with the exon menu option:\n Associating alternative spliced exon-level probe set to variant exons.",type="ok",icon="info"))
    Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
    if(!nchar(tempFileName))
    {
                tkfocus(.affylmGUIglobals$ttMain)
                return()
    }
    Try(mySel<-read.table(tempFileName, sep="\t", header=T, as.is=TRUE))
    Try(mychrs <- unique(as.character(mySel[,which(names(mySel) == "chr")])))
    Try(chrpos <- which(names(mySel) == "chr"))
    for( i in mychrs){
      outFile <- paste(tempFileName,".chr",i,".BED15.txt", sep="")
      mytrack <- paste("track type=\"array\" expScale=3.0 expStep=0.5 expNames=\"exon-levels,\" name=\"chr",i,"\" description=\"chr", i," exon-level track\"", sep="")
      writeLines(con=outFile, mytrack)
      Try(psr <- mySel[which(mySel[,chrpos] ==  i ),c(2:6, 12:14)])
      Try(blockSizes <- paste(psr$affywidth - 1, ",", sep=""))
      Try(bed15params <- cbind(rep(500, dim(psr)[1]), rep(0, dim(psr)[1]), rep(1, dim(psr)[1]), as.character(blockSizes), as.character(rep("0,", dim(psr)[1])), rep(1, dim(psr)[1]), rep(0, dim(psr)[1])))
      Try(psr.tmp <- cbind(psr[,1:dim(psr)[2] - 1], bed15params, psr[,dim(psr)[2]]))
      Try(names(psr.tmp) <- c("name","chromStart","chromEnd","width","strand","chr","genome","score","reserved","blockCount","blockSizes","chromStarts", "expCount","expIds","expScores"))
      Try(tmp.n <- paste(psr.tmp$name, signif(psr.tmp$expScores,2), sep="_"))
      Try(psr.tmp$name <- tmp.n)
      #col names
      #chrom  	chromStart      	chromEnd        	name       	score	strand  	thickStart     	 thickEnd        	reserved       	 blockCount     	 blockSizes      	chromStarts     	expCount       	 expIds  	expScores
      target <- cbind(paste("chr",psr.tmp$chr, sep=""),psr.tmp$chromStart,psr.tmp$chromEnd, psr.tmp$name, as.character(psr.tmp$score), psr.tmp$strand, psr.tmp$chromStart, psr.tmp$chromEnd, as.character(psr.tmp$reserved), as.character(psr.tmp$blockCount), as.character(psr.tmp$blockSizes), as.character(psr.tmp$chromStarts), as.character(psr.tmp$expCount), as.character(psr.tmp$expIds), psr.tmp$expScores)
      write.table(target, outFile, sep="\t", append = T, row.names=F, col.names=F, quote=F)
    }
    Try(tkmessageBox(title="Creating a BED15 for UCSC browser",message=paste("BED15 formatted files are ready in ", getwd()," to be loaded on UCSC Genome Browser.",sep=""),type="ok",icon="info"))

}

################################################################################
.cosie <- function(x, paramFile=NULL, exprExt=2) {
  # calculate corrected splicing indices (v 1.1)
  # arguments:
  #   x         : log2 probeset (exon) expression levels, one of:
  #                 - ExpressionSet (with feature and sample names)
  #                 - matrix (with row and column names)
  #   paramFile : filename with corrector parameters
  #   exprExt   : extend expression ranges observed in training set by
  #               this many log2-units on both sides to determine
  #               correctable expression levels
  # return value:
  #   list of three components:
  #      correctedSI : p-times-s matrix with corrected splicing indices
  #                    (p: correctable probesets, s: samples)
  #      transcriptClusterLevels : t-times-s matrix with transcript cluster levels
  #                                used in calculating splicing indices
  #                                (t: transcript clusters, s: samples)
  #      tcIds : p-element vector with transcript cluster ids corresponding to probesets

  # get sample and probeset ids
  if(is.matrix(x)) {
    sampleIds <- if(is.null(colnames(x))) as.character(1:ncol(x)) else colnames(x)
    psIds <- rownames(x)
  } else if(class(x) == 'ExpressionSet') {
    sampleIds <- sampleNames(x)
    psIds <- featureNames(x)
    x <- exprs(x)
  } else {
    stop("x needs to be a matrix or object of class 'ExpressionSet'", call.=FALSE)
  }
  nSamples <- length(sampleIds)

  # check input parameters
  if(is.null(paramFile)) {
    stop("no parameter file 'paramFile' specified. Aborting.", call.=FALSE)
  }
  if(any(!is.finite(x))) {
    stop("x must not have any missing or non-finite values", call.=FALSE)
  }
  if(max(x) > 20) {
    warning("x contains values larger than 20, and therefore is likely not to be in log2", call.=FALSE, immediate.=TRUE)
  }

  # calculate mean probeset expression over samples
  psExprMin <- 3.5 # only used to report expressed but uncorrectable probesets
  meanPsExpr <- rowMeans(x)
  
  # load parameter 
  param <- paramFile
  x2param <- match(param$psId, psIds)
  if(any(is.na(x2param))) {
    #missing <- param$psId[is.na(x2param)]
    #stop(length(missing), " probesets missing in expression data x: ", missing[1], ", ...")
    toRm.tcId <- unique(param$tcId[is.na(x2param)])
    toRm <- which(param$tcId %in% toRm.tcId)
    toRm.psId <- param$psId[toRm]
    warning(paste('Removing',length(toRm.tcId), 'transcript clusters (', length(which(is.na(x2param))), 'probesets) with probeset composition deviating from training data'), call.=FALSE, immediate.=TRUE)
    for(nm in names(param))
      param[[nm]] <- param[[nm]][-toRm]
    x2param <- match(param$psId, psIds)
    rm(toRm.tcId, toRm, toRm.psId)
  }
  psExprInTestButNotInTraining <- length(which(param$status==1 & meanPsExpr[match(param$psId,psIds)]>psExprMin))

  # select needed probesets
  toKeep <- which(param$status==0 | param$status==3)
  x2param <- x2param[toKeep]
  probesetsThatHaveToBeCorrected <- length(toKeep) + psExprInTestButNotInTraining
  for(nm in names(param))
    param[[nm]] <- param[[nm]][toKeep]
  param$tcId <- factor(param$tcId)
  
  # order x/psIds/meanPsExpr according to param
  x <- x[x2param,]
  psIds <- psIds[x2param]
  meanPsExpr <- meanPsExpr[x2param]

  # calculate transcript cluster (gene) expression levels
  ps.by.tc <- split(1:nrow(x), param$tcId)
  calcGnLevel <- function(j) { colMeans(x[j,]) }
  geneLevels <- matrix(sapply(ps.by.tc, calcGnLevel, USE.NAMES=FALSE),
                       ncol=nSamples, byrow=TRUE, dimnames=list(names(ps.by.tc), sampleIds))

  # check for correctable probesets
  toCorrect <- which(apply(geneLevels,1,min)[param$tcId]>param$geneTrainFrom - exprExt &
                     apply(geneLevels,1,max)[param$tcId]<param$geneTrainTo + exprExt &
                     param$status!=3)
  tcIds <- unique(param$tcId[toCorrect])
  probesetsThatCouldBeCorrected <- length(toCorrect)

  # correct probesets
  x <- x - geneLevels[param$tcId,] # subtract gene level from probeset level in all experiments
  x <- x[toCorrect,]
  meanPsExpr <- meanPsExpr[toCorrect]
  for(nm in names(param))
    param[[nm]] <- param[[nm]][toCorrect]
  
  csi <- matrix(NA_real_, ncol=nSamples, nrow=probesetsThatCouldBeCorrected,
                dimnames=list(psIds[toCorrect], sampleIds))
  for(i in 1:nSamples) {
    csi[,i] <- x[,i] + (param$a/param$d*log(exp(-param$d*geneLevels[param$tcId,i]) + exp(-param$d*param$c)) - param$b)
  }
  csi <- csi -rowMeans(csi) +meanPsExpr # set the mean to the probeset mean
  
  # return results
  correctedPercent <- round(100*probesetsThatCouldBeCorrected/probesetsThatHaveToBeCorrected, 2)
  cat(paste("Number of probesets that need correction:", probesetsThatHaveToBeCorrected, "\n"))
  cat(paste("Number of probesets that were corrected :", probesetsThatCouldBeCorrected, "(", correctedPercent, "%)\n\n"))
  list(correctedSI=csi, transcriptClusterLevels=geneLevels[tcIds,], tcIds=param$tcId)                
}
############cosieWrapper RETIRED!
cosieWrapper <- function(){
     Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
     if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
    }    
    #########################
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
    Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment) )
    Try(whichLib <- get("whichLib", env=affylmGUIenvironment))
    cat("\nLoading Cosie models...")
    if(whichLib[[1]][1] =="HuEx"){
                  Try(cosielibloc <- grep(paste("cosieHs", whichLib[[1]][2],sep=""), as.vector(unlist(data(package="oneChannelGUI"))), ignore.case = T))
                  Try(cosielibname <- as.vector(unlist(data(package="oneChannelGUI")))[cosielibloc])
                  Try(data(list=cosielibname,package="oneChannelGUI"))
                  Try(cosielib <- get(cosielibname,envir=.GlobalEnv))
    } else if(whichLib[[1]][1] =="MoEx"){
                  Try(cosielibloc <- grep(paste("cosieMm", whichLib[[1]][2],sep=""), as.vector(unlist(data(package="oneChannelGUI"))), ignore.case = T))
                  Try(cosielibname <- as.vector(unlist(data(package="oneChannelGUI")))[cosielibloc])
                  Try(data(list=cosielibname,package="oneChannelGUI"))
                  Try(cosielib <- get(cosielibname,envir=.GlobalEnv))
    } else{
           Try(tkmessageBox(title="Cosi SI bias correction",message="Cosie model for SI bias correction for Rn is not available, yet.\nPlease, run conventional SI calculation.",type="ok",icon="error"))
           cat("\nCosie model for SI bias correction for Rn is not available, yet.\nPlease, run conventional SI calculation\n")
           Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
   	       Try(tkfocus(.affylmGUIglobals$ttMain))
           Try(return())
    }
    cat("\nExecuting Cosie...\n")
    Try(cosieOut <- .cosie(exonAffyData, paramFile=cosielib))
    Try(correctedSI <- cosieOut$correctedSI)
    Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
    Try(transcriptClusterLevels <- cosieOut$transcriptClusterLevels)
    Try(allExons <- correctedSI)
    Try(exprs(exonAffyData) <- allExons)
    Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData)%in%as.character(dimnames(transcriptClusterLevels)[[1]])),])
    Try(assign("exonAffyData", exonAffyData ,affylmGUIenvironment))
    #preparing data structure for SI
    Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
    Try(x.exonid <-as.character(x.lib[,3]))
    Try(x.exonid <- paste(x.lib[,1], x.exonid)) 
    g.to.e<- function(x){
         tmp <- as.character(unlist(strsplit(x, " ")))
         tmp <- paste(tmp[1], tmp[2:length(tmp)], sep=".")
    }
    Try(g.e.out <- as.vector(unlist(sapply(x.exonid, g.to.e))))
    Try(g.e.out <- strsplit(g.e.out, "\\."))
    Try(g.out <- sapply(g.e.out, function(x) x[1]))
    Try(e.out <- sapply(g.e.out, function(x) x[2]))
    Try(e.g.df <- cbind(e.out, g.out))
    Try(e.g.df.which <- e.g.df[which(e.g.df[,1] %in% featureNames(exonAffyData)),])
    #remove duplications
    Try(e.g.df.which <- e.g.df.which[which(!duplicated(e.g.df.which[,1])),])
    Try(e.g.df.which <- e.g.df.which[order(e.g.df.which[,1]),])
    Try(exonAffyData <- exonAffyData[order(featureNames(exonAffyData)),])
    if(identical(featureNames(exonAffyData), e.g.df.which[,1])){
          spliceIndexData <-  cbind(as.numeric(e.g.df.which[,1]),as.numeric(e.g.df.which[,2]),exprs(exonAffyData))
    } else{
           Try(tkmessageBox(title="Cosi SI bias correction",message="Internal error 1005. Please, contact oneChannelGUI maintainer\n"))
           Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
   	       Try(tkfocus(.affylmGUIglobals$ttMain))
           Try(return())
    
    }
    
    Try(assign("spliceIndexData", spliceIndexData ,affylmGUIenvironment))
    Try(assign("spliceIndexData.Available", TRUE ,affylmGUIenvironment))
    Try(assign("cosie.Available", TRUE ,affylmGUIenvironment))

    Try(assign("NormalizedAffyData", NormalizedAffyData ,affylmGUIenvironment))

    Try(tkdelete(.affylmGUIglobals$mainTree,"spliceIndex.Status"))            
    Try(tkinsert(.affylmGUIglobals$mainTree,"end","spliceIndex","spliceIndex.Status" ,text="SI COSIE corrected",font=.affylmGUIglobals$affylmGUIfontTree))
    
    Try(tkdelete(.affylmGUIglobals$mainTree,"ExonArrays.Status"))
	  Try(tkinsert(.affylmGUIglobals$mainTree,"end","ExonArrays","ExonArrays.Status" ,text="Exon level COSIE corrected",font=.affylmGUIglobals$affylmGUIfontTree))

    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}


################################################################################
#detecting alternative splcing by limma analysis
#works at exon level
"limmaExons" <-function(){
   #error if no data are loaded
   Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
   if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
  }    
  Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
 	
  Try(Targets <- get("Targets",envir=affylmGUIenvironment))
	Try(design <- as.matrix(as.data.frame(model.matrix(~ -1 + factor(Targets$Target)))))
	Try(NumParameters <- ncol(design))
	Try(assign("NumParameters",NumParameters,affylmGUIenvironment))
	Try(colnames(design) <- gsub("factor\\(Targets\\$Target\\)","",colnames(design)))
	Try(rownames(design) <- Targets$FileName)
	Try(assign("designExon",design,affylmGUIenvironment))

  			Try(fit <- lm.series(exonAffyData,design))
#		}
#	)#end of Try
	Try(assign("LinearModelFitExon.Available",TRUE,affylmGUIenvironment))
	Try(assign("fitExon",fit,affylmGUIenvironment))
	Try(tkdelete(.affylmGUIglobals$mainTree,"LinearModelFitExon.Status"))
	Try(tkinsert(.affylmGUIglobals$mainTree,"end","LinearModelFitExon","LinearModelFitExon.Status",text="Available",font=.affylmGUIglobals$affylmGUIfontTree))
	Try(NumParameters <- get("NumParameters" , envir=affylmGUIenvironment))
	Try(if(NumParameters>0)
		Try(for (i in (1:NumParameters))
			Try(tkdelete(.affylmGUIglobals$mainTree,paste("Parameters.Status.",i,sep=""))))
	else
			Try(tkdelete(.affylmGUIglobals$mainTree,"Parameters.Status.1")))
	Try(for (i in (1:ncol(design)))
		Try(tkinsert(.affylmGUIglobals$mainTree,"end","Parameters",paste("Parameters.Status.",i,sep="") ,
			text=colnames(design)[i],font=.affylmGUIglobals$affylmGUIfontTree)))
	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))

	Try(tkmessageBox(title="Exon level Linear Model Fit Complete",
						message=paste("Calculation of the linear model fit is complete. ",
							"Contrasts can now be computed (from the Exon menu).")))
}#end of function ComputeLinearModelFit

################################################################################
#second step of exon analysis by limma
"exonContrasts" <- function(){
	# For now, we will assume that the number of contrasts is one less than the number of parameters,
	# e.g. with 4 treatments, we estimate 4 parameters, then 3 contrasts.

	Try(NumParameters <- get("NumParameters",envir=affylmGUIenvironment))
	Try(Targets <- get("Targets",envir=affylmGUIenvironment))
	Try(NumContrastParameterizations <- get("NumContrastParameterizations",envir=affylmGUIenvironment))
	Try(ContrastParameterizationNamesVec <- get("ContrastParameterizationNamesVec",envir=affylmGUIenvironment))
	Try(ContrastParameterizationList <- get("ContrastParameterizationList",envir=affylmGUIenvironment))
	Try(ContrastParameterizationTREEIndexVec <- get("ContrastParameterizationTREEIndexVec",envir=affylmGUIenvironment))
	Try(LinearModelFitExon.Available <- get("LinearModelFitExon.Available", envir=affylmGUIenvironment))

  #error if no data are loaded
  Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
  if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
  }    

	if(LinearModelFitExon.Available==FALSE){
		Try(limmaExons())
		Try(NumParameters <- get("NumParameters",envir=affylmGUIenvironment))
	}
	Try(fit		<- get("fitExon",	 envir=affylmGUIenvironment))
	Try(design <- get("designExon",envir=affylmGUIenvironment))
	#
	Try(ParameterNamesVec	<- colnames(design))
	#
	Try(NumContrasts <- NumParameters - 1)
	#
	Try(
		if(NumContrasts<=0){
			tkmessageBox(title="Compute Contrasts",message=paste("You need to have two or more treatments in order to compute contrasts."),type="ok",icon="error")
			Try(tkfocus(.affylmGUIglobals$ttMain))
			return()
		}#end of if(NumContrasts<=0)
	)#end of Try
	Try(NumContrasts <- min(NumContrasts,10))
	#
	Try(contrastsMatrixInList <- .GetContrasts(NumContrasts=NumContrasts))
	Try(if(nrow(contrastsMatrixInList$contrasts)==0) return())
	Try(contrastsMatrix <- as.matrix(contrastsMatrixInList$contrasts))
	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
	Try(contrastsFit <- contrasts.fit(fit,contrastsMatrix))
	#
	# NEW
	#
	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
	Try(
		if(min(contrastsFit$df)==0){
			Try(tkmessageBox(title="No degrees of freedom",message="Empirical Bayes statistics will not be available because of the lack of replicate arrays.",icon="warning"))
			Try(ebayesAvailable <- FALSE)
		}else{
			Try(ebayesAvailable <- TRUE)
		}
	)#end of Try
	#
	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
	Try(if(ebayesAvailable==TRUE)
		Try(contrastsEbayes <- eBayes(contrastsFit)))
	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
	Try(ContrastParameterizationNameText <- GetContrastParameterizationName())
	Try(if(ContrastParameterizationNameText=="GetContrastParameterizationName.CANCEL") return())
	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
	Try(
		while (nchar(ContrastParameterizationNameText)==0){
			Try(tkmessageBox(title="Contrasts Name",message="Please enter a name for this set of contrasts",type="ok",icon="error"))
			Try(ContrastParameterizationNameText <- GetContrastParameterizationName())
			if(ContrastParameterizationNameText=="GetContrastParameterizationName.CANCEL"){
				Try(tkfocus(.affylmGUIglobals$ttMain))
				return()
			}#end of if(ContrastParameterizationNameText=="GetContrastParameterizationName.CANCEL")
		}#end of while (nchar(ContrastParameterizationNameText)==0)
	)#end of Try
	#
	Try(contrastParameterizationIndex <- 0)
	Try(newContrastParameterization <- 1)
	Try(
		if(ContrastParameterizationNameText %in% ContrastParameterizationNamesVec){
			Try(contrastParameterizationIndex <- match(ContrastParameterizationNameText,ContrastParameterizationNamesVec))
			Try(mbVal<-tclvalue(tkmessageBox(title="Contrasts Parameterization Name",message="This contrasts parameterization name already exists.	Replace?",type="yesnocancel",icon="question")))
			Try(if(mbVal=="cancel") return())
			Try(if(mbVal=="yes") newContrastParameterization <- 0)
			Try(if(mbVal=="no") newContrastParameterization <- 1)
		}else{
			Try(newContrastParameterization <- 1)
		}#end of else/if(ContrastParameterizationNameText %in% ContrastParameterizationNamesVec)
	)#end of Try
	#
	Try(ContrastParameterizationTREEIndexVec <- get("ContrastParameterizationTREEIndexVec",envir=affylmGUIenvironment))
	Try(NumContrastParameterizations <- get("NumContrastParameterizations",envir=affylmGUIenvironment))
	#
	if(newContrastParameterization==1){
		Try(
			if(length(ContrastParameterizationTREEIndexVec)!=NumContrastParameterizations){
				Try(tkmessageBox(title="Contrasts Parameterizations","Length of ContrastParameterizationTREEIndexVec is not equal to NumContrastParameterizations.",type="ok",icon="error"))
				Try(tkfocus(.affylmGUIglobals$ttMain))
				return()
			}#end of if(length(ContrastParameterizationTREEIndexVec)!=NumContrastParameterizations)
		)#end of Try
		Try(NumContrastParameterizations <- NumContrastParameterizations + 1)
		Try(contrastParameterizationIndex <- NumContrastParameterizations)
		Try(
			if(length(ContrastParameterizationTREEIndexVec)==0){
				Try(.affylmGUIglobals$ContrastParameterizationTREEIndex <- 1)
			}else{
				Try(.affylmGUIglobals$ContrastParameterizationTREEIndex <- max(ContrastParameterizationTREEIndexVec)+1)
			}
		)#end of Try
		Try(ContrastParameterizationTREEIndexVec[contrastParameterizationIndex] <- .affylmGUIglobals$ContrastParameterizationTREEIndex)
		Try(ContrastParameterizationNamesVec <- c(ContrastParameterizationNamesVec,ContrastParameterizationNameText))
		Try(ContrastParameterizationNameNode <- paste("ContrastParameterizationName.",.affylmGUIglobals$ContrastParameterizationTREEIndex,sep=""))
		Try(ContrastParameterizationList[[ContrastParameterizationNameNode]] <- ContrastParameterizationNameText)
	}else{ # Replace existing contrasts parameterization with the same name.
		Try(.affylmGUIglobals$ContrastParameterizationTREEIndex <- ContrastParameterizationTREEIndexVec[contrastParameterizationIndex])
		Try(tkdelete(.affylmGUIglobals$ContrastParameterizationTREE,paste("ContrastParameterizationName.",.affylmGUIglobals$ContrastParameterizationTREEIndex,sep="")))
	}#end of else/if(newContrastParameterization==1)
	#
	Try(ContrastParameterizationNameNode <- paste("ContrastParameterizationName.",.affylmGUIglobals$ContrastParameterizationTREEIndex,sep=""))
	Try(ContrastParameterizationList[[ContrastParameterizationNameNode]] <- list())
	Try(ContrastParameterizationList[[ContrastParameterizationNameNode]]$NumContrastParameterizations <- NumContrastParameterizations)
	###Try(NormalizedAffyData <- get("NormalizedAffyData",affylmGUIenvironment))
  Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
	Try(contrastsFit$Amean <- rowMeans(exprs(exonAffyData)))
	#
	Try(ContrastParameterizationList[[ContrastParameterizationNameNode]]$fitExon <- contrastsFit)
	Try(
		if(ebayesAvailable==TRUE){
			Try(ContrastParameterizationList[[ContrastParameterizationNameNode]]$ebExon	<- contrastsEbayes)
		}else{
			Try(ContrastParameterizationList[[ContrastParameterizationNameNode]]$ebExon	<- list())
		}
	)#end of Try
	Try(ContrastParameterizationList[[ContrastParameterizationNameNode]]$contrastsMatrixInList <- contrastsMatrixInList)
	Try(ContrastParameterizationList[[ContrastParameterizationNameNode]]$ContrastParameterizationNameText <- ContrastParameterizationNameText)
	#
	if(NumContrastParameterizations>0){
		Try(ContrastsNames <- colnames(contrastsMatrix))
	}
	Try(tkinsert(.affylmGUIglobals$ContrastParameterizationTREE,"end","root",ContrastParameterizationNameNode,text=ContrastParameterizationNameText,font=.affylmGUIglobals$affylmGUIfontTree))
	Try(NumContrastsInContrastParameterization <- length(ContrastsNames))
	#
	Try(ContrastsNode <- paste("ContrastsNode.",.affylmGUIglobals$ContrastParameterizationTREEIndex))
	Try(tkinsert(.affylmGUIglobals$ContrastParameterizationTREE,"end",ContrastParameterizationNameNode,ContrastsNode,text="Contrasts",font=.affylmGUIglobals$affylmGUIfontTree))
	#
	Try(
		for (j in (1:NumContrastsInContrastParameterization)){
			Try(tkinsert(.affylmGUIglobals$ContrastParameterizationTREE,"end",ContrastsNode,paste("Contrasts.",.affylmGUIglobals$ContrastParameterizationTREEIndex,".",j,sep=""),text=ContrastsNames[j],font=.affylmGUIglobals$affylmGUIfontTree))
		}
	)#end of Try
	#
	Try(LinearModelFitNode			 <- paste("LinearModelFitNode.",.affylmGUIglobals$ContrastParameterizationTREEIndex))
	Try(LinearModelFitStatusNode <- paste("LinearModelFitStatusNode.",.affylmGUIglobals$ContrastParameterizationTREEIndex))
	Try(tkinsert(.affylmGUIglobals$ContrastParameterizationTREE,"end",ContrastParameterizationNameNode,LinearModelFitNode,text="Linear Model Fit",font=.affylmGUIglobals$affylmGUIfontTree))
	Try(tkinsert(.affylmGUIglobals$ContrastParameterizationTREE,"end",LinearModelFitNode,LinearModelFitStatusNode,text="Available",font=.affylmGUIglobals$affylmGUIfontTree))
	Try(EmpiricalBayesNode			 <- paste("EmpiricalBayesNode.",.affylmGUIglobals$ContrastParameterizationTREEIndex))
	Try(EmpiricalBayesStatusNode <- paste("EmpiricalBayesStatusNode.",.affylmGUIglobals$ContrastParameterizationTREEIndex))
	Try(tkinsert(.affylmGUIglobals$ContrastParameterizationTREE,"end",ContrastParameterizationNameNode,EmpiricalBayesNode,text="Empirical Bayes Statistics",font=.affylmGUIglobals$affylmGUIfontTree))
	Try(if(ebayesAvailable==TRUE)
		Try(tkinsert(.affylmGUIglobals$ContrastParameterizationTREE,"end",EmpiricalBayesNode,EmpiricalBayesStatusNode,text="Available",font=.affylmGUIglobals$affylmGUIfontTree))
	else
		Try(tkinsert(.affylmGUIglobals$ContrastParameterizationTREE,"end",EmpiricalBayesNode,EmpiricalBayesStatusNode,text="Not Available",font=.affylmGUIglobals$affylmGUIfontTree))			)
	Try(assign("ContrastParameterizationList",ContrastParameterizationList,affylmGUIenvironment))
	Try(assign("NumContrastParameterizations",NumContrastParameterizations,affylmGUIenvironment))
	Try(assign("ContrastParameterizationTREEIndexVec",ContrastParameterizationTREEIndexVec,affylmGUIenvironment))
	Try(assign("ContrastParameterizationNamesVec",ContrastParameterizationNamesVec,affylmGUIenvironment))
	#
	Try(
		if(NumContrastParameterizations>0){
			Try(for (i in (1:NumContrastParameterizations))
			Try(tkdelete(.affylmGUIglobals$mainTree,paste("ContrastParameterizations.Status.",i,sep=""))))
		}else{
			Try(tkdelete(.affylmGUIglobals$mainTree,"ContrastParameterizations.Status.1"))
		}
	)#end of Try
	Try(
		if(NumContrastParameterizations>0){
			for (contrastParameterizationIndex in (1:NumContrastParameterizations)){
				Try(.affylmGUIglobals$ContrastParameterizationTREEIndex <- ContrastParameterizationTREEIndexVec[contrastParameterizationIndex])
				Try(ContrastParameterizationNameNode <- paste("ContrastParameterizationName.",.affylmGUIglobals$ContrastParameterizationTREEIndex,sep=""))
				Try(ContrastParameterizationsStatusNameNode <- paste("ContrastParameterizations.Status.",.affylmGUIglobals$ContrastParameterizationTREEIndex,sep=""))
				Try(tkinsert(.affylmGUIglobals$mainTree,"end","ContrastParameterizations",ContrastParameterizationsStatusNameNode ,text=ContrastParameterizationNamesVec[contrastParameterizationIndex],font=.affylmGUIglobals$affylmGUIfontTree))
			}#end of for (contrastParameterizationIndex in (1:NumContrastParameterizations))
		}else{
			Try(tkinsert(.affylmGUIglobals$mainTree,"end","ContrastParameterizations","ContrastParameterizations.Status.1" ,text="None",font=.affylmGUIglobals$affylmGUIfontTree))
		}#end of else/if(NumContrastParameterizations>0)
	)#end of Try
	#
	tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow")
	.rawpCheckExons()
  .exonTopTable()
	Try(
		tkmessageBox(
			title="P-values spliced Exon Table",
			message=paste("Calculation of the exon-level contrasts fit and p-value detection is complete. ",
			"Alternative spliced exons can be now extracted with oneChannelGUI: Limma alternative splicing detection function.")
		)#end of tkmessageBox exonTopTable
	)#end of Try
}#end of function ComputeContrasts

################################################################################
".GetContrasts" <- function (NumContrasts = 0){
    Try(NumSlides <- get("NumSlides", envir = affylmGUIenvironment))
    Try(Targets <- get("Targets", envir = affylmGUIenvironment))
    Try(LinearModelFitExon.Available <- get("LinearModelFitExon.Available", 
        envir = affylmGUIenvironment))
    Try(ContrastParameterizationTREEIndexVec <- get("ContrastParameterizationTREEIndexVec", 
        envir = affylmGUIenvironment))
    if (LinearModelFitExon.Available == FALSE) {
        Try(limmaExon())
    }
    Try(design <- get("designExon", envir = affylmGUIenvironment))
    Try(NumParameters <- ncol(design))
    Try(ParameterNamesVec <- colnames(design))
    GetContrastsTable <- function(contrastsFromDropDowns) {
        Try(TclRequire("Tktable"))
        Try(ttContrastsTable <- tktoplevel(.affylmGUIglobals$ttMain))
        Try(tkwm.deiconify(ttContrastsTable))
        Try(tkgrab.set(ttContrastsTable))
        Try(tkfocus(ttContrastsTable))
        Try(tkwm.title(ttContrastsTable, "Contrasts Matrix"))
        Try(ReturnVal <- list(contrasts = data.frame(), contrastsCreatedFromDropDowns = FALSE))
        Try(contrastsMatrix <- contrastsFromDropDowns$contrasts)
        Try(tclArrayVar1 <- tclArrayVar())
        Try(tclArrayName <- ls(tclArrayVar1$env))
        onOK <- function() {
            Try(tcl("event", "generate", .Tk.ID(table1), "<Leave>"))
            NumRows <- NumParameters
            NumCols <- NumContrasts
            Try(contrastsMatrix <- as.data.frame(matrix(nrow = NumRows, 
                ncol = NumCols)))
            Try(rownamescontrastsMatrix <- c())
            for (i in (1:NumRows)) Try(rownamescontrastsMatrix[i] <- tclvalue(paste(tclArrayName, 
                "(", i, ",0)", sep = "")))
            Try(colnamescontrastsMatrix <- c())
            if (NumCols > 0) 
                for (j in (1:NumCols)) Try(colnamescontrastsMatrix[j] <- tclvalue(paste(tclArrayName, 
                  "(0,", j, ")", sep = "")))
            Try(rownames(contrastsMatrix) <- rownamescontrastsMatrix)
            Try(colnames(contrastsMatrix) <- colnamescontrastsMatrix)
            if (NumCols > 0) 
                for (i in (1:NumRows)) for (j in (1:NumCols)) Try(contrastsMatrix[i, 
                  j] <- as.numeric(tclvalue(paste(tclArrayName, 
                  "(", i, ",", j, ")", sep = ""))))
            Try(tkgrab.release(ttContrastsTable))
            Try(tkdestroy(ttContrastsTable))
            Try(tkfocus(.affylmGUIglobals$ttMain))
            Try(ReturnVal <<- list(contrasts = contrastsMatrix, 
                contrastsCreatedFromDropDowns = FALSE))
        }
        onCancel <- function() {
            Try(tkgrab.release(ttContrastsTable))
            Try(tkdestroy(ttContrastsTable))
            Try(tkfocus(.affylmGUIglobals$ttMain))
            ReturnVal <<- list(contrasts = data.frame(), contrastsCreatedFromDropDowns = FALSE)
        }
        Try(OK.but <- tkbutton(ttContrastsTable, text = "   OK   ", 
            command = onOK, font = .affylmGUIglobals$affylmGUIfont2))
        Try(Cancel.but <- tkbutton(ttContrastsTable, text = " Cancel ", 
            command = onCancel, font = .affylmGUIglobals$affylmGUIfont2))
        Try(tkgrid(tklabel(ttContrastsTable, text = "    ")))
        Try(PleaseEntercontrastsMatrixLabel <- tklabel(ttContrastsTable, 
            text = "Please enter the contrasts matrix to be used for linear-modelling.", 
            font = .affylmGUIglobals$affylmGUIfont2))
        Try(tkgrid(tklabel(ttContrastsTable, text = "    "), 
            PleaseEntercontrastsMatrixLabel))
        Try(tkgrid.configure(PleaseEntercontrastsMatrixLabel, 
            columnspan = 2))
        Try(tkgrid(tklabel(ttContrastsTable, text = "    ")))
        NumRows <- NumParameters
        NumCols <- NumContrasts
        Try(.affylmGUIglobals$ContrastParameterizationTREEIndex <- ContrastParameterizationTREEIndexVec)
        Try(if (nrow(contrastsMatrix) == 0) {
            Try(ContrastsNamesVec <- c())
            if (NumContrasts > 0) {
                for (i in (1:NumContrasts)) {
                  Try(ContrastsNamesVec <- c(ContrastsNamesVec, 
                    paste("Contrast ", i, sep = "")))
                }
            }
        }
        else {
            Try(ContrastsNamesVec <- colnames(contrastsMatrix))
        })
        Try(ColNamesVec <- ContrastsNamesVec)
        Try(rownamescontrastsMatrix <- c())
        Try(myRarray <- "    ")
        for (i in (1:NumRows)) {
            Try(RowName <- ParameterNamesVec[i])
            Try(rownamescontrastsMatrix <- c(rownamescontrastsMatrix, 
                RowName))
            Try(myRarray <- c(myRarray, paste(RowName)))
        }
        if (NumCols > 0) {
            for (j in (1:NumCols)) {
                Try(myRarray <- c(myRarray, paste(ColNamesVec[j])))
                for (i in (1:NumRows)) {
                  if (nrow(contrastsMatrix) == 0) 
                    Try(myRarray <- c(myRarray, "0"))
                  else Try(myRarray <- c(myRarray, paste(contrastsMatrix[i, 
                    j])))
                }
            }
        }
        Try(dim(myRarray) <- c(NumRows + 1, NumCols + 1))
        if (NumCols > 0) {
            for (i in (0:NumRows)) {
                for (j in (0:NumCols)) {
                  Try(tcl("set", paste(tclArrayName, "(", i, 
                    ",", j, ")", sep = ""), paste(myRarray[i + 
                    1, j + 1])))
                }
            }
        }
        Try(table1 <- .Tk.subwin(ttContrastsTable))
        Try(.Tcl(paste("table", .Tk.ID(table1), .Tcl.args(variable = tclArrayName, 
            rows = paste(NumRows + 1), cols = paste(NumCols + 
                1), titlerows = "0", titlecols = "0", selectmode = "extended", 
            colwidth = "13", background = "white", rowseparator = "\"\n\"", 
            colseparator = "\"\t\"", resizeborders = "col", multiline = "0"))))
        Try(tkgrid(tklabel(ttContrastsTable, text = "    "), 
            table1))
        Try(tcl(.Tk.ID(table1), "width", "0", paste(max(4, max(nchar(rownamescontrastsMatrix)) + 
            2))))
        Try(if (nrow(contrastsMatrix) > 0) {
            Try(for (j in (1:NumCols)) {
                Try(tcl(.Tk.ID(table1), "width", paste(j), paste(max(4, 
                  max(nchar(ColNamesVec)) + 2, max(nchar(contrastsMatrix[, 
                    j])) + 2))))
            })
        })
        Try(tkconfigure(table1, font = .affylmGUIglobals$affylmGUIfontTable))
        Try(tkgrid.configure(table1, columnspan = 2))
        Try(copyFcn <- function() .Tcl(paste("event", "generate", 
            .Tcl.args(.Tk.ID(table1), "<<Copy>>"))))
        openContrastsMatrixFile <- function() {
            Try(contrastsMatrixFileName <- tclvalue(tkgetOpenFile(filetypes = "{{Contrasts Matrix Files} {.txt}} {{All files} *}")))
            Try(if (!nchar(contrastsMatrixFileName)) 
                return())
            Try(contrastsMatrixTable <- read.table(contrastsMatrixFileName, 
                header = FALSE, sep = "\t", quote = "\"", as.is = TRUE))
            if (NumCols > 0) 
                for (i in (0:NumRows)) for (j in (0:NumCols)) Try(tcl("set", 
                  paste(tclArrayName, "(", i, ",", j, ")", sep = ""), 
                  paste(contrastsMatrixTable[i + 1, j + 1])))
        }
        saveContrastsMatrixFile <- function() {
            Try(contrastsMatrixFileName <- tclvalue(tkgetSaveFile(filetypes = "{{Contrasts Matrix Files} {.txt}} {{All files} *}")))
            Try(if (!nchar(contrastsMatrixFileName)) 
                return())
            Try(len <- nchar(contrastsMatrixFileName))
            if (len <= 4) {
                Try(contrastsMatrixFileName <- paste(contrastsMatrixFileName, 
                  ".txt", sep = ""))
            }
            else if (substring(contrastsMatrixFileName, len - 
                3, len) != ".txt") {
                Try(contrastsMatrixFileName <- paste(contrastsMatrixFileName, 
                  ".txt", sep = ""))
            }
            Try(contrastsMatrix <- as.data.frame(matrix(nrow = NumSlides, 
                ncol = NumParameters)))
            Try(rownamescontrastsMatrix <- c())
            Try(for (i in (1:NumRows)) {
                rownamescontrastsMatrix[i] <- tclvalue(paste(tclArrayName, 
                  "(", i, ",0)", sep = ""))
            })
            Try(colnamescontrastsMatrix <- c())
            if (NumParameters > 0) {
                Try(for (j in (1:NumCols)) {
                  colnamescontrastsMatrix[j] <- tclvalue(paste(tclArrayName, 
                    "(0,", j, ")", sep = ""))
                })
            }
            Try(rownames(contrastsMatrix) <- rownamescontrastsMatrix)
            Try(colnames(contrastsMatrix) <- colnamescontrastsMatrix)
            if (NumParameters > 0) {
                Try(for (i in (1:NumRows)) for (j in (1:NumParameters)) {
                  contrastsMatrix[i, j] <- as.numeric(tclvalue(paste(tclArrayName, 
                    "(", i, ",", j, ")", sep = "")))
                })
            }
            Try(write.table(contrastsMatrix, file = contrastsMatrixFileName, 
                col.names = NA, sep = "\t", quote = FALSE, row.names = TRUE))
        }
        Try(topMenu <- tkmenu(ttContrastsTable, tearoff = FALSE))
        Try(fileMenu <- tkmenu(topMenu, tearoff = FALSE))
        Try(tkadd(fileMenu, "command", label = "Open", command = openContrastsMatrixFile))
        Try(tkadd(fileMenu, "command", label = "Save As", command = saveContrastsMatrixFile))
        Try(tkadd(topMenu, "cascade", label = "File", menu = fileMenu))
        Try(editMenu <- tkmenu(topMenu, tearoff = FALSE))
        Try(tkadd(editMenu, "command", label = "Copy <Ctrl-C>", 
            command = copyFcn))
        Try(tkadd(topMenu, "cascade", label = "Edit", menu = editMenu))
        Try(tkconfigure(ttContrastsTable, menu = topMenu))
        Try(BlankLabel1 <- tklabel(ttContrastsTable, text = "    "))
        Try(tkgrid(BlankLabel1))
        Try(BlankLabel2 <- tklabel(ttContrastsTable, text = "    "))
        Try(tkgrid(BlankLabel2, OK.but, Cancel.but))
        Try(tkgrid.configure(OK.but, sticky = "e"))
        Try(tkgrid.configure(Cancel.but, sticky = "w"))
        Try(BlankLabel3 <- tklabel(ttContrastsTable, text = "    "))
        Try(tkgrid(BlankLabel3))
        Try(tkfocus(ttContrastsTable))
        Try(tkbind(ttContrastsTable, "<Destroy>", function() {
            Try(tkgrab.release(ttContrastsTable))
            Try(tkfocus(.affylmGUIglobals$ttMain))
        }))
        Try(tkwait.window(ttContrastsTable))
        return(ReturnVal)
    }
    if (NumParameters <= 0) {
        Try(tkmessageBox(title = "At Least Two RNA Types Are Required", 
            message = "You must have at least two types of RNA in your Targets file.", 
            type = "ok", icon = "error"))
        Try(tkfocus(.affylmGUIglobals$ttMain))
        return(list(contrasts = data.frame(), contrastsCreatedFromDropDowns = FALSE))
    }
    Try(NumRows <- NumParameters)
    Try(NumCols <- NumContrasts)
    Try(ttContrasts <- tktoplevel(.affylmGUIglobals$ttMain))
    Try(tkwm.deiconify(ttContrasts))
    Try(tkgrab.set(ttContrasts))
    Try(tkfocus(ttContrasts))
    Try(tkwm.title(ttContrasts, "Contrasts"))
    Try(lbl2 <- tklabel(ttContrasts, text = "Please specify pairs of parameters for which contrasts will be estimated", 
        font = .affylmGUIglobals$affylmGUIfont2))
    Try(lbl3 <- tklabel(ttContrasts, text = "                                                                    "))
    Try(tkgrid(tklabel(ttContrasts, text = "      "), row = 0, 
        column = 1, columnspan = 1))
    Try(tkgrid(tklabel(ttContrasts, text = "      "), row = 0, 
        column = 4, columnspan = 1))
    Try(tkgrid(lbl2, row = 1, column = 2, columnspan = 4, rowspan = 1, 
        sticky = "ew"))
    Try(tkgrid.configure(lbl2, sticky = "w"))
    Try(tkgrid(tklabel(ttContrasts, text = "         "), column = 1))
    Try(tkgrid(tklabel(ttContrasts, text = "         ")))
    Try(tkgrid(tklabel(ttContrasts, text = "         "), column = 1))
    Try(.affylmGUIglobals$ContrastParameterizationTREEIndex <- ContrastParameterizationTREEIndexVec)
    Try(TclList1AsString <- "{")
    Try(for (i in (1:NumParameters)) TclList1AsString <- paste(TclList1AsString, 
        "{", ParameterNamesVec[i], "} ", sep = ""))
    TclList1AsString <- paste(TclList1AsString, "}", sep = "")
    TclList2AsString <- TclList1AsString
    Try(plusOrMinusTclListAsString <- "{{minus}}")
    Try(TclRequire("BWidget"))
    Try(combo1 <- c())
    Try(combo2 <- c())
    Try(combo3 <- c())
    Try(if (NumCols > 0) {
        for (contrastIndex in (1:NumCols)) {
            Try(FirstDropDownColumn <- .Tk.subwin(ttContrasts))
            combo1 <- c(combo1, FirstDropDownColumn)
            Try(.Tcl(paste("ComboBox", .Tk.ID(FirstDropDownColumn), 
                "-editable false -values", TclList1AsString)))
            Try(SecondDropDownColumn <- .Tk.subwin(ttContrasts))
            Try(combo2 <- c(combo2, SecondDropDownColumn))
            Try(.Tcl(paste("ComboBox", .Tk.ID(SecondDropDownColumn), 
                "-editable false -values", TclList2AsString)))
            Try(plusOrMinusDropDown <- .Tk.subwin(ttContrasts))
            Try(combo3 <- c(combo3, plusOrMinusDropDown))
            Try(.Tcl(paste("ComboBox", .Tk.ID(plusOrMinusDropDown), 
                "-editable false -values", plusOrMinusTclListAsString)))
            Try(tcl(.Tk.ID(plusOrMinusDropDown), "setvalue", 
                "first"))
            Try(if (.affylmGUIglobals$affylmGUIpresentation == 
                TRUE) {
                Try(tkconfigure(FirstDropDownColumn, width = 10))
                Try(tkconfigure(SecondDropDownColumn, width = 10))
                Try(tkconfigure(plusOrMinusDropDown, width = 10))
            })
            Try(dropdownLabel <- paste("Contrast", contrastIndex, 
                "  "))
            Try(tkgrid(tklabel(ttContrasts, text = dropdownLabel, 
                font = .affylmGUIglobals$affylmGUIfont2), row = 2 + 
                contrastIndex, column = 0, sticky = "w"))
            Try(tkconfigure(FirstDropDownColumn, font = .affylmGUIglobals$affylmGUIfont2))
            Try(tkconfigure(SecondDropDownColumn, font = .affylmGUIglobals$affylmGUIfont2))
            Try(tkconfigure(plusOrMinusDropDown, font = .affylmGUIglobals$affylmGUIfont2))
            Try(tkgrid(FirstDropDownColumn, row = 2 + contrastIndex, 
                column = 2, columnspan = 1, rowspan = 1))
            Try(tkgrid(plusOrMinusDropDown, row = 2 + contrastIndex, 
                column = 4, columnspan = 1, rowspan = 1))
            Try(tkgrid(SecondDropDownColumn, row = 2 + contrastIndex, 
                column = 6, columnspan = 1, rowspan = 1))
            Try(tkgrid(tklabel(ttContrasts, text = "    "), row = 2 + 
                contrastIndex, column = 7))
        }
    })
    Try(tkgrid(tklabel(ttContrasts, text = "                                                "), 
        rowspan = 1, columnspan = 4))
    Try(ReturnVal <- list(contrasts = data.frame(), contrastsCreatedFromDropDowns = TRUE, 
        Param1 = c(), Param2 = c()))
    OnAdvanced <- function() {
        Try(contrastsFromDropDowns <- GetContrastsFromDropDowns())
        Try(ReturnValcontrastsMatrixTable <- GetContrastsTable(contrastsFromDropDowns))
        NumRows <- nrow(ReturnValcontrastsMatrixTable$contrasts)
        if (NumRows > 0) {
            Try(tkgrab.release(ttContrasts))
            Try(tkdestroy(ttContrasts))
            Try(tkfocus(.affylmGUIglobals$ttMain))
            ReturnVal <<- ReturnValcontrastsMatrixTable
        }
    }
    GetContrastsFromDropDowns <- function() {
        NumRows <- NumParameters
        NumCols <- NumContrasts
        Param1 <- c()
        Param2 <- c()
        NoParameter <- 99999
        if (NumCols > 0) {
            for (contrastIndex in (1:NumCols)) {
                selection1 <- tclvalue(.Tcl(paste(.Tk.ID(combo1[contrastIndex * 
                  2 - 1]), "getvalue")))
                selection2 <- tclvalue(.Tcl(paste(.Tk.ID(combo2[contrastIndex * 
                  2 - 1]), "getvalue")))
                selection3 <- tclvalue(.Tcl(paste(.Tk.ID(combo3[contrastIndex * 
                  2 - 1]), "getvalue")))
                Try(if ((selection1 != "-1")) 
                  Try(Param1 <- c(Param1, as.numeric(selection1) + 
                    1))
                else Try(Param1 <- c(Param1, NoParameter)))
                Try(if ((selection2 != "-1")) 
                  Try(Param2 <- c(Param2, as.numeric(selection2) + 
                    1))
                else Try(Param2 <- c(Param2, NoParameter)))
            }
        }
        contrastsMatrix <- as.data.frame(matrix(nrow = NumRows, 
            ncol = NumCols))
        Try(rownames(contrastsMatrix) <- ParameterNamesVec)
        Try(.affylmGUIglobals$ContrastParameterizationTREEIndex <- ContrastParameterizationTREEIndexVec)
        ContrastNamesVec <- vector(length = NumContrasts)
        if (NumContrasts > 0) 
            for (j in (1:NumContrasts)) ContrastNamesVec[j] <- SimplifyContrastsExpression(paste("(", 
                ParameterNamesVec[Param1[j]], ")-(", ParameterNamesVec[Param2[j]], 
                ")", sep = ""))
        colnames(contrastsMatrix) <- ContrastNamesVec
        Try(for (i in (1:NumParameters)) {
            for (j in (1:NumContrasts)) {
                Try(contrastsMatrix[i, j] <- 0)
                Try(if (Param1[j] == i) {
                  contrastsMatrix[i, j] <- 1
                })
                Try(if (Param2[j] == i) {
                  contrastsMatrix[i, j] <- -1
                })
            }
        })
        Try(if (max(abs(contrastsMatrix)) == 0) {
            Try(return(list(contrasts = data.frame(), contrastsCreatedFromDropDowns = TRUE, 
                Param1 = c(), Param2 = c())))
        })
        return(list(contrasts = contrastsMatrix, contrastsCreatedFromDropDowns = TRUE, 
            Param1 = Param1, Param2 = Param2))
    }
    onOK <- function() {
        Try(contrastsMatrixList <- GetContrastsFromDropDowns())
        Try(if (nrow(contrastsMatrixList$contrasts) == 0) {
            Try(tkmessageBox(title = "Contrasts", message = paste("Error in creating contrasts matrix from drop-down selection. ", 
                "Make sure you have selected a parameter pair for each contrast."), 
                type = "ok", icon = "error"))
            Try(ReturnVal <<- list(contrasts = data.frame(), 
                contrastsCreatedFromDropDowns = TRUE, Param1 = c(), 
                Param2 = c()))
            return()
        }
        else {
            Try(tkgrab.release(ttContrasts))
            Try(tkdestroy(ttContrasts))
            Try(tkfocus(.affylmGUIglobals$ttMain))
            Try(ReturnVal <<- contrastsMatrixList)
            Try(tkfocus(.affylmGUIglobals$ttMain))
            return()
        })
    }
    onCancel <- function() {
        Try(tkgrab.release(ttContrasts))
        Try(tkdestroy(ttContrasts))
        Try(tkfocus(.affylmGUIglobals$ttMain))
        ReturnVal <<- list(contrasts = data.frame(), contrastsCreatedFromDropDowns = TRUE, 
            Param1 = c(), Param2 = c())
    }
    Advanced.but <- tkbutton(ttContrasts, text = "Advanced...", 
        command = OnAdvanced, font = .affylmGUIglobals$affylmGUIfont2)
    Try(OK.but <- tkbutton(ttContrasts, text = "   OK   ", command = onOK, 
        font = .affylmGUIglobals$affylmGUIfont2))
    Try(Cancel.but <- tkbutton(ttContrasts, text = " Cancel ", 
        command = onCancel, font = .affylmGUIglobals$affylmGUIfont2))
    Try(tkgrid(OK.but, column = 2, row = 9 + NumParameters))
    Try(tkgrid(Cancel.but, column = 4, row = 9 + NumParameters))
    Try(tkgrid(Advanced.but, column = 6, row = 9 + NumParameters))
    Try(tkgrid(tklabel(ttContrasts, text = "    ")))
    Try(tkfocus(ttContrasts))
    Try(tkbind(ttContrasts, "<Destroy>", function() {
        Try(tkgrab.release(ttContrasts))
        Try(tkfocus(.affylmGUIglobals$ttMain))
    }))
    Try(tkwait.window(ttContrasts))
    return(ReturnVal)
}

################################################################################
".rawpCheckExons"<- function(){
  Try(tkmessageBox(title="P-values spliced Exon Table",message="Before deciding with type I error corretion method to be applyed. \nDistribution of uncorrected p-values is evaluated",type="ok",icon="info"))
  Try(NumContrastParameterizations <- get("NumContrastParameterizations",envir=affylmGUIenvironment))
  Try(ContrastParameterizationList <- get("ContrastParameterizationList",envir=affylmGUIenvironment))
  Try(ContrastParameterizationTREEIndexVec <- get("ContrastParameterizationTREEIndexVec",envir=affylmGUIenvironment))
  Try(if(NumContrastParameterizations==0)
  {
    Try(tkmessageBox(title="Exon Top Table",message="There are no contrast parameterizations available.  Select \"Compute Contrasts\" from the \"Exon\" menu.",type="ok",icon="error"))
    Try(tkfocus(.affylmGUIglobals$ttMain))
    return()
  })
  Try(contrastParameterizationIndex <- ChooseContrastParameterization())
  Try(if(contrastParameterizationIndex==0) return()) # Cancel
  Try(tkmessageBox(title="raw P-values",message=paste("Plot will be displayed in the main R window")))  

   #p.values plots
   n.contrasts<-dim(ContrastParameterizationList[[contrastParameterizationIndex]]$ebExon$p.value)
   names.contrasts<-dimnames(ContrastParameterizationList[[contrastParameterizationIndex]]$ebExon$p.value)[[2]]
   my.plots<-which(names.contrasts!="(NA)-(NA)")
   par(mfrow=c(1,length(my.plots)))
   for(i in my.plots){
   	   hist(ContrastParameterizationList[[contrastParameterizationIndex]]$eb$p.value[,i], main=names.contrasts[i], xlab="")
   }
}
################################################################################
#oneChannelGUI: Limma alternative splicing detection function
".exonTopTable" <- function(...,export=FALSE)
{
  Try(tkmessageBox(title="P-values spliced Exon Table",message="Calculating regularized t-test for the exon-level contrasts",type="ok",icon="info"))
  Try(NumContrastParameterizations <- get("NumContrastParameterizations",envir=affylmGUIenvironment))
  Try(ContrastParameterizationList <- get("ContrastParameterizationList",envir=affylmGUIenvironment))
  Try(ContrastParameterizationTREEIndexVec <- get("ContrastParameterizationTREEIndexVec",envir=affylmGUIenvironment))

  #error if no data are loaded
  Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
  if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="P-values spliced Exon Table",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
  }    

  Try(if(NumContrastParameterizations==0)
  {
    Try(tkmessageBox(title="P-values spliced Exon Table",message="There are no contrast parameterizations available.  Select \"Compute Contrasts\" from the \"Exon\" menu.",type="ok",icon="error"))
    Try(tkfocus(.affylmGUIglobals$ttMain))
    return()
  })
  Try(if(NumContrastParameterizations>1)
  {
    Try(tkmessageBox(title="P-values spliced Exon Table",message="IMPORTANT: Only the last analysed contrast will be stored.\nPlease, after p-values are calculated extract alternative spliced exons using the oneChannelGUI: Limma alternative splicing detection function.",type="ok",icon="error"))
  })
  Try(contrastParameterizationIndex <- ChooseContrastParameterization())
  Try(if(contrastParameterizationIndex==0) return()) # Cancel

  Try(.affylmGUIglobals$ContrastParameterizationTREEIndex <- ContrastParameterizationTREEIndexVec[contrastParameterizationIndex])
  Try(ContrastNamesVec  <- colnames(as.matrix(ContrastParameterizationList[[contrastParameterizationIndex]]$contrastsMatrixInList$contrasts)))

  Try(GetContrastReturnVal <- GetContrast(contrastParameterizationIndex))
  Try(if(GetContrastReturnVal$contrastIndex==0) return()) # Cancel
  Try(contrast <- GetContrastReturnVal$contrastIndex)
  Try(ContrastParameterizationNameNode <- paste("ContrastParameterizationName.",.affylmGUIglobals$ContrastParameterizationTREEIndex,sep=""))

  Try(fit <- (ContrastParameterizationList[[ContrastParameterizationNameNode]])$fitExon)

	Try(if(("ebExon" %in% names(ContrastParameterizationList[[contrastParameterizationIndex]]))&&
										length(ContrastParameterizationList[[contrastParameterizationIndex]]$ebExon)>0)
		Try(ebayesAvailable <- TRUE)
	else
		Try(ebayesAvailable <- FALSE))

  # This is a bit silly, calculating it again.  This should be tidied up later.  But basically, we're
  # checking whether we had degrees of freedom > 0 from the linear model fit (i.e. were there any
  # replicate arrays?)  If so, eBayes should work, and we can use Gordon's new method (adding new
  # attributes to the fit object rather than using eb), because this seems to work best with topTable,
  # affy data etc.
  Try(if(ebayesAvailable==TRUE)
    Try(fit <- eBayes(fit)))

  Try(ttToptableDialog<-tktoplevel(.affylmGUIglobals$ttMain))
  Try(tkwm.deiconify(ttToptableDialog))
  Try(tkgrab.set(ttToptableDialog))
  Try(tkfocus(ttToptableDialog))
  Try(tkwm.title(ttToptableDialog,"Exon Toptable Options"))
  Try(tkgrid(tklabel(ttToptableDialog,text="    ")))

  Try(frame2 <- tkframe(ttToptableDialog,relief="groove",borderwidth=2))
  Try(adjustMethodLabel <- tklabel(frame2,text="Adjust method:",font=.affylmGUIglobals$affylmGUIfont2))
  Try(tkgrid(adjustMethodLabel,sticky="w"))
  Try(tkgrid.configure(adjustMethodLabel,sticky="w"))
  Try(if(ebayesAvailable==TRUE)
    Try(adjustMethodTcl <- tclVar("BH"))
  else
     Try(adjustMethodTcl <- tclVar("none")))
  Try(none.but <- tkradiobutton(frame2,text="None",variable=adjustMethodTcl,value="none",font=.affylmGUIglobals$affylmGUIfont2))
  Try(bh.but   <- tkradiobutton(frame2,text="BH"  ,variable=adjustMethodTcl,value="BH"  ,font=.affylmGUIglobals$affylmGUIfont2))
  Try(by.but   <- tkradiobutton(frame2,text="BY"  ,variable=adjustMethodTcl,value="BY"  ,font=.affylmGUIglobals$affylmGUIfont2))
  Try(holm.but <- tkradiobutton(frame2,text="Holm",variable=adjustMethodTcl,value="holm",font=.affylmGUIglobals$affylmGUIfont2))

  Try(tkgrid(none.but,sticky="w"))
  Try(tkgrid(bh.but  ,sticky="w"))
  Try(tkgrid(by.but  ,sticky="w"))
  Try(tkgrid(holm.but,sticky="w"))

  Try(if(ebayesAvailable==FALSE)
  {
    Try(tkconfigure(none.but,state="disabled"))
    Try(tkconfigure(bh.but  ,state="disabled"))
    Try(tkconfigure(by.but  ,state="disabled"))
    Try(tkconfigure(holm.but,state="disabled"))
  })

  Try(totalGenes <- nrow(fit$coefficients))
  Try(Abort <- 1)
  Try(numberOfGenes <- 0)
  Try(adjustMethod <- "BH")
  Try(onOK <- function()
  {
      #Try(NumGenesChoice <- as.numeric(tclvalue(numberOfGenesTcl)))
      Try(tkgrab.release(ttToptableDialog))
      Try(tkdestroy(ttToptableDialog))
      Try(tkfocus(.affylmGUIglobals$ttMain))
      #Try(NumbersOfGenes <- c(10,30,50,100,totalGenes))
      Try(numberOfGenes  <<- totalGenes)
      Try(adjustMethod   <<- tclvalue(adjustMethodTcl))
      Try(Abort          <<- 0)
  })

  Try(frame3 <- tkframe(ttToptableDialog,borderwidth=2))
  Try(onCancel <- function() {Try(tkgrab.release(ttToptableDialog));Try(tkdestroy(ttToptableDialog));Try(tkfocus(.affylmGUIglobals$ttMain));Abort <<- 1})
  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(ttToptableDialog,text="    "),frame2,tklabel(ttToptableDialog,text="  ")))
  Try(tkgrid(tklabel(ttToptableDialog,text="    ")))
  Try(tkgrid(tklabel(ttToptableDialog,text="    "),frame3,tklabel(ttToptableDialog,text="  ")))
  Try(tkgrid(tklabel(ttToptableDialog,text="    ")))
  Try(tkgrid.configure(frame3,sticky="s"))

  Try(tkfocus(ttToptableDialog))
  Try(tkbind(ttToptableDialog, "<Destroy>", function() {Try(tkgrab.release(ttToptableDialog));Try(tkfocus(.affylmGUIglobals$ttMain));}))
  Try(tkwait.window(ttToptableDialog))

  Try(if(Abort==1)
     return())

  Try(if(numberOfGenes==totalGenes)
  {
      tkconfigure(.affylmGUIglobals$ttMain,cursor="watch")
      Try(tkfocus(.affylmGUIglobals$ttMain))
  })

  Try(options(digits=3))
  Try(exonAffyData <- get("exonAffyData",envir=affylmGUIenvironment))
  Try(genelist <- data.frame(ID=I(featureNames(exonAffyData))))
  Try(fit$genes <- genelist)
	# Note that it is difficult to use the limma toptable/topTable functions if you don't have ebayes statistics, so
	# in the case of no replicate arrays (no residual degrees of freedom) we will just do our own sorting.

  Try(if(ebayesAvailable==FALSE)
  {
    Try(table1 <- data.frame(genelist))
  })

# The 2's in front of toptables mean that they use the drop=FALSE option (even if the user hasn't upgraded limma since the 1.3 BioC release.)
#  Try(table1 <- toptable2(coef=contrast,number=numberOfGenes,fit=fit,eb=eb,genelist=genelist,adjust.method=adjustMethod,sort.by=sortBy))
  Try(if(ebayesAvailable==TRUE)
    Try(table1 <- topTable2(coef=contrast,number=numberOfGenes,fit=fit,genelist=genelist,adjust.method=adjustMethod)))
    Try(nrows <- nrow(table1))
    Try(ncols <- ncol(table1))
    Try(assign("AltSplLimma" , table1, affylmGUIenvironment))
    Try(assign("AltSplLimma.Available" , TRUE, affylmGUIenvironment))
  Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}
################################################################################
"exonTopTableExtract" <- function(){
         #error if no data are loaded
      Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
      if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
      }    
      #########################

     Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
     Try(AltSplLimma.Available <- get("AltSplLimma.Available", env=affylmGUIenvironment))
#     Try(exonAffyData.Available <- get("exonAffyData.Available", env=affylmGUIenvironment))
     Try(spliceIndexData.Available <- get("spliceIndexData.Available", env=affylmGUIenvironment))
     
     if(AltSplLimma.Available & spliceIndexData.Available){
            #assigning midas threshold graphical menu
                 Try(ttGetMidas<-tktoplevel(.affylmGUIglobals$ttMain))
                 Try(tkwm.deiconify(ttGetMidas))
                 Try(tkgrab.set(ttGetMidas))
                 Try(tkfocus(ttGetMidas))
                 Try(tkwm.title(ttGetMidas,"Assigning regularized t-test threshold"))
                 Try(tkgrid(tklabel(ttGetMidas,text="    ")))
                 Try(Midasnum <- "0.05")
                 Try(Local.Midas <- tclVar(init=Midasnum))
                 Try(entry.Midas <-tkentry(ttGetMidas,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.Midas,bg="white"))
                 Try(tkgrid(tklabel(ttGetMidas,text="Please enter a p-value threshold.",font=.affylmGUIglobals$affylmGUIfont2)))
                 Try(tkgrid(entry.Midas))
                 onOK <- function()
                 {
                     Try(Midasnum <- as.numeric(tclvalue(Local.Midas)))
                     Try(assign("Midasnum",Midasnum,affylmGUIenvironment))
                     Try(tclvalue(.affylmGUIglobals$MidasnumTcl) <- Midasnum)
                     Try(tkgrab.release(ttGetMidas));Try(tkdestroy(ttGetMidas));Try(tkfocus(.affylmGUIglobals$ttMain))                        
                 }
                 Try(OK.but <-tkbutton(ttGetMidas,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
                 Try(tkgrid(tklabel(ttGetMidas,text="    ")))
                 Try(tkgrid(OK.but))
                 Try(tkgrid.configure(OK.but))
                 Try(tkgrid(tklabel(ttGetMidas,text="       ")))
                 Try(tkfocus(entry.Midas))
                 Try(tkbind(entry.Midas, "<Return>",onOK))
                 Try(tkbind(ttGetMidas, "<Destroy>", function(){Try(tkgrab.release(ttGetMidas));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
                 Try(tkwait.window(ttGetMidas))
                 Try(tkfocus(.affylmGUIglobals$ttMain))
                                                                   
                 Try(AltSplLimma <- get("AltSplLimma", env=affylmGUIenvironment))
                 Try(spliceIndexData <- get("spliceIndexData", env=affylmGUIenvironment))
                 Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
                 Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
                 Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                 Try(Midasnum <- as.numeric(get("Midasnum", env= affylmGUIenvironment)))
                 #saving the list of exon significant
                 Try(which.exon <- AltSplLimma[which(AltSplLimma[,5] <= Midasnum),1])
                 Try(.saveFiltered(which.exon))

                 Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                 Try(x.exonid <-as.character(x.lib[,3]))
                 Try(x.exonid <- paste(x.lib[,1], x.exonid)) 
                 g.to.e<- function(x){
                        tmp <- as.character(unlist(strsplit(x, " ")))
                        tmp <- paste(tmp[1], tmp[2:length(tmp)], sep=".")
                 }
                 Try(g.e.out <- as.vector(unlist(sapply(x.exonid, g.to.e))))
                 Try(g.e.out <- strsplit(g.e.out, "\\."))
                 Try(g.out <- sapply(g.e.out, function(x) x[1]))
                 Try(e.out <- sapply(g.e.out, function(x) x[2]))
                 Try(g.e.df <- cbind(g.out, e.out))
                 Try(g.e.df.which <- g.e.df[which(g.e.df[,2] %in% which.exon),])
                 Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData)%in% g.e.df.which[,1]),])
                 Try(assign("NormalizedAffyData",NormalizedAffyData,affylmGUIenvironment))

                 Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%featureNames(NormalizedAffyData)),3]) #in the list obtained from NetAffx there are all the probe set ids and I have to subset only those related to the exon library loaded with the data set
                 Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
                 Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
                 Try(exonAffyData <- exonAffyData[which(featureNames(exonAffyData)%in%x.lib.subset),])
                 Try(assign("exonAffyData",exonAffyData,affylmGUIenvironment))
                 Try(spliceIndexData <- spliceIndexData[which(spliceIndexData[,1]%in%x.lib.subset),])
                 Try(assign("spliceIndexData",spliceIndexData,affylmGUIenvironment))
                 
                 Try(info.dataset<-paste("Genes= ", dim(exprs(NormalizedAffyData))[1],"\n",
                                         "Exons= ", dim(exprs(exonAffyData))[1],"\n",
                                         "SI= ",    dim(spliceIndexData)[1],"\n",
                                         "Samples= ", dim(exprs(NormalizedAffyData))[2],"\n",
                                         "Annotation library= ", .annotation(NormalizedAffyData),"\n", sep=""))
                 
                Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
               #######################################################
            
     } else if(AltSplLimma.Available){
            #assigning midas threshold graphical menu
                 Try(ttGetMidas<-tktoplevel(.affylmGUIglobals$ttMain))
                 Try(tkwm.deiconify(ttGetMidas))
                 Try(tkgrab.set(ttGetMidas))
                 Try(tkfocus(ttGetMidas))
                 Try(tkwm.title(ttGetMidas,"Assigning regularized t-test threshold"))
                 Try(tkgrid(tklabel(ttGetMidas,text="    ")))
                 Try(Midasnum <- "0.05")
                 Try(Local.Midas <- tclVar(init=Midasnum))
                 Try(entry.Midas <-tkentry(ttGetMidas,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.Midas,bg="white"))
                 Try(tkgrid(tklabel(ttGetMidas,text="Please enter a p-value threshold.",font=.affylmGUIglobals$affylmGUIfont2)))
                 Try(tkgrid(entry.Midas))
                 onOK <- function()
                 {
                     Try(Midasnum <- as.numeric(tclvalue(Local.Midas)))
                     Try(assign("Midasnum",Midasnum,affylmGUIenvironment))
                     Try(tclvalue(.affylmGUIglobals$MidasnumTcl) <- Midasnum)
                     Try(tkgrab.release(ttGetMidas));Try(tkdestroy(ttGetMidas));Try(tkfocus(.affylmGUIglobals$ttMain))                        
                 }
                 Try(OK.but <-tkbutton(ttGetMidas,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
                 Try(tkgrid(tklabel(ttGetMidas,text="    ")))
                 Try(tkgrid(OK.but))
                 Try(tkgrid.configure(OK.but))
                 Try(tkgrid(tklabel(ttGetMidas,text="       ")))
                 Try(tkfocus(entry.Midas))
                 Try(tkbind(entry.Midas, "<Return>",onOK))
                 Try(tkbind(ttGetMidas, "<Destroy>", function(){Try(tkgrab.release(ttGetMidas));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
                 Try(tkwait.window(ttGetMidas))
                 Try(tkfocus(.affylmGUIglobals$ttMain))
                                                                   
                 Try(AltSplLimma <- get("AltSplLimma", env=affylmGUIenvironment))
                 Try(NormalizedAffyData <- get("NormalizedAffyData", env=affylmGUIenvironment))
                 Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
                 Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                 Try(Midasnum <- as.numeric(get("Midasnum", env= affylmGUIenvironment)))
                 #saving the list of exon significant
                 Try(which.exon <- AltSplLimma[which(AltSplLimma[,5] <= Midasnum),1])
                 Try(.saveFiltered(which.exon))

                 Try(x.lib <- affylmGUIenvironment$exprConsoleLibs$exon.library)
                 Try(x.exonid <-as.character(x.lib[,3]))
                 Try(x.exonid <- paste(x.lib[,1], x.exonid)) 
                 g.to.e<- function(x){
                        tmp <- as.character(unlist(strsplit(x, " ")))
                        tmp <- paste(tmp[1], tmp[2:length(tmp)], sep=".")
                 }
                 Try(g.e.out <- as.vector(unlist(sapply(x.exonid, g.to.e))))
                 Try(g.e.out <- strsplit(g.e.out, "\\."))
                 Try(g.out <- sapply(g.e.out, function(x) x[1]))
                 Try(e.out <- sapply(g.e.out, function(x) x[2]))
                 Try(g.e.df <- cbind(g.out, e.out))
                 Try(g.e.df.which <- g.e.df[which(g.e.df[,2] %in% which.exon),])
                 Try(NormalizedAffyData <- NormalizedAffyData[which(featureNames(NormalizedAffyData)%in% g.e.df.which[,1]),])
                 Try(assign("NormalizedAffyData",NormalizedAffyData,affylmGUIenvironment))

                 Try(x.lib.subset <- x.lib[which(x.lib[,1]%in%featureNames(NormalizedAffyData)),3]) #in the list obtained from NetAffx there are all the probe set ids and I have to subset only those related to the exon library loaded with the data set
                 Try(x.lib.subset <- sapply(x.lib.subset ,function(x){strsplit(x, " ")}))
                 Try(x.lib.subset<-as.vector(unlist(x.lib.subset)))
                 Try(exonAffyData <- exonAffyData[which(featureNames(exonAffyData)%in%x.lib.subset),])
                 Try(assign("exonAffyData",exonAffyData,affylmGUIenvironment))
                 
                 Try(info.dataset<-paste("Genes= ", dim(exprs(NormalizedAffyData))[1],"\n",
                                         "Exons= ", dim(exprs(exonAffyData))[1],"\n",
                                         "SI= \n",
                                         "Samples= ", dim(exprs(NormalizedAffyData))[2],"\n",
                                         "Annotation library= ", .annotation(NormalizedAffyData),"\n", sep=""))
                Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
               #######################################################
    } else {
              Try(tkmessageBox(title="Exons analysis",message="Limma regularized t-test p-values are not available\nYou need to calculate them before using this function.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
				    	 Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
              Try(return())
    } 

}
################################################################################
"genomePlot"  <- function(){
        Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
        #error if no data are loaded
        Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
        if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
       }    
#       require(GenomeGraphs) || stop("\nGenomeGraphs package is missing!\n")
     #selecting the exon-level id
       Try(ttGetProbesetName<-tktoplevel(.affylmGUIglobals$ttMain))
       Try(tkwm.deiconify(ttGetProbesetName))
       Try(tkgrab.set(ttGetProbesetName))
       Try(tkfocus(ttGetProbesetName))
       Try(tkwm.title(ttGetProbesetName,"Exon-level probe set"))
       Try(tkgrid(tklabel(ttGetProbesetName,text="    ")))
       Try(ProbesetNameText <- "")
       Try(Local.ProbesetName <- tclVar(init=ProbesetNameText))
       Try(entry.ProbesetName <-tkentry(ttGetProbesetName,width="10",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.ProbesetName,bg="white"))
       Try(tkgrid(tklabel(ttGetProbesetName,text="Please enter the exon-level probe set which was detected as spliced.",font=.affylmGUIglobals$affylmGUIfont2)))
       Try(tkgrid(entry.ProbesetName))
       onOK <- function()
       {
             Try(ProbesetNameText <- tclvalue(Local.ProbesetName))
             if(nchar(ProbesetNameText)==0)
                      ProbesetNameText <- "Unselected"
             Try(assign("exonProbesetText",ProbesetNameText,affylmGUIenvironment))
             Try(tclvalue(.affylmGUIglobals$ProbesetNameTcl) <- ProbesetNameText)
             Try(tkgrab.release(ttGetProbesetName));Try(tkdestroy(ttGetProbesetName));Try(tkfocus(.affylmGUIglobals$ttMain))
       }
       Try(OK.but <-tkbutton(ttGetProbesetName,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
       Try(tkgrid(tklabel(ttGetProbesetName,text="    ")))
       Try(tkgrid(OK.but))
       Try(tkgrid.configure(OK.but))
       Try(tkgrid(tklabel(ttGetProbesetName,text="       ")))
       Try(tkfocus(entry.ProbesetName))
       Try(tkbind(entry.ProbesetName, "<Return>",onOK))
       Try(tkbind(ttGetProbesetName, "<Destroy>", function(){Try(tkgrab.release(ttGetProbesetName));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
       Try(tkwait.window(ttGetProbesetName))
       Try(tkfocus(.affylmGUIglobals$ttMain))
      
       Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))
       Try(myexon <- get("exonProbesetText",envir=affylmGUIenvironment))
       Try(cat("\nRetrieving gene/exon-level annotations.\n"))
       if(whichLib[[1]][1] == "HuEx"){
          mart <- useMart("ensembl", dataset = "hsapiens_gene_ensembl")

      #    require(HuExExonProbesetLocation) || stop("\nMissing HuExExonProbesetLocation package\n")
          data(HuExExonProbesetLocation)
          crosshybhuex.annotation<- get("HuExExonProbesetLocation",envir=.GlobalEnv)

          Try(gid <- as.character(crosshybhuex.annotation[which(as.character(crosshybhuex.annotation$EPROBESETID)==myexon),6]))
          Try(eg <- .gettingOneEG(gid))
          emblInfo <- getBM(attributes = c('external_gene_id','entrezgene','ensembl_gene_id'), filters = 'entrezgene',  values = eg, mart = mart)
          #position of gene in ensembl db
          gPosition<- getBM(attributes = c("ensembl_gene_id", "chromosome_name", "start_position", "end_position"),  filters = "ensembl_gene_id", values = emblInfo[3], mart = mart)

#obsolete
#		      Try(mbVal <- tkmessageBox(title="Using external exon-level annotation file",
#				    											message="Do you wish to use external exon-level data?\n File should be formatted as indicated in the help file.", icon="question",type="yesnocancel",default="no"
#								    						 )
#		      )
#		      if(tclvalue(mbVal)=="yes"){
#               Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
#               if(!nchar(tempFileName))
#               {
#                  tkfocus(.affylmGUIglobals$ttMain)
#                  return()
#               }
#               eanns <- read.table(tempFileName, header=T, as.is=T)
#          }
#		      if(tclvalue(mbVal)=="cancel"){
#			        Try(tkfocus(.affylmGUIglobals$ttMain))
#              return()
#		      }
#		      if(tclvalue(mbVal)=="no"){
               Try(eanns <- crosshybhuex.annotation[intersect(which(as.character(crosshybhuex.annotation$GPROBESETID)==gid), which(as.character(crosshybhuex.annotation$ANNLEVEL)==whichLib[[1]][2])),])
#          }
        #
        eanns <- eanns[order(eanns$START),]
        min.eanns <- min(as.numeric(eanns$START))
        max.eanns <- max(as.numeric(eanns$STOP))
#obsolete
#        if(min.eanns < gPosition[3] &  max.eanns < gPosition[4]){
#           delta <- gPosition[3] -  min.eanns
#           tmp <- sapply(as.numeric(eanns$START), function(x) x + delta)
#           eanns$START <- tmp
#           tmp <- sapply(as.numeric(eanns$STOP), function(x) x + delta)
#           eanns$STOP <- tmp  
#        }
#        if(min.eanns > gPosition[3] &  max.eanns > gPosition[4]){
#           delta <- min.eanns - gPosition[3]
#           tmp <- sapply(as.numeric(eanns$START), function(x) x - delta)
#           eanns$START <- tmp
#           tmp <- sapply(as.numeric(eanns$STOP), function(x) x - delta)
#           eanns$STOP <- tmp  
#        } 

        Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
        esgnl <- exonAffyData[which(featureNames(exonAffyData) %in% eanns$EPROBESETID),]
        Targets <- get("Targets",envir=affylmGUIenvironment)
        covars <- unique(Targets$Target)
        e1 <- apply(exprs(esgnl)[,which(Targets$Target==covars[1])],1, mean)
        e2 <- apply(exprs(esgnl)[,which(Targets$Target==covars[2])],1, mean)
        meanIntensity <- cbind(e1,e2)
        common.names<- intersect(as.character(eanns[,1]), featureNames(esgnl))
        eanns <- eanns[which(as.character(eanns[,1]) %in% common.names),]
        #correctly ordering the exon probesets on the basis of their position 
        tmp.mat <- matrix(rep(0, dim(meanIntensity)[1] * dim(meanIntensity)[2]), ncol=dim(meanIntensity)[2])
        dimnames(tmp.mat) <- list(common.names, covars)
        for(i in 1: dim(tmp.mat)[1]){
             tmp.mat[i,] <- meanIntensity[which(rownames(meanIntensity) == rownames(tmp.mat)[i]),]
        }

        nProbes <- rep(4, dim(exprs(esgnl))[1])
        cols <- c("black","red")
        mapcols <- rep("dodgerblue2", dim(exprs(esgnl))[1])
        mapcols[which(eanns$EPROBESETID == myexon)] <- "red"
#        affyModel.model <- makeGeneModel(start = as.numeric(eanns[,4]), end = as.numeric(eanns[,5]))
#        affyModel <- makeAnnotationTrack(start = as.numeric(eanns[,4]), end = as.numeric(eanns[,5]), feature = "gene_model", group = as.character(emblInfo[3]), dp = DisplayPars(gene_model = "darkblue"))
        ea1 <- new("ExonArray", intensity=tmp.mat, probeStart=as.numeric(eanns[,4]),
                       probeEnd=as.numeric(eanns[,5]), probeId=as.character(eanns[,1]),
                       nProbes=as.numeric(nProbes),
                       dp = DisplayPars(plotMap=T, color=cols, mapColor = mapcols), displayProbesets=F)
        gr <- makeGene(id = as.character(emblInfo[3]), biomart = mart)
        tr <- makeTranscript(id = as.character(emblInfo[3]), biomart = mart)
        
        #saving plotting info
        mygenelist <- list("exprs" = tmp.mat, "eprobesetLoc"=eanns, "emblInfo"=emblInfo, "gPosition"=gPosition)
        save(mygenelist, file=paste("exprs_genomic_info.",myexon,".rda", sep=""), ascii=T)
        cat("\nExpression and genomics info of the plotted gene are saved in ", paste("exprs_genomic_info.",myexon,".rda", sep=""), "\n")

#obsolete
#        if (gPosition[3] > gPosition[4]) {
#           genomeAxis = new("GenomeAxis", add53=TRUE)
#           mystrand = new("GeneRegion", chromosome = as.character(gPosition[2]), start = as.numeric(gPosition[3]), end = as.numeric(gPosition[4]), strand = "+", biomart = mart)
#        } else {
           genomeAxis = new("GenomeAxis", add35=TRUE)
#           mystrand = new("GeneRegion", chromosome = as.character(gPosition[2]), start = as.numeric(gPosition[3]), end = as.numeric(gPosition[4]), strand = "-", biomart = mart)
#        }
#       gr <- new("GeneRegion", chromosome=sub("chr","",unique(eanns$CHR)), start=min(as.numeric(eanns[,4])), end = max(as.numeric(eanns[,5])), strand = unique(eanns$STRAND), biomart = mart)
#       tr<-new("Transcript",id=unique(gr@ens[,"ensembl_gene_id"]), biomart=mart,dp=DisplayPars(plotId=TRUE))                       
        boxwidth <- 0                       
        rOverlay <- makeRectangleOverlay(start = (as.numeric(eanns[which(eanns$EPROBESETID== myexon),4]) - boxwidth), end = (as.numeric(eanns[which(eanns$EPROBESETID== myexon),5])+ boxwidth), dp = DisplayPars(alpha = 0.2, fill = "olivedrab1"), region=c(3,4))
        gdPlot( list(ea1,genomeAxis, gr,tr), overlay=rOverlay)
#         gdPlot( list(ea1,genomeAxis, gr,tr))
#        gdPlot( list(ea1,genomeAxis,mystrand), minBase = as.numeric(gPosition[3]), maxBase =  as.numeric(gPosition[4]))
       .resize(eanns, mart, ea1, gr, tr)
    }
    if(whichLib[[1]][1] == "MoEx"){
          mart <- useMart("ensembl", dataset = "mmusculus_gene_ensembl")

      #    require(MoExExonProbesetLocation) || stop("\nMissing MoExExonProbesetLocation package\n")
          data(MoExExonProbesetLocation)
          crosshybmoex.annotation<- get("MoExExonProbesetLocation",envir=.GlobalEnv)

          Try(gid <- as.character(crosshybmoex.annotation[which(as.character(crosshybmoex.annotation$EPROBESETID)==myexon),6]))
          Try(eg <- .gettingOneEG(gid))
          emblInfo <- getBM(attributes = c('external_gene_id','entrezgene','ensembl_gene_id'), filters = 'entrezgene',  values = eg, mart = mart)
          #position of gene in ensembl db
          gPosition<- getBM(attributes = c("ensembl_gene_id", "chromosome_name", "start_position", "end_position"),  filters = "ensembl_gene_id", values = emblInfo[3], mart = mart)

#obsolete
#		      Try(mbVal <- tkmessageBox(title="Using external exon-level annotation file",
#				    											message="Do you wish to use external exon-level data?\n File should be formatted as indicated in the help file.", icon="question",type="yesnocancel",default="no"
#								    						 )
#		      )
#		      if(tclvalue(mbVal)=="yes"){
#               Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
#               if(!nchar(tempFileName))
#               {
#                  tkfocus(.affylmGUIglobals$ttMain)
#                  return()
#               }
#               eanns <- read.table(tempFileName, header=T, as.is=T)
#          }
#		      if(tclvalue(mbVal)=="cancel"){
#			        Try(tkfocus(.affylmGUIglobals$ttMain))
#              return()
#		      }
#		      if(tclvalue(mbVal)=="no"){
               Try(eanns <- crosshybmoex.annotation[intersect(which(as.character(crosshybmoex.annotation$GPROBESETID)==gid), which(as.character(crosshybmoex.annotation$ANNLEVEL)==whichLib[[1]][2])),])
#          }
        #
        eanns <- eanns[order(eanns$START),]
        min.eanns <- min(as.numeric(eanns$START))
        max.eanns <- max(as.numeric(eanns$STOP))
#obsolete        
#        if(min.eanns < gPosition[3] &  max.eanns < gPosition[4]){
#           delta <- gPosition[3] -  min.eanns
#           tmp <- sapply(as.numeric(eanns$START), function(x) x + delta)
#           eanns$START <- tmp
#           tmp <- sapply(as.numeric(eanns$STOP), function(x) x + delta)
#           eanns$STOP <- tmp  
#        }
#        if(min.eanns > gPosition[3] &  max.eanns > gPosition[4]){
#           delta <- min.eanns - gPosition[3]
#           tmp <- sapply(as.numeric(eanns$START), function(x) x - delta)
#           eanns$START <- tmp
#           tmp <- sapply(as.numeric(eanns$STOP), function(x) x - delta)
#           eanns$STOP <- tmp  
#        }

        Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
        esgnl <- exonAffyData[which(featureNames(exonAffyData) %in% eanns$EPROBESETID),]
        Targets <- get("Targets",envir=affylmGUIenvironment)
        covars <- unique(Targets$Target)
        e1 <- apply(exprs(esgnl)[,which(Targets$Target==covars[1])],1, mean)
        e2 <- apply(exprs(esgnl)[,which(Targets$Target==covars[2])],1, mean)
        meanIntensity <- cbind(e1,e2)
         common.names<- intersect(as.character(eanns[,1]), featureNames(esgnl))
        eanns <- eanns[which(as.character(eanns[,1]) %in% common.names),]
    #correctly ordering the exon probesets on the basis of their position 
        tmp.mat <- matrix(rep(0, dim(meanIntensity)[1] * dim(meanIntensity)[2]), ncol=dim(meanIntensity)[2])
        dimnames(tmp.mat) <- list(common.names, covars)
        for(i in 1: dim(tmp.mat)[1]){
             tmp.mat[i,] <- meanIntensity[which(rownames(meanIntensity) == rownames(tmp.mat)[i]),]
        }
        
        nProbes <- rep(4, dim(exprs(esgnl))[1])
        cols <- c("black","red")
        mapcols <- rep("dodgerblue2", dim(exprs(esgnl))[1])
        mapcols[which(eanns$EPROBESETID == myexon)] <- "red"
#        affyModel.model <- makeGeneModel(start = as.numeric(eanns[,4]), end = as.numeric(eanns[,5]))
#        affyModel <- makeAnnotationTrack(start = as.numeric(eanns[,4]), end = as.numeric(eanns[,5]), feature = "gene_model", group = as.character(emblInfo[3]), dp = DisplayPars(gene_model = "darkblue"))
        ea1 <- new("ExonArray", intensity=tmp.mat, probeStart=as.numeric(eanns[,4]),
                       probeEnd=as.numeric(eanns[,5]), probeId=as.character(eanns[,1]),
                       nProbes=as.numeric(nProbes),
                       dp = DisplayPars(plotMap=T, color=cols, mapColor = mapcols), displayProbesets=F)
        
        #saving exprs and mapping info
        mygenelist <- list("exprs" = tmp.mat, "eprobesetLoc"=eanns, "emblInfo"=emblInfo, "gPosition"=gPosition)
        save(mygenelist, file=paste("exprs_genomic_info.",myexon,".rda", sep=""), ascii=T)
        cat("\nExpression and genomics info of the plotted gene are saved in ", paste("exprs_genomic_info.",myexon,".rda", sep=""), "\n")

        gr <- makeGene(id = as.character(emblInfo[3]), biomart = mart)
        tr <- makeTranscript(id = as.character(emblInfo[3]), biomart = mart)
#obsolete
#        if (gPosition[3] > gPosition[4]) {
#           genomeAxis = new("GenomeAxis", add53=TRUE)
#           mystrand = new("GeneRegion", chromosome = as.character(gPosition[2]), start = as.numeric(gPosition[3]), end = as.numeric(gPosition[4]), strand = "+", biomart = mart)
#        } else {
           genomeAxis = new("GenomeAxis", add35=TRUE)
#           mystrand = new("GeneRegion", chromosome = as.character(gPosition[2]), start = as.numeric(gPosition[3]), end = as.numeric(gPosition[4]), strand = "-", biomart = mart)
#        }
#       gr <- new("GeneRegion", chromosome=sub("chr","",unique(eanns$CHR)), start=min(as.numeric(eanns[,4])), end = max(as.numeric(eanns[,5])), strand = unique(eanns$STRAND), biomart = mart)
#       tr<-new("Transcript",id=unique(gr@ens[,"ensembl_gene_id"]), biomart=mart,dp=DisplayPars(plotId=TRUE))                       
        boxwidth <- 0                       
        rOverlay <- makeRectangleOverlay(start = (as.numeric(eanns[which(eanns$EPROBESETID== myexon),4]) - boxwidth), end = (as.numeric(eanns[which(eanns$EPROBESETID== myexon),5])+ boxwidth), dp = DisplayPars(alpha = 0.2, fill = "olivedrab1"), region=c(3,4))
        gdPlot( list(ea1,genomeAxis, gr,tr), overlay=rOverlay)
#         gdPlot( list(ea1,genomeAxis, gr,tr))
#        gdPlot( list(ea1,genomeAxis,mystrand), minBase = as.numeric(gPosition[3]), maxBase =  as.numeric(gPosition[4]))
       .resize(eanns, mart, ea1, gr, tr)
    }
    if(whichLib[[1]][1] == "RaEx"){
          mart <- useMart("ensembl", dataset = "rnorvegicus_gene_ensembl")

      #    require(RaExExonProbesetLocation) || stop("\nMissing RaExExonProbesetLocation package\n")
          data(RaExExonProbesetLocation)
          crosshybmoex.annotation<- get("RaExExonProbesetLocation",envir=.GlobalEnv)

          Try(gid <- as.character(crosshybraex.annotation[which(as.character(crosshybraex.annotation$EPROBESETID)==myexon),6]))
          Try(eg <- .gettingOneEG(gid))
          emblInfo <- getBM(attributes = c('external_gene_id','entrezgene','ensembl_gene_id'), filters = 'entrezgene',  values = eg, mart = mart)
          #position of gene in ensembl db
          gPosition<- getBM(attributes = c("ensembl_gene_id", "chromosome_name", "start_position", "end_position"),  filters = "ensembl_gene_id", values = emblInfo[3], mart = mart)

#obsolete
#		      Try(mbVal <- tkmessageBox(title="Using external exon-level annotation file",
#				    											message="Do you wish to use external exon-level data?\n File should be formatted as indicated in the help file.", icon="question",type="yesnocancel",default="no"
#								    						 )
#		      )
#		      if(tclvalue(mbVal)=="yes"){
#               Try(tempFileName <- tclvalue(tkgetOpenFile(filetypes="{{Text Files} {.txt}} {{All files} *}")))
#               if(!nchar(tempFileName))
#               {
#                  tkfocus(.affylmGUIglobals$ttMain)
#                  return()
#               }
#               eanns <- read.table(tempFileName, header=T, as.is=T)
#          }
#		      if(tclvalue(mbVal)=="cancel"){
#			        Try(tkfocus(.affylmGUIglobals$ttMain))
#              return()
#		      }
#		      if(tclvalue(mbVal)=="no"){
               Try(eanns <- crosshybraex.annotation[intersect(which(as.character(crosshybraex.annotation$GPROBESETID)==gid), which(as.character(crosshybraex.annotation$ANNLEVEL)==whichLib[[1]][2])),])
#          }
        #
        eanns <- eanns[order(eanns$START),]
        min.eanns <- min(as.numeric(eanns$START))
        max.eanns <- max(as.numeric(eanns$STOP))
#obsolete
#        if(min.eanns < gPosition[3] &  max.eanns < gPosition[4]){
#           delta <- gPosition[3] -  min.eanns
#           tmp <- sapply(as.numeric(eanns$START), function(x) x + delta)
#           eanns$START <- tmp
#           tmp <- sapply(as.numeric(eanns$STOP), function(x) x + delta)
#           eanns$STOP <- tmp  
#        }
#        if(min.eanns > gPosition[3] &  max.eanns > gPosition[4]){
#           delta <- min.eanns - gPosition[3]
#           tmp <- sapply(as.numeric(eanns$START), function(x) x - delta)
#           eanns$START <- tmp
#           tmp <- sapply(as.numeric(eanns$STOP), function(x) x - delta)
#           eanns$STOP <- tmp  
#        }

        Try(exonAffyData <- get("exonAffyData", env=affylmGUIenvironment))
        esgnl <- exonAffyData[which(featureNames(exonAffyData) %in% as.character(eanns$EPROBESETID)),]
        Targets <- get("Targets",envir=affylmGUIenvironment)
        covars <- unique(Targets$Target)
        e1 <- apply(exprs(esgnl)[,which(Targets$Target==covars[1])],1, mean)
        e2 <- apply(exprs(esgnl)[,which(Targets$Target==covars[2])],1, mean)
        meanIntensity <- cbind(e1,e2)
         common.names<- intersect(as.character(eanns[,1]), featureNames(esgnl))
        eanns <- eanns[which(as.character(eanns[,1]) %in% common.names),]
#correctly ordering the exon probesets on the basis of their position 
        tmp.mat <- matrix(rep(0, dim(meanIntensity)[1] * dim(meanIntensity)[2]), ncol=dim(meanIntensity)[2])
        dimnames(tmp.mat) <- list(common.names, covars)
        for(i in 1: dim(tmp.mat)[1]){
             tmp.mat[i,] <- meanIntensity[which(rownames(meanIntensity) == rownames(tmp.mat)[i]),]
        }
        
        nProbes <- rep(4, dim(exprs(esgnl))[1])
        cols <- c("black","red")
        mapcols <- rep("dodgerblue2", dim(exprs(esgnl))[1])
        mapcols[which(eanns$EPROBESETID == myexon)] <- "red"
#        affyModel.model <- makeGeneModel(start = as.numeric(eanns[,4]), end = as.numeric(eanns[,5]))
#        affyModel <- makeAnnotationTrack(start = as.numeric(eanns[,4]), end = as.numeric(eanns[,5]), feature = "gene_model", group = as.character(emblInfo[3]), dp = DisplayPars(gene_model = "darkblue"))
        ea1 <- new("ExonArray", intensity= tmp.mat, probeStart=as.numeric(eanns[,4]),
                       probeEnd=as.numeric(eanns[,5]), probeId=as.character(eanns[,1]),
                       nProbes=as.numeric(nProbes),
                       dp = DisplayPars(plotMap=T, color=cols, mapColor = mapcols), displayProbesets=F)
                       
        #saving exprs and mapping info
        mygenelist <- list("exprs" = tmp.mat, "eprobesetLoc"=eanns, "emblInfo"=emblInfo, "gPosition"=gPosition)
        save(mygenelist, file=paste("exprs_genomic_info.",myexon,".rda", sep=""), ascii=T)
        cat("\nExpression and genomics info of the plotted gene are saved in ", paste("exprs_genomic_info.",myexon,".rda", sep=""), "\n")

        gr <- makeGene(id = as.character(emblInfo[3]), biomart = mart)
        tr <- makeTranscript(id = as.character(emblInfo[3]), biomart = mart)
#obsolete
#        if (gPosition[3] > gPosition[4]) {
#           genomeAxis = new("GenomeAxis", add53=TRUE)
#           mystrand = new("GeneRegion", chromosome = as.character(gPosition[2]), start = as.numeric(gPosition[3]), end = as.numeric(gPosition[4]), strand = "+", biomart = mart)
#        } else {
           genomeAxis = new("GenomeAxis", add35=TRUE)
#           mystrand = new("GeneRegion", chromosome = as.character(gPosition[2]), start = as.numeric(gPosition[3]), end = as.numeric(gPosition[4]), strand = "-", biomart = mart)
#        }
#       gr <- new("GeneRegion", chromosome=sub("chr","",unique(eanns$CHR)), start=min(as.numeric(eanns[,4])), end = max(as.numeric(eanns[,5])), strand = unique(eanns$STRAND), biomart = mart)
#       tr<-new("Transcript",id=unique(gr@ens[,"ensembl_gene_id"]), biomart=mart,dp=DisplayPars(plotId=TRUE))                       
        boxwidth <- 0                       
        rOverlay <- makeRectangleOverlay(start = (as.numeric(eanns[which(eanns$EPROBESETID== myexon),4]) - boxwidth), end = (as.numeric(eanns[which(eanns$EPROBESETID== myexon),5])+ boxwidth), dp = DisplayPars(alpha = 0.2, fill = "olivedrab1"), region=c(3,4))
        gdPlot( list(ea1,genomeAxis, gr,tr), overlay=rOverlay)
#         gdPlot( list(ea1,genomeAxis, gr,tr))
#        gdPlot( list(ea1,genomeAxis,mystrand), minBase = as.numeric(gPosition[3]), maxBase =  as.numeric(gPosition[4]))
       .resize(eanns, mart, ea1, gr, tr)
    }


    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
 }
 .resize <- function(eanns, mart, ea1, gr, tr){
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
    Try(myexon <- get("exonProbesetText",envir=affylmGUIenvironment))
    Try(mbVal <- tkmessageBox(title="Repositioning of exon location box",
				    											message="Do you wish to move the box locating the exon-level probeset?", icon="question",type="yesno",default="no"
								    						 )
		)
		if(tclvalue(mbVal)=="yes"){
       #selecting the resizing boxwidth
       Try(ttGetboxwidth<-tktoplevel(.affylmGUIglobals$ttMain))
       Try(tkwm.deiconify(ttGetboxwidth))
       Try(tkgrab.set(ttGetboxwidth))
       Try(tkfocus(ttGetboxwidth))
       Try(tkwm.title(ttGetboxwidth,"Resizing box width"))
       Try(tkgrid(tklabel(ttGetboxwidth,text="    ")))
       Try(boxwidth <- "500")
       Try(Local.boxwidth <- tclVar(init=boxwidth))
       Try(entry.boxwidth <-tkentry(ttGetboxwidth,width="10",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.boxwidth,bg="white"))
       Try(tkgrid(tklabel(ttGetboxwidth,text="Please enter the value to move the initial position of the box \ndefining the position of the spliced exon-level probeset.",font=.affylmGUIglobals$affylmGUIfont2)))
       Try(tkgrid(entry.boxwidth))
       onOK <- function()
       {
             Try(boxwidth <- tclvalue(Local.boxwidth))
             if(nchar(boxwidth)==0)
                      boxwidth <- "0"
             Try(assign("boxwidth",boxwidth,affylmGUIenvironment))
             Try(tclvalue(.affylmGUIglobals$boxwidthTcl) <- boxwidth)
             Try(tkgrab.release(ttGetboxwidth));Try(tkdestroy(ttGetboxwidth));Try(tkfocus(.affylmGUIglobals$ttMain))
       }
       Try(OK.but <-tkbutton(ttGetboxwidth,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
       Try(tkgrid(tklabel(ttGetboxwidth,text="    ")))
       Try(tkgrid(OK.but))
       Try(tkgrid.configure(OK.but))
       Try(tkgrid(tklabel(ttGetboxwidth,text="       ")))
       Try(tkfocus(entry.boxwidth))
       Try(tkbind(entry.boxwidth, "<Return>",onOK))
       Try(tkbind(ttGetboxwidth, "<Destroy>", function(){Try(tkgrab.release(ttGetboxwidth));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
       Try(tkwait.window(ttGetboxwidth))
       Try(tkfocus(.affylmGUIglobals$ttMain))
       Try(boxwidth <- as.numeric(get("boxwidth",envir=affylmGUIenvironment)))
       Try(xbVal <- tkmessageBox(title="Repositioning of exon location box",
				    											message="Where, do you wish to move the box?\nYes: upstream\nNo: downstream", icon="question",type="yesno",default="no"
								    						 )
		  )
	    if(tclvalue(xbVal)=="yes"){
           rOverlay <- makeRectangleOverlay(start = (as.numeric(eanns[which(eanns$EPROBESETID== myexon),4]) - boxwidth), end = as.numeric(eanns[which(eanns$EPROBESETID== myexon),5]), dp = DisplayPars(alpha = 0.2, fill = "olivedrab1"))
           gdPlot( list(ea1,gr,tr), overlay=rOverlay)
	    }
	    if(tclvalue(xbVal)=="no"){
           rOverlay <- makeRectangleOverlay(start = as.numeric(eanns[which(eanns$EPROBESETID== myexon),4]), end = (as.numeric(eanns[which(eanns$EPROBESETID== myexon),5]) + boxwidth), dp = DisplayPars(alpha = 0.2, fill = "olivedrab1"))
           gdPlot( list(ea1,gr,tr), overlay=rOverlay)
	    }

   }
	 if(tclvalue(mbVal)=="no"){
			    Try(tkfocus(.affylmGUIglobals$ttMain))
			    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
			    Try(return())
	}
	.resize(eanns, mart, ea1, gr, tr)
	Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
 }
 
 .gettingOneEG <- function(gid){
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
#    require(annotate, quietly = TRUE) || stop("\nneed data package: annotate\n")
    Try(whichLib <- get("whichLib", envir = affylmGUIenvironment))
    Try(if (whichLib[[1]][1] == "HuEx") {
        Try(annlibname <- system.file("affylibs/huex.annotation.rda",package="oneChannelGUI"))
        Try(load(annlibname))
   #     Try(require(org.Hs.eg.db, quietly = TRUE) || stop("\nneed data package: org.Hs.eg.db\n"))
        Try(lib <- "org.Hs.eg.db")
        Try(myacc <- as.character(huex.annotation$ACC[which(huex.annotation$PROBESETID%in%gid)]))
        Try(lltoacc <- as.character(unlist(lookUp(as.character(myacc), lib, "ACCNUM2EG"))))
    })
    Try(if (whichLib[[1]][1] == "MoEx") {
        Try(annlibname <- system.file("affylibs/moex.annotation.rda",package="oneChannelGUI"))
        Try(load(annlibname))
    #    Try(require(org.Mm.eg.db, quietly = TRUE) || stop("\nneed data package: org.Mm.eg.db\n"))
        Try(lib <- "org.Mm.eg.db")
        Try(myacc <- as.character(moex.annotation$ACC[which(moex.annotation$PROBESETID%in%gid)]))
        Try(lltoacc <- as.character(unlist(lookUp(as.character(myacc), lib, "ACCNUM2EG"))))
    })
    Try(if (whichLib[[1]][1] == "RaEx") {
        Try(annlibname <- system.file("affylibs/raex.annotation.rda",package="oneChannelGUI"))
        Try(load(annlibname))
     #   Try(require(org.Rn.eg.db, quietly = TRUE) || stop("\nneed data package: org.Rn.eg.db\n"))
        Try(lib <- "org.Rn.eg.db")
        Try(myacc <- as.character(raex.annotation$ACC[which(raex.annotation$PROBESETID%in%gid)]))
        Try(lltoacc <- as.character(unlist(lookUp(as.character(myacc), lib, "ACCNUM2EG"))))
   })
    Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
    return(lltoacc)
 }
################################################################################
"retrievePSRseq1gid" <- function(){
        Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
        #error if no data are loaded
        Try(whichArrayPlatform <- get("whichArrayPlatform",envir=affylmGUIenvironment))
        if(whichArrayPlatform ==""){
              Try(tkmessageBox(title="Exons analysis",message="No arrays have been loaded.	Please try New or Open from the File menu.",type="ok",icon="error"))
				    	Try(tkfocus(.affylmGUIglobals$ttMain))
              Try(return())
       }    
     #selecting the gene-level id
       Try(ttGetProbesetName<-tktoplevel(.affylmGUIglobals$ttMain))
       Try(tkwm.deiconify(ttGetProbesetName))
       Try(tkgrab.set(ttGetProbesetName))
       Try(tkfocus(ttGetProbesetName))
       Try(tkwm.title(ttGetProbesetName,"Gene-level probe set"))
       Try(tkgrid(tklabel(ttGetProbesetName,text="    ")))
       Try(ProbesetNameText <- "")
       Try(Local.ProbesetName <- tclVar(init=ProbesetNameText))
       Try(entry.ProbesetName <-tkentry(ttGetProbesetName,width="10",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.ProbesetName,bg="white"))
       Try(tkgrid(tklabel(ttGetProbesetName,text="Please enter the gene-level probe set to extract \nexon-level Probeset Selection Regions (PSR).",font=.affylmGUIglobals$affylmGUIfont2)))
       Try(tkgrid(entry.ProbesetName))
       onOK <- function()
       {
             Try(ProbesetNameText <- tclvalue(Local.ProbesetName))
             if(nchar(ProbesetNameText)==0)
                      ProbesetNameText <- "Unselected"
             Try(assign("geneProbesetText",ProbesetNameText,affylmGUIenvironment))
             Try(tclvalue(.affylmGUIglobals$ProbesetNameTcl) <- ProbesetNameText)
             Try(tkgrab.release(ttGetProbesetName));Try(tkdestroy(ttGetProbesetName));Try(tkfocus(.affylmGUIglobals$ttMain))
       }
       Try(OK.but <-tkbutton(ttGetProbesetName,text="   OK   ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
       Try(tkgrid(tklabel(ttGetProbesetName,text="    ")))
       Try(tkgrid(OK.but))
       Try(tkgrid.configure(OK.but))
       Try(tkgrid(tklabel(ttGetProbesetName,text="       ")))
       Try(tkfocus(entry.ProbesetName))
       Try(tkbind(entry.ProbesetName, "<Return>",onOK))
       Try(tkbind(ttGetProbesetName, "<Destroy>", function(){Try(tkgrab.release(ttGetProbesetName));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
       Try(tkwait.window(ttGetProbesetName))
       Try(tkfocus(.affylmGUIglobals$ttMain))
       Try(whichLib <- get("whichLib",envir=affylmGUIenvironment))
       Try(exprConsoleLibs <- get("exprConsoleLibs", env=affylmGUIenvironment))
       Try(mygene <- get("geneProbesetText",envir=affylmGUIenvironment))
       Try(eprobesetid <- as.vector(unlist(strsplit(exprConsoleLibs$exon.library$"probeset_list"[
                            which(as.character(exprConsoleLibs$exon.library$"probeset_id")==
                            as.character(mygene))], split=" "))))
    Try(cat("\nRetrieving e-level target sequences from RRE database\n"))
    #retrieving from RRE the target sequences for EPROBESETID
    #defining a temporary file tu save the exon-level target sequences downloaded by RRE
    tempSeq <- tempfile(pattern = "RRE", tmpdir = "")
    tempSeq <- sub( "\\\\","",tempSeq)
    tempSeq <- sub( "/","",tempSeq)
    workingDir <- getwd()
    workingDir <- sub( "/$","",workingDir)  
    tempSeq <- paste(workingDir, "/", tempSeq, ".fa", sep="")
                            
    if(length(eprobesetid) <= 1000){
        Try(query1 <- "http://www6.unito.it/RRE/Query/probeSet.php?glist=")
        Try(query2 <- paste(eprobesetid, collapse=","))
        if(whichLib[[1]][1] =="HuEx"){
           Try(query3 <- "&organism=Human&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        if(whichLib[[1]][1] =="MoEx"){
           Try(query3 <- "&organism=Mouse&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        if(whichLib[[1]][1] =="RaEx"){
           Try(query3 <- "&organism=Rat&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
        }
        Try(query.all <- paste(query1, query2, query3, collapse=""))
        Try(query.all <- gsub(" ", "", query.all))
        Try(download.file(query.all, tempSeq, mode="w"))
    } else{
      Try(steps <- seq(1, length(eprobesetid), by=1000))
      Try(stepsi <- steps)
      Try(stepsj <- c(steps[2:length(steps)] - 1, length(eprobesetid)))
      Try(query1 <- "http://www6.unito.it/RRE/Query/probeSet.php?glist=")
      if(whichLib[[1]][1] =="HuEx"){
              Try(query3 <- "&organism=Human&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      if(whichLib[[1]][1] =="MoEx"){
              Try(query3 <- "&organism=Mouse&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      if(whichLib[[1]][1] =="RaEx"){
              Try(query3 <- "&organism=Rat&sep=,&Start=no&Stop=no,&style=fastaAffymetrix")
      }
      for(i in 1:length(stepsi)){
       #       Try(require(stats))
              Try(for(n in 1:50) mad(runif(100000)))#to wait a bit 
              Try(query2 <- paste(eprobesetid[stepsi[i]:stepsj[i]], collapse=","))
              Try(query.all <- paste(query1, query2, query3, collapse=""))
              Try(query.all <- gsub(" ", "", query.all))
              Try(download.file(query.all, tempSeq, mode="a"))
      }
   }
   #see the file
   Try(readORnot <- tclvalue(tkmessageBox(title="Retrieving PSR",message=paste("File", tempSeq, "contains Probe Selection Regions of the exon-level probesets.\nDoyou want to see it?", sep=" "),type="yesno",icon="question")))
   if (readORnot=="yes"){
     ttToptableTable <- tktoplevel(.affylmGUIglobals$ttMain)
     tkwm.title(ttToptableTable,"Selected PSR")
     xscr <-tkscrollbar(ttToptableTable, repeatinterval=5,orient="horizontal", command=function(...)tkxview(txt,...))
     scr <- tkscrollbar(ttToptableTable, repeatinterval=5, command=function(...)tkyview(txt,...))
     txt <- tktext(ttToptableTable, bg="white", font="courier",xscrollcommand=function(...)tkset(xscr,...), yscrollcommand=function(...)tkset(scr,...),wrap="none",width=100)
     tkpack(scr, side="right", fill="y")
     tkpack(xscr, side="bottom", fill="x")
     tkpack(txt, side="left", fill="both", expand="yes")

     chn <- tclvalue(tclopen(tempSeq))
     tkinsert(txt, "end", tclvalue(tclread( chn)))
     tclclose( chn)
     tkconfigure(txt, state="disabled")
     tkmark.set(txt,"insert","0.0")
     tkfocus(txt)
                    
     topMenu2 <- tkmenu(ttToptableTable)
     tkconfigure(ttToptableTable, menu=topMenu2)
     fileMenu2 <- tkmenu(topMenu2, tearoff=FALSE)
     tkadd(fileMenu2, "command", label="Close", command=function() tkdestroy(ttToptableTable)) # ) # ,font=affylmGUIfontMenu)
     tkadd(topMenu2, "cascade", label="File", menu=fileMenu2) # ,font=affylmGUIfontMenu)
   } else {
         Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
         Try(return())
   }            
}



################################################################################

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.