Repository 'exomedepth'
hg clone https://toolshed.g2.bx.psu.edu/repos/crs4/exomedepth

Changeset 7:45af4a9748cf (2019-11-08)
Previous changeset 6:165732ee5a48 (2018-06-11) Next changeset 8:5d60331757d3 (2020-11-25)
Commit message:
"planemo upload for repository https://github.com/galaxyproject/tools-iuc/tree/master/tools/exomedepth commit 91a0182476a7fc26be7bef1677790518c4e88348"
modified:
exomedepth.R
exomedepth.xml
added:
test-data/CNV_TruSeq_Chr2.bed
test-data/CNV_case_small.bam
test-data/CNV_control_small.bam
removed:
exomedepth-a9701c421408/exomedepth.R
b
diff -r 165732ee5a48 -r 45af4a9748cf exomedepth-a9701c421408/exomedepth.R
--- a/exomedepth-a9701c421408/exomedepth.R Mon Jun 11 09:34:25 2018 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
[
@@ -1,95 +0,0 @@
-# Load ExomeDepth library (without warnings)
-suppressMessages(library(ExomeDepth))
-
-# Import parameters from xml wrapper (args_file)
-args  <- commandArgs(trailingOnly=TRUE)
-param <- read.table(args[1],sep="=", as.is=TRUE)
-
-# Set common parameters
-target      <- param[match("target",param[,1]),2]
-trans_prob  <- as.numeric(param[match("trans_prob",param[,1]),2])
-output      <- param[match("output",param[,1]),2]
-test_vs_ref <- as.logical(param[match("test_vs_ref",param[,1]),2])
-
-# Create symbolic links for multiple bam and bai 
-bam         <- param[param[,1]=="bam",2]
-bam_bai     <- param[param[,1]=="bam_bai",2]
-bam_label   <- param[param[,1]=="bam_label",2]
-bam_label   <- gsub(" ", "_", bam_label)
-
-for(i in 1:length(bam)){
-  stopifnot(file.symlink(bam[i], paste(bam_label[i], "bam", sep=".")))
-  stopifnot(file.symlink(bam_bai[i], paste(bam_label[i], "bam.bai", sep=".")))
-}
-
-# Generate read count data
-BAMFiles <- paste(bam_label, "bam", sep=".")
-sink("/dev/null")
-ExomeCount <- suppressMessages(getBamCounts(bed.file=target, bam.files = BAMFiles))
-sink()
-
-# Convert counts in a data frame
-ExomeCount.dafr <- as(ExomeCount[, colnames(ExomeCount)], 'data.frame')
-
-# Prepare the main matrix of read count data
-ExomeCount.mat <- as.matrix(ExomeCount.dafr[, grep(names(ExomeCount.dafr), pattern='.bam')])
-
-# Remove .bam from sample name
-colnames(ExomeCount.mat) <- gsub(".bam", "", colnames(ExomeCount.mat))
-
-# Set nsamples == 1 if mode is test vs reference, assuming test is sample 1
-nsamples <- ifelse(test_vs_ref, 1, ncol(ExomeCount.mat))
-
-# Loop over samples
-for (i in 1:nsamples){
-
- # Create the aggregate reference set for this sample
- my.choice <- suppressWarnings(suppressMessages(
- select.reference.set(test.counts = ExomeCount.mat[,i],  
-                             reference.counts = subset(ExomeCount.mat, select=-i),  
-                                 bin.length = (ExomeCount.dafr$end - ExomeCount.dafr$start)/1000,
-                                     n.bins.reduced = 10000)))
-
- my.reference.selected <- apply(X = ExomeCount.mat[, my.choice$reference.choice, drop=FALSE],
-                                   MAR = 1,
-                                   FUN = sum)
-                               
- # Now create the ExomeDepth object for the CNVs call
- all.exons<-suppressWarnings(suppressMessages(new('ExomeDepth',
-               test = ExomeCount.mat[,i],
-               reference = my.reference.selected,
-               formula = 'cbind(test,reference)~1')))
-
-
- # Now call the CNVs
- result <- try(all.exons<-suppressMessages(CallCNVs(x=all.exons,
-                            transition.probability = trans_prob,
-                            chromosome = ExomeCount.dafr$space,
-                            start = ExomeCount.dafr$start,
-                            end = ExomeCount.dafr$end,
-                            name = ExomeCount.dafr$names)), silent=T)
-
- # Next if CNVs are not detected
- if (class(result)=="try-error"){
- next
- }
-
- # Compute correlation between ref and test
- my.cor <- cor(all.exons@reference, all.exons@test)
- n.call <- nrow(all.exons@CNV.calls)
-
- # Write results
- my.results <- cbind(all.exons@CNV.calls[,c(7,5,6,3)], 
-               sample=colnames(ExomeCount.mat)[i],
-             corr=my.cor,
-             all.exons@CNV.calls[,c(4,9,12)])
-            
-     # Re-order by chr and position
-     chrOrder<-c(paste("chr",1:22,sep=""),"chrX","chrY","chrM")
-     my.results[,1] <- factor(my.results[,1], levels=chrOrder)
-     my.results <- my.results[order(my.results[,1], my.results[,2], my.results[,3]),]
-    
- write.table(sep='\t', quote=FALSE, file = output,
-             x = my.results,
-        row.names = FALSE, col.names = FALSE, dec=".", append=TRUE)
-}
b
diff -r 165732ee5a48 -r 45af4a9748cf exomedepth.R
--- a/exomedepth.R Mon Jun 11 09:34:25 2018 -0400
+++ b/exomedepth.R Fri Nov 08 13:25:44 2019 -0500
[
@@ -3,8 +3,7 @@
 
 # Import parameters from xml wrapper (args_file)
 args  <- commandArgs(trailingOnly=TRUE)
-eval(parse(text=args[[1]]))
-param <- read.table(mypars,sep="=", as.is=TRUE)
+param <- read.table(args[1],sep="=", as.is=TRUE)
 
 # Set common parameters
 target      <- param[match("target",param[,1]),2]
b
diff -r 165732ee5a48 -r 45af4a9748cf exomedepth.xml
--- a/exomedepth.xml Mon Jun 11 09:34:25 2018 -0400
+++ b/exomedepth.xml Fri Nov 08 13:25:44 2019 -0500
[
@@ -1,31 +1,17 @@
-<tool id="exomedepth" name="ExomeDepth" version="1.0.0">
-  <description>cnv caller</description>
-  <requirements>
-   <requirement type="package" version="1.1.10">r-exomedepth</requirement>
-  </requirements>
-  <command>
-    R CMD BATCH --no-save --no-restore '--args mypars="$args_file"' $__tool_directory__/exomedepth.R
-  </command>
-  <inputs>
-    <param format="bed" name="targetFile" type="data" label="Target regions (BED)">
-      <validator type="unspecified_build" />
-    </param>
-    <param name="test_vs_ref" type="boolean" truevalue="TRUE" falsevalue="FALSE" checked="false" label="Call CNVs using 1st sample as test" help="If checked, the tool will call CNVs in the first sample vs all the others. If unchecked, an all vs all CNV call will be performed" />
-    <repeat name="inputs" title="BAM" min="2" help="Need to add more files? Use controls below.">
-      <param format="bam" name="input" type="data" label="BAM file">
-        <options>
-          <filter type="data_meta" ref="targetFile" key="dbkey"/>
-        </options>
-      </param>
-      <param name="label" type="text" size="30" value="" label="Label" help="Label to use in the output. If not given, the dataset name will be used instead">
-           <validator type="regex" message="Spaces are not allowed">^\S*$</validator>
-      </param>  
-    </repeat>
-    <param name="transition_probability" size="10" type="float" value="0.0001" label="Transition probability" help="Transition probability of the hidden Markov Chain from the normal copy number state to either a deletion or a duplication. The default value (0.0001) expects approximately 20 CNVs genome-wide" />
-  </inputs>
-
-  <configfiles>
-    <configfile name="args_file">target=$targetFile
+<tool id="exomedepth" name="ExomeDepth" version="1.1.0">
+    <description>Calls copy number variants (CNVs) from targeted sequence data</description>
+    <requirements>
+        <requirement type="package" version="1.1.10">r-exomedepth</requirement>
+    </requirements>
+    <version_command><![CDATA[
+echo $(R --version | grep version | grep -v GNU)", ExomeDepth version" $(R --vanilla --slave -e "library(ExomeDepth); cat(sessionInfo()\$otherPkgs\$ExomeDepth\$Version)")
+    ]]></version_command>
+    <command detect_errors="exit_code"><![CDATA[
+    Rscript '${__tool_directory__}/exomedepth.R' '$args_file'
+    ]]></command>
+    <configfiles>
+        <configfile name="args_file"><![CDATA[
+target=$targetFile
 test_vs_ref=$test_vs_ref
 #for $i in $inputs
 bam=${i.input}
@@ -38,13 +24,51 @@
 #end for
 trans_prob=$transition_probability
 output=$output
-</configfile>
-  </configfiles>
-  <outputs>
-    <data format="tabular" name="output" label="${tool.name} on ${on_string}" />
-  </outputs>
-  <help>
-
+        ]]></configfile>
+    </configfiles>
+    <inputs>
+        <param name="targetFile" type="data" format="bed" label="Target regions (BED)">
+            <validator type="unspecified_build" />
+        </param>
+        <param name="test_vs_ref" type="boolean" truevalue="TRUE" falsevalue="FALSE" checked="false" label="Call CNVs using 1st sample as test" help="If checked, the tool will call CNVs in the first sample vs all the others. If unchecked, an all vs all CNV call will be performed" />
+        <repeat name="inputs" title="BAM" min="2" help="Need to add more files? Use controls below.">
+            <param name="input" type="data" format="bam" label="BAM file">
+                <options>
+                    <filter type="data_meta" ref="targetFile" key="dbkey"/>
+                </options>
+            </param>
+            <param name="label" type="text" size="30" value="" label="Label" help="Label to use in the output. If not given, the dataset name will be used instead">
+                <validator type="regex" message="Spaces are not allowed">^\S*$</validator>
+            </param>  
+        </repeat>
+        <param name="transition_probability" size="10" type="float" value="0.0001" label="Transition probability" help="Transition probability of the hidden Markov Chain from the normal copy number state to either a deletion or a duplication. The default value (0.0001) expects approximately 20 CNVs genome-wide" />
+    </inputs>
+    <outputs>
+        <data name="output" format="tabular" label="${tool.name} on ${on_string}" />
+    </outputs>
+    <tests>
+        <test>
+            <param name="targetFile" value="CNV_TruSeq_Chr2.bed" dbkey="hg19" ftype="bed"/>
+            <param name="test_vs_ref" value="True"/>
+            <repeat name="inputs">
+                <param name="input" value="CNV_case_small.bam"/>
+            </repeat>
+            <repeat name="inputs">
+                <param name="input" value="CNV_control_small.bam"/>
+            </repeat>
+            <param name="transition_probability" value="0.5"/>
+            <output name="output">
+                <assert_contents>
+                    <has_text text="chr2" />
+                    <has_text text="97890544" />
+                    <has_text text="97890616" />
+                    <has_text text="deletion" />
+                    <has_text text="CNV_case_small" />
+                </assert_contents>
+            </output>
+        </test>
+    </tests>
+    <help><![CDATA[
 .. class:: warningmark
 
 **Warning about counts for chromosome X**
@@ -92,30 +116,9 @@
 (at least 20 genes, say, but probably more would be useful). Also note that PCR based enrichment studies are often 
 not well suited for this type of read depth analysis. The reason is that as the number of cycles is often set to a high 
 number in order to equalize the representation of each amplicon, which can discard the CNV information.
-
-**License and citation**
-
-This Galaxy tool is Copyright © 2014 `CRS4 Srl.`_ and is released under the `MIT license`_.
-
-.. _CRS4 Srl.: http://www.crs4.it/
-.. _MIT license: http://opensource.org/licenses/MIT
-
-You can use this tool only if you agree to the license terms of: `ExomeDepth`_.
-
-.. _ExomeDepth: http://cran.r-project.org/web/packages/ExomeDepth/
-
-If you use this tool, please cite:
-
-- |Cuccuru2014|_
-- |Plagnol2012|_.
-
-.. |Cuccuru2014| replace:: Cuccuru, G., Orsini, M., Pinna, A., Sbardellati, A., Soranzo, N., Travaglione, A., Uva, P., Zanetti, G., Fotia, G. (2014) Orione, a web-based framework for NGS analysis in microbiology. *Bioinformatics* 30(13), 1928-1929
-.. _Cuccuru2014: http://bioinformatics.oxfordjournals.org/content/30/13/1928
-.. |Plagnol2012| replace:: Plagnol, V., *et al.* (2012) A robust model for read count data in exome sequencing experiments and implications for copy number variant calling. *Bioinformatics* 28(21), 2747-2754
-.. _Plagnol2012: http://bioinformatics.oxfordjournals.org/content/28/21/2747
-  </help>
+    ]]></help>
     <citations>
-    <citation type="doi">10.1093/bioinformatics/btu135</citation>
-    <citation type="doi">10.1093/bioinformatics/bts526</citation>
-  </citations>
+        <citation type="doi">10.1093/bioinformatics/btu135</citation>
+        <citation type="doi">10.1093/bioinformatics/bts526</citation>
+    </citations>
 </tool>
b
diff -r 165732ee5a48 -r 45af4a9748cf test-data/CNV_TruSeq_Chr2.bed
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/test-data/CNV_TruSeq_Chr2.bed Fri Nov 08 13:25:44 2019 -0500
b
b'@@ -0,0 +1,746 @@\n+chr2\t91824709\t91825059\tLOC654342\n+chr2\t91842946\t91843023\tLOC654342\n+chr2\t91843394\t91843528\tLOC654342\n+chr2\t91963368\t91964133\tGGT8P\n+chr2\t91968436\t91970153\tGGT8P\n+chr2\t92129159\t92130494\tFKSG73\n+chr2\t95426675\t95426777\tANKRD20B\n+chr2\t95426875\t95426910\tANKRD20B\n+chr2\t95455916\t95455995\tANKRD20B\n+chr2\t95456835\t95456888\tANKRD20B\n+chr2\t95458058\t95458103\tANKRD20B\n+chr2\t95461541\t95461763\tANKRD20B\n+chr2\t95463672\t95463886\tANKRD20B\n+chr2\t95464479\t95464758\tANKRD20B\n+chr2\t95472086\t95472215\tANKRD20B\n+chr2\t95474216\t95474328\tANKRD20B\n+chr2\t95479136\t95479285\tANKRD20B\n+chr2\t95480827\t95481750\tANKRD20B\n+chr2\t95482918\t95483098\tANKRD20B\n+chr2\t95484506\t95484669\tANKRD20B\n+chr2\t95488749\t95488819\tANKRD20B\n+chr2\t95494751\t95494823\tANKRD20B\n+chr2\t95494915\t95494943\tANKRD20B\n+chr2\t95497752\t95497833\tANKRD20B\n+chr2\t95511110\t95511180\tANKRD20B\n+chr2\t95513762\t95513899\tANKRD20B\n+chr2\t95514946\t95515052\tANKRD20B\n+chr2\t95518947\t95519120\tANKRD20B\n+chr2\t95519283\t95519397\tANKRD20B\n+chr2\t95522712\t95522820\tANKRD20B\n+chr2\t95537232\t95537822\tTEKT4\n+chr2\t95539265\t95539335\tTEKT4\n+chr2\t95539710\t95539853\tTEKT4\n+chr2\t95540521\t95540743\tTEKT4\n+chr2\t95541333\t95541487\tTEKT4\n+chr2\t95542298\t95542568\tTEKT4\n+chr2\t95691479\t95691630\tMAL\n+chr2\t95713704\t95713871\tMAL\n+chr2\t95715326\t95715451\tMAL\n+chr2\t95719126\t95719735\tMAL\n+chr2\t95752953\t95753326\tMRPS5\n+chr2\t95756131\t95756267\tMRPS5\n+chr2\t95766219\t95766281\tMRPS5\n+chr2\t95766582\t95766639\tMRPS5\n+chr2\t95767422\t95767468\tMRPS5\n+chr2\t95770385\t95770475\tMRPS5\n+chr2\t95772168\t95772202\tMRPS5\n+chr2\t95773920\t95774153\tMRPS5\n+chr2\t95775661\t95775786\tMRPS5\n+chr2\t95780811\t95780948\tMRPS5\n+chr2\t95783610\t95783690\tMRPS5\n+chr2\t95787479\t95787754\tMRPS5\n+chr2\t95813400\t95816012\tZNF514\n+chr2\t95818419\t95818514\tZNF514\n+chr2\t95818878\t95819004\tZNF514\n+chr2\t95823096\t95823184\tZNF514\n+chr2\t95824985\t95825263\tZNF514\n+chr2\t95831183\t95831605\tZNF2\n+chr2\t95841933\t95842004\tZNF2\n+chr2\t95843228\t95843354\tZNF2\n+chr2\t95845904\t95846017\tZNF2\n+chr2\t95846848\t95850062\tZNF2\n+chr2\t95940201\t95940577\tPROM2\n+chr2\t95941209\t95941258\tPROM2\n+chr2\t95941678\t95941880\tPROM2\n+chr2\t95941975\t95942095\tPROM2\n+chr2\t95942342\t95942405\tPROM2\n+chr2\t95942720\t95942809\tPROM2\n+chr2\t95943112\t95943314\tPROM2\n+chr2\t95943678\t95943752\tPROM2\n+chr2\t95944469\t95944532\tPROM2\n+chr2\t95944733\t95944892\tPROM2\n+chr2\t95945593\t95945745\tPROM2\n+chr2\t95946990\t95947113\tPROM2\n+chr2\t95947673\t95947764\tPROM2\n+chr2\t95947890\t95947974\tPROM2\n+chr2\t95950717\t95950863\tPROM2\n+chr2\t95951387\t95951458\tPROM2\n+chr2\t95952227\t95952319\tPROM2\n+chr2\t95952552\t95952605\tPROM2\n+chr2\t95952881\t95952961\tPROM2\n+chr2\t95953144\t95953212\tPROM2\n+chr2\t95953959\t95954048\tPROM2\n+chr2\t95954231\t95954337\tPROM2\n+chr2\t95954681\t95954754\tPROM2\n+chr2\t95954972\t95957053\tPROM2\n+chr2\t95963072\t95963201\tKCNIP3\n+chr2\t95976103\t95976268\tKCNIP3\n+chr2\t96012768\t96012870\tKCNIP3\n+chr2\t96040044\t96040168\tKCNIP3\n+chr2\t96040596\t96040665\tKCNIP3\n+chr2\t96040886\t96040956\tKCNIP3\n+chr2\t96047344\t96047451\tKCNIP3\n+chr2\t96048125\t96048229\tKCNIP3\n+chr2\t96048980\t96049042\tKCNIP3\n+chr2\t96049750\t96051824\tKCNIP3\n+chr2\t96068448\t96068620\tFAHD2A\n+chr2\t96071301\t96071551\tFAHD2A\n+chr2\t96072689\t96072905\tFAHD2A\n+chr2\t96076275\t96076334\tFAHD2A\n+chr2\t96076612\t96076774\tFAHD2A\n+chr2\t96078182\t96078290\tFAHD2A\n+chr2\t96078425\t96078512\tFAHD2A\n+chr2\t96078643\t96078878\tFAHD2A\n+chr2\t96146053\t96146283\tTRIM43B\n+chr2\t96147343\t96147438\tTRIM43B\n+chr2\t96148052\t96148466\tTRIM43B\n+chr2\t96150354\t96150479\tTRIM43B\n+chr2\t96257766\t96257897\tTRIM43\n+chr2\t96259768\t96260182\tTRIM43\n+chr2\t96260798\t96260893\tTRIM43\n+chr2\t96261950\t96262180\tTRIM43\n+chr2\t96263077\t96263099\tTRIM43\n+chr2\t96264840\t96265467\tTRIM43\n+chr2\t96676299\t96676480\tLOC729234\n+chr2\t96686873\t96686981\tLOC729234\n+chr2\t96687116\t96687213\tLOC729234\n+chr2\t96687695\t96688023\tGPAT2\n+chr2\t96688416\t96688421\tGPAT2\n+chr2\t96688472\t96688705\tLOC729234\n+chr2\t96688772\t96688853\tLOC729234\n+chr2\t96688883\t96688974\tGPAT2\n+chr2\t96689057\t96689188\tGPAT2\n+chr2\t96689671\t96689748\tGPAT2\n+chr2\t96689937\t96690085\tGPAT2\n+chr2\t96690175\t96690415\tGPAT2\n+chr2\t96690521\t96690591\tGPAT2\n+chr2\t96691233\t96691351\tGPAT2\n+chr2\t966916'..b'1\tINPP4A\n+chr2\t99154326\t99154437\tINPP4A\n+chr2\t99155354\t99155444\tINPP4A\n+chr2\t99155991\t99156138\tINPP4A\n+chr2\t99160340\t99160470\tINPP4A\n+chr2\t99162432\t99162536\tINPP4A\n+chr2\t99163049\t99163157\tINPP4A\n+chr2\t99165418\t99165432\tINPP4A\n+chr2\t99169249\t99169432\tINPP4A\n+chr2\t99170734\t99170952\tINPP4A\n+chr2\t99172016\t99172154\tINPP4A\n+chr2\t99175926\t99175958\tINPP4A\n+chr2\t99179928\t99180100\tINPP4A\n+chr2\t99181103\t99181226\tINPP4A\n+chr2\t99182103\t99182229\tINPP4A\n+chr2\t99182492\t99182632\tINPP4A\n+chr2\t99185034\t99185131\tINPP4A\n+chr2\t99189278\t99189390\tINPP4A\n+chr2\t99193452\t99193606\tINPP4A\n+chr2\t99198039\t99198284\tINPP4A\n+chr2\t99203939\t99207495\tINPP4A\n+chr2\t99215866\t99217256\tC2orf64\n+chr2\t99220571\t99220654\tC2orf64\n+chr2\t99224770\t99224955\tC2orf64\n+chr2\t99225042\t99225189\tUNC50\n+chr2\t99226219\t99226502\tUNC50\n+chr2\t99227238\t99227358\tUNC50\n+chr2\t99232670\t99232809\tUNC50\n+chr2\t99232895\t99232996\tUNC50\n+chr2\t99234631\t99234975\tUNC50\n+chr2\t99235571\t99237968\tMGAT4A\n+chr2\t99242186\t99242298\tMGAT4A\n+chr2\t99251685\t99251751\tMGAT4A\n+chr2\t99252980\t99253058\tMGAT4A\n+chr2\t99256271\t99256464\tMGAT4A\n+chr2\t99256584\t99256691\tMGAT4A\n+chr2\t99260386\t99260516\tMGAT4A\n+chr2\t99261891\t99262005\tMGAT4A\n+chr2\t99271908\t99271983\tMGAT4A\n+chr2\t99272815\t99272928\tMGAT4A\n+chr2\t99274681\t99274727\tMGAT4A\n+chr2\t99279509\t99279642\tMGAT4A\n+chr2\t99279804\t99279936\tMGAT4A\n+chr2\t99291498\t99291638\tMGAT4A\n+chr2\t99294767\t99294934\tMGAT4A\n+chr2\t99342702\t99343030\tMGAT4A\n+chr2\t99410309\t99411134\tC2orf55\n+chr2\t99412583\t99412727\tC2orf55\n+chr2\t99413813\t99414000\tC2orf55\n+chr2\t99438320\t99440000\tC2orf55\n+chr2\t99443438\t99443632\tC2orf55\n+chr2\t99448811\t99448975\tC2orf55\n+chr2\t99449325\t99449460\tC2orf55\n+chr2\t99454582\t99454750\tC2orf55\n+chr2\t99463194\t99463273\tC2orf55\n+chr2\t99552401\t99552684\tC2orf55\n+chr2\t99613725\t99614684\tTSGA10\n+chr2\t99634663\t99634812\tTSGA10\n+chr2\t99634999\t99635103\tTSGA10\n+chr2\t99636743\t99636945\tTSGA10\n+chr2\t99651693\t99651902\tTSGA10\n+chr2\t99681402\t99681587\tTSGA10\n+chr2\t99685351\t99685461\tTSGA10\n+chr2\t99688169\t99688337\tTSGA10\n+chr2\t99689481\t99689536\tTSGA10\n+chr2\t99695122\t99695276\tTSGA10\n+chr2\t99697745\t99697860\tTSGA10\n+chr2\t99720430\t99720581\tTSGA10\n+chr2\t99721822\t99721899\tTSGA10\n+chr2\t99721990\t99722160\tTSGA10\n+chr2\t99725296\t99725454\tTSGA10\n+chr2\t99725852\t99725975\tTSGA10\n+chr2\t99727313\t99727378\tTSGA10\n+chr2\t99734007\t99734222\tTSGA10\n+chr2\t99735014\t99735149\tTSGA10\n+chr2\t99743511\t99743639\tTSGA10\n+chr2\t99757891\t99758037\tTSGA10\n+chr2\t99758185\t99758400\tC2orf15\n+chr2\t99758748\t99758864\tC2orf15\n+chr2\t99763865\t99763956\tC2orf15\n+chr2\t99766946\t99767926\tC2orf15\n+chr2\t99771156\t99771187\tTSGA10\n+chr2\t99771418\t99771514\tLIPT1\n+chr2\t99771945\t99772007\tLIPT1\n+chr2\t99773190\t99773317\tLIPT1\n+chr2\t99778420\t99779611\tLIPT1\n+chr2\t99785726\t99785933\tMITD1\n+chr2\t99786013\t99786073\tMITD1\n+chr2\t99787000\t99787115\tMITD1\n+chr2\t99787806\t99787892\tMITD1\n+chr2\t99787973\t99788109\tMITD1\n+chr2\t99790378\t99790479\tMITD1\n+chr2\t99797294\t99797492\tMITD1\n+chr2\t99797578\t99797712\tMRPL30\n+chr2\t99802640\t99802717\tMRPL30\n+chr2\t99804640\t99804720\tMRPL30\n+chr2\t99811214\t99811360\tMRPL30\n+chr2\t99811579\t99811652\tMRPL30\n+chr2\t99812036\t99814088\tMRPL30\n+chr2\t99858711\t99858945\tLYG2\n+chr2\t99860462\t99860600\tLYG2\n+chr2\t99861725\t99861921\tLYG2\n+chr2\t99863143\t99863283\tLYG2\n+chr2\t99870681\t99870748\tLYG2\n+chr2\t99871483\t99871570\tLYG2\n+chr2\t99900702\t99900974\tLYG1\n+chr2\t99901151\t99901283\tLYG1\n+chr2\t99907700\t99907884\tLYG1\n+chr2\t99908999\t99909103\tLYG1\n+chr2\t99912091\t99912165\tLYG1\n+chr2\t99914922\t99915012\tLYG1\n+chr2\t99917513\t99917639\tLYG1\n+chr2\t99935489\t99936262\tTXNDC9\n+chr2\t99938418\t99938672\tTXNDC9\n+chr2\t99943998\t99944116\tTXNDC9\n+chr2\t99949485\t99949705\tTXNDC9\n+chr2\t99952702\t99952860\tTXNDC9\n+chr2\t99953834\t99954052\tEIF5B\n+chr2\t99976699\t99976824\tEIF5B\n+chr2\t99976928\t99977012\tEIF5B\n+chr2\t99977611\t99978283\tEIF5B\n+chr2\t99980108\t99980325\tEIF5B\n+chr2\t99980734\t99980884\tEIF5B\n+chr2\t99984956\t99985054\tEIF5B\n+chr2\t99985855\t99985944\tEIF5B\n+chr2\t99988119\t99988193\tEIF5B\n+chr2\t99992810\t99993099\tEIF5B\n+chr2\t99995482\t99995589\tEIF5B\n+chr2\t99995781\t99995891\tEIF5B\n+chr2\t99998622\t99998689\tEIF5B\n+chr2\t99999243\t99999384\tEIF5B\n'
b
diff -r 165732ee5a48 -r 45af4a9748cf test-data/CNV_case_small.bam
b
Binary file test-data/CNV_case_small.bam has changed
b
diff -r 165732ee5a48 -r 45af4a9748cf test-data/CNV_control_small.bam
b
Binary file test-data/CNV_control_small.bam has changed