# HG changeset patch
# User devteam
# Date 1406561426 14400
# Node ID 542c4323ed8304e2d09395234a9d2399051743ef
Imported from capsule None
diff -r 000000000000 -r 542c4323ed83 plot_from_lda.xml
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/plot_from_lda.xml Mon Jul 28 11:30:26 2014 -0400
@@ -0,0 +1,262 @@
+
+ on "Perform LDA" output
+
+ R
+
+
+ r_wrapper.sh $script_file
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+ rm(list = objects() )
+
+ ############# FORMAT X DATA #########################
+ format<-function(data) {
+ ind=NULL
+ for(i in 1 : ncol(data)){
+ if (is.na(data[nrow(data),i])) {
+ ind<-c(ind,i)
+ }
+ }
+ #print(is.null(ind))
+ if (!is.null(ind)) {
+ data<-data[,-c(ind)]
+ }
+
+ data
+ }
+
+ ########GET RESPONSES ###############################
+ get_resp<- function(data) {
+ resp1<-as.vector(data[,ncol(data)])
+ resp=numeric(length(resp1))
+ for (i in 1:length(resp1)) {
+ if (resp1[i]=="Control ") {
+ resp[i] = 0
+ }
+ if (resp1[i]=="XLMR ") {
+ resp[i] = 1
+ }
+ }
+ return(resp)
+ }
+
+ ######## CHARS TO NUMBERS ###########################
+ f_to_numbers<- function(F) {
+ ind<-NULL
+ G<-matrix(0,nrow(F), ncol(F))
+ for (i in 1:nrow(F)) {
+ for (j in 1:ncol(F)) {
+ G[i,j]<-as.integer(F[i,j])
+ }
+ }
+ return(G)
+ }
+
+ ###################NORMALIZING#########################
+ norm <- function(M, a=NULL, b=NULL) {
+ C<-NULL
+ ind<-NULL
+
+ for (i in 1: ncol(M)) {
+ if (sd(M[,i])!=0) {
+ M[,i]<-(M[,i]-mean(M[,i]))/sd(M[,i])
+ }
+ # else {print(mean(M[,i]))}
+ }
+ return(M)
+ }
+
+ ##### LDA DIRECTIONS #################################
+ lda_dec <- function(data, k){
+ priors=numeric(k)
+ grandmean<-numeric(ncol(data)-1)
+ means=matrix(0,k,ncol(data)-1)
+ B = matrix(0, ncol(data)-1, ncol(data)-1)
+ N=nrow(data)
+ for (i in 1:k){
+ priors[i]=sum(data[,1]==i)/N
+ grp=subset(data,data\$group==i)
+ means[i,]=mean(grp[,2:ncol(data)])
+ #print(means[i,])
+ #print(priors[i])
+ #print(priors[i]*means[i,])
+ grandmean = priors[i]*means[i,] + grandmean
+ }
+
+ for (i in 1:k) {
+ B= B + priors[i]*((means[i,]-grandmean)%*%t(means[i,]-grandmean))
+ }
+
+ W = var(data[,2:ncol(data)])
+ svdW = svd(W)
+ inv_sqrtW =solve(svdW\$v %*% diag(sqrt(svdW\$d)) %*% t(svdW\$v))
+ B_star= t(inv_sqrtW)%*%B%*%inv_sqrtW
+ B_star_decomp = svd(B_star)
+ directions = inv_sqrtW%*%B_star_decomp\$v
+ return( list(directions, B_star_decomp\$d) )
+ }
+
+ ################ NAIVE BAYES FOR 1D SIR OR LDA ##############
+ naive_bayes_classifier <- function(resp, tr_data, test_data, k=2, tau) {
+ tr_data=data.frame(resp=resp, dir=tr_data)
+ means=numeric(k)
+ #print(k)
+ cl=numeric(k)
+ predclass=numeric(length(test_data))
+ for (i in 1:k) {
+ grp = subset(tr_data, resp==i)
+ means[i] = mean(grp\$dir)
+ #print(i, means[i])
+ }
+ cutoff = tau*means[1]+(1-tau)*means[2]
+ #print(tau)
+ #print(means)
+ #print(cutoff)
+ if (cutoff>means[1]) {
+ cl[1]=1
+ cl[2]=2
+ }
+ else {
+ cl[1]=2
+ cl[2]=1
+ }
+
+ for (i in 1:length(test_data)) {
+
+ if (test_data[i] <= cutoff) {
+ predclass[i] = cl[1]
+ }
+ else {
+ predclass[i] = cl[2]
+ }
+ }
+ #print(means)
+ #print(mean(means))
+ #X11()
+ #plot(test_data,pch=predclass, col=resp)
+ predclass
+ }
+
+ ################# EXTENDED ERROR RATES #################
+ ext_error_rate <- function(predclass, actualclass,msg=c("you forgot the message"), pr=1) {
+ er=sum(predclass != actualclass)/length(predclass)
+
+ matr<-data.frame(predclass=predclass,actualclass=actualclass)
+ escapes = subset(matr, actualclass==1)
+ subjects = subset(matr, actualclass==2)
+ er_esc=sum(escapes\$predclass != escapes\$actualclass)/length(escapes\$predclass)
+ er_subj=sum(subjects\$predclass != subjects\$actualclass)/length(subjects\$predclass)
+
+ if (pr==1) {
+ # print(paste(c(msg, 'overall : ', (1-er)*100, "%."),collapse=" "))
+ # print(paste(c(msg, 'within escapes : ', (1-er_esc)*100, "%."),collapse=" "))
+ # print(paste(c(msg, 'within subjects: ', (1-er_subj)*100, "%."),collapse=" "))
+ }
+ return(c((1-er)*100, (1-er_esc)*100, (1-er_subj)*100))
+ }
+
+ ## Main Function ##
+
+ files_alias<-c("${my_title}")
+ tau=seq(0,1,by=0.005)
+ nfiles=1
+ f = c("${input}")
+
+ rez_ext<-list()
+ for (i in 1:nfiles) {
+ rez_ext[[i]]<-dget(paste(f[i], sep="",collapse=""))
+ }
+
+ tau<-tau[1:(length(tau)-1)]
+ for (i in 1:nfiles) {
+ rez_ext[[i]]<-rez_ext[[i]][,1:(length(tau)-1)]
+ }
+
+ ######## OPTIMAIL TAU ###########################
+
+ #rez_ext
+
+ rate<-c("Optimal tau","Tr total", "Tr Y", "Tr X")
+
+ m_tr<-numeric(nfiles)
+ m_xp22<-numeric(nfiles)
+ m_x<-numeric(nfiles)
+
+ for (i in 1:nfiles) {
+ r<-rez_ext[[i]]
+ #tr
+ # rate<-rbind(rate, c(files_alias[i]," "," "," ") )
+ mm<-which((r[3,])==max(r[3,]))
+
+ m_tr[i]<-mm[1]
+ rate<-rbind(rate,c(tau[m_tr[i]],r[,m_tr[i]]))
+ }
+ print(rate)
+
+ pdf(file= paste("${pdf_output}"))
+
+ plot(rez_ext[[i]][2,]~rez_ext[[i]][3,], xlim=c(0,100), ylim=c(0,100), xlab="${X_axis} [1-FP(False Positive)]", ylab="${Y_axis} [1-FP(False Positive)]", type="l", lty=1, col="blue", xaxt='n', yaxt='n')
+ for (i in 1:nfiles) {
+ lines(rez_ext[[i]][2,]~rez_ext[[i]][3,], xlab="${X_axis} [1-FP(False Positive)]", ylab="${Y_axis} [1-FP(False Positive)]", type="l", lty=1, col=i)
+ # pt=c(r,)
+ points(x=rez_ext[[i]][3,m_tr[i]],y=rez_ext[[i]][2,m_tr[i]], pch=16, col=i)
+ }
+
+
+ title(main="${my_title}", adj=0, cex.main=1.1)
+ axis(2, at=c(0,20,40,60,80,100), labels=c('0','20','40','60','80','100%'))
+ axis(1, at=c(0,20,40,60,80,100), labels=c('0','20','40','60','80','100%'))
+
+ #leg=c("10 kb","50 kb","100 kb")
+ #legend("bottomleft",legend=leg , col=c(1,2,3), lty=c(1,1,1))
+
+ #dev.off()
+
+
+
+
+
+
+.. class:: infomark
+
+**What it does**
+
+This tool generates a Receiver Operating Characteristic (ROC) plot that shows LDA classification success rates for different values of the tuning parameter tau as Figure 3 in Carrel et al., 2006 (PMID: 17009873).
+
+*Carrel L, Park C, Tyekucheva S, Dunn J, Chiaromonte F, et al. (2006) Genomic Environment Predicts Expression Patterns on the Human Inactive X Chromosome. PLoS Genet 2(9): e151. doi:10.1371/journal.pgen.0020151*
+
+-----
+
+.. class:: warningmark
+
+**Note**
+
+- Output from "Perform LDA" tool is used as input file for this tool.
+
+
+
+
+
+
diff -r 000000000000 -r 542c4323ed83 r_wrapper.sh
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/r_wrapper.sh Mon Jul 28 11:30:26 2014 -0400
@@ -0,0 +1,23 @@
+#!/bin/sh
+
+### Run R providing the R script in $1 as standard input and passing
+### the remaining arguments on the command line
+
+# Function that writes a message to stderr and exits
+fail()
+{
+ echo "$@" >&2
+ exit 1
+}
+
+# Ensure R executable is found
+which R > /dev/null || fail "'R' is required by this tool but was not found on path"
+
+# Extract first argument
+infile=$1; shift
+
+# Ensure the file exists
+test -f $infile || fail "R input file '$infile' does not exist"
+
+# Invoke R passing file named by first argument to stdin
+R --vanilla --slave $* < $infile
diff -r 000000000000 -r 542c4323ed83 test-data/lda_analy_output.txt
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/test-data/lda_analy_output.txt Mon Jul 28 11:30:26 2014 -0400
@@ -0,0 +1,134 @@
+structure(c(37.9310344827586, 23.6363636363636, 62.5, 37.9310344827586,
+23.6363636363636, 62.5, 37.9310344827586, 23.6363636363636, 62.5,
+37.9310344827586, 23.6363636363636, 62.5, 37.9310344827586, 23.6363636363636,
+62.5, 37.9310344827586, 23.6363636363636, 62.5, 37.9310344827586,
+23.6363636363636, 62.5, 37.9310344827586, 23.6363636363636, 62.5,
+37.9310344827586, 23.6363636363636, 62.5, 37.9310344827586, 23.6363636363636,
+62.5, 37.9310344827586, 23.6363636363636, 62.5, 37.9310344827586,
+23.6363636363636, 62.5, 37.9310344827586, 23.6363636363636, 62.5,
+37.9310344827586, 23.6363636363636, 62.5, 37.9310344827586, 23.6363636363636,
+62.5, 37.9310344827586, 23.6363636363636, 62.5, 37.9310344827586,
+23.6363636363636, 62.5, 37.9310344827586, 23.6363636363636, 62.5,
+37.9310344827586, 23.6363636363636, 62.5, 37.9310344827586, 23.6363636363636,
+62.5, 37.9310344827586, 23.6363636363636, 62.5, 39.0804597701149,
+23.6363636363636, 65.625, 39.0804597701149, 23.6363636363636,
+65.625, 39.0804597701149, 23.6363636363636, 65.625, 39.0804597701149,
+23.6363636363636, 65.625, 39.0804597701149, 23.6363636363636,
+65.625, 39.0804597701149, 23.6363636363636, 65.625, 39.0804597701149,
+23.6363636363636, 65.625, 39.0804597701149, 23.6363636363636,
+65.625, 39.0804597701149, 23.6363636363636, 65.625, 39.0804597701149,
+23.6363636363636, 65.625, 39.0804597701149, 23.6363636363636,
+65.625, 39.0804597701149, 23.6363636363636, 65.625, 39.0804597701149,
+23.6363636363636, 65.625, 39.0804597701149, 23.6363636363636,
+65.625, 39.0804597701149, 23.6363636363636, 65.625, 39.0804597701149,
+23.6363636363636, 65.625, 39.0804597701149, 23.6363636363636,
+65.625, 39.0804597701149, 23.6363636363636, 65.625, 39.0804597701149,
+23.6363636363636, 65.625, 39.0804597701149, 23.6363636363636,
+65.625, 39.0804597701149, 23.6363636363636, 65.625, 39.0804597701149,
+23.6363636363636, 65.625, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 40.2298850574713, 23.6363636363636,
+68.75, 40.2298850574713, 23.6363636363636, 68.75, 40.2298850574713,
+23.6363636363636, 68.75, 39.0804597701149, 21.8181818181818,
+68.75, 39.0804597701149, 21.8181818181818, 68.75, 39.0804597701149,
+21.8181818181818, 68.75, 39.0804597701149, 21.8181818181818,
+68.75, 39.0804597701149, 21.8181818181818, 68.75, 39.0804597701149,
+21.8181818181818, 68.75, 39.0804597701149, 21.8181818181818,
+68.75, 39.0804597701149, 21.8181818181818, 68.75, 39.0804597701149,
+21.8181818181818, 68.75, 40.2298850574713, 21.8181818181818,
+71.875, 40.2298850574713, 21.8181818181818, 71.875, 40.2298850574713,
+21.8181818181818, 71.875, 40.2298850574713, 21.8181818181818,
+71.875, 40.2298850574713, 21.8181818181818, 71.875, 40.2298850574713,
+21.8181818181818, 71.875, 40.2298850574713, 21.8181818181818,
+71.875, 41.3793103448276, 21.8181818181818, 75, 42.5287356321839,
+21.8181818181818, 78.125, 42.5287356321839, 21.8181818181818,
+78.125, 42.5287356321839, 21.8181818181818, 78.125, 42.5287356321839,
+21.8181818181818, 78.125, 42.5287356321839, 21.8181818181818,
+78.125, 42.5287356321839, 21.8181818181818, 78.125, 42.5287356321839,
+21.8181818181818, 78.125, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 43.6781609195402, 21.8181818181818, 81.25, 43.6781609195402,
+21.8181818181818, 81.25, 43.6781609195402, 21.8181818181818,
+81.25, 56.3218390804598, 78.1818181818182, 18.75), .Dim = c(3L,
+201L))
diff -r 000000000000 -r 542c4323ed83 test-data/plot_for_lda_output.pdf
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/test-data/plot_for_lda_output.pdf Mon Jul 28 11:30:26 2014 -0400
@@ -0,0 +1,610 @@
+%PDF-1.4
+%âãÏÓ\r
+1 0 obj
+<<
+/CreationDate (D:20110308105151)
+/ModDate (D:20110308105151)
+/Title (R Graphics Output)
+/Producer (R 2.11.0)
+/Creator (R)
+>>
+endobj
+2 0 obj
+<<
+/Type /Catalog
+/Pages 3 0 R
+>>
+endobj
+5 0 obj
+<<
+/Type /Page
+/Parent 3 0 R
+/Contents 6 0 R
+/Resources 4 0 R
+>>
+endobj
+6 0 obj
+<<
+/Length 7 0 R
+>>
+stream
+1 J 1 j q
+Q q 59.04 73.44 414.72 371.52 re W n
+0.000 0.000 1.000 RG
+0.75 w
+[] 0 d
+1 J
+1 j
+10.00 M
+314.40 168.51 m
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+362.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+S
+Q q
+0.000 0.000 0.000 RG
+0.75 w
+[] 0 d
+1 J
+1 j
+10.00 M
+59.04 73.44 m
+473.76 73.44 l
+473.76 444.96 l
+59.04 444.96 l
+59.04 73.44 l
+S
+Q q
+BT
+0.000 0.000 0.000 rg
+/F2 1 Tf 12.00 0.00 -0.00 12.00 176.67 18.72 Tm [(T) 120 (est Plot2 [1-FP\(F) 50 (alse P) 50 (ositiv) 25 (e\)])] TJ
+ET
+BT
+/F2 1 Tf 0.00 12.00 -12.00 0.00 12.96 169.47 Tm [(T) 120 (est Plot3 [1-FP\(F) 50 (alse P) 50 (ositiv) 25 (e\)])] TJ
+ET
+Q q 59.04 73.44 414.72 371.52 re W n
+0.000 0.000 0.000 RG
+0.75 w
+[] 0 d
+1 J
+1 j
+10.00 M
+314.40 168.51 m
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+314.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+326.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 168.51 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+338.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+350.40 162.25 l
+362.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+374.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+386.40 162.25 l
+S
+0.000 0.000 0.000 rg
+BT
+/F1 1 Tf 0 Tr 7.48 0 0 7.48 383.44 159.66 Tm (l) Tj 0 Tr
+ET
+Q q
+BT
+0.000 0.000 0.000 rg
+/F3 1 Tf 13.00 0.00 -0.00 13.00 59.04 469.81 Tm [(T) 60 (est Plot1)] TJ
+ET
+Q q
+0.000 0.000 0.000 RG
+0.75 w
+[] 0 d
+1 J
+1 j
+10.00 M
+59.04 87.20 m 59.04 431.20 l S
+59.04 87.20 m 51.84 87.20 l S
+59.04 156.00 m 51.84 156.00 l S
+59.04 224.80 m 51.84 224.80 l S
+59.04 293.60 m 51.84 293.60 l S
+59.04 362.40 m 51.84 362.40 l S
+59.04 431.20 m 51.84 431.20 l S
+BT
+0.000 0.000 0.000 rg
+/F2 1 Tf 0.00 12.00 -12.00 0.00 41.76 83.86 Tm (0) Tj
+ET
+BT
+/F2 1 Tf 0.00 12.00 -12.00 0.00 41.76 149.33 Tm (20) Tj
+ET
+BT
+/F2 1 Tf 0.00 12.00 -12.00 0.00 41.76 218.13 Tm (40) Tj
+ET
+BT
+/F2 1 Tf 0.00 12.00 -12.00 0.00 41.76 286.93 Tm (60) Tj
+ET
+BT
+/F2 1 Tf 0.00 12.00 -12.00 0.00 41.76 355.73 Tm (80) Tj
+ET
+BT
+/F2 1 Tf 0.00 12.00 -12.00 0.00 41.76 415.86 Tm (100%) Tj
+ET
+74.40 73.44 m 458.40 73.44 l S
+74.40 73.44 m 74.40 66.24 l S
+151.20 73.44 m 151.20 66.24 l S
+228.00 73.44 m 228.00 66.24 l S
+304.80 73.44 m 304.80 66.24 l S
+381.60 73.44 m 381.60 66.24 l S
+458.40 73.44 m 458.40 66.24 l S
+BT
+/F2 1 Tf 12.00 0.00 -0.00 12.00 71.06 47.52 Tm (0) Tj
+ET
+BT
+/F2 1 Tf 12.00 0.00 -0.00 12.00 144.53 47.52 Tm (20) Tj
+ET
+BT
+/F2 1 Tf 12.00 0.00 -0.00 12.00 221.33 47.52 Tm (40) Tj
+ET
+BT
+/F2 1 Tf 12.00 0.00 -0.00 12.00 298.13 47.52 Tm (60) Tj
+ET
+BT
+/F2 1 Tf 12.00 0.00 -0.00 12.00 374.93 47.52 Tm (80) Tj
+ET
+BT
+/F2 1 Tf 12.00 0.00 -0.00 12.00 443.06 47.52 Tm (100%) Tj
+ET
+Q
+endstream
+endobj
+7 0 obj
+8413
+endobj
+3 0 obj
+<<
+/Type /Pages
+/Kids [
+5 0 R
+]
+/Count 1
+/MediaBox [0 0 504 504]
+>>
+endobj
+4 0 obj
+<<
+/ProcSet [/PDF /Text]
+/Font << /F1 9 0 R /F2 10 0 R /F3 11 0 R >>
+/ExtGState << >>
+>>
+endobj
+8 0 obj
+<<
+/Type /Encoding
+/BaseEncoding /WinAnsiEncoding
+/Differences [ 45/minus 96/quoteleft
+144/dotlessi /grave /acute /circumflex /tilde /macron /breve /dotaccent
+/dieresis /.notdef /ring /cedilla /.notdef /hungarumlaut /ogonek /caron /space]
+>>
+endobj
+9 0 obj
+<<
+/Type /Font
+/Subtype /Type1
+/Name /F1
+/BaseFont /ZapfDingbats
+>>
+endobj
+10 0 obj <<
+/Type /Font
+/Subtype /Type1
+/Name /F2
+/BaseFont /Helvetica
+/Encoding 8 0 R
+>> endobj
+11 0 obj <<
+/Type /Font
+/Subtype /Type1
+/Name /F3
+/BaseFont /Helvetica-Bold
+/Encoding 8 0 R
+>> endobj
+xref
+0 12
+0000000000 65535 f
+0000000021 00000 n
+0000000164 00000 n
+0000008779 00000 n
+0000008862 00000 n
+0000000213 00000 n
+0000000293 00000 n
+0000008759 00000 n
+0000008966 00000 n
+0000009223 00000 n
+0000009306 00000 n
+0000009403 00000 n
+trailer
+<<
+/Size 12
+/Info 1 0 R
+/Root 2 0 R
+>>
+startxref
+9505
+%%EOF
diff -r 000000000000 -r 542c4323ed83 tool_dependencies.xml
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/tool_dependencies.xml Mon Jul 28 11:30:26 2014 -0400
@@ -0,0 +1,6 @@
+
+
+
+
+
+