Nothing
importfusions <- function(){
#Try(require(chimera) || stop("\nchimera library is not installed\n"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
Try(my.dir <- getwd())
#results
Try(tkmessageBox(title="Importing fusion-finder output",message="Select the fusion-finder tool used to detection fusion events",type="ok",icon="info"))
Try(ttGetFilterMethod <- tktoplevel(.affylmGUIglobals$ttMain))
Try(tkwm.deiconify(ttGetFilterMethod))
Try(tkgrab.set(ttGetFilterMethod))
Try(tkfocus(ttGetFilterMethod))
Try(tkwm.title(ttGetFilterMethod,"Fusion import menu"))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" ")))
Try(ttGetFilterMethodTcl <- tclVar("chimerascan"))
Try(rbIQR1 <- tkradiobutton(ttGetFilterMethod,text="ChimeraScan",variable=ttGetFilterMethodTcl,value="chimerascan",font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.9<-tkradiobutton(ttGetFilterMethod,text="FusionMap",variable=ttGetFilterMethodTcl,value="fusionmap",font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.8<-tkradiobutton(ttGetFilterMethod,text="Tophat-Fusion",variable=ttGetFilterMethodTcl,value="tophat-fusion",font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.7<-tkradiobutton(ttGetFilterMethod,text="mapSplice",variable=ttGetFilterMethodTcl,value="mapsplice",font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.6<-tkradiobutton(ttGetFilterMethod,text="FusionHunter",variable=ttGetFilterMethodTcl,value="fusionhunter",font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.5<-tkradiobutton(ttGetFilterMethod,text="FusionFinder",variable=ttGetFilterMethodTcl,value="fusionfinder",font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.4<-tkradiobutton(ttGetFilterMethod,text="deFuse",variable=ttGetFilterMethodTcl,value="defuse",font=.affylmGUIglobals$affylmGUIfont2))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR1))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.9))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.8))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.7))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.6))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.5))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.4))
Try(tkgrid.configure(rbIQR1,rbIQR.9,rbIQR.8,rbIQR.7,rbIQR.6,rbIQR.5, rbIQR.4,columnspan=2,sticky="w"))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),tklabel(ttGetFilterMethod,text=" ")))
Try(ReturnVal <- "")
Try(onCancel <- function() {Try(ReturnVal <<- "");Try(tkgrab.release(ttGetFilterMethod));Try(tkdestroy(ttGetFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})
Try(onOK <- function() {Try(ReturnVal <<- tclvalue(ttGetFilterMethodTcl));Try(tkgrab.release(ttGetFilterMethod));Try(tkdestroy(ttGetFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})
Try(OK.but <- tkbutton(ttGetFilterMethod,text="OK",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
Try(Cancel.but <- tkbutton(ttGetFilterMethod,text="Cancel",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),OK.but,Cancel.but, tklabel(ttGetFilterMethod,text=" ")))
Try(tkgrid.configure(OK.but,sticky="e"))
Try(tkgrid.configure(Cancel.but,sticky="w"))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" ")))
Try(tkbind(ttGetFilterMethod,"<Destroy>",function() {ReturnVal <- "";Try(tkgrab.release(ttGetFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain));}))
Try(tkbind(OK.but, "<Return>",onOK))
Try(tkbind(Cancel.but, "<Return>",onCancel))
Try(tkwait.window(ttGetFilterMethod))
if(ReturnVal==""){
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
Try(return())
}#cancel
Try(tkmessageBox(title="Loading fusion-finder output",message=paste("With the next widget, please select the ",ReturnVal," output file."),type="ok",icon="info"))
Try(fusions.file <- fileBrowser())
if(ReturnVal == "fusionmap"){
Try(raw.fusions <- importFusionData("fusionmap", fusions.file, org="hs"))
}else if(ReturnVal == "chimerascan"){
Try(raw.fusions <- importFusionData("chimerascan", fusions.file))
}else if(ReturnVal == "tophat-fusion"){
Try(raw.fusions <- importFusionData("tophat-fusion", fusions.file))
}else if(ReturnVal == "mapsplice"){
Try(raw.fusions <- importFusionData("mapsplice", fusions.file))
}else if(ReturnVal == "fusionhunter"){
Try(raw.fusions <- importFusionData("mapsplice", fusions.file))
}else if(ReturnVal == "fusionfinder"){
Try(raw.fusions <- importFusionData("mapsplice", fusions.file))
} else if(ReturnVal == "defuse"){
Try(raw.fusions <- importFusionData("defuse", fusions.file))
}
Try(save(raw.fusions, file=paste("raw.fusions_",ReturnVal,".rda",sep="")))
Try(tkmessageBox(title="Saving chimera output",message=paste("Reformatted fusions data are saved in raw.fusions_",ReturnVal,".rda",sep=""),type="ok",icon="info"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}
###############
fusionNS <- function(){
#Try(require(chimera) || stop("\nchimera library is not installed\n"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
Try(tkmessageBox(title="Loading chimera formatted data",message=paste("With the next widget, please select the file chimera reformatted file \nwith the extention .rda"),type="ok",icon="info"))
Try(chimera.file <- fileBrowser())
Try(load(chimera.file))
Try(chimera.filetmp <- as.character(unlist(strsplit(chimera.file, "/"))))
Try(chimera.file <- chimera.filetmp[length(chimera.filetmp)])
Try(chimera.file <- sub(".rda$","", chimera.file))
Try(fusion.names <- fusionName(raw.fusions))
Try(supporting.reads <- supportingReads(raw.fusions))
Try(df.fusion <- cbind(fusion.names, supporting.reads))
Try(df.fusion <- as.data.frame(df.fusion))
Try(names(df.fusion) <- c("fusion.name", "supporting.reads"))
Try(write.table(df.fusion, paste("data_", chimera.file, ".txt",sep=""), sep="\t", row.names=F))
Try(tkmessageBox(title="Saving fusions names and supporting reads number",message=paste("Fusions data are saved in data_",chimera.file,".txt", sep=""),type="ok",icon="info"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}
###############
fusionfilter <- function(){
#Try(require(chimera) || stop("\nchimera library is not installed\n"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
Try(tkmessageBox(title="Loading chimera formatted data",message="With the next widget, please select the file chimera reformatted file \nwith the extention .rda",type="ok",icon="info"))
Try(chimera.file <- fileBrowser())
Try(load(chimera.file))
Try(chimera.filetmp <- as.character(unlist(strsplit(chimera.file, "/"))))
Try(chimera.file <- chimera.filetmp[length(chimera.filetmp)])
Try(chimera.file <- sub(".rda$","", chimera.file))
Try(tkmessageBox(title="Filtering chimera",message="With the next widget. please define the filtering parameters",type="ok",icon="info"))
Try(ttGetFilterMethod <- tktoplevel(.affylmGUIglobals$ttMain))
Try(tkwm.deiconify(ttGetFilterMethod))
Try(tkgrab.set(ttGetFilterMethod))
Try(tkfocus(ttGetFilterMethod))
Try(tkwm.title(ttGetFilterMethod,"fusion.names"))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" ")))
Try(ttGetFilterMethodTcl <- tclVar("chimerascan"))
Try(rbIQR1 <- tkradiobutton(ttGetFilterMethod,text="Fusion name",variable=ttGetFilterMethodTcl,value="fusion.names",font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.9<-tkradiobutton(ttGetFilterMethod,text="Intronic",variable=ttGetFilterMethodTcl,value="intronic",font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.8<-tkradiobutton(ttGetFilterMethod,text="Junction reads number > 0",variable=ttGetFilterMethodTcl,value=1,font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.7<-tkradiobutton(ttGetFilterMethod,text="Junction reads number > 1",variable=ttGetFilterMethodTcl,value=2,font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.6<-tkradiobutton(ttGetFilterMethod,text="Junction reads number > 5",variable=ttGetFilterMethodTcl,value=6,font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.5<-tkradiobutton(ttGetFilterMethod,text="Junction reads number > 10",variable=ttGetFilterMethodTcl,value=11,font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.4<-tkradiobutton(ttGetFilterMethod,text="Junction reads number > 50",variable=ttGetFilterMethodTcl,value=51,font=.affylmGUIglobals$affylmGUIfont2))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR1))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.9))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.8))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.7))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.6))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.5))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.4))
Try(tkgrid.configure(rbIQR1,rbIQR.9,rbIQR.8,rbIQR.7,rbIQR.6,rbIQR.5, rbIQR.4,columnspan=2,sticky="w"))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),tklabel(ttGetFilterMethod,text=" ")))
Try(ReturnVal1 <- "")
Try(onCancel <- function() {Try(ReturnVal1 <<- "");Try(tkgrab.release(ttGetFilterMethod));Try(tkdestroy(ttGetFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})
Try(onOK <- function() {Try(ReturnVal1 <<- tclvalue(ttGetFilterMethodTcl));Try(tkgrab.release(ttGetFilterMethod));Try(tkdestroy(ttGetFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})
Try(OK.but <- tkbutton(ttGetFilterMethod,text="OK",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
Try(Cancel.but <- tkbutton(ttGetFilterMethod,text="Cancel",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),OK.but,Cancel.but, tklabel(ttGetFilterMethod,text=" ")))
Try(tkgrid.configure(OK.but,sticky="e"))
Try(tkgrid.configure(Cancel.but,sticky="w"))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" ")))
Try(tkbind(ttGetFilterMethod,"<Destroy>",function() {ReturnVal1 <- "";Try(tkgrab.release(ttGetFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain));}))
Try(tkbind(OK.but, "<Return>",onOK))
Try(tkbind(Cancel.but, "<Return>",onCancel))
Try(tkwait.window(ttGetFilterMethod))
if(ReturnVal1==""){
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
Try(return())
}#cancel
if(ReturnVal1 == "fusion.names"){
Try(ttgene<-tktoplevel(.affylmGUIglobals$ttMain))
Try(tkwm.deiconify(ttgene))
Try(tkgrab.set(ttgene))
Try(tkfocus(ttgene))
Try(tkwm.title(ttgene,"Gene to be plotted"))
Try(tkgrid(tklabel(ttgene,text=" ")))
Try(geneName<- "")
Try(Local.gene <- tclVar(init=geneName))
Try(entry.gene <-tkentry(ttgene,width="20",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.gene,bg="white"))
Try(tkgrid(tklabel(ttgene,text="Please enter the fusion name.",font=.affylmGUIglobals$affylmGUIfont2)))
Try(tkgrid(entry.gene))
onOK <- function()
{
Try(fusionname <<- as.character(tclvalue(Local.gene)))
Try(tkgrab.release(ttgene));Try(tkdestroy(ttgene));Try(tkfocus(.affylmGUIglobals$ttMain))
}
Try(OK.but <-tkbutton(ttgene,text=" OK ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
Try(tkgrid(tklabel(ttgene,text=" ")))
Try(tkgrid(OK.but))
Try(tkgrid.configure(OK.but))
Try(tkgrid(tklabel(ttgene,text=" ")))
Try(tkfocus(entry.gene))
Try(tkbind(entry.gene, "<Return>",onOK))
Try(tkbind(ttgene, "<Destroy>", function(){Try(tkgrab.release(ttgene));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
Try(tkwait.window(ttgene))
Try(tkfocus(.affylmGUIglobals$ttMain))
Try(my.fset <- filterList(raw.fusions, type="fusion.names", fusionname))
Try(my.fset <- my.fset[[1]])
Try(fusionname <- sub(":","-", fusionname))
Try(save(my.fset, file=paste("fset_",fusionname,".rda", sep="")))
Try(tkmessageBox(title="Saving a chimera dataset",message=paste("Your chimera is safe as fset_",fusionname,".rda", sep=""),type="ok",icon="info"))
}else if(ReturnVal1 == "intronic"){
Try(raw.fusions <- filterList(raw.fusions, type="intronic"))
Try(save(raw.fusions, file=paste("raw.fusions_filtered_",ReturnVal1,".rda",sep="")))
Try(tkmessageBox(title="Saving chimera output",message=paste(length(raw.fusions)," filtered fusions data are saved in raw.fusions_filtered_",ReturnVal1,".rda",sep=""),type="ok",icon="info"))
}else if(ReturnVal1 == 1){
Try(raw.fusions <- filterList(raw.fusions, type="supporting.reads", 1))
Try(save(raw.fusions, file=paste("raw.fusions_filtered_",ReturnVal1,".rda",sep="")))
Try(tkmessageBox(title="Saving chimera output",message=paste(length(raw.fusions)," filtered fusions data are saved in raw.fusions_filtered_",ReturnVal1,".rda",sep=""),type="ok",icon="info"))
}else if(ReturnVal1 == 2){
Try(raw.fusions <- filterList(raw.fusions, type="supporting.reads", 2))
Try(save(raw.fusions, file=paste("raw.fusions_filtered_",ReturnVal1,".rda",sep="")))
Try(tkmessageBox(title="Saving chimera output",message=paste(length(raw.fusions)," filtered fusions data are saved in raw.fusions_filtered_",ReturnVal1,".rda",sep=""),type="ok",icon="info"))
}else if(ReturnVal1 == 6){
Try(raw.fusions <- filterList(raw.fusions, type="supporting.reads", 6))
Try(save(raw.fusions, file=paste("raw.fusions_filtered_",ReturnVal1,".rda",sep="")))
Try(tkmessageBox(title="Saving chimera output",message=paste(length(raw.fusions)," filtered fusions data are saved in raw.fusions_filtered_",ReturnVal1,".rda",sep=""),type="ok",icon="info"))
}else if(ReturnVal1 == 11){
Try(raw.fusions <- filterList(raw.fusions, type="supporting.reads", 11))
Try(save(raw.fusions, file=paste("raw.fusions_filtered_",ReturnVal1,".rda",sep="")))
Try(tkmessageBox(title="Saving chimera output",message=paste(length(raw.fusions)," filtered fusions data are saved in raw.fusions_filtered_",ReturnVal1,".rda",sep=""),type="ok",icon="info"))
} else if(ReturnVal1 == 51){
Try(raw.fusions <- filterList(raw.fusions, type="supporting.reads", 51))
Try(save(raw.fusions, file=paste("raw.fusions_filtered_",ReturnVal1,".rda",sep="")))
Try(tkmessageBox(title="Saving chimera output",message=paste(length(raw.fusions)," filtered fusions data are saved in raw.fusions_filtered_",ReturnVal1,".rda",sep=""),type="ok",icon="info"))
}
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}
#######
chimeraseq <- function(){
#Try(require(chimera) || stop("\nchimera library is not installed\n"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
Try(tkmessageBox(title="Loading chimera formatted data for one chimera",message="With the next widget, please select the file\nwith the format fset_SYMBOL1-SYMBOL2.rda",type="ok",icon="info"))
Try(chimera.file <- fileBrowser())
Try(load(chimera.file))
if(length(grep("my.fset",ls()))==0){
Try(tkmessageBox(title="Loading chimera formatted data for one chimera",message="The file loaded seems not to have the correct format.\nPlease use filtering function by fusion name to generate \nthe file to be used with this function.",type="ok",icon="error"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
Try(return())
}
Try(chimera.filetmp <- as.character(unlist(strsplit(chimera.file, "/"))))
Try(chimera.file <- chimera.filetmp[length(chimera.filetmp)])
Try(chimera.file <- sub(".rda$","", chimera.file))
Try(my.seq <- chimeraSeqs(my.fset, type="transcripts"))
Try(writeXStringSet(my.seq, paste(chimera.file,".fa", sep="")))
Try(my.fset <- addRNA(my.fset, my.seq))
Try(save(my.fset, file=paste(chimera.file,".rda", sep="")))
Try(print(my.fset))
Try(tkmessageBox(title="Saving a chimera dataset",message=paste("Your chimera is saved as ",chimera.file,".rda","\n","Your chimera seq is saved as ",chimera.file,".fa", sep=""),type="ok",icon="info"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}
######
tophatrun <-function(){
#Try(require(chimera) || stop("\nchimera library is not installed\n"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
Try(tkmessageBox(title="Loading fastq R1",message="With the next widget, please select the fastq file R1 of the pair end",type="ok",icon="info"))
Try(fq1 <- fileBrowser())
Try(tkmessageBox(title="Loading fastq R2",message="With the next widget, please select the fastq file R2 of the pair end",type="ok",icon="info"))
Try(fq2 <- fileBrowser())
Try(tkmessageBox(title="Loading fasta of the chimera",message="With the next widget, please select the fasta of the chimera under analysis",type="ok",icon="info"))
Try(fa <- fileBrowser())
#setting the number of cores involverd in the run
Try(ttCores<-tktoplevel(.affylmGUIglobals$ttMain))
Try(tkwm.deiconify(ttCores))
Try(tkgrab.set(ttCores))
Try(tkfocus(ttCores))
Try(tkwm.title(ttCores,"Defining the between reads distance"))
Try(tkgrid(tklabel(ttCores,text=" ")))
Try(Coresnum <- "1")
Try(Local.Cores <- tclVar(init=Coresnum))
Try(entry.Cores <-tkentry(ttCores,width="4",font=.affylmGUIglobals$affylmGUIfont2,textvariable=Local.Cores,bg="white"))
Try(tkgrid(tklabel(ttCores,text="Please enter number of cores used for the analysis.",font=.affylmGUIglobals$affylmGUIfont2)))
Try(tkgrid(entry.Cores))
onOK <- function()
{
Try(Cores <- as.numeric(tclvalue(Local.Cores)))
Try(assign("Cores", as.numeric(tclvalue(Local.Cores)),affylmGUIenvironment))
Try(assign("Cores.available", TRUE,affylmGUIenvironment))
Try(tkgrab.release(ttCores));Try(tkdestroy(ttCores));Try(tkfocus(.affylmGUIglobals$ttMain))
}
Try(OK.but <-tkbutton(ttCores,text=" OK ",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
Try(tkgrid(tklabel(ttCores,text=" ")))
Try(tkgrid(OK.but))
Try(tkgrid.configure(OK.but))
Try(tkgrid(tklabel(ttCores,text=" ")))
Try(tkfocus(entry.Cores))
Try(tkbind(entry.Cores, "<Return>",onOK))
Try(tkbind(ttCores, "<Destroy>", function(){Try(tkgrab.release(ttCores));Try(tkfocus(.affylmGUIglobals$ttMain));return(0)}))
Try(tkwait.window(ttCores))
Try(tkfocus(.affylmGUIglobals$ttMain))
Try(Coresnum <- get("Cores", env=affylmGUIenvironment))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
Try(tophatRun(input1=fq1, input2=fq2, ebwt=fa, alignment="se", output=getwd(), cores=Coresnum))
}
##########
addga <- function(){
#Try(require(chimera) || stop("\nchimera library is not installed\n"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
Try(tkmessageBox(title="Loading chimera formatted data for one chimera",message="With the next widget, please select the file\nwith the format fset_SYMBOL1-SYMBOL2.rda",type="ok",icon="info"))
Try(chimera.file <- fileBrowser())
Try(load(chimera.file))
if(length(grep("my.fset",ls()))==0){
Try(tkmessageBox(title="Loading chimera formatted data for one chimera",message="The file loaded seems not to have the correct format.\nPlease use filtering function by fusion name to generate \nthe file to be used with this function.",type="ok",icon="error"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
Try(return())
}
Try(chimera.filetmp <- as.character(unlist(strsplit(chimera.file, "/"))))
Try(chimera.file <- chimera.filetmp[length(chimera.filetmp)])
Try(chimera.file <- sub(".rda$","", chimera.file))
Try(tkmessageBox(title="Loading bam file",message="With the next widget, please select the accepted_hits.bam file generated with TopHat",type="ok",icon="info"))
Try(bam <- fileBrowser())
Try(my.fset <- addGA(my.fset, bam))
Try(save(my.fset, file=paste(chimera.file,".rda", sep="")))
Try(print(my.fset))
Try(system("rm accepted_hits.bam_sorted.bam"))
Try(system("rm accepted_hits.bam_sorted.bam.bai"))
Try(tkmessageBox(title="saving coverage data",message="Coverage data have been added to the fusion object.",type="ok",icon="info"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}
############
plotcoverage <- function(){
#Try(require(chimera) || stop("\nchimera library is not installed\n"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
Try(tkmessageBox(title="Loading chimera formatted data for one chimera",message="With the next widget, please select the file\nwith the format fset_SYMBOL1-SYMBOL2.rda",type="ok",icon="info"))
Try(chimera.file <- fileBrowser())
Try(load(chimera.file))
if(length(grep("my.fset",ls()))==0){
Try(tkmessageBox(title="Loading chimera formatted data for one chimera",message="The file loaded seems not to have the correct format.\nPlease use filtering function by fusion name to generate \nthe file to be used with this function.",type="ok",icon="error"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
Try(return())
}
Try(chimera.filetmp <- as.character(unlist(strsplit(chimera.file, "/"))))
Try(chimera.file <- chimera.filetmp[length(chimera.filetmp)])
Try(chimera.file <- sub(".rda$","", chimera.file))
Try(tkmessageBox(title="Plotting chimera",message="With the next widget, please define the plotting parameters",type="ok",icon="info"))
Try(ttGetFilterMethod <- tktoplevel(.affylmGUIglobals$ttMain))
Try(tkwm.deiconify(ttGetFilterMethod))
Try(tkgrab.set(ttGetFilterMethod))
Try(tkfocus(ttGetFilterMethod))
Try(tkwm.title(ttGetFilterMethod,"exons"))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" ")))
Try(ttGetFilterMethodTcl <- tclVar("Plotting coverage options"))
Try(rbIQR1 <- tkradiobutton(ttGetFilterMethod,text="Exons coverage",variable=ttGetFilterMethodTcl,value="exons",font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.9<-tkradiobutton(ttGetFilterMethod,text="Junctions coverage",variable=ttGetFilterMethodTcl,value="junctions",font=.affylmGUIglobals$affylmGUIfont2))
Try(rbIQR.8<-tkradiobutton(ttGetFilterMethod,text="Fusion boundary coverage",variable=ttGetFilterMethodTcl,value="fusion",font=.affylmGUIglobals$affylmGUIfont2))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR1))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),rbIQR.9))
Try(tkgrid.configure(rbIQR1,rbIQR.9,rbIQR.8,columnspan=2,sticky="w"))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),tklabel(ttGetFilterMethod,text=" ")))
Try(ReturnVal2 <- "")
Try(onCancel <- function() {Try(ReturnVal2 <<- "");Try(tkgrab.release(ttGetFilterMethod));Try(tkdestroy(ttGetFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})
Try(onOK <- function() {Try(ReturnVal2 <<- tclvalue(ttGetFilterMethodTcl));Try(tkgrab.release(ttGetFilterMethod));Try(tkdestroy(ttGetFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain))})
Try(OK.but <- tkbutton(ttGetFilterMethod,text="OK",command=onOK,font=.affylmGUIglobals$affylmGUIfont2))
Try(Cancel.but <- tkbutton(ttGetFilterMethod,text="Cancel",command=onCancel,font=.affylmGUIglobals$affylmGUIfont2))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" "),OK.but,Cancel.but, tklabel(ttGetFilterMethod,text=" ")))
Try(tkgrid.configure(OK.but,sticky="e"))
Try(tkgrid.configure(Cancel.but,sticky="w"))
Try(tkgrid(tklabel(ttGetFilterMethod,text=" ")))
Try(tkbind(ttGetFilterMethod,"<Destroy>",function() {ReturnVal2<- "";Try(tkgrab.release(ttGetFilterMethod));Try(tkfocus(.affylmGUIglobals$ttMain));}))
Try(tkbind(OK.but, "<Return>",onOK))
Try(tkbind(Cancel.but, "<Return>",onCancel))
Try(tkwait.window(ttGetFilterMethod))
if(ReturnVal2==""){
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
Try(return())
}#cancel
if(ReturnVal2=="exons"){
Try(plotCoverage(my.fset, plot.type="exons", col.box1="red", col.box2="green", ybox.lim=c(-4,-1)))
}else if(ReturnVal2=="junctions"){
Try(plotCoverage(my.fset, plot.type="junctions", col.box1="red", col.box2="yellow", ybox.lim=c(-4,-1)))
}else if(ReturnVal2=="fusion"){
Try(plotCoverage(my.fset, fusion.only=TRUE, col.box1="red", col.box2="yellow", ybox.lim=c(-4,-1)))
}
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
}
#######
fusionpeptides <- function(){
#Try(require(chimera) || stop("\nchimera library is not installed\n"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="watch"))
Try(tkmessageBox(title="Loading chimera formatted data for one chimera",message="With the next widget, please select the file\nwith the format fset_SYMBOL1-SYMBOL2.rda",type="ok",icon="info"))
Try(chimera.file <- fileBrowser())
Try(load(chimera.file))
if(length(grep("my.fset",ls()))==0){
Try(tkmessageBox(title="Loading chimera formatted data for one chimera",message="The file loaded seems not to have the correct format.\nPlease use filtering function by fusion name to generate \nthe file to be used with this function.",type="ok",icon="error"))
Try(tkconfigure(.affylmGUIglobals$ttMain,cursor="arrow"))
Try(return())
}
Try(chimera.filetmp <- as.character(unlist(strsplit(chimera.file, "/"))))
Try(chimera.file <- chimera.filetmp[length(chimera.filetmp)])
Try(chimera.file <- sub(".rda$","", chimera.file))
Try(fusion.info <- fusionPeptides(my.fset, which.isoform=1, donor.up=50, acceptor.down=50))
Try(save(fusion.info, file=paste(chimera.file,".rda", sep="")))
Try(print(fusion.info))
Try(writeXStringSet(DNAStringSet(fusion.info$transcript1), paste("transcript1_",chimera.file,".fa",sep="")))
Try(writeXStringSet(DNAStringSet(fusion.info$transcript2), paste("transcript2_",chimera.file,".fa",sep="")))
Try(writeXStringSet(AAStringSet(fusion.info$pep1), paste("pep1_",chimera.file,".fa",sep="")))
Try(writeXStringSet(AAStringSet(fusion.info$pep2), paste("pep2_",chimera.file,".fa",sep="")))
Try(writeXStringSet(BStringSet(fusion.info$validation.seq), paste("validation.seq_",chimera.file,".fa",sep="")))
Try(tkmessageBox(title="Saving fusion info",message=paste("Information about the fusion are saved in fusion_info_",chimera.file,".rda\ntranscript,pep,vaidation.seq_",chimera.file,".fa", sep=""),type="ok",icon="info"))
}
Any scripts or data that you put into this service are public.
Add the following code to your website.
For more information on customizing the embed code, read Embedding Snippets.