Browse code

support new version of bam_tally

Michael Lawrence authored on 12/06/2019 22:48:54
Showing 17 changed files

... ...
@@ -116,3 +116,4 @@ src/gstruct/src/stamp-h1
116 116
 inst/user
117 117
 inst/usr
118 118
 /src/samtools/libbam.a
119
+/src/gstruct/src/libgstruct_1.0_la-expr.lo
... ...
@@ -9,7 +9,7 @@ Description: GSNAP and GMAP are a pair of tools to align short-read
9 9
         methods to work with GMAP and GSNAP from within R. In addition,
10 10
         it provides methods to tally alignment results on a
11 11
         per-nucleotide basis using the bam_tally tool.
12
-Version: 1.27.1
12
+Version: 1.27.2
13 13
 Depends: R (>= 2.15.0), methods, GenomeInfoDb (>= 1.1.3),
14 14
         GenomicRanges (>= 1.31.8), Rsamtools (>= 1.31.2)
15 15
 Imports: S4Vectors (>= 0.17.25), IRanges (>= 2.13.12), BiocGenerics (>= 0.25.1),
... ...
@@ -17,9 +17,11 @@ setClass("BamTallyParam",
17 17
                         ignore_duplicates = "logical",
18 18
                         min_depth = "integer",
19 19
                         variant_strand = "integer",
20
+                        variant_pct = "numeric",
20 21
                         ignore_query_Ns = "logical",
21 22
                         indels = "logical",
22
-                        include_soft_clips = "integer",
23
+                        min_softclip = "integer",
24
+                        max_softclip = "integer",
23 25
                         exon_iit = "character_OR_NULL",
24 26
                         xs = "logical",
25 27
                         read_pos = "logical",
... ...
@@ -103,9 +105,9 @@ BamTallyParam <- function(genome, which = GRanges(),
103 105
                           desired_read_group = NULL, minimum_mapq = 0L,
104 106
                           concordant_only = FALSE, unique_only = FALSE,
105 107
                           primary_only = FALSE, ignore_duplicates = FALSE,
106
-                          min_depth = 0L, variant_strand = 0L,
108
+                          min_depth = 0L, variant_strand = 0L, variant_pct = 0,
107 109
                           ignore_query_Ns = FALSE,
108
-                          indels = FALSE, include_soft_clips = 0L,
110
+                          indels = FALSE, min_softclip = 0L, max_softclip = 0L,
109 111
                           exon_iit = NULL, IIT_BPPARAM = NULL,
110 112
                           xs = FALSE, read_pos = FALSE,
111 113
                           min_base_quality = 0L, noncovered = FALSE,
... ...
@@ -127,12 +129,18 @@ BamTallyParam <- function(genome, which = GRanges(),
127 129
     stop("min_depth must be a single, non-negative, non-NA number")
128 130
   if (!variant_strand %in% c(0, 1, 2))
129 131
     stop("variant_strand must be one of 0, 1, or 2")
132
+  if (variant_pct < 0)
133
+    stop("variant_pct must be non-negative")
130 134
   if (!isTRUEorFALSE(ignore_query_Ns))
131 135
     stop("ignore_query_Ns must be TRUE or FALSE")
132 136
   if (!isTRUEorFALSE(indels))
133 137
     stop("indels must be TRUE or FALSE")
134
-  if (include_soft_clips < 0)
135
-    stop("include_soft_clips must be non-negative")
138
+  if (max_softclip < 0L)
139
+    stop("max_softclip must be non-negative")
140
+  if (min_softclip < 0L)
141
+    stop("min_softclip must be non-negative")
142
+  if (max_softclip < min_softclip)
143
+    stop("max_softclip must be at least equal to min_softclip")
136 144
   if (!isTRUEorFALSE(xs))
137 145
     stop("xs must be TRUE or FALSE")
138 146
   if (!isTRUEorFALSE(read_pos))
... ...
@@ -149,7 +157,7 @@ BamTallyParam <- function(genome, which = GRanges(),
149 157
   params$which <- normArgWhich(which, params$genome)
150 158
   params$exon_iit = normArgCdsIIT(params$exon_iit, BPPARAM = IIT_BPPARAM)
151 159
   integer_params <- c("minimum_mapq", "min_depth", "variant_strand",
152
-                      "include_soft_clips")
160
+                      "min_softclip", "max_softclip")
153 161
   params[integer_params] <- lapply(params[integer_params], as.integer)
154 162
   params = params[names(params) != "IIT_BPPARAM"]
155 163
   do.call(new, c("BamTallyParam", params))  
... ...
@@ -205,6 +205,13 @@ normArgSingleInteger <- function(x) {
205 205
     stop("'", name, "' should be a single, non-NA integer")
206 206
   x
207 207
 }
208
+normArgSingleNumber <- function(x) {
209
+    name <- deparse(substitute(x))
210
+    x <- as.numeric(x)
211
+    if (!isSingleNumber(x))
212
+        stop("'", name, "' should be a single, non-NA number")
213
+    x
214
+}
208 215
 normArgTRUEorFALSE <- function(x) {
209 216
   name <- deparse(substitute(x))
210 217
   if (!isTRUEorFALSE(x))
... ...
@@ -227,11 +234,11 @@ normArgSingleCharacterOrNULL <- function(x) {
227 234
                          maximum_nhits = 1000000L,
228 235
                          concordant_only = FALSE, unique_only = FALSE,
229 236
                          primary_only = FALSE, ignore_duplicates = FALSE,
230
-                         min_depth = 0L, variant_strand = 0L,
237
+                         min_depth = 0L, variant_strand = 0L, variant_pct = 0,
231 238
                          ignore_query_Ns = FALSE,
232 239
                          indels = FALSE,
233 240
                          blocksize = 1000L, verbosep = FALSE,
234
-                         include_soft_clips = 0L,
241
+                         min_softclip = 0L, max_softclip = 0L,
235 242
                          exon_iit = NULL, xs = FALSE, read_pos = FALSE,
236 243
                          min_base_quality = 0L, noncovered = FALSE, nm = FALSE)
237 244
 {
... ...
@@ -258,11 +265,13 @@ normArgSingleCharacterOrNULL <- function(x) {
258 265
         normArgTRUEorFALSE(ignore_duplicates),
259 266
         normArgSingleInteger(min_depth),
260 267
         normArgSingleInteger(variant_strand),
268
+        normArgSingleNumber(variant_pct),
261 269
         normArgTRUEorFALSE(ignore_query_Ns),
262 270
         normArgTRUEorFALSE(indels),
263 271
         normArgSingleInteger(blocksize),
264 272
         normArgTRUEorFALSE(verbosep),
265
-        normArgSingleInteger(include_soft_clips),
273
+        normArgSingleInteger(min_softclip),
274
+        normArgSingleInteger(max_softclip),
266 275
         normArgSingleCharacterOrNULL(exon_iit),
267 276
         normArgTRUEorFALSE(xs),
268 277
         normArgTRUEorFALSE(read_pos),
... ...
@@ -8,9 +8,9 @@ test_BamTallyParam <- function() {
8 8
                minimum_mapq = 0L,
9 9
                concordant_only = FALSE, unique_only = FALSE,
10 10
                primary_only = FALSE, ignore_duplicates = FALSE,
11
-               min_depth = 0L, variant_strand = 0L,
11
+               min_depth = 0L, variant_strand = 0L, variant_pct = 0,
12 12
                ignore_query_Ns = FALSE,
13
-               indels = FALSE, include_soft_clips = 0L,
13
+               indels = FALSE, min_softclip = 0L, max_softclip = 0L,
14 14
                xs = FALSE, read_pos = FALSE, min_base_quality = 0L,
15 15
                noncovered = FALSE, nm = FALSE)
16 16
   which <- TP53Which()
... ...
@@ -19,9 +19,9 @@
19 19
                 minimum_mapq = 0L,
20 20
                 concordant_only = FALSE, unique_only = FALSE,
21 21
                 primary_only = FALSE, ignore_duplicates = FALSE,
22
-                min_depth = 0L, variant_strand = 0L,
22
+                min_depth = 0L, variant_strand = 0L, variant_pct = 0,
23 23
                 ignore_query_Ns = FALSE,
24
-                indels = FALSE, include_soft_clips = 0L,
24
+                indels = FALSE, min_softclip = 0L, max_softclip = 0L,
25 25
                 exon_iit = NULL, IIT_BPPARAM = NULL,
26 26
                 xs = FALSE, read_pos = FALSE,
27 27
                 min_base_quality = 0L, noncovered = FALSE, nm = FALSE)
... ...
@@ -52,6 +52,8 @@
52 52
     only positions where a variant was seen on at least one strand, and
53 53
     2 requires the variant be seen on both strands. Setting this to 1
54 54
     is a good way to save resources.}
55
+  \item{variant_pct}{The minimum alternate allele fraction
56
+    for a variant to be reported for a strand.} 
55 57
   \item{ignore_query_Ns}{Whether to ignore the N base pairs when
56 58
     counting. Can save a lot of resources when processing low quality data.}
57 59
   \item{indels}{Whether to return indel counts. The \code{ref} and
... ...
@@ -60,7 +62,8 @@
60 62
     always spans the sequence in \code{ref}; so e.g. a deletion extends
61 63
     one nt upstream of the actual deleted sequence.
62 64
   }
63
-  \item{include_soft_clips}{Maximum length of soft clips that are
65
+  \item{min_softclip, max_softclip}{
66
+    Minimum and maximum length of soft clips that are
64 67
     considered for counting. Soft-clipping is often useful (for GSNAP at
65 68
     least) during alignment, and it should be preserved in the
66 69
     output. However, soft clipping can preferentially occur in regions
... ...
@@ -7,7 +7,7 @@
7 7
 static const R_CallMethodDef callMethods[] = {
8 8
 
9 9
   /* bamtally.c */
10
-  CALLMETHOD_DEF(R_Bamtally_iit, 26),
10
+  CALLMETHOD_DEF(R_Bamtally_iit, 28),
11 11
   CALLMETHOD_DEF(R_tally_iit_parse, 6),
12 12
   
13 13
   /* bamreader.c */
... ...
@@ -19,11 +19,11 @@ R_Bamtally_iit (SEXP bamreader_R, SEXP genome_dir_R, SEXP db_R,
19 19
                 SEXP maximum_nhits_R,
20 20
                 SEXP need_concordant_p_R, SEXP need_unique_p_R,
21 21
                 SEXP need_primary_p_R, SEXP ignore_duplicates_p_R,
22
-                SEXP min_depth_R, SEXP variant_strands_R,
22
+                SEXP min_depth_R, SEXP variant_strands_R, SEXP variant_pct_R,
23 23
                 SEXP ignore_query_Ns_p_R,
24 24
                 SEXP print_indels_p_R,
25 25
                 SEXP blocksize_R, 
26
-                SEXP verbosep_R, SEXP max_softclip_R,
26
+                SEXP verbosep_R, SEXP min_softclip_R, SEXP max_softclip_R,
27 27
                 SEXP exon_iit_file_R,
28 28
                 SEXP print_xs_scores_p_R, SEXP print_cycles_p_R,
29 29
                 SEXP minimum_quality_score_R, SEXP noncovered_R,
... ...
@@ -34,6 +34,7 @@ R_Bamtally_iit (SEXP bamreader_R, SEXP genome_dir_R, SEXP db_R,
34 34
     genome_dir_R == R_NilValue ? NULL : CHAR(asChar(genome_dir_R));
35 35
   const char *db = CHAR(asChar(db_R));
36 36
   int alloclength = asInteger(alloclength_R);
37
+  int pastlength = alloclength;
37 38
   const char *desired_read_group =
38 39
     desired_read_group_R == R_NilValue ? NULL :
39 40
     CHAR(asChar(desired_read_group_R));
... ...
@@ -46,10 +47,12 @@ R_Bamtally_iit (SEXP bamreader_R, SEXP genome_dir_R, SEXP db_R,
46 47
   bool ignore_duplicates_p = asLogical(ignore_duplicates_p_R);
47 48
   int min_depth = asInteger(min_depth_R);
48 49
   int variant_strands = asInteger(variant_strands_R);
50
+  double variant_pct = asReal(variant_pct_R);
49 51
   bool ignore_query_Ns_p = asLogical(ignore_query_Ns_p_R);
50 52
   bool print_indels_p = asLogical(print_indels_p_R);
51 53
   int blocksize = asInteger(blocksize_R);
52 54
   int verbosep = asLogical(verbosep_R);
55
+  int min_softclip = asInteger(min_softclip_R);
53 56
   int max_softclip = asInteger(max_softclip_R);
54 57
   bool print_xs_scores_p = asLogical(print_xs_scores_p_R);
55 58
   bool print_cycles_p = asLogical(print_cycles_p_R);
... ...
@@ -79,7 +82,7 @@ R_Bamtally_iit (SEXP bamreader_R, SEXP genome_dir_R, SEXP db_R,
79 82
                                  genome,
80 83
                                  chromosome_iit,
81 84
                                  map_iit,
82
-                                 alloclength,
85
+                                 alloclength, pastlength,
83 86
                                  (char *)desired_read_group,
84 87
                                  minimum_mapq, good_unique_mapq,
85 88
                                  minimum_quality_score,
... ...
@@ -87,10 +90,11 @@ R_Bamtally_iit (SEXP bamreader_R, SEXP genome_dir_R, SEXP db_R,
87 90
                                  need_unique_p, need_primary_p,
88 91
                                  ignore_duplicates_p,
89 92
                                  min_depth, variant_strands,
90
-				 /* TODO: variant_pct */ 0,
93
+				 variant_pct,
91 94
 				 ignore_query_Ns_p,
92 95
                                  print_indels_p, blocksize, verbosep,
93
-                                 /*readlevel_p*/false, max_softclip,
96
+                                 /*readlevel_p*/false,
97
+				 min_softclip, max_softclip,
94 98
                                  print_cycles_p,
95 99
                                  print_nm_scores_p,
96 100
                                  print_xs_scores_p, noncovered_p);
... ...
@@ -16,14 +16,14 @@ R_Bamtally_iit (SEXP bamreader_R, SEXP genome_dir_R, SEXP db_R,
16 16
                 SEXP maximum_nhits_R,
17 17
                 SEXP need_concordant_p_R, SEXP need_unique_p_R,
18 18
                 SEXP need_primary_p_R, SEXP ignore_duplicates_p_R,
19
-                SEXP min_depth_R, SEXP variant_strands_R,
20
-                SEXP ignore_query_Ns_p,
19
+                SEXP min_depth_R, SEXP variant_strands_R, SEXP variant_pct_R,
20
+                SEXP ignore_query_Ns_p_R,
21 21
                 SEXP print_indels_p_R,
22 22
                 SEXP blocksize_R, 
23
-                SEXP verbosep_R, SEXP max_softclip_R,
24
-                SEXP genome_iit_file_R,
23
+                SEXP verbosep_R, SEXP min_softclip_R, SEXP max_softclip_R,
24
+                SEXP exon_iit_file_R,
25 25
                 SEXP print_xs_scores_p_R, SEXP print_cycles_p_R,
26
-                SEXP minimum_quality_score_R, SEXP nonconvered_R,
26
+                SEXP minimum_quality_score_R, SEXP noncovered_R,
27 27
                 SEXP print_nm_scores_p_R);
28 28
 
29 29
 SEXP
... ...
@@ -23,12 +23,12 @@ BAM_TALLY_FILES = fopen.h bool.h types.h bam.h bgzf.h \
23 23
  md5.c md5.h complement.h sequence.c sequence.h genome.c genome.h \
24 24
  uinttable.c uinttable.h table.c table.h \
25 25
  chrnum.c chrnum.h \
26
- bamread.c bamread.h samread.c samread.h parserange.c parserange.h \
26
+ samflags.h bamread.c bamread.h samread.c samread.h parserange.c parserange.h \
27 27
  tableuint.c tableuint.h iit-write.c iit-write.h ucharlist.c ucharlist.h \
28 28
  matchdef.h matchpool.c matchpool.h mismatchdef.h mismatchpool.c mismatchpool.h tally.c tally.h \
29
- translation.c translation.h bamtally.c bamtally.h \
29
+ translation.c translation.h expr.c expr.h bamtally.c bamtally.h \
30 30
  datadir.c datadir.h \
31
- getopt.c getopt1.c getopt.h bamtally_main.c
31
+ getline.c getline.h getopt.c getopt1.c getopt.h bamtally_main.c
32 32
 
33 33
 if HAVE_SAMTOOLS_LIB
34 34
 bam_tally_CFLAGS = $(AM_CFLAGS) $(PTHREAD_CFLAGS) $(SIMD_CFLAGS) $(POPCNT_FLAGS) $(SAMTOOLS_CFLAGS) -DTARGET=\"$(target)\" -DGMAPDB=\"$(GMAPDB)\"
... ...
@@ -48,10 +48,10 @@ LIBGSTRUCT_LA_FILES = config.h fopen.h bool.h types.h \
48 48
  md5.c md5.h sequence.c sequence.h genome.c genome.h \
49 49
  uinttable.c uinttable.h table.c table.h \
50 50
  chrnum.c chrnum.h \
51
- bamread.c bamread.h samread.c samread.h parserange.c parserange.h \
51
+ samflags.h bamread.c bamread.h samread.c samread.h parserange.c parserange.h \
52 52
  tableuint.c tableuint.h iit-write.c iit-write.h ucharlist.c ucharlist.h \
53 53
  matchdef.h matchpool.c matchpool.h mismatchdef.h mismatchpool.c mismatchpool.h tally.c tally.h \
54
- translation.c translation.h bamtally.c bamtally.h \
54
+ translation.c translation.h expr.c expr.h bamtally.c bamtally.h \
55 55
  datadir.c datadir.h
56 56
 
57 57
 # Do not add SAMTOOLS LIBS here
... ...
@@ -167,12 +167,12 @@ am__dist_libgstruct_@LIBGSTRUCT_API_VERSION@_la_SOURCES_DIST =  \
167 167
 	iit-read.c iit-read.h complement.h chrom.c chrom.h \
168 168
 	genomicpos.c genomicpos.h md5.c md5.h sequence.c sequence.h \
169 169
 	genome.c genome.h uinttable.c uinttable.h table.c table.h \
170
-	chrnum.c chrnum.h bamread.c bamread.h samread.c samread.h \
171
-	parserange.c parserange.h tableuint.c tableuint.h iit-write.c \
172
-	iit-write.h ucharlist.c ucharlist.h matchdef.h matchpool.c \
173
-	matchpool.h mismatchdef.h mismatchpool.c mismatchpool.h \
174
-	tally.c tally.h translation.c translation.h bamtally.c \
175
-	bamtally.h datadir.c datadir.h
170
+	chrnum.c chrnum.h samflags.h bamread.c bamread.h samread.c \
171
+	samread.h parserange.c parserange.h tableuint.c tableuint.h \
172
+	iit-write.c iit-write.h ucharlist.c ucharlist.h matchdef.h \
173
+	matchpool.c matchpool.h mismatchdef.h mismatchpool.c \
174
+	mismatchpool.h tally.c tally.h translation.c translation.h \
175
+	expr.c expr.h bamtally.c bamtally.h datadir.c datadir.h
176 176
 am__objects_1 = libgstruct_@LIBGSTRUCT_API_VERSION@_la-except.lo \
177 177
 	libgstruct_@LIBGSTRUCT_API_VERSION@_la-assert.lo \
178 178
 	libgstruct_@LIBGSTRUCT_API_VERSION@_la-mem.lo \
... ...
@@ -203,6 +203,7 @@ am__objects_1 = libgstruct_@LIBGSTRUCT_API_VERSION@_la-except.lo \
203 203
 	libgstruct_@LIBGSTRUCT_API_VERSION@_la-mismatchpool.lo \
204 204
 	libgstruct_@LIBGSTRUCT_API_VERSION@_la-tally.lo \
205 205
 	libgstruct_@LIBGSTRUCT_API_VERSION@_la-translation.lo \
206
+	libgstruct_@LIBGSTRUCT_API_VERSION@_la-expr.lo \
206 207
 	libgstruct_@LIBGSTRUCT_API_VERSION@_la-bamtally.lo \
207 208
 	libgstruct_@LIBGSTRUCT_API_VERSION@_la-datadir.lo
208 209
 @HAVE_SAMTOOLS_LIB_TRUE@dist_libgstruct_@LIBGSTRUCT_API_VERSION@_la_OBJECTS =  \
... ...
@@ -228,13 +229,14 @@ am__dist_bam_tally_SOURCES_DIST = fopen.h bool.h types.h bam.h bgzf.h \
228 229
 	access.h iitdef.h iit-read.c iit-read.h chrom.c chrom.h \
229 230
 	genomicpos.c genomicpos.h md5.c md5.h complement.h sequence.c \
230 231
 	sequence.h genome.c genome.h uinttable.c uinttable.h table.c \
231
-	table.h chrnum.c chrnum.h bamread.c bamread.h samread.c \
232
-	samread.h parserange.c parserange.h tableuint.c tableuint.h \
233
-	iit-write.c iit-write.h ucharlist.c ucharlist.h matchdef.h \
234
-	matchpool.c matchpool.h mismatchdef.h mismatchpool.c \
235
-	mismatchpool.h tally.c tally.h translation.c translation.h \
236
-	bamtally.c bamtally.h datadir.c datadir.h getopt.c getopt1.c \
237
-	getopt.h bamtally_main.c
232
+	table.h chrnum.c chrnum.h samflags.h bamread.c bamread.h \
233
+	samread.c samread.h parserange.c parserange.h tableuint.c \
234
+	tableuint.h iit-write.c iit-write.h ucharlist.c ucharlist.h \
235
+	matchdef.h matchpool.c matchpool.h mismatchdef.h \
236
+	mismatchpool.c mismatchpool.h tally.c tally.h translation.c \
237
+	translation.h expr.c expr.h bamtally.c bamtally.h datadir.c \
238
+	datadir.h getline.c getline.h getopt.c getopt1.c getopt.h \
239
+	bamtally_main.c
238 240
 am__objects_2 = bam_tally-except.$(OBJEXT) bam_tally-assert.$(OBJEXT) \
239 241
 	bam_tally-mem.$(OBJEXT) bam_tally-intlist.$(OBJEXT) \
240 242
 	bam_tally-list.$(OBJEXT) bam_tally-littleendian.$(OBJEXT) \
... ...
@@ -250,7 +252,8 @@ am__objects_2 = bam_tally-except.$(OBJEXT) bam_tally-assert.$(OBJEXT) \
250 252
 	bam_tally-iit-write.$(OBJEXT) bam_tally-ucharlist.$(OBJEXT) \
251 253
 	bam_tally-matchpool.$(OBJEXT) bam_tally-mismatchpool.$(OBJEXT) \
252 254
 	bam_tally-tally.$(OBJEXT) bam_tally-translation.$(OBJEXT) \
253
-	bam_tally-bamtally.$(OBJEXT) bam_tally-datadir.$(OBJEXT) \
255
+	bam_tally-expr.$(OBJEXT) bam_tally-bamtally.$(OBJEXT) \
256
+	bam_tally-datadir.$(OBJEXT) bam_tally-getline.$(OBJEXT) \
254 257
 	bam_tally-getopt.$(OBJEXT) bam_tally-getopt1.$(OBJEXT) \
255 258
 	bam_tally-bamtally_main.$(OBJEXT)
256 259
 @HAVE_SAMTOOLS_LIB_TRUE@dist_bam_tally_OBJECTS = $(am__objects_2)
... ...
@@ -492,12 +495,12 @@ BAM_TALLY_FILES = fopen.h bool.h types.h bam.h bgzf.h \
492 495
  md5.c md5.h complement.h sequence.c sequence.h genome.c genome.h \
493 496
  uinttable.c uinttable.h table.c table.h \
494 497
  chrnum.c chrnum.h \
495
- bamread.c bamread.h samread.c samread.h parserange.c parserange.h \
498
+ samflags.h bamread.c bamread.h samread.c samread.h parserange.c parserange.h \
496 499
  tableuint.c tableuint.h iit-write.c iit-write.h ucharlist.c ucharlist.h \
497 500
  matchdef.h matchpool.c matchpool.h mismatchdef.h mismatchpool.c mismatchpool.h tally.c tally.h \
498
- translation.c translation.h bamtally.c bamtally.h \
501
+ translation.c translation.h expr.c expr.h bamtally.c bamtally.h \
499 502
  datadir.c datadir.h \
500
- getopt.c getopt1.c getopt.h bamtally_main.c
503
+ getline.c getline.h getopt.c getopt1.c getopt.h bamtally_main.c
501 504
 
502 505
 @HAVE_SAMTOOLS_LIB_TRUE@bam_tally_CFLAGS = $(AM_CFLAGS) $(PTHREAD_CFLAGS) $(SIMD_CFLAGS) $(POPCNT_FLAGS) $(SAMTOOLS_CFLAGS) -DTARGET=\"$(target)\" -DGMAPDB=\"$(GMAPDB)\"
503 506
 @HAVE_SAMTOOLS_LIB_TRUE@bam_tally_LDFLAGS = $(AM_LDFLAGS) $(STATIC_LDFLAG) $(PTHREAD_CFLAGS) $(SAMTOOLS_LDFLAGS)
... ...
@@ -513,10 +516,10 @@ LIBGSTRUCT_LA_FILES = config.h fopen.h bool.h types.h \
513 516
  md5.c md5.h sequence.c sequence.h genome.c genome.h \
514 517
  uinttable.c uinttable.h table.c table.h \
515 518
  chrnum.c chrnum.h \
516
- bamread.c bamread.h samread.c samread.h parserange.c parserange.h \
519
+ samflags.h bamread.c bamread.h samread.c samread.h parserange.c parserange.h \
517 520
  tableuint.c tableuint.h iit-write.c iit-write.h ucharlist.c ucharlist.h \
518 521
  matchdef.h matchpool.c matchpool.h mismatchdef.h mismatchpool.c mismatchpool.h tally.c tally.h \
519
- translation.c translation.h bamtally.c bamtally.h \
522
+ translation.c translation.h expr.c expr.h bamtally.c bamtally.h \
520 523
  datadir.c datadir.h
521 524
 
522 525
 
... ...
@@ -707,8 +710,10 @@ distclean-compile:
707 710
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/bam_tally-chrom.Po@am__quote@
708 711
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/bam_tally-datadir.Po@am__quote@
709 712
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/bam_tally-except.Po@am__quote@
713
+@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/bam_tally-expr.Po@am__quote@
710 714
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/bam_tally-genome.Po@am__quote@
711 715
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/bam_tally-genomicpos.Po@am__quote@
716
+@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/bam_tally-getline.Po@am__quote@
712 717
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/bam_tally-getopt.Po@am__quote@
713 718
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/bam_tally-getopt1.Po@am__quote@
714 719
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/bam_tally-iit-read.Po@am__quote@
... ...
@@ -741,6 +746,7 @@ distclean-compile:
741 746
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-chrom.Plo@am__quote@
742 747
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-datadir.Plo@am__quote@
743 748
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-except.Plo@am__quote@
749
+@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-expr.Plo@am__quote@
744 750
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-genome.Plo@am__quote@
745 751
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-genomicpos.Plo@am__quote@
746 752
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-iit-read.Plo@am__quote@
... ...
@@ -996,6 +1002,13 @@ libgstruct_@LIBGSTRUCT_API_VERSION@_la-translation.lo: translation.c
996 1002
 @AMDEP_TRUE@@am__fastdepCC_FALSE@	DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@
997 1003
 @am__fastdepCC_FALSE@	$(AM_V_CC@am__nodep@)$(LIBTOOL) $(AM_V_lt) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(libgstruct_@LIBGSTRUCT_API_VERSION@_la_CFLAGS) $(CFLAGS) -c -o libgstruct_@LIBGSTRUCT_API_VERSION@_la-translation.lo `test -f 'translation.c' || echo '$(srcdir)/'`translation.c
998 1004
 
1005
+libgstruct_@LIBGSTRUCT_API_VERSION@_la-expr.lo: expr.c
1006
+@am__fastdepCC_TRUE@	$(AM_V_CC)$(LIBTOOL) $(AM_V_lt) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(libgstruct_@LIBGSTRUCT_API_VERSION@_la_CFLAGS) $(CFLAGS) -MT libgstruct_@LIBGSTRUCT_API_VERSION@_la-expr.lo -MD -MP -MF $(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-expr.Tpo -c -o libgstruct_@LIBGSTRUCT_API_VERSION@_la-expr.lo `test -f 'expr.c' || echo '$(srcdir)/'`expr.c
1007
+@am__fastdepCC_TRUE@	$(AM_V_at)$(am__mv) $(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-expr.Tpo $(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-expr.Plo
1008
+@AMDEP_TRUE@@am__fastdepCC_FALSE@	$(AM_V_CC)source='expr.c' object='libgstruct_@LIBGSTRUCT_API_VERSION@_la-expr.lo' libtool=yes @AMDEPBACKSLASH@
1009
+@AMDEP_TRUE@@am__fastdepCC_FALSE@	DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@
1010
+@am__fastdepCC_FALSE@	$(AM_V_CC@am__nodep@)$(LIBTOOL) $(AM_V_lt) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(libgstruct_@LIBGSTRUCT_API_VERSION@_la_CFLAGS) $(CFLAGS) -c -o libgstruct_@LIBGSTRUCT_API_VERSION@_la-expr.lo `test -f 'expr.c' || echo '$(srcdir)/'`expr.c
1011
+
999 1012
 libgstruct_@LIBGSTRUCT_API_VERSION@_la-bamtally.lo: bamtally.c
1000 1013
 @am__fastdepCC_TRUE@	$(AM_V_CC)$(LIBTOOL) $(AM_V_lt) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(libgstruct_@LIBGSTRUCT_API_VERSION@_la_CFLAGS) $(CFLAGS) -MT libgstruct_@LIBGSTRUCT_API_VERSION@_la-bamtally.lo -MD -MP -MF $(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-bamtally.Tpo -c -o libgstruct_@LIBGSTRUCT_API_VERSION@_la-bamtally.lo `test -f 'bamtally.c' || echo '$(srcdir)/'`bamtally.c
1001 1014
 @am__fastdepCC_TRUE@	$(AM_V_at)$(am__mv) $(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-bamtally.Tpo $(DEPDIR)/libgstruct_@LIBGSTRUCT_API_VERSION@_la-bamtally.Plo
... ...
@@ -1430,6 +1443,20 @@ bam_tally-translation.obj: translation.c
1430 1443
 @AMDEP_TRUE@@am__fastdepCC_FALSE@	DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@
1431 1444
 @am__fastdepCC_FALSE@	$(AM_V_CC@am__nodep@)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -c -o bam_tally-translation.obj `if test -f 'translation.c'; then $(CYGPATH_W) 'translation.c'; else $(CYGPATH_W) '$(srcdir)/translation.c'; fi`
1432 1445
 
1446
+bam_tally-expr.o: expr.c
1447
+@am__fastdepCC_TRUE@	$(AM_V_CC)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -MT bam_tally-expr.o -MD -MP -MF $(DEPDIR)/bam_tally-expr.Tpo -c -o bam_tally-expr.o `test -f 'expr.c' || echo '$(srcdir)/'`expr.c
1448
+@am__fastdepCC_TRUE@	$(AM_V_at)$(am__mv) $(DEPDIR)/bam_tally-expr.Tpo $(DEPDIR)/bam_tally-expr.Po
1449
+@AMDEP_TRUE@@am__fastdepCC_FALSE@	$(AM_V_CC)source='expr.c' object='bam_tally-expr.o' libtool=no @AMDEPBACKSLASH@
1450
+@AMDEP_TRUE@@am__fastdepCC_FALSE@	DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@
1451
+@am__fastdepCC_FALSE@	$(AM_V_CC@am__nodep@)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -c -o bam_tally-expr.o `test -f 'expr.c' || echo '$(srcdir)/'`expr.c
1452
+
1453
+bam_tally-expr.obj: expr.c
1454
+@am__fastdepCC_TRUE@	$(AM_V_CC)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -MT bam_tally-expr.obj -MD -MP -MF $(DEPDIR)/bam_tally-expr.Tpo -c -o bam_tally-expr.obj `if test -f 'expr.c'; then $(CYGPATH_W) 'expr.c'; else $(CYGPATH_W) '$(srcdir)/expr.c'; fi`
1455
+@am__fastdepCC_TRUE@	$(AM_V_at)$(am__mv) $(DEPDIR)/bam_tally-expr.Tpo $(DEPDIR)/bam_tally-expr.Po
1456
+@AMDEP_TRUE@@am__fastdepCC_FALSE@	$(AM_V_CC)source='expr.c' object='bam_tally-expr.obj' libtool=no @AMDEPBACKSLASH@
1457
+@AMDEP_TRUE@@am__fastdepCC_FALSE@	DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@
1458
+@am__fastdepCC_FALSE@	$(AM_V_CC@am__nodep@)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -c -o bam_tally-expr.obj `if test -f 'expr.c'; then $(CYGPATH_W) 'expr.c'; else $(CYGPATH_W) '$(srcdir)/expr.c'; fi`
1459
+
1433 1460
 bam_tally-bamtally.o: bamtally.c
1434 1461
 @am__fastdepCC_TRUE@	$(AM_V_CC)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -MT bam_tally-bamtally.o -MD -MP -MF $(DEPDIR)/bam_tally-bamtally.Tpo -c -o bam_tally-bamtally.o `test -f 'bamtally.c' || echo '$(srcdir)/'`bamtally.c
1435 1462
 @am__fastdepCC_TRUE@	$(AM_V_at)$(am__mv) $(DEPDIR)/bam_tally-bamtally.Tpo $(DEPDIR)/bam_tally-bamtally.Po
... ...
@@ -1458,6 +1485,20 @@ bam_tally-datadir.obj: datadir.c
1458 1485
 @AMDEP_TRUE@@am__fastdepCC_FALSE@	DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@
1459 1486
 @am__fastdepCC_FALSE@	$(AM_V_CC@am__nodep@)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -c -o bam_tally-datadir.obj `if test -f 'datadir.c'; then $(CYGPATH_W) 'datadir.c'; else $(CYGPATH_W) '$(srcdir)/datadir.c'; fi`
1460 1487
 
1488
+bam_tally-getline.o: getline.c
1489
+@am__fastdepCC_TRUE@	$(AM_V_CC)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -MT bam_tally-getline.o -MD -MP -MF $(DEPDIR)/bam_tally-getline.Tpo -c -o bam_tally-getline.o `test -f 'getline.c' || echo '$(srcdir)/'`getline.c
1490
+@am__fastdepCC_TRUE@	$(AM_V_at)$(am__mv) $(DEPDIR)/bam_tally-getline.Tpo $(DEPDIR)/bam_tally-getline.Po
1491
+@AMDEP_TRUE@@am__fastdepCC_FALSE@	$(AM_V_CC)source='getline.c' object='bam_tally-getline.o' libtool=no @AMDEPBACKSLASH@
1492
+@AMDEP_TRUE@@am__fastdepCC_FALSE@	DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@
1493
+@am__fastdepCC_FALSE@	$(AM_V_CC@am__nodep@)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -c -o bam_tally-getline.o `test -f 'getline.c' || echo '$(srcdir)/'`getline.c
1494
+
1495
+bam_tally-getline.obj: getline.c
1496
+@am__fastdepCC_TRUE@	$(AM_V_CC)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -MT bam_tally-getline.obj -MD -MP -MF $(DEPDIR)/bam_tally-getline.Tpo -c -o bam_tally-getline.obj `if test -f 'getline.c'; then $(CYGPATH_W) 'getline.c'; else $(CYGPATH_W) '$(srcdir)/getline.c'; fi`
1497
+@am__fastdepCC_TRUE@	$(AM_V_at)$(am__mv) $(DEPDIR)/bam_tally-getline.Tpo $(DEPDIR)/bam_tally-getline.Po
1498
+@AMDEP_TRUE@@am__fastdepCC_FALSE@	$(AM_V_CC)source='getline.c' object='bam_tally-getline.obj' libtool=no @AMDEPBACKSLASH@
1499
+@AMDEP_TRUE@@am__fastdepCC_FALSE@	DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@
1500
+@am__fastdepCC_FALSE@	$(AM_V_CC@am__nodep@)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -c -o bam_tally-getline.obj `if test -f 'getline.c'; then $(CYGPATH_W) 'getline.c'; else $(CYGPATH_W) '$(srcdir)/getline.c'; fi`
1501
+
1461 1502
 bam_tally-getopt.o: getopt.c
1462 1503
 @am__fastdepCC_TRUE@	$(AM_V_CC)$(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) $(CPPFLAGS) $(bam_tally_CFLAGS) $(CFLAGS) -MT bam_tally-getopt.o -MD -MP -MF $(DEPDIR)/bam_tally-getopt.Tpo -c -o bam_tally-getopt.o `test -f 'getopt.c' || echo '$(srcdir)/'`getopt.c
1463 1504
 @am__fastdepCC_TRUE@	$(AM_V_at)$(am__mv) $(DEPDIR)/bam_tally-getopt.Tpo $(DEPDIR)/bam_tally-getopt.Po
... ...
@@ -1317,7 +1317,7 @@ print_allele_counts_simple (FILE *fp, Tally_T this, Genome_T genome, Genomicpos_
1317 1317
     fprintf(fp,"^");
1318 1318
     for (p = this->insertions_byshift; p != NULL; p = List_next(p)) {
1319 1319
       ins = (Insertion_T) List_head(p);
1320
-      fprintf(fp,"%s %ld ref:%ld",
1320
+      fprintf(fp,"%s %ld ref:%d",
1321 1321
 	      ins->segment,ins->count,
1322 1322
 	      insertion_refcount(&refcount_plus,ins,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip));
1323 1323
     }
... ...
@@ -1329,7 +1329,7 @@ print_allele_counts_simple (FILE *fp, Tally_T this, Genome_T genome, Genomicpos_
1329 1329
     fprintf(fp,"_");
1330 1330
     for (p = this->deletions_byshift; p != NULL; p = List_next(p)) {
1331 1331
       del = (Deletion_T) List_head(p);
1332
-      fprintf(fp,"%s %ld ref:%ld",
1332
+      fprintf(fp,"%s %ld ref:%d",
1333 1333
 	      del->segment,del->count,
1334 1334
 	      deletion_refcount(&refcount_plus,del,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip));
1335 1335
     }
... ...
@@ -1341,7 +1341,7 @@ print_allele_counts_simple (FILE *fp, Tally_T this, Genome_T genome, Genomicpos_
1341 1341
     fprintf(fp,"x");
1342 1342
     for (p = this->microinvs_byshift; p != NULL; p = List_next(p)) {
1343 1343
       minv = (Microinv_T) List_head(p);
1344
-      fprintf(fp,"%s %ld ref:%ld",
1344
+      fprintf(fp,"%s %ld ref:%d",
1345 1345
 	      minv->segment,minv->count,
1346 1346
 	      minv_refcount(&refcount_plus,minv,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip));
1347 1347
     }
... ...
@@ -1360,7 +1360,7 @@ print_allele_counts_simple (FILE *fp, Tally_T this, Genome_T genome, Genomicpos_
1360 1360
   }
1361 1361
 
1362 1362
   if (this->delcounts_plus + this->delcounts_minus > 0) {
1363
-    fprintf(fp," _%ld",this->delcounts_plus + this->delcounts_minus);
1363
+    fprintf(fp," _%d",this->delcounts_plus + this->delcounts_minus);
1364 1364
   }
1365 1365
 
1366 1366
   return;
... ...
@@ -1617,7 +1617,7 @@ print_zeroes (Genomicpos_T start, Genomicpos_T end, char *printchr, int blocksiz
1617 1617
       blockstart = chrpos;
1618 1618
       blockend = chrpos + blocksize;
1619 1619
       if (blockp == true) {
1620
-	printf(">%ld %s:%u..%u\n",/*total*/0,printchr,blockstart,blockend-1U);
1620
+	printf(">%d %s:%u..%u\n",/*total*/0,printchr,blockstart,blockend-1U);
1621 1621
       }
1622 1622
       for (chrpos0 = blockstart; chrpos0 < blockend; chrpos0++) {
1623 1623
 	if (blockp == false) {
... ...
@@ -1632,7 +1632,7 @@ print_zeroes (Genomicpos_T start, Genomicpos_T end, char *printchr, int blocksiz
1632 1632
       blockstart = chrpos;
1633 1633
       blockend = end;
1634 1634
       if (blockp == true) {
1635
-	printf(">%ld %s:%u..%u\n",/*total*/0,printchr,blockstart,blockend-1U);
1635
+	printf(">%d %s:%u..%u\n",/*total*/0,printchr,blockstart,blockend-1U);
1636 1636
       }
1637 1637
       for (chrpos0 = blockstart; chrpos0 < blockend; chrpos0++) {
1638 1638
 	if (blockp == false) {
... ...
@@ -3772,9 +3772,9 @@ print_softclip_jcns_low (Tally_T this, char *printchr, Genomicpos_T chrpos,
3772 3772
   }
3773 3773
 
3774 3774
   if (signed_counts_p == false) {
3775
-    printf("%ld",count_plus + count_minus);
3775
+    printf("%d",count_plus + count_minus);
3776 3776
   } else {
3777
-    printf("%ld|%ld",count_plus,count_minus);
3777
+    printf("%d|%d",count_plus,count_minus);
3778 3778
   }
3779 3779
 
3780 3780
   if (print_cycles_p == true) {
... ...
@@ -3826,9 +3826,9 @@ print_softclip_jcns_high (Tally_T this, char *printchr, Genomicpos_T chrpos,
3826 3826
   }
3827 3827
 
3828 3828
   if (signed_counts_p == false) {
3829
-    printf("%ld",count_plus + count_minus);
3829
+    printf("%d",count_plus + count_minus);
3830 3830
   } else {
3831
-    printf("%ld|%ld",count_plus,count_minus);
3831
+    printf("%d|%d",count_plus,count_minus);
3832 3832
   }
3833 3833
 
3834 3834
   if (print_cycles_p == true) {
... ...
@@ -4036,10 +4036,10 @@ print_insertions (Tally_T this, char *printchr, Genomicpos_T chrpos,
4036 4036
       }
4037 4037
     }
4038 4038
     if (signed_counts_p == false) {
4039
-      printf(" ref:%ld",insertion_refcount(&refcount_plus,ins0,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip));
4039
+      printf(" ref:%d",insertion_refcount(&refcount_plus,ins0,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip));
4040 4040
     } else {
4041 4041
       refcount = insertion_refcount(&refcount_plus,ins0,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip);
4042
-      printf(" ref:%ld|%ld",refcount_plus,refcount - refcount_plus);
4042
+      printf(" ref:%d|%d",refcount_plus,refcount - refcount_plus);
4043 4043
     }
4044 4044
   }
4045 4045
 
... ...
@@ -4255,10 +4255,10 @@ print_deletions (Tally_T this, char *printchr, Genomicpos_T chrpos,
4255 4255
       }
4256 4256
     }
4257 4257
     if (signed_counts_p == false) {
4258
-      printf(" ref:%ld",deletion_refcount(&refcount_plus,del0,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip));
4258
+      printf(" ref:%d",deletion_refcount(&refcount_plus,del0,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip));
4259 4259
     } else {
4260 4260
       refcount = deletion_refcount(&refcount_plus,del0,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip);
4261
-      printf(" ref:%ld|%ld",refcount_plus,refcount - refcount_plus);
4261
+      printf(" ref:%d|%d",refcount_plus,refcount - refcount_plus);
4262 4262
     }
4263 4263
   }
4264 4264
 
... ...
@@ -4475,10 +4475,10 @@ print_microinversions (Tally_T this, char *printchr, Genomicpos_T chrpos,
4475 4475
     }
4476 4476
 
4477 4477
     if (signed_counts_p == false) {
4478
-      printf(" ref:%ld",minv_refcount(&refcount_plus,minv0,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip));
4478
+      printf(" ref:%d",minv_refcount(&refcount_plus,minv0,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip));
4479 4479
     } else {
4480 4480
       refcount = minv_refcount(&refcount_plus,minv0,alloc_tallies,alloc_low,alloc_high,min_softclip,max_softclip);
4481
-      printf(" ref:%ld|%ld",refcount_plus,refcount - refcount_plus);
4481
+      printf(" ref:%d|%d",refcount_plus,refcount - refcount_plus);
4482 4482
     }
4483 4483
   }
4484 4484
 
... ...
@@ -4545,10 +4545,10 @@ print_matches (Tally_T this, long int total_matches_plus, long int total_matches
4545 4545
       for (shift = 0; shift <= this->max_byshift_minus; shift++) {
4546 4546
 	if (this->matches_byshift_minus[shift] > 0) {
4547 4547
 	  if (firstp == true) {
4548
-	    printf("(%ld@%d",this->matches_byshift_minus[shift],-shift);
4548
+	    printf("(%d@%d",this->matches_byshift_minus[shift],-shift);
4549 4549
 	    firstp = false;
4550 4550
 	  } else {
4551
-	    printf(",%ld@%d",this->matches_byshift_minus[shift],-shift);
4551
+	    printf(",%d@%d",this->matches_byshift_minus[shift],-shift);
4552 4552
 	  }
4553 4553
 	  this->matches_byshift_minus[shift] = 0; /* clear */
4554 4554
 	}
... ...
@@ -4556,10 +4556,10 @@ print_matches (Tally_T this, long int total_matches_plus, long int total_matches
4556 4556
       for (shift = this->max_byshift_plus; shift >= 0; shift--) {
4557 4557
 	if (this->matches_byshift_plus[shift] > 0) {
4558 4558
 	  if (firstp == true) {
4559
-	    printf("(%ld@%d",this->matches_byshift_plus[shift],shift);
4559
+	    printf("(%d@%d",this->matches_byshift_plus[shift],shift);
4560 4560
 	    firstp = false;
4561 4561
 	  } else {
4562
-	    printf(",%ld@%d",this->matches_byshift_plus[shift],shift);
4562
+	    printf(",%d@%d",this->matches_byshift_plus[shift],shift);
4563 4563
 	  }
4564 4564
 	  this->matches_byshift_plus[shift] = 0; /* clear */
4565 4565
 	}
... ...
@@ -4588,10 +4588,10 @@ print_matches (Tally_T this, long int total_matches_plus, long int total_matches
4588 4588
       for (nm = 0; nm <= this->max_nm; nm++) {
4589 4589
 	if (this->matches_bynm[nm] > 0) {
4590 4590
 	  if (firstp == true) {
4591
-	    printf("(%ldNM%d",this->matches_bynm[nm],nm);
4591
+	    printf("(%dNM%d",this->matches_bynm[nm],nm);
4592 4592
 	    firstp = false;
4593 4593
 	  } else {
4594
-	    printf(",%ldNM%d",this->matches_bynm[nm],nm);
4594
+	    printf(",%dNM%d",this->matches_bynm[nm],nm);
4595 4595
 	  }
4596 4596
 	  this->matches_bynm[nm] = 0; /* clear */
4597 4597
 	}
... ...
@@ -4633,10 +4633,10 @@ print_matches (Tally_T this, long int total_matches_plus, long int total_matches
4633 4633
       for (xs = 0; xs < 3; xs++) {
4634 4634
 	if (this->matches_byxs[xs] > 0) {
4635 4635
 	  if (firstp == true) {
4636
-	    printf("(%ldXS",this->matches_byxs[xs]);
4636
+	    printf("(%dXS",this->matches_byxs[xs]);
4637 4637
 	    firstp = false;
4638 4638
 	  } else {
4639
-	    printf(",%ldXS",this->matches_byxs[xs]);
4639
+	    printf(",%dXS",this->matches_byxs[xs]);
4640 4640
 	  }
4641 4641
 	  switch (xs) {
4642 4642
 	  case 0: printf("0"); break;
4643 4643
new file mode 100644
... ...
@@ -0,0 +1,70 @@
1
+static char rcsid[] = "$Id: expr.c 206180 2017-05-11 20:34:12Z twu $";
2
+#ifdef HAVE_CONFIG_H
3
+#include <config.h>
4
+#endif
5
+
6
+#include "expr.h"
7
+#include <stdio.h>		/* For sprintf */
8
+#include <stdlib.h>
9
+#include "mem.h"
10
+
11
+#define T Expr_T
12
+
13
+struct T {
14
+  Genomicpos_T chrpos;
15
+  long int total;
16
+  Intlist_T acclist;
17
+  Intlist_T exonlist;
18
+  Intlist_T ntlist;
19
+};
20
+
21
+
22
+void
23
+Expr_free (T *old) {
24
+  Intlist_free(&(*old)->acclist);
25
+  Intlist_free(&(*old)->exonlist);
26
+  Intlist_free(&(*old)->ntlist);
27
+
28
+  FREE(*old);
29
+  return;
30
+}
31
+
32
+
33
+T
34
+Expr_new (Genomicpos_T chrpos, long int total, Intlist_T acclist, Intlist_T exonlist, Intlist_T ntlist) {
35
+  T new = (T) MALLOC(sizeof(*new));
36
+
37
+  new->chrpos = chrpos;
38
+  new->total = total;
39
+  new->acclist = acclist;
40
+  new->exonlist = exonlist;
41
+  new->ntlist = ntlist;
42
+
43
+  return new;
44
+}
45
+
46
+Genomicpos_T
47
+Expr_chrpos (T this) {
48
+  return this->chrpos;
49
+}
50
+
51
+long int
52
+Expr_total (T this) {
53
+  return this->total;
54
+}
55
+
56
+Intlist_T
57
+Expr_acclist (T this) {
58
+  return this->acclist;
59
+}
60
+
61
+Intlist_T
62
+Expr_exonlist (T this) {
63
+  return this->exonlist;
64
+}
65
+
66
+Intlist_T
67
+Expr_ntlist (T this) {
68
+  return this->ntlist;
69
+}
70
+
0 71
new file mode 100644
... ...
@@ -0,0 +1,28 @@
1
+/* $Id: expr.h 206180 2017-05-11 20:34:12Z twu $ */
2
+#ifndef EXPR_INCLUDED
3
+#define EXPR_INCLUDED
4
+#include "intlist.h"
5
+#include "genomicpos.h"
6
+
7
+#define T Expr_T
8
+typedef struct T *T;
9
+
10
+extern void
11
+Expr_free (T *old);
12
+extern T
13
+Expr_new (Genomicpos_T chrpos, long int total, Intlist_T acclist, Intlist_T exonlist, Intlist_T ntlist);
14
+
15
+extern Genomicpos_T
16
+Expr_chrpos (T this);
17
+extern long int
18
+Expr_total (T this);
19
+extern Intlist_T
20
+Expr_acclist (T this);
21
+extern Intlist_T
22
+Expr_exonlist (T this);
23
+extern Intlist_T
24
+Expr_ntlist (T this);
25
+
26
+
27
+#undef T
28
+#endif
0 29
new file mode 100644
... ...
@@ -0,0 +1,150 @@
1
+static char rcsid[] = "$Id: getline.c 219286 2019-05-21 01:03:23Z twu $";
2
+
3
+/* #define STANDALONE 1 */
4
+
5
+#include "getline.h"
6
+
7
+#include <stdlib.h>
8
+#include <string.h>		/* For memcpy */
9
+#include <strings.h>		/* For rindex */
10
+
11
+#ifdef STANDALONE
12
+#define MALLOC malloc
13
+#define FREE free
14
+#else
15
+#include "mem.h"
16
+#endif
17
+
18
+
19
+#define BUFSIZE 1024
20
+
21
+/* Reads arbitrarily long lines from fp.  Strips the '\n' character from the end */
22
+char *
23
+Getline (FILE *fp) {
24
+  size_t size, length;
25
+  char *buffer, *ptr;
26
+
27
+  size = BUFSIZE;
28
+  buffer = (char *) MALLOC(BUFSIZE*sizeof(char));
29
+  if (fgets(buffer,BUFSIZE,fp) == NULL) {
30
+    FREE(buffer);
31
+    return (char *) NULL;
32
+
33
+  } else {
34
+    length = strlen(buffer);
35
+    while (!feof(fp) && buffer[length-1] != '\n') {
36
+      size += BUFSIZE;
37
+
38
+      ptr = buffer;
39
+      buffer = (char *) MALLOC(size*sizeof(char));
40
+      memcpy(buffer,ptr,length*sizeof(char));
41
+      FREE(ptr);
42
+
43
+      ptr = fgets(&(buffer[length]),BUFSIZE,fp);
44
+      length += strlen(ptr);
45
+    }
46
+
47
+    if (buffer[length-1] == '\n') {
48
+      buffer[length-1] = '\0';
49
+      length -= 1;
50
+    }
51
+
52
+    return buffer;
53
+  }
54
+}
55
+
56
+/* length does not include the "\n" character */
57
+char *
58
+Getline_wlength (int *string_length, FILE *fp) {
59
+  size_t size, length;
60
+  char *buffer, *ptr;
61
+
62
+  size = BUFSIZE;
63
+  buffer = (char *) MALLOC(BUFSIZE*sizeof(char));
64
+  if (fgets(buffer,BUFSIZE,fp) == NULL) {
65
+    FREE(buffer);
66
+    *string_length = 0;
67
+    return (char *) NULL;
68
+
69
+  } else {
70
+    length = strlen(buffer);
71
+    while (!feof(fp) && buffer[length-1] != '\n') {
72
+      size += BUFSIZE;
73
+
74
+      ptr = buffer;
75
+      buffer = (char *) MALLOC(size*sizeof(char));
76
+      memcpy(buffer,ptr,length*sizeof(char));
77
+      FREE(ptr);
78
+
79
+      ptr = fgets(&(buffer[length]),BUFSIZE,fp);
80
+      length += strlen(ptr);
81
+    }
82
+
83
+    if (buffer[length-1] == '\n') {
84
+      buffer[length-1] = '\0';
85
+      length -= 1;
86
+    }
87
+
88
+    *string_length = length;
89
+    return buffer;
90
+  }
91
+}
92
+
93
+
94
+/* Reads arbitrarily long lines from fp.  Does not strip the '\n'
95
+   character from the end.  Can be used if we want to reproduce the
96
+   input file exactly. */
97
+char *
98
+Getline_wlinefeed (FILE *fp) {
99
+  size_t size, length;
100
+  char *buffer, *ptr;
101
+
102
+  size = BUFSIZE;
103
+  buffer = (char *) MALLOC(BUFSIZE*sizeof(char));
104
+  if (fgets(buffer,BUFSIZE,fp) == NULL) {
105
+    FREE(buffer);
106
+    return (char *) NULL;
107
+
108
+  } else {
109
+    length = strlen(buffer);
110
+    while (!feof(fp) && buffer[length-1] != '\n') {
111
+      size += BUFSIZE;
112
+
113
+      ptr = buffer;
114
+      buffer = (char *) MALLOC(size*sizeof(char));
115
+      memcpy(buffer,ptr,length*sizeof(char));
116
+      FREE(ptr);
117
+
118
+      ptr = fgets(&(buffer[length]),BUFSIZE,fp);
119
+      length += strlen(ptr);
120
+    }
121
+
122
+#if 0
123
+    if (buffer[length-1] == '\n') {
124
+      buffer[length-1] = '\0';
125
+      length -= 1;
126
+    }
127
+#endif
128
+
129
+    return buffer;
130
+  }
131
+}
132
+
133
+
134
+#ifdef STANDALONE
135
+int
136
+main (int argc, char *argv[]) {
137
+  FILE *fp;
138
+  char *line;
139
+  int length;
140
+
141
+  fp = fopen(argv[1],"r");
142
+  while ((line = Getline_wlength(&length,fp)) != NULL) {
143
+    printf("%d: %s\n",length,line);
144
+    FREE(line);
145
+  }
146
+  fclose(fp);
147
+
148
+  return 0;
149
+}
150
+#endif
0 151
new file mode 100644
... ...
@@ -0,0 +1,15 @@
1
+#ifndef GETLINE_INCLUDED
2
+#define GETLINE_INCLUDED
3
+
4
+#include <stdio.h>
5
+
6
+extern char *
7
+Getline (FILE *fp);
8
+extern char *
9
+Getline_wlength (int *string_length, FILE *fp);
10
+extern char *
11
+Getline_wlinefeed (FILE *fp);
12
+
13
+#endif
14
+
15
+
... ...
@@ -1,4 +1,4 @@
1
-/* $Id: samflags.h 106634 2013-09-03 17:01:14Z twu $ */
1
+/* $Id: samflags.h 219289 2019-05-21 01:13:18Z twu $ */
2 2
 #ifndef SAMFLAGS_INCLUDED
3 3
 #define SAMFLAGS_INCLUDED
4 4
 
... ...
@@ -13,6 +13,7 @@
13 13
 #define NOT_PRIMARY        0x0100 /* 256 */
14 14
 #define BAD_READ_QUALITY   0x0200 /* 512 */
15 15
 #define DUPLICATE_READ     0x0400 /* 1024 */
16
+#define SUPPLEMENTARY      0x0800 /* 2048 */
16 17
 
17 18
 /* 83 = first read, minus strand for paired */
18 19
 /* 99 = first read, plus strand for paired */
... ...
@@ -22,28 +23,5 @@
22 23
 /* For forcing a read to be primary */
23 24
 #define SET_PRIMARY        0xFEFF /* do a logical-and (&) with this */
24 25
 
25
-
26
-/* XO tag for output type */
27
-#define ABBREV_NOMAPPING_1 "N1"
28
-#define ABBREV_NOMAPPING_2 "N2"
29
-#define ABBREV_HALFMAPPING_UNIQ "HU"
30
-#define ABBREV_HALFMAPPING_CIRCULAR "HC"
31
-#define ABBREV_HALFMAPPING_TRANSLOC "HT"
32
-#define ABBREV_HALFMAPPING_MULT "HM"
33
-#define ABBREV_UNPAIRED_UNIQ "UU"
34
-#define ABBREV_UNPAIRED_CIRCULAR "UC"
35
-#define ABBREV_UNPAIRED_TRANSLOC "UT"
36
-#define ABBREV_UNPAIRED_MULT "UM"
37
-#define ABBREV_PAIRED_UNIQ_CIRCULAR "PC"
38
-#define ABBREV_PAIRED_UNIQ_INV "PI"
39
-#define ABBREV_PAIRED_UNIQ_SCR "PS"
40
-#define ABBREV_PAIRED_UNIQ_LONG "PL"
41
-#define ABBREV_PAIRED_MULT "PM"
42
-#define ABBREV_CONCORDANT_UNIQ "CU"
43
-#define ABBREV_CONCORDANT_CIRCULAR "CC"
44
-#define ABBREV_CONCORDANT_TRANSLOC "CT"
45
-#define ABBREV_CONCORDANT_MULT "CM"
46
-
47
-
48 26
 #endif
49 27