paul-shannon authored on 23/03/2022 21:48:50
Showing 24 changed files

... ...
@@ -1,2 +1,7 @@
1 1
 ^doc$
2 2
 ^Meta$
3
+inst/scripts
4
+misc/
5
+notInstalled/
6
+explore/
7
+inst/unitTests/*.RData
3 8
\ No newline at end of file
... ...
@@ -1,8 +1,8 @@
1 1
 Package: MotifDb
2 2
 Type: Package
3 3
 Title: An Annotated Collection of Protein-DNA Binding Sequence Motifs
4
-Version: 1.35.5
5
-Date: 2021-09-01
4
+Version: 1.37.2
5
+Date: 2022-03-04
6 6
 Author: Paul Shannon, Matt Richards
7 7
 Maintainer: Paul Shannon <pshannon@systemsbiology.org>
8 8
 Depends: R (>= 3.5.0), methods, BiocGenerics, S4Vectors, IRanges, GenomicRanges, Biostrings
... ...
@@ -247,7 +247,7 @@ setMethod('show', 'MotifList',
247 247
       if (length (object) == 0)
248 248
         return ()
249 249
 
250
-      cat ('| Created from downloaded public sources: 2013-Aug-30', '\n', sep='')
250
+      cat ('| Created from downloaded public sources, last update: 2022-Mar-04', '\n', sep='')
251 251
 
252 252
       tbl.dataSource = as.data.frame (table (mcols (object)$dataSource))
253 253
       tbl.org = as.data.frame (table (mcols (object)$organism))
... ...
@@ -13,6 +13,7 @@ MotifDb <- NULL
13 13
     for(data.file in data.files) {
14 14
        # define these to keep 'check' happy.  they are loaded by 'load'
15 15
       tbl.md = NA; matrices = NA;
16
+      # print(noquote(sprintf("--- about to load and append from file '%s'", data.file)))
16 17
       variables = load(data.file)
17 18
       mdb = append(mdb, MotifList(matrices, tbl.md))
18 19
       if(!quiet)
19 20
new file mode 100644
... ...
@@ -0,0 +1,42 @@
1
+library(MotifDb)
2
+library(trena)   # only for MotifMatcher
3
+library(igvR)
4
+library(chipDB)
5
+
6
+#------------------------------------------------------------------------------------------------------------------------
7
+targetGene <- "GATA2"
8
+tf <- "ZNF263"
9
+motif <- query(MotifDb, c("sapiens", tf, "jaspar2018"))
10
+stopifnot(length(motif) == 1)
11
+
12
+igv <- igvR()
13
+setGenome(igv, "hg38")
14
+showGenomicRegion(igv, "GATA2")
15
+getGenomicRegion(igv)
16
+
17
+tbl.region <- with(getGenomicRegion(igv), data.frame(chrom=chrom, start=start, end=end, stringsAsFactors=FALSE))
18
+
19
+matcher <- MultiMethodMotifMatcher("hg38", as.list(motif), tbl.region, "Biostrings matchPWM", .80)
20
+
21
+
22
+tbl.enhancers <- get(load(system.file(package="TrenaProject", "extdata", "genomeAnnotation", "geneHancer.v4.7.allGenes.RData")))
23
+tbl.targetGeneEnhancers <- subset(tbl.enhancers, geneSymbol==targetGene)
24
+track <- DataFrameQuantitativeTrack("enhancers", tbl.targetGeneEnhancers[, c("chrom", "start", "end", "combinedScore")],
25
+                                    autoscale=FALSE, min=0, max=50, color="brown")
26
+displayTrack(igv, track)
27
+showGenomicRegion(igv, "chr3:128,470,539-128,502,070")
28
+
29
+
30
+motifMatcher <- MotifMatcher("hg38", as.list(motif))
31
+tbl.out <- findMatchesByChromosomalRegion(motifMatcher, tbl.region, pwmMatchMinimumAsPercentage=80)[, c(2,3,4,7)]
32
+
33
+track <- DataFrameQuantitativeTrack("moods-ZNF263", tbl.out, autoscale=TRUE, color="blue")
34
+displayTrack(igv, track)
35
+
36
+cdb <- chipDB(quiet=FALSE)
37
+tbl.cdb <- with(getGenomicRegion(igv), getHits(cdb, chrom, start, end))
38
+tbl.csHits <- subset(tbl.cdb, tf=="ZNF263")
39
+track <- DataFrameAnnotationTrack(sprintf("%s-chip", tf), tbl.csHits[,c(1,2,3,5)], color="red")
40
+displayTrack(igv, track)
41
+
42
+
0 43
new file mode 100644
... ...
@@ -0,0 +1,117 @@
1
+library(MotifDb)
2
+library(TrenaViz)   # only for MultiMethodMotifMatcher
3
+library(igvR)
4
+igv <- igvR()
5
+igvR::setGenome(igv, "hg38")
6
+showGenomicRegion(igv, "GATA2")
7
+
8
+library(TrenaProjectErythropoiesis)
9
+tp <- TrenaProjectErythropoiesis()
10
+setTargetGene(tp, "GATA2")
11
+
12
+tbl.enhancers <- getEnhancers(tp)[, c(1,2,3,5)]
13
+
14
+track <- DataFrameQuantitativeTrack("GH", tbl.enhancers,
15
+                                    autoscale=FALSE, min=0, max=50, color="brown")
16
+displayTrack(igv, track)
17
+tbl.bigRegion <- with(tbl.enhancers, data.frame(chrom=tbl.enhancers$chrom[1], start=min(start)-5000, end=max(end)+5000),
18
+                      stringsAsFactors=FALSE)
19
+
20
+bigRegion <- with(tbl.enhancers, sprintf("%s:%d-%d", chrom=tbl.enhancers$chrom[1], start=min(start)-5000, end=max(end)+5000))
21
+showGenomicRegion(igv, bigRegion)
22
+
23
+motif.tbx15 <- query(MotifDb, c("TBX15", "sapiens"), "jaspar2018")
24
+m4.biostrings <- MultiMethodMotifMatcher("hg38", as.list(motif.tbx15), tbl.bigRegion, "Biostrings matchPWM", .80)
25
+tbl.tbx15 <- matchMotifInSequence(m4.biostrings)
26
+dim(tbl.tbx15)
27
+track <- DataFrameQuantitativeTrack("matchPWM-tbx15", tbl.tbx15[, c(1,2,3,6)], autoscale=TRUE, color="blue")
28
+displayTrack(igv, track)
29
+
30
+
31
+motif.znf263 <- query(MotifDb, c("sapiens", "ZNF263", "jaspar2018"))
32
+
33
+tbl.znf263 <- matchMotifInSequence(m4.biostrings)
34
+dim(tbl.znf263)
35
+tbl.znf263$chrom <- as.character(tbl.znf263$chrom)
36
+
37
+
38
+tbl.tbx15$chrom <- as.character(tbl.tbx15$chrom)
39
+track <- DataFrameQuantitativeTrack("jaspar2018-TBX15-MA0803.1", tbl.tbx15[, c(1,2,3,6)], autoscale=TRUE, color="blue")
40
+displayTrack(igv, track)
41
+
42
+m4.moods <- MultiMethodMotifMatcher("hg38", as.list(motif), tbl.bigRegion, "MOODS matchMotifs", 6)
43
+tbl.tbx15.2 <-  matchMotifInSequence(m4.moods)
44
+dim(tbl.tbx15.2)
45
+track <- DataFrameQuantitativeTrack("moods jaspar2018-TBX15-MA0803.1", tbl.tbx15.2[, c(1,2,3,6)], autoscale=TRUE, color="green")
46
+displayTrack(igv, track)
47
+
48
+
49
+library(FimoClient)
50
+
51
+FIMO_HOST <- "localhost"
52
+FIMO_PORT <- 600161
53
+if(!exists("fimoServerStarted")){
54
+   fimoServerStarted <- TRUE
55
+   export(motif, con="motif.meme", format="meme")
56
+   cmd <- sprintf("make -f ~/github/fimoService/server/makefile", PORT=%d MOTIFS=motif.meme", FIMO_PORT)
57
+   system(cmd)
58
+   #meme.file <- system.file(package="FimoClient", "extdata", "human.jaspar2018.meme")
59
+   #stopifnot(file.exists(meme.file))
60
+   #cmd <- sprintf("make -f ~/github/fimoService/server/makefile PORT=%d MOTIFS=%s", FIMO_PORT, meme.file)
61
+   #print(cmd)
62
+   #system(cmd)
63
+   printf("--- sleeping 5, making sure fimo server is awake")
64
+   Sys.sleep(5)
65
+   }
66
+
67
+
68
+fc <- FimoClient(FIMO_HOST, FIMO_PORT, quiet=FALSE)
69
+tbl.fimo <- requestMatchForRegions(fc, tbl.bigRegion, "hg38", pvalThreshold=0.00006)
70
+track <- DataFrameQuantitativeTrack("fimo jaspar2018-TBX15-MA0803.1", tbl.fimo[, c(1,2,3,6)], autoscale=TRUE, color="darkred")
71
+displayTrack(igv, track)
72
+
73
+tbl.fimo.qScore <- tbl.fimo[, c(1,2,3,8)]
74
+tbl.fimo.qScore$qValue <- -log10(tbl.fimo.qScore$qValue)
75
+track <- DataFrameQuantitativeTrack("fimo qScore TBX15", tbl.fimo.qScore[, c(1,2,3,4)], autoscale=TRUE, color="orange")
76
+displayTrack(igv, track)
77
+
78
+
79
+library(chipDB)
80
+cdb <- chipDB(quiet=FALSE)
81
+tbl.cdb <- with(getGenomicRegion(igv), getHits(cdb, chrom, start, end))
82
+
83
+tbl.tf <- as.data.frame(table(tbl.cdb$tf))
84
+colnames(tbl.tf) <- c("tf", "count")
85
+tbl.tf <- tbl.tf[order(tbl.tf$count, decreasing=TRUE),]
86
+tfs <- unique(tbl.cdb$tf)
87
+length(tfs)
88
+
89
+
90
+genesInModelForMarjorie <- c("FOXM1", "RELA", "GATA1", "PAX6", "ATF2", "GTF2I", "ELK3", "SREBF2", "TBX15", "VDR", "PATZ1",
91
+                             "SIN3A", "RFX5", "ZNF263", "BATF", "PLAGL1", "MYB")
92
+length(genesInModelForMarjorie)  # [1] 17
93
+subset(tbl.tf, tf %in% genesInModelForMarjorie)   # 10
94
+ #         tf count
95
+ # 218  SIN3A    44
96
+ # 206   RELA    21
97
+ # 90   GATA1    11
98
+ # 291 ZNF263    10
99
+ # 273    VDR     8
100
+ # 85   FOXM1     5
101
+ # 154    MYB     5
102
+ # 208   RFX5     4
103
+ # 239 SREBF2     2
104
+ # 12    ATF2     1
105
+
106
+track <- DataFrameAnnotationTrack("ZNF263", subset(tbl.cdb, tf=="ZNF263")[, c("chrom", "start", "end", "tissueOrCellType")])
107
+displayTrack(igv, track)
108
+
109
+motif.znf263 <- query(MotifDb, c("sapiens", "ZNF263", "jaspar2018"))
110
+
111
+tbl.region <- with(getGenomicRegion(igv), data.frame(chrom=chrom, start=start, end=end, stringsAsFactors=FALSE))
112
+m4.biostrings <- MultiMethodMotifMatcher("hg38", as.list(motif.znf263), tbl.region, "Biostrings matchPWM", .75)
113
+tbl.znf263 <- matchMotifInSequence(m4.biostrings)
114
+dim(tbl.znf263)
115
+tbl.znf263$chrom <- as.character(tbl.znf263$chrom)
116
+track <- DataFrameQuantitativeTrack("moods-ZNF263", tbl.znf263[, c(1,2,3,6)], autoscale=TRUE, color="blue")
117
+displayTrack(igv, track)
0 118
new file mode 100644
... ...
@@ -0,0 +1,23 @@
1
+MEME version 4
2
+
3
+ALPHABET= ACGT
4
+
5
+strands: + -
6
+
7
+Background letter frequencies
8
+A 0.250 C 0.250 G 0.250 T 0.250 
9
+
10
+MOTIF Hsapiens-jaspar2018-TBX15-MA0803.1
11
+letter-probability matrix: alength= 4 w= 8 nsites= 45 E=8.1e-020
12
+ 0.9251233263  0.0065186751  0.0584918957  0.0098661029
13
+ 0.0410247223  0.0090469366  0.9407022573  0.0092260838
14
+ 0.0018047112  0.0006648936  0.9975303951  0.0000000000
15
+ 0.0055540381  0.0159337157  0.0223072020  0.9562050442
16
+ 0.0000000000  0.0007611798  0.9992388202  0.0000000000
17
+ 0.0122796246  0.0381545478  0.0284185598  0.9211472678
18
+ 0.0036860183  0.0380330066  0.8797855408  0.0784954344
19
+ 0.9569020501  0.0064692483  0.0278815490  0.0087471526
20
+
21
+
22
+
23
+
0 24
new file mode 100644
... ...
@@ -0,0 +1,7381 @@
1
+
2
+>AbdA_Cell_FBgn0000014
3
+1	3	0	14
4
+0	0	0	18
5
+16	0	0	2
6
+18	0	0	0
7
+1	0	0	17
8
+0	0	6	12
9
+15	1	2	0
10
+>AbdB_Cell_FBgn0000015
11
+1	5	12	3
12
+6	1	2	12
13
+1	0	0	20
14
+0	0	0	21
15
+5	0	0	16
16
+21	0	0	0
17
+0	3	0	18
18
+3	0	11	7
19
+13	0	5	3
20
+>Achi_Cell_FBgn0033749
21
+4	3	1	15
22
+6	4	1	12
23
+0	0	0	23
24
+0	0	23	0
25
+23	0	0	0
26
+0	22	0	1
27
+23	0	0	0
28
+>Al_Cell_FBgn0000061
29
+0	0	0	20
30
+20	0	0	0
31
+20	0	0	0
32
+0	0	0	20
33
+0	0	0	20
34
+17	0	3	0
35
+18	0	2	0
36
+>Antp_Cell_FBgn0000095
37
+1	5	2	8
38
+1	1	0	14
39
+0	0	0	16
40
+16	0	0	0
41
+16	0	0	0
42
+0	0	0	16
43
+0	0	9	7
44
+15	0	1	0
45
+>Ap_Cell_FBgn0000099
46
+5	4	9	1
47
+2	10	0	7
48
+1	0	0	18
49
+19	0	0	0
50
+19	0	0	0
51
+0	0	0	19
52
+0	0	6	13
53
+16	0	3	0
54
+>Ara_Cell_FBgn0015904
55
+12	5	10	7
56
+16	7	6	5
57
+24	1	1	8
58
+14	0	5	15
59
+23	0	0	11
60
+34	0	0	0
61
+0	34	0	0
62
+34	0	0	0
63
+>Awh_Cell_FBgn0013751
64
+3	16	0	21
65
+1	0	0	39
66
+33	0	7	0
67
+40	0	0	0
68
+0	0	1	39
69
+0	0	8	32
70
+34	0	4	2
71
+>Bap_Cell_FBgn0004862
72
+7	4	4	8
73
+1	9	5	8
74
+0	0	1	22
75
+0	0	0	23
76
+23	0	0	0
77
+23	0	0	0
78
+0	0	23	0
79
+1	0	0	22
80
+7	0	16	0
81
+3	8	9	3
82
+>Bcd_Cell_FBgn0000166
83
+1	6	10	5
84
+3	5	3	11
85
+0	0	0	22
86
+20	0	0	2
87
+22	0	0	0
88
+0	0	1	21
89
+0	22	0	0
90
+0	21	0	1
91
+>BH1_Cell_FBgn0011758
92
+1	5	12	3
93
+4	4	0	13
94
+0	0	0	21
95
+21	0	0	0
96
+21	0	0	0
97
+8	0	0	13
98
+1	7	0	13
99
+1	0	20	0
100
+7	3	8	3
101
+>BH2_Cell_FBgn0004854
102
+2	7	7	5
103
+6	2	1	12
104
+0	0	0	21
105
+21	0	0	0
106
+21	0	0	0
107
+5	0	0	16
108
+3	1	2	15
109
+0	0	21	0
110
+5	4	11	1
111
+>Bsh_Cell_FBgn0000529
112
+3	5	1	7
113
+1	3	2	10
114
+0	0	0	16
115
+16	0	0	0
116
+16	0	0	0
117
+0	1	0	15
118
+0	3	6	7
119
+7	0	9	0
120
+3	3	9	1
121
+>Btn_Cell_FBgn0014949
122
+4	9	5	5
123
+5	1	4	13
124
+0	0	0	23
125
+22	0	1	0
126
+23	0	0	0
127
+0	1	0	22
128
+0	0	15	8
129
+19	0	3	1
130
+>C15_Cell_FBgn0004863
131
+2	4	8	5
132
+1	1	0	17
133
+0	0	0	19
134
+17	0	0	2
135
+19	0	0	0
136
+6	2	0	11
137
+0	3	6	10
138
+10	0	9	0
139
+>Cad_Cell_FBgn0000251
140
+12	6	4	16
141
+3	3	3	29
142
+4	0	0	34
143
+12	0	2	24
144
+38	0	0	0
145
+0	0	0	38
146
+4	0	7	27
147
+22	0	15	1
148
+>Caup_Cell_FBgn0015919
149
+4	9	2	4
150
+9	0	3	7
151
+8	0	4	7
152
+4	1	2	12
153
+14	0	2	3
154
+19	0	0	0
155
+0	19	0	0
156
+19	0	0	0
157
+>Ct_Cell_FBgn0004198
158
+3	3	7	7
159
+3	8	6	3
160
+0	6	0	14
161
+1	2	0	17
162
+9	0	11	0
163
+20	0	0	0
164
+17	0	1	2
165
+0	19	1	0
166
+>Dfd_Cell_FBgn0000439
167
+8	9	4	3
168
+1	4	3	16
169
+0	0	0	24
170
+24	0	0	0
171
+24	0	0	0
172
+0	0	0	24
173
+1	0	19	4
174
+21	0	3	0
175
+>Dll_Cell_FBgn0000157
176
+1	0	0	22
177
+21	0	2	0
178
+23	0	0	0
179
+0	0	0	23
180
+4	0	2	17
181
+11	0	8	4
182
+0	12	4	7
183
+>Dr_Cell_FBgn0000492
184
+4	8	9	0
185
+11	2	4	4
186
+1	13	6	1
187
+0	16	0	5
188
+21	0	0	0
189
+21	0	0	0
190
+0	0	0	21
191
+0	0	0	21
192
+21	0	0	0
193
+>E5_Cell_FBgn0008646
194
+11	9	12	11
195
+5	15	6	17
196
+3	0	0	40
197
+43	0	0	0
198
+42	0	0	1
199
+1	0	1	41
200
+5	0	16	22
201
+34	0	9	0
202
+>Ems_Cell_FBgn0000576
203
+8	1	2	9
204
+3	7	1	9
205
+3	0	0	17
206
+19	0	0	1
207
+19	0	1	0
208
+0	0	0	20
209
+0	1	10	9
210
+14	0	6	0
211
+>En_Cell_FBgn0000577
212
+3	3	12	5
213
+2	8	2	11
214
+0	0	0	23
215
+23	0	0	0
216
+23	0	0	0
217
+0	0	0	23
218
+0	0	2	21
219
+13	0	10	0
220
+>Eve_Cell_FBgn0000606
221
+6	1	9	6
222
+3	10	0	9
223
+1	0	0	21
224
+22	0	0	0
225
+22	0	0	0
226
+0	2	1	19
227
+0	2	11	9
228
+17	0	4	1
229
+>Exd_Cell_FBgn0000611
230
+4	4	4	5
231
+1	0	2	14
232
+0	0	0	17
233
+0	0	0	17
234
+0	0	17	0
235
+17	0	0	0
236
+0	12	0	5
237
+11	0	6	0
238
+>Exex_Cell_FBgn0041156
239
+0	6	10	7
240
+5	0	0	18
241
+23	0	0	0
242
+18	0	0	5
243
+0	1	0	22
244
+3	0	3	17
245
+19	3	1	0
246
+>Ftz_Cell_FBgn0001077
247
+3	5	8	2
248
+1	2	0	15
249
+1	0	0	17
250
+18	0	0	0
251
+18	0	0	0
252
+0	0	0	18
253
+0	0	9	9
254
+14	0	4	0
255
+>Gsc_Cell_FBgn0010323
256
+8	8	5	1
257
+4	5	4	9
258
+0	0	0	22
259
+22	0	0	0
260
+22	0	0	0
261
+0	0	0	22
262
+0	22	0	0
263
+0	14	2	6
264
+>H2.0_Cell_FBgn0001170
265
+4	1	3	24
266
+10	1	0	21
267
+18	0	1	13
268
+21	0	0	11
269
+8	0	0	24
270
+9	0	9	14
271
+23	0	7	2
272
+>Hbn_Cell_FBgn0008636
273
+0	1	1	15
274
+5	0	0	12
275
+17	0	0	0
276
+12	0	0	5
277
+0	0	0	17
278
+2	0	3	12
279
+12	0	4	1
280
+>Hgtx_Cell_FBgn0040318
281
+4	1	5	10
282
+4	2	3	11
283
+0	0	0	20
284
+20	0	0	0
285
+20	0	0	0
286
+0	0	0	20
287
+1	0	6	13
288
+15	0	5	0
289
+>Hmx_Cell_FBgn0085448
290
+1	3	0	16
291
+0	0	0	20
292
+20	0	0	0
293
+20	0	0	0
294
+1	0	0	19
295
+0	3	0	17
296
+4	0	16	0
297
+>Hth_Cell_FBgn0001235
298
+0	0	0	17
299
+0	0	17	0
300
+17	0	0	0
301
+0	17	0	0
302
+14	0	3	0
303
+>Ind_Cell_FBgn0025776
304
+1	9	2	9
305
+9	4	6	2
306
+0	12	0	9
307
+0	0	0	21
308
+21	0	0	0
309
+21	0	0	0
310
+0	0	1	20
311
+0	0	8	13
312
+19	0	2	0
313
+>Inv_Cell_FBgn0001269
314
+4	0	3	9
315
+1	9	0	6
316
+0	0	0	16
317
+16	0	0	0
318
+16	0	0	0
319
+0	0	0	16
320
+0	0	0	16
321
+11	0	5	0
322
+>Lab_Cell_FBgn0002522
323
+1	3	0	12
324
+0	0	0	16
325
+16	0	0	0
326
+16	0	0	0
327
+1	0	0	15
328
+0	0	6	10
329
+16	0	0	0
330
+>Lag1_Cell_FBgn0040918
331
+0	19	0	0
332
+0	9	0	10
333
+17	2	0	0
334
+1	18	0	0
335
+0	12	0	7
336
+18	0	1	0
337
+12	0	4	3
338
+10	3	4	2
339
+10	1	0	8
340
+3	2	1	13
341
+>Lbe_Cell_FBgn0011278
342
+3	5	9	5
343
+4	6	2	10
344
+0	0	0	22
345
+22	0	0	0
346
+22	0	0	0
347
+1	10	2	9
348
+4	5	3	10
349
+19	0	3	0
350
+>Lbl_Cell_FBgn0008651
351
+5	5	11	2
352
+5	10	0	8
353
+0	0	0	23
354
+23	0	0	0
355
+23	0	0	0
356
+0	5	0	18
357
+1	3	7	12
358
+17	0	6	0
359
+>Lim1_Cell_FBgn0026411
360
+0	2	0	16
361
+0	0	0	18
362
+18	0	0	0
363
+18	0	0	0
364
+0	0	0	18
365
+0	0	0	18
366
+17	0	1	0
367
+>Lim3_Cell_FBgn0002023
368
+8	5	2	5
369
+3	7	2	8
370
+4	0	0	16
371
+16	0	3	1
372
+20	0	0	0
373
+0	0	0	20
374
+0	2	4	14
375
+16	0	4	0
376
+>Mirr_Cell_FBgn0014343
377
+18	6	6	11
378
+18	4	10	9
379
+22	7	6	6
380
+20	1	1	19
381
+29	0	2	10
382
+41	0	0	0
383
+0	41	0	0
384
+41	0	0	0
385
+>NK7.1_Cell_FBgn0024321
386
+13	9	5	8
387
+5	5	1	24
388
+0	0	0	35
389
+33	0	2	0
390
+35	0	0	0
391
+4	0	5	26
392
+6	0	7	22
393
+13	0	22	0
394
+>Oc_Cell_FBgn0004102
395
+5	2	1	11
396
+0	0	0	19
397
+19	0	0	0
398
+19	0	0	0
399
+0	0	2	17
400
+0	19	0	0
401
+0	17	1	1
402
+>Odsh_Cell_FBgn0026058
403
+0	11	4	7
404
+0	0	0	22
405
+22	0	0	0
406
+22	0	0	0
407
+0	0	0	22
408
+0	0	0	22
409
+13	0	8	1
410
+>onecut_Cell_FBgn0028996
411
+1	2	0	12
412
+0	0	0	15
413
+0	0	15	0
414
+15	0	0	0
415
+0	0	0	15
416
+0	0	0	15
417
+5	0	4	6
418
+>Optix_Cell_FBgn0025360
419
+12	4	2	9
420
+13	4	3	7
421
+4	4	16	3
422
+0	5	0	22
423
+0	0	27	0
424
+27	0	0	0
425
+0	0	0	27
426
+26	0	1	0
427
+>Otp_Cell_FBgn0015524
428
+3	4	2	11
429
+1	6	2	11
430
+0	1	0	19
431
+20	0	0	0
432
+20	0	0	0
433
+0	0	0	20
434
+0	1	4	15
435
+15	0	3	2
436
+>Pb_Cell_FBgn0051481
437
+3	3	10	8
438
+4	9	0	11
439
+0	0	0	24
440
+24	0	0	0
441
+24	0	0	0
442
+0	0	0	24
443
+0	0	11	13
444
+24	0	0	0
445
+>PhdP_Cell_FBgn0025334
446
+5	5	0	7
447
+1	0	0	16
448
+15	0	0	2
449
+16	0	1	0
450
+1	0	0	16
451
+1	0	1	15
452
+>Pph13_Cell_FBgn0023489
453
+10	4	3	4
454
+6	9	2	4
455
+0	0	0	21
456
+21	0	0	0
457
+21	0	0	0
458
+0	0	0	21
459
+0	1	0	20
460
+13	1	6	1
461
+>Ptx1_Cell_FBgn0020912
462
+0	5	1	14
463
+0	0	0	20
464
+20	0	0	0
465
+20	0	0	0
466
+0	0	0	20
467
+0	20	0	0
468
+0	19	0	1
469
+>Repo_Cell_FBgn0011701
470
+6	3	6	13
471
+1	4	4	19
472
+1	0	0	27
473
+27	0	0	1
474
+28	0	0	0
475
+0	0	0	28
476
+0	0	0	28
477
+21	0	7	0
478
+>Ro_Cell_FBgn0003267
479
+5	4	11	3
480
+1	12	3	7
481
+0	0	0	23
482
+23	0	0	0
483
+23	0	0	0
484
+0	0	0	23
485
+0	0	3	20
486
+19	0	4	0
487
+>Rx_Cell_FBgn0020617
488
+7	5	12	3
489
+3	13	0	11
490
+0	0	0	27
491
+27	0	0	0
492
+27	0	0	0
493
+0	0	0	27
494
+0	0	0	27
495
+17	0	10	0
496
+>Scr_Cell_FBgn0003339
497
+5	14	1	5
498
+8	5	9	3
499
+3	7	0	15
500
+0	0	0	25
501
+25	0	0	0
502
+25	0	0	0
503
+0	0	0	25
504
+0	0	18	7
505
+23	0	2	0
506
+>Six4_Cell_FBgn0027364
507
+10	2	2	6
508
+4	2	3	11
509
+6	2	3	9
510
+0	0	0	20
511
+0	0	20	0
512
+20	0	0	0
513
+0	7	4	9
514
+20	0	0	0
515
+1	19	0	0
516
+>Slou_Cell_FBgn0002941
517
+2	3	6	11
518
+3	5	1	13
519
+0	1	0	21
520
+22	0	0	0
521
+21	0	1	0
522
+0	0	0	22
523
+2	1	5	14
524
+11	0	11	0
525
+>So_Cell_FBgn0003460
526
+12	4	5	6
527
+13	1	10	3
528
+0	0	1	26
529
+0	0	27	0
530
+27	0	0	0
531
+0	0	1	26
532
+27	0	0	0
533
+>Tin_Cell_FBgn0004110
534
+0	9	3	4
535
+1	0	0	15
536
+0	11	1	4
537
+16	0	0	0
538
+16	0	0	0
539
+0	0	16	0
540
+0	0	0	16
541
+3	0	13	0
542
+>Tup_Cell_FBgn0003896
543
+1	9	5	1
544
+5	1	1	9
545
+1	1	0	14
546
+15	0	0	1
547
+16	0	0	0
548
+1	0	2	13
549
+1	0	6	9
550
+2	0	14	0
551
+>Ubx_Cell_FBgn0003944
552
+3	5	3	9
553
+0	0	0	20
554
+0	0	0	20
555
+17	0	0	3
556
+20	0	0	0
557
+0	0	0	20
558
+0	0	6	14
559
+14	0	6	0
560
+>Unc4_Cell_FBgn0024184
561
+2	9	5	5
562
+1	5	2	13
563
+0	0	0	21
564
+21	0	0	0
565
+21	0	0	0
566
+0	0	0	21
567
+1	0	0	20
568
+6	1	14	0
569
+>Unpg_Cell_FBgn0015561
570
+5	10	3	3
571
+1	6	4	10
572
+1	0	0	20
573
+21	0	0	0
574
+21	0	0	0
575
+0	0	0	21
576
+0	0	2	19
577
+14	0	7	0
578
+>Vis_Cell_FBgn0033748
579
+0	0	0	22
580
+0	0	22	0
581
+22	0	0	0
582
+0	22	0	0
583
+22	0	0	0
584
+>Vnd_Cell_FBgn0003986
585
+4	0	2	13
586
+1	8	1	9
587
+0	0	0	19
588
+0	15	2	2
589
+19	0	0	0
590
+19	0	0	0
591
+0	0	19	0
592
+2	0	0	17
593
+9	0	10	0
594
+>Zen_Cell_FBgn0004053
595
+3	5	4	4
596
+2	8	4	2
597
+2	9	0	5
598
+0	0	0	16
599
+16	0	0	0
600
+16	0	0	0
601
+0	0	0	16
602
+0	0	11	5
603
+16	0	0	0
604
+>Zen2_Cell_FBgn0004054
605
+4	7	2	13
606
+7	9	6	4
607
+3	7	5	11
608
+1	0	0	25
609
+26	0	0	0
610
+26	0	0	0
611
+0	1	0	25
612
+0	0	10	16
613
+22	0	4	0
614
+>CG11085_Cell_FBgn0030408
615
+2	4	2	5
616
+0	3	0	10
617
+0	0	0	13
618
+13	0	0	0
619
+13	0	0	0
620
+1	0	0	12
621
+2	1	2	8
622
+1	0	12	0
623
+2	4	6	1
624
+>CG11294_Cell_FBgn0030058
625
+0	3	0	12
626
+0	2	0	13
627
+15	0	0	0
628
+15	0	0	0
629
+0	0	0	15
630
+0	0	0	15
631
+15	0	0	0
632
+>CG11617_Cell_FBgn0031232
633
+7	0	3	7
634
+2	0	1	14
635
+1	0	0	16
636
+0	0	0	17
637
+10	0	3	4
638
+17	0	0	0
639
+0	17	0	0
640
+17	0	0	0
641
+>CG12361_Cell_FBgn0250756
642
+2	2	3	9
643
+2	0	0	14
644
+2	0	0	14
645
+6	0	2	8
646
+16	0	0	0
647
+0	0	0	16
648
+0	2	6	8
649
+13	0	3	0
650
+>CG13424_Cell_FBgn0034520
651
+6	5	4	6
652
+2	7	1	11
653
+0	0	0	21
654
+21	0	0	0
655
+21	0	0	0
656
+0	0	0	21
657
+3	0	4	14
658
+8	0	13	0
659
+>CG15696_Cell_FBgn0038833
660
+3	7	8	14
661
+2	3	3	24
662
+2	3	0	27
663
+21	0	6	5
664
+32	0	0	0
665
+0	0	0	32
666
+0	0	2	30
667
+16	0	16	0
668
+>CG18599_Cell_FBgn0038592
669
+4	10	1	10
670
+0	0	0	25
671
+25	0	0	0
672
+25	0	0	0
673
+0	0	0	25
674
+0	1	8	16
675
+23	0	2	0
676
+>CG32105_Cell_FBgn0052105
677
+9	1	0	9
678
+2	4	0	13
679
+2	0	0	17
680
+17	0	0	2
681
+19	0	0	0
682
+0	0	1	18
683
+0	0	1	18
684
+15	0	4	0
685
+6	4	9	0
686
+>CG32532_Cell_FBgn0052532
687
+2	6	2	13
688
+0	0	0	23
689
+23	0	0	0
690
+23	0	0	0
691
+0	0	0	23
692
+0	0	2	21
693
+12	0	10	1
694
+>CG33980_Cell_FBgn0053980
695
+1	1	5	6
696
+2	2	0	9
697
+0	0	0	13
698
+13	0	0	0
699
+13	0	0	0
700
+0	0	0	13
701
+0	0	0	13
702
+10	0	3	0
703
+1	2	10	0
704
+>CG34031_Cell_FBgn0054031
705
+2	4	4	15
706
+0	1	1	23
707
+0	0	0	25
708
+22	0	0	3
709
+25	0	0	0
710
+2	0	0	23
711
+7	0	1	17
712
+3	0	22	0
713
+>CG4136_Cell_FBgn0029775
714
+1	8	1	12
715
+0	0	0	22
716
+22	0	0	0
717
+22	0	0	0
718
+0	0	0	22
719
+2	0	3	17
720
+15	0	6	1
721
+>CG4328_Cell_FBgn0036274
722
+12	6	4	8
723
+12	2	3	13
724
+7	1	0	22
725
+13	0	0	17
726
+30	0	0	0
727
+0	0	0	30
728
+0	0	6	24
729
+15	0	15	0
730
+>CG7056_Cell_FBgn0038852
731
+7	3	2	14
732
+0	7	0	19
733
+0	6	7	13
734
+21	0	2	3
735
+26	0	0	0
736
+0	3	3	20
737
+7	0	1	18
738
+22	0	4	0
739
+>CG9876_Cell_FBgn0034821
740
+11	2	4	3
741
+2	9	3	6
742
+0	0	0	20
743
+18	0	0	2
744
+20	0	0	0
745
+0	0	0	20
746
+0	0	1	19
747
+14	0	6	0
748
+>bcd_NAR_FBgn0000166
749
+2	6	2	9
750
+4	2	0	13
751
+18	0	0	1
752
+19	0	0	0
753
+1	0	5	13
754
+0	17	0	2
755
+0	9	0	10
756
+>Blimp-1_NAR_FBgn0035625
757
+4	0	8	0
758
+11	0	0	1
759
+10	1	1	0
760
+12	0	0	0
761
+1	0	11	0
762
+0	2	1	9
763
+0	0	12	0
764
+12	0	0	0
765
+11	0	1	0
766
+12	0	0	0
767
+1	0	11	0
768
+0	3	0	9
769
+>btd_NAR_FBgn0000233
770
+14	3	7	5
771
+10	0	19	0
772
+4	0	18	7
773
+2	0	27	0
774
+0	0	29	0
775
+0	0	29	0
776
+2	27	0	0
777
+0	0	29	0
778
+0	0	20	9
779
+15	1	9	4
780
+>D_NAR_FBgn0000411
781
+20	2	1	11
782
+9	6	11	8
783
+22	3	8	1
784
+34	0	0	0
785
+0	34	0	0
786
+31	3	0	0
787
+30	0	4	0
788
+8	0	0	26
789
+12	0	18	4
790
+5	1	28	0
791
+16	9	8	1
792
+>fkh_NAR_FBgn0000659
793
+3	0	0	24
794
+5	0	22	0
795
+0	0	0	27
796
+0	0	0	27
797
+0	0	1	26
798
+13	0	14	0
799
+4	13	2	8
800
+6	7	3	11
801
+0	11	2	14
802
+23	0	1	3
803
+15	4	4	4
804
+>gt_NAR_FBgn0001150
805
+2	10	8	9
806
+0	8	13	8
807
+6	7	10	6
808
+2	3	4	20
809
+14	0	15	0
810
+0	0	0	29
811
+0	0	0	29
812
+24	0	5	0
813
+0	29	0	0
814
+5	0	24	0
815
+0	1	0	28
816
+26	3	0	0
817
+29	0	0	0
818
+0	10	5	14
819
+>h_NAR_FBgn0001168
820
+0	1	17	0
821
+3	4	6	5
822
+0	18	0	0
823
+12	0	6	0
824
+0	18	0	0
825
+1	0	17	0
826
+0	5	0	13
827
+0	0	18	0
828
+2	13	3	0
829
+0	18	0	0
830
+>hb_NAR_FBgn0001180
831
+0	19	3	4
832
+25	0	1	0
833
+21	5	0	0
834
+26	0	0	0
835
+26	0	0	0
836
+26	0	0	0
837
+26	0	0	0
838
+25	1	0	0
839
+12	10	0	4
840
+12	11	3	0
841
+>hkb_NAR_FBgn0001204
842
+3	0	18	11
843
+8	0	24	0
844
+0	0	32	0
845
+0	0	32	0
846
+0	32	0	0
847
+0	0	32	0
848
+0	0	3	29
849
+0	0	31	1
850
+24	3	2	3
851
+>kni_NAR_FBgn0001320
852
+19	1	2	4
853
+25	1	0	0
854
+16	0	0	10
855
+5	9	6	6
856
+0	4	1	21
857
+21	0	5	0
858
+0	0	26	0
859
+17	0	8	1
860
+1	3	18	4
861
+0	26	0	0
862
+25	0	1	0
863
+5	12	7	2
864
+>Kr_NAR_FBgn0001325
865
+3	17	5	6
866
+11	4	10	6
867
+24	0	7	0
868
+30	0	0	1
869
+18	6	7	0
870
+0	0	31	0
871
+2	0	29	0
872
+2	0	29	0
873
+0	1	7	23
874
+4	0	5	22
875
+20	4	3	4
876
+>nub_NAR_FBgn0085424
877
+2	1	1	25
878
+29	0	0	0
879
+0	0	0	29
880
+0	0	25	4
881
+0	19	1	9
882
+24	0	0	5
883
+28	0	1	0
884
+28	0	0	1
885
+4	1	0	24
886
+6	5	8	10
887
+19	5	1	4
888
+4	3	15	7
889
+>odd_NAR_FBgn0002985
890
+7	5	0	3
891
+10	5	0	0
892
+0	14	1	0
893
+12	0	3	0
894
+0	0	15	0
895
+0	0	0	15
896
+15	0	0	0
897
+0	0	15	0
898
+0	15	0	0
899
+11	3	1	0
900
+5	4	6	0
901
+>opa_NAR_FBgn0003002
902
+0	1	15	2
903
+10	7	1	0
904
+1	16	0	1
905
+1	15	1	1
906
+0	16	1	1
907
+0	18	0	0
908
+0	18	0	0
909
+0	14	0	4
910
+4	0	13	1
911
+0	14	2	2
912
+3	1	4	10
913
+2	0	16	0
914
+>prd_NAR_FBgn0003145
915
+5	6	4	15
916
+3	14	4	9
917
+8	16	3	3
918
+0	1	25	4
919
+4	0	0	26
920
+0	27	0	3
921
+28	1	0	1
922
+0	30	0	0
923
+2	0	28	0
924
+0	18	12	0
925
+5	8	0	17
926
+>slp1_NAR_FBgn0003430
927
+8	3	14	16
928
+0	0	0	41
929
+3	0	38	0
930
+0	0	0	41
931
+0	0	1	40
932
+0	0	2	39
933
+27	0	4	10
934
+1	22	7	11
935
+17	8	15	1
936
+4	13	3	21
937
+15	3	4	19
938
+>tll_NAR_FBgn0003720
939
+20	4	4	5
940
+29	0	4	0
941
+33	0	0	0
942
+31	1	1	0
943
+0	0	33	0
944
+0	2	0	31
945
+0	33	0	0
946
+33	0	0	0
947
+31	0	1	1
948
+17	10	2	4
949
+>ttk_NAR_FBgn0003870
950
+10	8	3	1
951
+22	0	0	0
952
+0	0	22	0
953
+0	0	22	0
954
+22	0	0	0
955
+0	5	0	17
956
+21	0	0	1
957
+22	0	0	0
958
+1	5	3	13
959
+>odd_NBT_1.5_FBgn0002985
960
+2	1	19	0
961
+0	20	2	0
962
+2	0	0	20
963
+16	0	0	6
964
+0	22	0	0
965
+0	10	0	12
966
+0	0	21	1
967
+3	2	11	6
968
+10	2	2	8
969
+>odd_NBT_2.5_FBgn0002985
970
+0	0	24	0
971
+0	24	0	0
972
+0	0	0	24
973
+22	0	0	2
974
+0	23	0	1
975
+0	12	0	12
976
+0	0	23	1
977
+2	0	10	12
978
+9	1	6	8
979
+>odd_NBT_5_FBgn0002985
980
+0	0	23	0
981
+0	23	0	0
982
+0	0	0	23
983
+23	0	0	0
984
+0	23	0	0
985
+0	5	0	18
986
+0	0	23	0
987
+1	0	6	16
988
+9	0	5	9
989
+>dl_NBT_FBgn0000462
990
+0	0	32	0
991
+0	0	32	0
992
+2	0	24	6
993
+18	0	0	14
994
+18	0	0	14
995
+8	0	0	24
996
+2	8	0	22
997
+0	32	0	0
998
+0	30	0	2
999
+7	20	5	0
1000
+>run_Bgb_NBT_FBgn0013753
1001
+13	3	0	15
1002
+28	0	2	1
1003
+29	0	2	0
1004
+0	31	0	0
1005
+0	30	1	0
1006
+7	1	23	0
1007
+0	31	0	0
1008
+30	0	0	1
1009
+22	0	9	0
1010
+>run_Bgb_NBT_FBgn0003300
1011
+13	3	0	15
1012
+28	0	2	1
1013
+29	0	2	0
1014
+0	31	0	0
1015
+0	30	1	0
1016
+7	1	23	0
1017
+0	31	0	0
1018
+30	0	0	1
1019
+22	0	9	0
1020
+>Abd-A_FlyReg_FBgn0000014
1021
+5	2	13	17
1022
+10	15	3	9
1023
+22	15	0	0
1024
+36	0	0	1
1025
+0	0	0	37
1026
+11	2	0	24
1027
+33	1	0	3
1028
+18	2	4	13
1029
+>Abd-B_FlyReg_FBgn0000015
1030
+1	2	0	4
1031
+1	5	1	0
1032
+6	0	1	0
1033
+0	0	0	7
1034
+7	0	0	0
1035
+7	0	0	0
1036
+6	0	0	1
1037
+5	0	1	1
1038
+>Adf1_FlyReg_FBgn0000054
1039
+1	6	0	0
1040
+0	0	7	0
1041
+5	0	2	0
1042
+0	6	0	1
1043
+0	4	0	3
1044
+0	0	7	0
1045
+0	7	0	0
1046
+2	0	5	0
1047
+>Aef1_FlyReg_FBgn0005694
1048
+0	3	0	0
1049
+3	0	0	0
1050
+3	0	0	0
1051
+0	3	0	0
1052
+2	0	0	1
1053
+3	0	0	0
1054
+0	3	0	0
1055
+2	0	0	1
1056
+>Antp_FlyReg_FBgn0000095
1057
+8	0	0	4
1058
+0	0	0	12
1059
+11	0	1	0
1060
+12	0	0	0
1061
+0	0	3	9
1062
+3	0	0	9
1063
+>ap_FlyReg_FBgn0000099
1064
+1	4	2	5
1065
+12	0	0	0
1066
+12	0	0	0
1067
+0	1	1	10
1068
+4	3	1	4
1069
+11	0	1	0
1070
+>bab1_FlyReg_FBgn0004870
1071
+1	0	0	5
1072
+6	0	0	0
1073
+0	0	0	6
1074
+2	0	0	4
1075
+4	0	1	1
1076
+2	0	0	4
1077
+0	0	0	6
1078
+3	0	3	0
1079
+0	0	0	6
1080
+0	0	1	5
1081
+>bcd_FlyReg_FBgn0000166
1082
+9	18	3	18
1083
+8	3	1	36
1084
+45	1	1	1
1085
+47	0	1	0
1086
+1	0	16	31
1087
+1	44	0	3
1088
+2	26	3	17
1089
+5	12	18	13
1090
+>bin_FlyReg_FBgn0045759
1091
+0	0	0	5
1092
+4	0	0	1
1093
+4	0	0	1
1094
+4	1	0	0
1095
+0	5	0	0
1096
+5	0	0	0
1097
+3	0	2	0
1098
+2	2	1	0
1099
+0	0	5	0
1100
+4	0	1	0
1101
+>brk_FlyReg_FBgn0024250
1102
+1	5	4	0
1103
+0	4	0	6
1104
+0	0	10	0
1105
+0	0	10	0
1106
+0	10	0	0
1107
+1	0	9	0
1108
+1	8	0	1
1109
+0	5	1	4
1110
+>br-Z1_FlyReg_FBgn0000210
1111
+12	0	2	3
1112
+12	2	3	0
1113
+9	0	0	8
1114
+0	3	0	14
1115
+14	0	2	1
1116
+1	4	9	3
1117
+11	3	2	1
1118
+16	1	0	0
1119
+>br-Z2_FlyReg_FBgn0000210
1120
+7	3	1	10
1121
+0	15	4	2
1122
+0	0	0	21
1123
+21	0	0	0
1124
+1	0	5	15
1125
+2	5	5	9
1126
+12	1	1	7
1127
+11	4	1	5
1128
+>br-Z3_FlyReg_FBgn0000210
1129
+7	3	3	3
1130
+12	1	0	3
1131
+10	0	6	0
1132
+1	11	0	4
1133
+0	0	1	15
1134
+7	0	3	6
1135
+0	0	10	6
1136
+0	0	1	15
1137
+>br-Z4_FlyReg_FBgn0000210
1138
+5	0	3	0
1139
+2	5	0	1
1140
+1	0	0	7
1141
+8	0	0	0
1142
+8	0	0	0
1143
+1	0	0	7
1144
+>byn_FlyReg_FBgn0011723
1145
+8	0	0	1
1146
+4	0	2	3
1147
+0	0	8	1
1148
+0	1	0	8
1149
+0	0	9	0
1150
+1	7	0	1
1151
+3	0	4	2
1152
+7	0	0	2
1153
+>cad_FlyReg_FBgn0000251
1154
+0	5	3	5
1155
+2	0	3	8
1156
+0	0	0	13
1157
+1	0	0	12
1158
+6	2	1	4
1159
+0	4	3	6
1160
+3	1	9	0
1161
+7	3	2	1
1162
+0	4	0	9
1163
+>Cf2-II_FlyReg_FBgn0000286
1164
+1	0	2	0
1165
+1	1	0	1
1166
+0	0	3	0
1167
+0	0	0	3
1168
+3	0	0	0
1169
+0	0	0	3
1170
+3	0	0	0
1171
+2	0	0	1
1172
+>Deaf1_FlyReg_FBgn0013799
1173
+0	3	0	7
1174
+0	0	0	10
1175
+0	10	0	0
1176
+0	0	10	0
1177
+0	0	5	5
1178
+1	3	4	2
1179
+>Dfd_FlyReg_FBgn0000439
1180
+1	2	2	11
1181
+1	0	0	15
1182
+15	1	0	0
1183
+15	1	0	0
1184
+0	0	0	16
1185
+1	0	5	10
1186
+8	0	6	2
1187
+0	5	2	9
1188
+>dl_FlyReg_FBgn0000462
1189
+2	8	22	6
1190
+8	4	26	0
1191
+3	0	34	1
1192
+33	1	4	0
1193
+34	2	0	2
1194
+36	0	1	1
1195
+24	1	2	11
1196
+4	12	3	19
1197
+8	23	2	5
1198
+8	24	4	2
1199
+>Dref_FlyReg_FBgn0015664
1200
+3	0	1	4
1201
+2	2	2	2
1202
+4	0	0