Browse code

Removed fixed RNA focus for Modifier and SequenceData* classes

All classes can now be used to detect RNA and DNA modification. For this the seqtype slot was added to Modifier class via inheritance to RNAModifier and DNAModifier classes. seqtype getter is available for Modifier class, and getter/setter for SequenceData* classes.

Felix Ernst authored on 27/09/2019 16:13:26
Showing 39 changed files

... ...
@@ -9,6 +9,7 @@ export(End5SequenceData)
9 9
 export(End5SequenceDataFrame)
10 10
 export(EndSequenceData)
11 11
 export(EndSequenceDataFrame)
12
+export(ModDNASequenceTrack)
12 13
 export(ModInosine)
13 14
 export(ModRNASequenceTrack)
14 15
 export(ModSetInosine)
... ...
@@ -58,12 +59,14 @@ export(validAggregate)
58 59
 export(validModification)
59 60
 exportClasses(CoverageSequenceData)
60 61
 exportClasses(CoverageSequenceDataFrame)
62
+exportClasses(DNAModifier)
61 63
 exportClasses(End3SequenceData)
62 64
 exportClasses(End3SequenceDataFrame)
63 65
 exportClasses(End5SequenceData)
64 66
 exportClasses(End5SequenceDataFrame)
65 67
 exportClasses(EndSequenceData)
66 68
 exportClasses(EndSequenceDataFrame)
69
+exportClasses(ModDNASequenceTrack)
67 70
 exportClasses(ModInosine)
68 71
 exportClasses(ModRNASequenceTrack)
69 72
 exportClasses(ModSetInosine)
... ...
@@ -77,12 +80,14 @@ exportClasses(PileupSequenceData)
77 80
 exportClasses(PileupSequenceDataFrame)
78 81
 exportClasses(ProtectedEndSequenceData)
79 82
 exportClasses(ProtectedEndSequenceDataFrame)
83
+exportClasses(RNAModifier)
80 84
 exportClasses(RNASequenceTrack)
81 85
 exportClasses(SequenceDFrame)
82 86
 exportClasses(SequenceDataFrame)
83 87
 exportClasses(SequenceDataList)
84 88
 exportClasses(SequenceDataSet)
85 89
 exportMethods("[")
90
+exportMethods("seqtype<-")
86 91
 exportMethods("settings<-")
87 92
 exportMethods(Modifier)
88 93
 exportMethods(ModifierSet)
... ...
@@ -115,6 +120,7 @@ exportMethods(ranges)
115 120
 exportMethods(rbind)
116 121
 exportMethods(replicates)
117 122
 exportMethods(seqinfo)
123
+exportMethods(seqtype)
118 124
 exportMethods(sequenceData)
119 125
 exportMethods(sequences)
120 126
 exportMethods(settings)
... ...
@@ -143,11 +149,13 @@ importFrom(BiocParallel,SerialParam)
143 149
 importFrom(BiocParallel,bplapply)
144 150
 importFrom(BiocParallel,bpmapply)
145 151
 importFrom(BiocParallel,register)
152
+importFrom(Biostrings,"seqtype<-")
146 153
 importFrom(Biostrings,DNAString)
147 154
 importFrom(Biostrings,DNAStringSet)
148 155
 importFrom(Biostrings,RNAString)
149 156
 importFrom(Biostrings,RNAStringSet)
150 157
 importFrom(Biostrings,getSeq)
158
+importFrom(Biostrings,seqtype)
151 159
 importFrom(Biostrings,subseq)
152 160
 importFrom(Biostrings,xscat)
153 161
 importFrom(GenomeInfoDb,seqnames)
... ...
@@ -165,6 +173,8 @@ importFrom(IRanges,LogicalList)
165 173
 importFrom(IRanges,PartitioningByEnd)
166 174
 importFrom(IRanges,PartitioningByWidth)
167 175
 importFrom(IRanges,SplitDataFrameList)
176
+importFrom(Modstrings,ModDNAString)
177
+importFrom(Modstrings,ModDNAStringSet)
168 178
 importFrom(Modstrings,ModRNAString)
169 179
 importFrom(Modstrings,ModRNAStringSet)
170 180
 importFrom(Modstrings,combineIntoModstrings)
... ...
@@ -197,3 +197,56 @@ ModRNASequenceTrack <- function(sequence, chromosome, genome, ...){
197 197
                                       .get_ModRNA_bio_color(),
198 198
                                       ...)
199 199
 }
200
+
201
+################################################################################
202
+## Gviz + ModDNAString #########################################################
203
+################################################################################
204
+
205
+#' @name ModDNASequenceTrack
206
+#' @aliases ModDNASequenceTrack-class
207
+#' 
208
+#' @title ModDNASequenceTrack
209
+#' 
210
+#' @description 
211
+#' A \code{Gviz} compatible 
212
+#' \code{\link[Gviz:SequenceTrack-class]{SequenceTrack}} for showing modified 
213
+#' DNA sequences.
214
+#' 
215
+#' @export
216
+setClass("ModDNASequenceTrack",
217
+         contains = "ModifiedSequenceTrack",
218
+         representation = representation(sequence = "ModDNAStringSet",
219
+                                         chromosome = "character",
220
+                                         genome = "character"),
221
+         prototype = prototype(seqType = "ModDNAString",
222
+                               sequence = ModDNAStringSet(),
223
+                               name = "Sequence",
224
+                               chromosome = "chr0",
225
+                               genome = "all")
226
+)
227
+
228
+#' @rdname ModDNASequenceTrack
229
+#' 
230
+#' @param sequence A \code{character} vector or \code{ModDNAString} object of 
231
+#' length one. The sequence to display. See 
232
+#' \code{\link[Gviz:SequenceTrack-class]{SequenceTrack}}.
233
+#' @param chromosome,genome,... See 
234
+#' \code{\link[Gviz:SequenceTrack-class]{SequenceTrack}}.
235
+#' 
236
+#' @return a \code{ModDNASequenceTrack} object
237
+#'   
238
+#' @export
239
+#' 
240
+#' @examples
241
+#' seq <- ModDNAStringSet(c(chr1 = paste0(alphabet(ModDNAString()),collapse = "")))
242
+#' st <- ModDNASequenceTrack(seq)
243
+#' Gviz::plotTracks(st, chromosome = "chr1",from = 1L, to = 20L)
244
+ModDNASequenceTrack <- function(sequence, chromosome, genome, ...){
245
+  .stringSet_to_ModifiedSequenceTrack("ModDNASequenceTrack",
246
+                                      "ModDNAStringSet",
247
+                                      sequence,
248
+                                      chromosome,
249
+                                      genome,
250
+                                      .get_ModDNA_bio_color(),
251
+                                      ...)
252
+}
... ...
@@ -2,6 +2,15 @@
2 2
 #' @include Gviz-ModifiedSequenceTrack-class.R
3 3
 NULL
4 4
 
5
+.get_ModDNA_bio_color <- function(){
6
+  alphabetNames <- alphabet(ModDNAString())
7
+  alphabet <- rep("#33FF00",length(alphabetNames))
8
+  names(alphabet) <- alphabetNames
9
+  dna_color <- getBioColor(type="DNA_BASES_N")
10
+  alphabet[match(names(dna_color),names(alphabet))] <- dna_color
11
+  alphabet
12
+}
13
+
5 14
 .get_ModRNA_bio_color <- function(){
6 15
   alphabetNames <- alphabet(ModRNAString())
7 16
   alphabet <- rep("#33FF00",length(alphabetNames))
... ...
@@ -143,7 +143,7 @@ NULL
143 143
 #' @rdname ModInosine
144 144
 #' @export
145 145
 setClass("ModInosine",
146
-         contains = c("Modifier"),
146
+         contains = c("RNAModifier"),
147 147
          prototype = list(mod = "I",
148 148
                           score = "score",
149 149
                           dataType = "PileupSequenceData"))
... ...
@@ -23,8 +23,13 @@ invalidMessage <- paste0("Settings were changed after data aggregation or ",
23 23
 #' Each subclass has to implement the following functions:
24 24
 #'
25 25
 #' \itemize{
26
-#' \item{\code{\link{aggregateData}}: }{used for specific data aggregation}
27
-#' \item{\code{\link{findMod}}: }{used for specific search for modifications}
26
+#' \item{Slot \code{nucleotide}: } {Either "RNA" or "DNA". For conveniance the
27
+#' subclasses \code{RNAModifier} and \code{DNAModifier} are already available
28
+#' and can be inherited from.}
29
+#' \item{Function \code{\link{aggregateData}}: }{used for specific data 
30
+#' aggregation}
31
+#' \item{Function \code{\link{findMod}}: }{used for specific search for 
32
+#' modifications}
28 33
 #' }
29 34
 #'
30 35
 #' Optionally the function \code{\link[=Modifier-functions]{settings<-}} can be
... ...
@@ -106,9 +111,12 @@ invalidMessage <- paste0("Settings were changed after data aggregation or ",
106 111
 #' objects, if \code{x} is not a \code{SequenceData} object or a list of
107 112
 #' \code{SequenceData} objects.
108 113
 #'
114
+#' @slot nucleotide a \code{character} value, which needs to contain "RNA" or 
115
+#' "DNA"
109 116
 #' @slot mod a \code{character} value, which needs to contain one or more
110 117
 #' elements from the alphabet of a
111
-#' \code{\link[Modstrings:ModRNAString]{ModRNAString}} class.
118
+#' \code{\link[Modstrings:ModRNAString]{ModRNAString}} or 
119
+#' \code{\link[Modstrings:ModDNAString]{ModDNAString}} class.
112 120
 #' @slot score the main score identifier used for visualizations
113 121
 #' @slot dataType the class name(s) of the \code{SequenceData} class used
114 122
 #' @slot bamfiles the input bam files as \code{BamFileList}
... ...
@@ -145,8 +153,9 @@ NULL
145 153
 #'
146 154
 #' @param x,object a \code{Modifier} or \code{ModifierSet} class
147 155
 #' @param modified For \code{sequences}: \code{TRUE} or \code{FALSE}: Should
148
-#' the sequences be returned as a \code{ModRNAString} with the found
149
-#' modifications added on top of the \code{RNAString}? See
156
+#' the sequences be returned as a \code{ModRNAString}/\code{ModDNAString} with
157
+#' the found modifications added on top of the \code{RNAString}/
158
+#' \code{DNAString}? See 
150 159
 #' \code{\link[Modstrings:separate]{combineIntoModstrings}}.
151 160
 #' @param perTranscript \code{TRUE} or \code{FALSE}: Should the positions shown
152 161
 #' per transcript? (default: \code{perTranscript = FALSE})
... ...
@@ -156,6 +165,10 @@ NULL
156 165
 #' \itemize{
157 166
 #' \item{\code{modifierType}:} {a character vector with the appropriate class
158 167
 #' Name of a \code{\link[=Modifier-class]{Modifier}}.}
168
+#' \item{\code{modType}:} {a character vector with the modifications detected by
169
+#' the \code{Modifier} class.}
170
+#' \item{\code{seqtype}:} {a single character value defining if either
171
+#' "RNA" or "DNA" modifications are detected by the \code{Modifier} class.}
159 172
 #' \item{\code{mainScore}:} {a character vector.}
160 173
 #' \item{\code{sequenceData}:} {a \code{SequenceData} object.}
161 174
 #' \item{\code{modifications}:} {a \code{GRanges} or \code{GRangesList} object
... ...
@@ -177,7 +190,9 @@ NULL
177 190
 #' data(msi,package="RNAmodR")
178 191
 #' mi <- msi[[1]]
179 192
 #' modifierType(mi) # The class name of the Modifier object
180
-#' modifierType(msi) #
193
+#' modifierType(msi)
194
+#' seqtype(mi)
195
+#' modType(mi)
181 196
 #' mainScore(mi)
182 197
 #' sequenceData(mi)
183 198
 #' modifications(mi)
... ...
@@ -198,7 +213,8 @@ setClassUnion("list_OR_BamFileList",
198 213
 #' @export
199 214
 setClass("Modifier",
200 215
          contains = c("VIRTUAL"),
201
-         slots = c(mod = "character", # this have to be populated by subclass
216
+         slots = c(seqtype = "character", # this have to be populated by subclass,
217
+                   mod = "character", # this have to be populated by subclass
202 218
                    score = "character", # this have to be populated by subclass
203 219
                    dataType = "list_OR_character", # this have to be populated by subclass
204 220
                    bamfiles = "list_OR_BamFileList",
... ...
@@ -265,7 +281,18 @@ setClass("Modifier",
265 281
 }
266 282
 
267 283
 .valid_Modifier <- function(x){
284
+  if(is.null(x@seqtype)){
285
+    return("'seqtype' slot not populated.")
286
+  }
287
+  if(!.is_valid_nucleotide_seqtype(seqtype(x))){
288
+    return(paste0("'seqtype' slot must contain the character value '",
289
+                  seqtype(RNAString()),"' or '",seqtype(DNAString()),"'."))
290
+  }
268 291
   seqdata <- x@data
292
+  if(seqtype(x) != seqtype(seqdata)){
293
+    return("'seqtype' does not match seqtype() of SequenceData contained ",
294
+           "within Modifier object.")
295
+  }
269 296
   if(is.list(x@bamfiles)){
270 297
     test <- !vapply(x@bamfiles,is,logical(1),"BamFileList")
271 298
     if(any(test)){
... ...
@@ -345,7 +372,9 @@ setMethod(
345 372
         "with",length(object@data),"elements.\n")
346 373
     files <- BiocGenerics::path(object@bamfiles)
347 374
     cat("| Input files:\n",paste0("  - ",names(files),": ",files,"\n"))
348
-    cat("| Modification type(s): ",paste0(object@mod, collapse = " / "),"\n")
375
+    cat("| Nucleotide - Modification type(s): ",
376
+        paste0(seqtype(object), collapse = " / ")," - ",
377
+        paste0(modType(object), collapse = " / "),"\n")
349 378
     cat("| Modifications found:",ifelse(length(object@modifications) != 0L,
350 379
                                       paste0("yes (",
351 380
                                              length(object@modifications),
... ...
@@ -377,6 +406,7 @@ setMethod(
377 406
 setMethod(f = "bamfiles",
378 407
           signature = signature(x = "Modifier"),
379 408
           definition = function(x){x@bamfiles})
409
+
380 410
 #' @rdname Modifier-functions
381 411
 #' @export
382 412
 setMethod(f = "conditions",
... ...
@@ -384,6 +414,7 @@ setMethod(f = "conditions",
384 414
           definition = function(object){
385 415
             object@condition
386 416
           })
417
+
387 418
 #' @rdname Modifier-functions
388 419
 #' @export
389 420
 setMethod(f = "mainScore",
... ...
@@ -430,31 +461,37 @@ setMethod(f = "modifications",
430 461
               x@modifications
431 462
             }
432 463
 )
464
+
433 465
 #' @rdname Modifier-functions
434 466
 #' @export
435 467
 setMethod(f = "modifierType",
436 468
           signature = signature(x = "Modifier"),
437
-          definition = function(x){class(x)[[1]]})
469
+          definition = function(x){class(x)[[1L]]})
470
+
438 471
 #' @rdname Modifier-functions
439 472
 #' @export
440 473
 setMethod(f = "modType",
441 474
           signature = signature(x = "Modifier"),
442 475
           definition = function(x){x@mod})
476
+
443 477
 #' @rdname Modifier-functions
444 478
 #' @export
445 479
 setMethod(f = "dataType",
446 480
           signature = signature(x = "Modifier"),
447 481
           definition = function(x){x@dataType})
482
+
448 483
 #' @rdname Modifier-functions
449 484
 #' @export
450 485
 setMethod(f = "names",
451 486
           signature = signature(x = "Modifier"),
452 487
           definition = function(x){names(sequenceData(x))})
488
+
453 489
 #' @rdname Modifier-functions
454 490
 #' @export
455 491
 setMethod(f = "ranges",
456 492
           signature = signature(x = "Modifier"),
457 493
           definition = function(x){ranges(sequenceData(x))})
494
+
458 495
 #' @rdname Modifier-functions
459 496
 #' @export
460 497
 setMethod(f = "replicates",
... ...
@@ -462,11 +499,55 @@ setMethod(f = "replicates",
462 499
           definition = function(x){
463 500
             x@replicate
464 501
           })
502
+
503
+#' @rdname Modifier-functions
504
+#' @export
505
+setMethod(f = "seqinfo",
506
+          signature = signature(x = "Modifier"),
507
+          definition = function(x){seqinfo(sequenceData(x))}
508
+)
509
+
510
+#' @rdname Modifier-functions
511
+#' @export
512
+setMethod(f = "seqtype",
513
+          signature = signature(x = "Modifier"),
514
+          definition = function(x){x@seqtype}
515
+)
516
+
465 517
 #' @rdname Modifier-functions
466 518
 #' @export
467 519
 setMethod(f = "sequenceData",
468 520
           signature = signature(x = "Modifier"),
469 521
           definition = function(x){x@data})
522
+
523
+.get_modified_sequences <- function(x, modified){
524
+  if(is(x,"Modifier")){
525
+    seqData <- sequenceData(x)
526
+  } else if(is(x,"ModifierSet")) {
527
+    seqData <- sequenceData(x[[1L]])
528
+  } else {
529
+    stop("")
530
+  }
531
+  if(!modified){
532
+    return(sequences(seqData))
533
+  }
534
+  mod <- .get_modifications_per_transcript(x)
535
+  mod <- .rebase_seqnames(mod, mod$Parent)
536
+  mod <- split(mod,factor(mod$Parent, levels = mod$Parent))
537
+  if(seqtype(x) == seqtype(RNAString())){
538
+    ans <- ModRNAStringSet(sequences(seqData))
539
+  } else if(seqtype(x) == seqtype(DNAString())){
540
+    ans <- ModDNAStringSet(sequences(seqData))
541
+  } else {
542
+    stop("")
543
+  }
544
+  modSeqList <- ans[names(ans) %in% names(mod)]
545
+  mod <- mod[match(names(mod),names(modSeqList))]
546
+  ans[names(ans) %in% names(mod)] <-
547
+    Modstrings::combineIntoModstrings(modSeqList, mod)
548
+  ans
549
+}
550
+
470 551
 #' @rdname Modifier-functions
471 552
 #' @export
472 553
 setMethod(f = "sequences",
... ...
@@ -477,32 +558,17 @@ setMethod(f = "sequences",
477 558
                 stop("'modified' has to be a single logical value.",
478 559
                      call. = FALSE)
479 560
               }
480
-              if(!modified){
481
-                return(sequences(sequenceData(x)))
482
-              }
483
-              mod <- .get_modifications_per_transcript(x)
484
-              mod <- .rebase_seqnames(mod, mod$Parent)
485
-              mod <- split(mod,factor(mod$Parent, levels = mod$Parent))
486
-              ans <- ModRNAStringSet(sequences(sequenceData(x)))
487
-              modSeqList <- ans[names(ans) %in% names(mod)]
488
-              mod <- mod[match(names(mod),names(modSeqList))]
489
-              ans[names(ans) %in% names(mod)] <-
490
-                Modstrings::combineIntoModstrings(modSeqList, mod)
491
-              ans
561
+              .get_modified_sequences(x, modified)
492 562
             }
493 563
 )
494
-#' @rdname Modifier-functions
495
-#' @export
496
-setMethod(f = "seqinfo",
497
-          signature = signature(x = "Modifier"),
498
-          definition = function(x){seqinfo(sequenceData(x))}
499
-)
564
+
500 565
 #' @rdname Modifier-functions
501 566
 #' @export
502 567
 setMethod(f = "validAggregate",
503 568
           signature = signature(x = "Modifier"),
504 569
           definition = function(x) x@aggregateValidForCurrentArguments
505 570
 )
571
+
506 572
 #' @rdname Modifier-functions
507 573
 #' @export
508 574
 setMethod(f = "validModification",
... ...
@@ -635,7 +701,7 @@ setReplaceMethod(f = "settings",
635 701
   replicate <- replicates[m]
636 702
   # create Modifier object
637 703
   new(className,
638
-      mod = .norm_mod(proto@mod, className),
704
+      mod = .norm_mod(proto),
639 705
       bamfiles = bamfiles,
640 706
       condition = condition,
641 707
       replicate = replicate,
... ...
@@ -695,7 +761,7 @@ setReplaceMethod(f = "settings",
695 761
   proto <- new(className)
696 762
   # short cut for creating an empty object
697 763
   if(is.null(x)){
698
-    return(new2(className, mod = .norm_mod(proto@mod, className)))
764
+    return(new2(className, mod = .norm_mod(proto)))
699 765
   }
700 766
   bamfiles <- .norm_bamfiles(x, className) # check bam files
701 767
   # settings
... ...
@@ -709,7 +775,8 @@ setReplaceMethod(f = "settings",
709 775
   # get SequenceData
710 776
   data <- .load_SequenceData(dataType(proto), bamfiles = bamfiles,
711 777
                              annotation = annotation, sequences = sequences,
712
-                             seqinfo = seqinfo, args = settings(proto))
778
+                             seqinfo = seqinfo,
779
+                             args = list(settings(proto),seqtype(proto)))
713 780
   .new_ModFromSequenceData(className, data, ...)
714 781
 }
715 782
 
... ...
@@ -723,8 +790,15 @@ setReplaceMethod(f = "settings",
723 790
   ans <- aggregate(ans)
724 791
   # search for modifications
725 792
   if(settings(ans,"find.mod")){
726
-    f <- which(Modstrings::shortName(Modstrings::ModRNAString()) %in% ans@mod)
727
-    modName <- Modstrings::fullName(Modstrings::ModRNAString())[f]
793
+    if(seqtype(ans) == seqtype(RNAString())){
794
+      f <- which(Modstrings::shortName(Modstrings::ModRNAString()) %in% modType(ans))
795
+      modName <- Modstrings::fullName(Modstrings::ModRNAString())[f]
796
+    } else if(seqtype(ans) == seqtype(DNAString())){
797
+      f <- which(Modstrings::shortName(Modstrings::ModDNAString()) %in% modType(ans))
798
+      modName <- Modstrings::fullName(Modstrings::ModDNAString())[f]
799
+    } else {
800
+      stop("")
801
+    }
728 802
     message("Starting to search for '", paste(tools::toTitleCase(modName),
729 803
                                               collapse = "', '"),
730 804
             "' ... ", appendLF = FALSE)
... ...
@@ -1013,3 +1087,17 @@ setMethod(f = "findMod",
1013 1087
                    '",class(x),"'.",call. = FALSE)
1014 1088
             }
1015 1089
 )
1090
+
1091
+# RNAModifier and DNAModifier --------------------------------------------------
1092
+
1093
+#' @rdname Modifier-class
1094
+#' @export
1095
+setClass("RNAModifier",
1096
+         contains = c("VIRTUAL","Modifier"),
1097
+         prototype = list(seqtype = seqtype(RNAString())))
1098
+
1099
+#' @rdname Modifier-class
1100
+#' @export
1101
+setClass("DNAModifier",
1102
+         contains = c("VIRTUAL","Modifier"),
1103
+         prototype = list(seqtype = seqtype(DNAString())))
... ...
@@ -37,9 +37,10 @@ NULL
37 37
 #' \item{\code{type}:} {the modification type used for subsetting. By default 
38 38
 #' this is derived from the \code{modType(x)}, but it can be overwritten using 
39 39
 #' \code{type}. It must be a valid shortName for a modification according to
40
-#' \code{shortName(ModRNAString())} and of course be present in metadata column 
41
-#' \code{mod} of \code{coord}. To disable subsetting based on type, set 
42
-#' \code{type = NA}.}
40
+#' \code{shortName(ModRNAString())} or \code{shortName(ModDNAString())} 
41
+#' (depending on the type of Modifier class) and of course be present in 
42
+#' metadata column \code{mod} of \code{coord}. To disable subsetting based on 
43
+#' type, set \code{type = NA}.}
43 44
 #' \item{\code{flanking}:} {a single integer value to select how many flanking
44 45
 #' position should be included in the subset (default: \code{flanking = 0L}).}
45 46
 #' \item{\code{merge}:} {\code{TRUE} or \code{FALSE}: Should the 
... ...
@@ -17,7 +17,8 @@ setMethod(f = "constructModRanges",
17 17
             if(!.is_valid_modType(modType)){
18 18
               stop("Modification '",modType,"' not found in the short name ",
19 19
                    "alphabet from the Modstrings package. ",
20
-                   "'shortName(ModRNAString())'",call. = FALSE)
20
+                   "'shortName(ModRNAString())' or 'shortName(ModDNAString())'",
21
+                   call. = FALSE)
21 22
             }
22 23
             positions <- as.integer(rownames(data))
23 24
             scores <- do.call(scoreFun,
... ...
@@ -338,7 +338,8 @@ setMethod(
338 338
   signature = signature(object = "ModifierSet"),
339 339
   definition = function(object) {
340 340
     callNextMethod()
341
-    cat("| Modification type(s): ",paste0(object[[1]]@mod, collapse = " / "))
341
+    cat("| Modification type(s): ",
342
+        paste0(modType(object[[1]]),collapse = " / "))
342 343
     mf <- lapply(seq_along(object),
343 344
                  function(i){
344 345
                    o <- object[[i]]
... ...
@@ -399,6 +400,7 @@ setMethod(f = "bamfiles",
399 400
             S4Vectors::SimpleList(lapply(x, bamfiles))
400 401
           }
401 402
 )
403
+
402 404
 #' @rdname Modifier-functions
403 405
 #' @export
404 406
 setMethod(f = "conditions", 
... ...
@@ -407,12 +409,13 @@ setMethod(f = "conditions",
407 409
             ans <- S4Vectors::SimpleList(lapply(object,conditions))
408 410
             ans
409 411
           })
412
+
410 413
 #' @rdname Modifier-functions
411 414
 #' @export
412 415
 setMethod(f = "mainScore", 
413 416
           signature = signature(x = "ModifierSet"),
414
-          definition = function(x) mainScore(new(elementType(x)))
415
-)
417
+          definition = function(x) mainScore(new(elementType(x))))
418
+
416 419
 #' @rdname Modifier-functions
417 420
 #' @export
418 421
 setMethod(f = "modifications", 
... ...
@@ -421,32 +424,33 @@ setMethod(f = "modifications",
421 424
             GenomicRanges::GRangesList(lapply(x,modifications,perTranscript))
422 425
           }
423 426
 )
427
+
424 428
 #' @rdname Modifier-functions
425 429
 #' @export
426 430
 setMethod(f = "modifierType", 
427 431
           signature = signature(x = "ModifierSet"),
428
-          definition = function(x) modifierType(new(elementType(x)))
429
-)
432
+          definition = function(x) modifierType(new(elementType(x))))
433
+
430 434
 #' @rdname Modifier-functions
431 435
 #' @export
432 436
 setMethod(f = "modType", 
433 437
           signature = signature(x = "ModifierSet"),
434
-          definition = function(x) modType(new(elementType(x)))
435
-)
438
+          definition = function(x) modType(new(elementType(x))))
439
+
436 440
 #' @rdname Modifier-functions
437 441
 #' @export
438 442
 setMethod(f = "dataType", 
439 443
           signature = signature(x = "ModifierSet"),
440
-          definition = function(x){dataType(x[[1]])}
441
-)
444
+          definition = function(x){dataType(x[[1L]])})
445
+
442 446
 #' @rdname Modifier-functions
443 447
 #' @export
444 448
 setMethod(f = "ranges", 
445 449
           signature = signature(x = "ModifierSet"),
446 450
           definition = function(x){
447 451
             ranges(x[[1]])
448
-          }
449
-)
452
+          })
453
+
450 454
 #' @rdname Modifier-functions
451 455
 #' @export
452 456
 setMethod(f = "replicates", 
... ...
@@ -455,6 +459,7 @@ setMethod(f = "replicates",
455 459
             ans <- S4Vectors::SimpleList(lapply(x,replicates))
456 460
             ans
457 461
           })
462
+
458 463
 #' @rdname Modifier-functions
459 464
 #' @export
460 465
 setMethod(f = "seqinfo", 
... ...
@@ -463,6 +468,13 @@ setMethod(f = "seqinfo",
463 468
             S4Vectors::SimpleList(lapply(x, seqinfo))
464 469
           }
465 470
 )
471
+
472
+#' @rdname Modifier-functions
473
+#' @export
474
+setMethod(f = "seqtype", 
475
+          signature = signature(x = "ModifierSet"),
476
+          definition = function(x){seqtype(x[[1L]])})
477
+
466 478
 #' @rdname Modifier-functions
467 479
 #' @export
468 480
 setMethod(f = "sequences", 
... ...
@@ -473,18 +485,7 @@ setMethod(f = "sequences",
473 485
                 stop("'modified' has to be a single logical value.",
474 486
                      call. = FALSE)
475 487
               }
476
-              if(!modified){
477
-                return(sequences(sequenceData(x[[1]])))
478
-              }
479
-              mod <- .get_modifications_per_transcript(x)
480
-              mod <- .rebase_seqnames(mod, mod$Parent)
481
-              mod <- split(mod,factor(mod$Parent, levels = mod$Parent))
482
-              ans <- ModRNAStringSet(sequences(sequenceData(x[[1]])))
483
-              modSeqList <- ans[names(ans) %in% names(mod)]
484
-              mod <- mod[match(names(mod),names(modSeqList))]
485
-              ans[names(ans) %in% names(mod)] <- 
486
-                Modstrings::combineIntoModstrings(modSeqList, mod)
487
-              ans
488
+              .get_modified_sequences(x, modified)
488 489
             }
489 490
 )
490 491
 
... ...
@@ -70,8 +70,9 @@ NULL
70 70
 #' @import BiocGenerics
71 71
 #' @import XVector
72 72
 #' @importFrom Biostrings DNAString RNAString DNAStringSet RNAStringSet getSeq
73
-#' @importFrom Modstrings ModRNAString ModRNAStringSet combineIntoModstrings
74
-#' shortName fullName
73
+#' seqtype seqtype<-
74
+#' @importFrom Modstrings ModRNAString ModRNAStringSet ModDNAString 
75
+#' ModDNAStringSet combineIntoModstrings shortName fullName
75 76
 #' @importClassesFrom IRanges IntegerList CharacterList LogicalList IRanges
76 77
 #' SplitDataFrameList PartitioningByEnd PartitioningByWidth
77 78
 #' @importFrom IRanges IntegerList CharacterList LogicalList IRanges
... ...
@@ -89,7 +89,8 @@ NULL
89 89
 #' description of this argument.
90 90
 #' 
91 91
 #' @slot sequencesType a \code{character} value for the class name of 
92
-#' \code{sequences}. Either \code{RNAStringSet} or \code{ModRNAStringSet}.
92
+#' \code{sequences}. Either \code{RNAStringSet}, \code{ModRNAStringSet}, 
93
+#' \code{DNAStringSet} or \code{ModDNAStringSet}.
93 94
 #' @slot minQuality a \code{integer} value describing a threshold of the minimum
94 95
 #' quality of reads to be used.
95 96
 #' 
... ...
@@ -98,12 +99,10 @@ NULL
98 99
 
99 100
 setClass("SequenceData",
100 101
          contains = c("VIRTUAL", "CompressedSplitDataFrameList"),
101
-         slots = c(sequencesType = "character",
102
-                   minQuality = "integer",
102
+         slots = c(minQuality = "integer",
103 103
                    unlistData = "SequenceDataFrame",
104 104
                    unlistType = "character",
105
-                   dataDescription = "character"),
106
-         prototype = list(sequencesType = "RNAStringSet"))
105
+                   dataDescription = "character"))
107 106
 
108 107
 setMethod(
109 108
   f = "initialize",
... ...
@@ -112,9 +111,6 @@ setMethod(
112 111
     if(!assertive::is_a_non_empty_string(.Object@dataDescription)){
113 112
       stop("'dataDescription' must be a single non empty character value.")
114 113
     }
115
-    if(!(.Object@sequencesType %in% c("RNAStringSet","ModRNAStringSet"))){
116
-      stop("'sequencesType' must be either 'RNAStringSet' or 'ModRNAStringSet'")
117
-    }
118 114
     callNextMethod(.Object, ...)
119 115
   }
120 116
 )
... ...
@@ -469,9 +465,6 @@ setMethod("unlist", "SequenceData",
469 465
   if(!assertive::is_a_non_empty_string(proto@dataDescription)){
470 466
     stop("'dataDescription' must be a single non empty character value.")
471 467
   }
472
-  if(!(proto@sequencesType %in% c("RNAStringSet","ModRNAStringSet"))){
473
-    stop("'sequencesType' must be either 'RNAStringSet' or 'ModRNAStringSet'")
474
-  }
475 468
   if(is.null(minQuality)){
476 469
     stop("Minimum quality is not set for '", className ,"'.",
477 470
          call. = FALSE)
... ...
@@ -508,7 +501,6 @@ setMethod("unlist", "SequenceData",
508 501
   rownames(data) <- IRanges::CharacterList(positions)
509 502
   data <- .order_read_data_by_strand(data, ranges)
510 503
   # order sequences
511
-  sequences <- as(sequences, proto@sequencesType)
512 504
   sequences <- sequences[match(names(ranges), names(sequences))]
513 505
   # basic checks
514 506
   names(data) <- names(ranges)
... ...
@@ -540,16 +532,20 @@ setMethod("unlist", "SequenceData",
540 532
 .SequenceData_settings <- data.frame(
541 533
   variable = c("max_depth",
542 534
                "minLength",
543
-               "maxLength"),
535
+               "maxLength",
536
+               "seqtype"),
544 537
   testFUN = c(".not_integer_bigger_than_10",
545 538
               ".not_integer_bigger_equal_than_zero_nor_na",
546
-              ".not_integer_bigger_equal_than_one_nor_na"),
539
+              ".not_integer_bigger_equal_than_one_nor_na",
540
+              ".is_valid_nucleotide_seqtype"),
547 541
   errorValue = c(TRUE,
548 542
                  TRUE,
549
-                 TRUE),
543
+                 TRUE,
544
+                 FALSE),
550 545
   errorMessage = c("'max_depth' must be integer with a value higher than 10L.",
551 546
                    "'minLength' must be integer with a value higher than 0L or NA.",
552
-                   "'maxLength' must be integer with a value higher than 1L or NA."),
547
+                   "'maxLength' must be integer with a value higher than 1L or NA.",
548
+                   paste0("'seqtype' must be either '",seqtype(RNAString()) ,"' or '",seqtype(DNAString()) ,"'.")),
553 549
   stringsAsFactors = FALSE)
554 550
 
555 551
 .get_SequenceData_args <- function(input){
... ...
@@ -557,8 +553,9 @@ setMethod("unlist", "SequenceData",
557 553
   max_depth <- 10000L # the default is 250, which is to small
558 554
   minLength <- NA_integer_
559 555
   maxLength <- NA_integer_
556
+  seqtype <- seqtype(RNAString()) 
560 557
   args <- .norm_settings(input, .SequenceData_settings, max_depth, minLength,
561
-                         maxLength)
558
+                         maxLength, seqtype)
562 559
   if(!is.na(args[["minLength"]]) && !is.na(args[["maxLength"]])){
563 560
     if(args[["minLength"]] > args[["maxLength"]]){
564 561
       stop("'minLength' must be smaller or equal to 'maxLength'.",
... ...
@@ -596,7 +593,7 @@ setMethod("unlist", "SequenceData",
596 593
       stop("No overlap between bamfiles, annotation and seqinfo.")
597 594
     }
598 595
   }
599
-  sequences <- .load_transcript_sequences(sequences, grl)
596
+  sequences <- .load_sequences(sequences, grl, args)
600 597
   # create the class
601 598
   .SequenceData(className, bamfiles, grl, sequences, seqinfo, args)
602 599
 }
... ...
@@ -643,11 +640,12 @@ setMethod("unlist", "SequenceData",
643 640
 #' @importFrom Biostrings xscat
644 641
 # load the transcript sequence per transcript aka. one sequence per GRangesList
645 642
 # element
646
-.load_transcript_sequences <- function(sequences, grl){
643
+.load_sequences <- function(sequences, grl, args){
647 644
   seq <- Biostrings::getSeq(sequences, unlist(grl))
648 645
   seq <- relist(unlist(seq),IRanges::PartitioningByWidth(sum(width(grl))))
649 646
   names(seq) <- names(grl)
650
-  as(seq,"RNAStringSet")
647
+  seqtype(seq) <- args[["seqtype"]]
648
+  seq
651 649
 }
652 650
 
653 651
 # remove any elements, which are not in the seqinfo
... ...
@@ -788,11 +786,13 @@ setMethod("getData",
788 786
 setMethod(f = "bamfiles", 
789 787
           signature = signature(x = "SequenceData"),
790 788
           definition = function(x){bamfiles(unlist(x))})
789
+
791 790
 #' @rdname SequenceData-functions
792 791
 #' @export
793 792
 setMethod(f = "conditions", 
794 793
           signature = signature(object = "SequenceData"),
795 794
           definition = function(object){conditions(unlist(object))})
795
+
796 796
 #' @rdname SequenceData-functions
797 797
 #' @export
798 798
 setMethod(
... ...
@@ -810,21 +810,41 @@ setMethod(
810 810
       names(partitioning_relist) <- names(x)
811 811
       relist(unlisted_ranges, partitioning_relist)
812 812
     })
813
+
813 814
 #' @rdname SequenceData-functions
814 815
 #' @export
815 816
 setMethod(f = "replicates", 
816 817
           signature = signature(x = "SequenceData"),
817 818
           definition = function(x){replicates(unlist(x))})
819
+
818 820
 #' @rdname SequenceData-functions
819 821
 #' @export
820 822
 setMethod(f = "seqinfo", 
821 823
           signature = signature(x = "SequenceData"),
822 824
           definition = function(x){seqinfo(unlist(x))})
825
+
823 826
 #' @rdname SequenceData-functions
824 827
 #' @export
825 828
 setMethod(f = "sequences", 
826 829
           signature = signature(x = "SequenceData"),
827 830
           definition = function(x){relist(sequences(unlist(x)),x)})
831
+
832
+#' @rdname SequenceData-functions
833
+#' @export
834
+setMethod(f = "seqtype", 
835
+          signature = signature(x = "SequenceData"),
836
+          definition = function(x){seqtype(unlist(x))})
837
+
838
+#' @rdname SequenceData-functions
839
+#' @export
840
+setReplaceMethod(f = "seqtype", 
841
+                 signature = signature(x = "SequenceData"),
842
+                 definition = function(x, value){
843
+                   unlisted_x <- unlist(x)
844
+                   seqtype(unlisted_x) <- value
845
+                   relist(unlisted_x,x)
846
+                 })
847
+
828 848
 #' @rdname SequenceData-functions
829 849
 #' @export
830 850
 setMethod(f = "dataType",
... ...
@@ -41,8 +41,10 @@ NULL
41 41
 .norm_subset_args <- function(input,x){
42 42
   name <- NA_character_
43 43
   if(is(x,"Modifier") || is(x,"ModifierSet")){
44
+    seqtype <- seqtype(x)
44 45
     type <- modType(x)
45 46
   } else {
47
+    seqtype <- NA_character_
46 48
     type <- NA_character_
47 49
   }
48 50
   merge <- TRUE
... ...
@@ -53,8 +55,9 @@ NULL
53 55
   args <- .norm_settings(input, .subset_settings, name, type, merge, flanking,
54 56
                          perTranscript, sequenceData, rawData)
55 57
   if(all(!is.na(args[["type"]]))){
56
-    if(any(!.is_valid_modType(args[["type"]]))){
57
-      stop("'type' must be one or more elements of shortName(ModRNAString()).",
58
+    if(any(!.is_valid_modType(args[["type"]], seqtype))){
59
+      stop("'type' must be one or more elements of 'shortName(ModRNAString())'",
60
+           " or 'shortName(ModDNAString())'.",
58 61
            call. = FALSE)
59 62
     }
60 63
   }
... ...
@@ -216,22 +216,22 @@ NULL
216 216
                        args[["sequence.track.pars"]]))
217 217
     track
218 218
   }
219
-  if(!is(seq,"DNAStringSet") && 
220
-     !is(seq,"RNAStringSet") && 
221
-     !is(seq,"ModRNAStringSet")){
219
+  if(!is(seq,"DNAStringSet") &&  !is(seq,"RNAStringSet") && 
220
+     !is(seq,"ModRNAStringSet") && !is(seq,"ModDNAStringSet")){
222 221
     stop("Invalid sequence type '",class(seq),"'. sequences(x) must be a ",
223
-         "RNA/ModRNA/DNAStringSet.",
222
+         "RNA/ModRNA/DNA/ModDNA*StringSet.",
224 223
          call. = FALSE)
225 224
   }
226
-  if(is(seq,"DNAStringSet")){
227
-    seq <- as(seq,"RNAStringSet")
228
-  }
229 225
   # reconstruct the chromosomal sequences for plotting
230 226
   seq <- .stitch_chromosome(seq, ranges, chromosome)
231 227
   if(is(seq,"RNAStringSet")){
232 228
     st <- FUN("RNASequenceTrack","RNAStringSet", seq, args)
233 229
   } else if(is(seq,"ModRNAStringSet")){
234 230
     st <- FUN("ModRNASequenceTrack","ModRNAStringSet", seq, args)
231
+  } else if(is(seq,"DNAStringSet")){
232
+    st <- FUN("SequenceTrack","DNAStringSet", seq, args)
233
+  } else if(is(seq,"ModDNAStringSet")){
234
+    st <- FUN("ModDNASequenceTrack","ModDNAStringSet", seq, args)
235 235
   } else {
236 236
     stop("")
237 237
   }
... ...
@@ -16,10 +16,12 @@ NULL
16 16
 #' \code{SequenceDataList} or a \code{SequenceDataFrame} object.
17 17
 #' @param bamfiles a \code{BamFileList}.
18 18
 #' @param grl a \code{GRangesList} from \code{exonsBy(..., by = "tx")}
19
-#' @param sequences a \code{XStringSet} of type \code{RNAStringSet} or 
20
-#' \code{ModRNAStringSet}
19
+#' @param sequences a \code{XStringSet} of type \code{RNAStringSet}, 
20
+#' \code{ModRNAStringSet}, \code{DNAStringSet} or 
21
+#' \code{ModDNAStringSet}
21 22
 #' @param param a \code{\link[Rsamtools:ScanBamParam-class]{ScanBamParam}} 
22 23
 #' object
24
+#' @param value a new \code{seqtype}, either "RNA" or "DNA"
23 25
 #' @param args a list of addition arguments
24 26
 #' 
25 27
 #' @return 
... ...
@@ -151,9 +153,23 @@ setMethod("show", "SequenceDataFrame",
151 153
 #' @rdname SequenceData-functions
152 154
 #' @export
153 155
 setMethod(
154
-  f = "sequences", 
156
+  f = "conditions", 
157
+  signature = signature(object = "SequenceDataFrame"),
158
+  definition = function(object){object@condition})
159
+
160
+#' @rdname SequenceData-functions
161
+#' @export
162
+setMethod(
163
+  f = "bamfiles", 
155 164
   signature = signature(x = "SequenceDataFrame"),
156
-  definition = function(x){x@sequence})
165
+  definition = function(x){x@bamfiles})
166
+
167
+#' @rdname SequenceData-functions
168
+#' @export
169
+setMethod(f = "dataType",
170
+          signature = signature(x = "SequenceDataFrame"),
171
+          definition = function(x){gsub("SequenceDataFrame","",class(x))})
172
+
157 173
 #' @rdname SequenceData-functions
158 174
 #' @export
159 175
 setMethod(
... ...
@@ -167,29 +183,48 @@ setMethod(
167 183
   f = "replicates", 
168 184
   signature = signature(x = "SequenceDataFrame"),
169 185
   definition = function(x){x@replicate})
186
+
170 187
 #' @rdname SequenceData-functions
171 188
 #' @export
172 189
 setMethod(
173
-  f = "conditions", 
174
-  signature = signature(object = "SequenceDataFrame"),
175
-  definition = function(object){object@condition})
190
+  f = "seqinfo", 
191
+  signature = signature(x = "SequenceDataFrame"),
192
+  definition = function(x){x@seqinfo})
193
+
176 194
 #' @rdname SequenceData-functions
177 195
 #' @export
178 196
 setMethod(
179
-  f = "bamfiles", 
197
+  f = "seqinfo", 
180 198
   signature = signature(x = "SequenceDataFrame"),
181
-  definition = function(x){x@bamfiles})
199
+  definition = function(x){x@seqinfo})
200
+
182 201
 #' @rdname SequenceData-functions
183 202
 #' @export
184 203
 setMethod(
185
-  f = "seqinfo", 
204
+  f = "seqtype", 
186 205
   signature = signature(x = "SequenceDataFrame"),
187
-  definition = function(x){x@seqinfo})
206
+  definition = function(x){seqtype(sequences(x))})
207
+
188 208
 #' @rdname SequenceData-functions
189 209
 #' @export
190
-setMethod(f = "dataType",
191
-          signature = signature(x = "SequenceDataFrame"),
192
-          definition = function(x){gsub("SequenceDataFrame","",class(x))})
210
+setReplaceMethod(
211
+  f = "seqtype", 
212
+  signature = signature(x = "SequenceDataFrame"),
213
+  definition = function(x, value){
214
+    if(!(value %in% c(seqtype(DNAString()),seqtype(RNAString())))){
215
+      stop("Invalid new seqtype.")
216
+    }
217
+    seqtype(x@sequence) <- value
218
+    x
219
+  }
220
+)
221
+
222
+#' @rdname SequenceData-functions
223
+#' @export
224
+setMethod(
225
+  f = "sequences", 
226
+  signature = signature(x = "SequenceDataFrame"),
227
+  definition = function(x){x@sequence})
193 228
 
194 229
 # internals for SequenceDataFrame ----------------------------------------------
195 230
 
... ...
@@ -437,6 +472,9 @@ sequenceDataFrameClass <- function(dataType){
437 472
   if(nrow(x) != length(sequences(x))){
438 473
     return("data length and sequence length do not match.")
439 474
   }
475
+  if(!is(sequences(x),"RNAString") && !is(sequences(x),"DNAString")){
476
+    stop("")
477
+  }
440 478
   S4Vectors:::.valid.DataFrame(x)
441 479
   NULL
442 480
 }
... ...
@@ -204,6 +204,7 @@ setMethod(f = "bamfiles",
204 204
             names(ans) <- names(x@listData)
205 205
             ans
206 206
           })
207
+
207 208
 #' @rdname SequenceData-functions
208 209
 #' @export
209 210
 setMethod(f = "conditions", 
... ...
@@ -212,20 +213,23 @@ setMethod(f = "conditions",
212 213
             ans <- S4Vectors::SimpleList(lapply(object,conditions))
213 214
             ans
214 215
           })
216
+
215 217
 #' @rdname SequenceData-functions
216 218
 #' @export
217 219
 setMethod(f = "names", 
218 220
           signature = signature(x = "SequenceDataList"),
219 221
           definition = function(x){
220
-            names(x[[1]])
222
+            names(x[[1L]])
221 223
           })
224
+
222 225
 #' @rdname SequenceData-functions
223 226
 #' @export
224 227
 setMethod(f = "ranges", 
225 228
           signature = signature(x = "SequenceDataList"),
226 229
           definition = function(x){
227
-            ranges(x[[1]])
230
+            ranges(x[[1L]])
228 231
           })
232
+
229 233
 #' @rdname SequenceData-functions
230 234
 #' @export
231 235
 setMethod(f = "replicates", 
... ...
@@ -234,19 +238,35 @@ setMethod(f = "replicates",
234 238
             ans <- S4Vectors::SimpleList(lapply(x,replicates))
235 239
             ans
236 240
           })
241
+
237 242
 #' @rdname SequenceData-functions
238 243
 #' @export
239 244
 setMethod(f = "seqinfo", 
240 245
           signature = signature(x = "SequenceDataList"),
241 246
           definition = function(x){
242
-            seqinfo(x[[1]])
247
+            seqinfo(x[[1L]])
243 248
           })
249
+
250
+#' @rdname SequenceData-functions
251
+#' @export
252
+setMethod(f = "seqtype", 
253
+          signature = signature(x = "SequenceDataList"),
254
+          definition = function(x){seqtype(x[[1L]])})
255
+
256
+#' @rdname SequenceData-functions
257
+#' @export
258
+setReplaceMethod(f = "seqtype", 
259
+                 signature = signature(x = "SequenceDataList"),
260
+                 definition = function(x, value){
261
+                   as(lapply(x,`seqtype<-`,value),"SequenceDataList")
262
+                 })
263
+
244 264
 #' @rdname SequenceData-functions
245 265
 #' @export
246 266
 setMethod(f = "sequences", 
247 267
           signature = signature(x = "SequenceDataList"),
248 268
           definition = function(x){
249
-            sequences(x[[1]])
269
+            sequences(x[[1L]])
250 270
           })
251 271
 
252 272
 # aggregate --------------------------------------------------------------------
... ...
@@ -244,26 +244,34 @@ setAs("ANY", "SequenceDataSet",
244 244
 
245 245
 #' @rdname SequenceData-functions
246 246
 #' @export
247
-setMethod(f = "seqinfo", 
247
+setMethod(f = "bamfiles", 
248 248
           signature = signature(x = "SequenceDataSet"),
249 249
           definition = function(x){
250
-            seqinfo(x[[1]])
250
+            bamfiles(x[[1L]])
251 251
           })
252 252
 
253 253
 #' @rdname SequenceData-functions
254 254
 #' @export
255
-setMethod(f = "names", 
256
-          signature = signature(x = "SequenceDataSet"),
257
-          definition = function(x){
258
-            names(x[[1]])
255
+setMethod(f = "conditions", 
256
+          signature = signature(object = "SequenceDataSet"),
257
+          definition = function(object){
258
+            ans <- IRanges::FactorList(
259
+              lapply(object[1L],
260
+                     function(o){
261
+                       ia <- as.integer(interaction(conditions(o),
262
+                                                    replicates(o)))
263
+                       m <- match(unique(ia),ia)
264
+                       conditions(o)[m]
265
+                     }))
266
+            ans[[1L]]
259 267
           })
260 268
 
261 269
 #' @rdname SequenceData-functions
262 270
 #' @export
263
-setMethod(f = "sequences", 
271
+setMethod(f = "names", 
264 272
           signature = signature(x = "SequenceDataSet"),
265 273
           definition = function(x){
266
-            sequences(x[[1]])
274
+            names(x[[1L]])
267 275
           })
268 276
 
269 277
 #' @rdname SequenceData-functions
... ...
@@ -271,45 +279,53 @@ setMethod(f = "sequences",
271 279
 setMethod(f = "ranges", 
272 280
           signature = signature(x = "SequenceDataSet"),
273 281
           definition = function(x){
274
-            ranges(x[[1]])
282
+            ranges(x[[1L]])
275 283
           })
276 284
 
277 285
 #' @rdname SequenceData-functions
278 286
 #' @export
279
-setMethod(f = "bamfiles", 
287
+setMethod(f = "replicates", 
280 288
           signature = signature(x = "SequenceDataSet"),
281 289
           definition = function(x){
282
-            bamfiles(x[[1]])
283
-          })
284
-#' @rdname SequenceData-functions
285
-#' @export
286
-setMethod(f = "conditions", 
287
-          signature = signature(object = "SequenceDataSet"),
288
-          definition = function(object){
289 290
             ans <- IRanges::FactorList(
290
-              lapply(object[1L],
291
+              lapply(x[1L],
291 292
                      function(o){
292 293
                        ia <- as.integer(interaction(conditions(o),
293 294
                                                     replicates(o)))
294 295
                        m <- match(unique(ia),ia)
295
-                       conditions(o)[m]
296
+                       replicates(o)[m]
296 297
                      }))
297 298
             ans[[1L]]
298 299
           })
300
+
299 301
 #' @rdname SequenceData-functions
300 302
 #' @export
301
-setMethod(f = "replicates", 
303
+setMethod(f = "seqinfo", 
302 304
           signature = signature(x = "SequenceDataSet"),
303 305
           definition = function(x){
304
-            ans <- IRanges::FactorList(
305
-              lapply(x[1L],
306
-                     function(o){
307
-                       ia <- as.integer(interaction(conditions(o),
308
-                                                    replicates(o)))
309
-                       m <- match(unique(ia),ia)
310
-                       replicates(o)[m]
311
-                     }))
312
-            ans[[1L]]
306
+            seqinfo(x[[1L]])
307
+          })
308
+
309
+#' @rdname SequenceData-functions
310
+#' @export
311
+setMethod(f = "seqtype", 
312
+          signature = signature(x = "SequenceDataSet"),
313
+          definition = function(x){seqtype(x[[1L]])})
314
+
315
+#' @rdname SequenceData-functions
316
+#' @export
317
+setReplaceMethod(f = "seqtype", 
318
+                 signature = signature(x = "SequenceDataSet"),
319
+                 definition = function(x, value){
320
+                   as(lapply(x,`seqtype<-`,value),"SequenceDataSet")
321
+                 })
322
+
323
+#' @rdname SequenceData-functions
324
+#' @export
325
+setMethod(f = "sequences", 
326
+          signature = signature(x = "SequenceDataSet"),
327
+          definition = function(x){
328
+            sequences(x[[1L]])
313 329
           })
314 330
 
315 331
 # aggregate --------------------------------------------------------------------
... ...
@@ -254,14 +254,15 @@ SAMPLE_TYPES <- c("treated","control")
254 254
   x
255 255
 }
256 256
 
257
-.norm_mod <- function(mod, className){
258
-  f <- .is_valid_modType(mod)
259
-  if(length(which(f)) != length(mod)){
260
-    stop("Modification '",mod[!f],"' as defined for ",className," does not ",
261
-         "exist in the Modstrings dictionary for modified RNA sequences.",
257
+.norm_mod <- function(x){
258
+  modType <- modType(x)
259
+  f <- .is_valid_modType(modType, seqtype(x))
260
+  if(length(which(f)) != length(modType)){
261
+    stop("Modification '",modType[!f],"' as defined for ",class(x)," does not ",
262
+         "exist in the Modstrings dictionary for modified RNA/DNA sequences.",
262 263
          call. = FALSE)
263 264
   }
264
-  mod
265
+  modType
265 266
 }
266 267
 
267 268
 # check data validity ----------------------------------------------------------
... ...
@@ -1,12 +1,33 @@
1 1
 #' @include RNAmodR.R
2 2
 NULL
3 3
 
4
-# Modstrings related helper functions ------------------------------------------
4
+# Biostrings/Modstrings related helper functions -------------------------------
5 5
 
6
-.is_valid_modType <- function(modType){
6
+.is_valid_modType <- function(modType, seqtype = NA){
7
+  if(is.na(seqtype)){
8
+    return(.is_valid_RNAmodType(modType) | .is_valid_DNAmodType(modType))
9
+  }
10
+  if(seqtype == seqtype(RNAString())){
11
+    .is_valid_RNAmodType(modType)
12
+  } else if(seqtype == seqtype(DNAString())){
13
+    .is_valid_DNAmodType(modType)
14
+  } else {
15
+    stop("")
16
+  }
17
+}
18
+
19
+.is_valid_RNAmodType <- function(modType){
7 20
   modType %in% Modstrings::shortName(Modstrings::ModRNAString())
8 21
 }
9 22
 
23
+.is_valid_DNAmodType <- function(modType){
24
+  modType %in% Modstrings::shortName(Modstrings::ModDNAString())
25
+}
26
+
27
+.is_valid_nucleotide_seqtype <- function(seqtype){
28
+  seqtype %in% c(seqtype(RNAString()),seqtype(DNAString()))
29
+}
30
+
10 31
 # testthat
11 32
 
12 33
 .test_test_TRUE <- function(x){TRUE}
13 34
Binary files a/data/csd.rda and b/data/csd.rda differ
14 35
Binary files a/data/e3sd.rda and b/data/e3sd.rda differ
15 36
Binary files a/data/e5sd.rda and b/data/e5sd.rda differ
16 37
Binary files a/data/esd.rda and b/data/esd.rda differ
17 38
Binary files a/data/msi.rda and b/data/msi.rda differ
18 39
Binary files a/data/ne3sd.rda and b/data/ne3sd.rda differ
19 40
Binary files a/data/ne5sd.rda and b/data/ne5sd.rda differ
20 41
Binary files a/data/pesd.rda and b/data/pesd.rda differ
21 42
Binary files a/data/psd.rda and b/data/psd.rda differ
22 43
Binary files a/data/sdl.rda and b/data/sdl.rda differ
23 44
Binary files a/data/sds.rda and b/data/sds.rda differ
24 45
new file mode 100644
... ...
@@ -0,0 +1,31 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/Gviz-ModifiedSequenceTrack-class.R
3
+\docType{class}
4
+\name{ModDNASequenceTrack}
5
+\alias{ModDNASequenceTrack}
6
+\alias{ModDNASequenceTrack-class}
7
+\title{ModDNASequenceTrack}
8
+\usage{
9
+ModDNASequenceTrack(sequence, chromosome, genome, ...)
10
+}
11
+\arguments{
12
+\item{sequence}{A \code{character} vector or \code{ModDNAString} object of 
13
+length one. The sequence to display. See 
14
+\code{\link[Gviz:SequenceTrack-class]{SequenceTrack}}.}
15
+
16
+\item{chromosome, genome, ...}{See 
17
+\code{\link[Gviz:SequenceTrack-class]{SequenceTrack}}.}
18
+}
19
+\value{
20
+a \code{ModDNASequenceTrack} object
21
+}
22
+\description{
23
+A \code{Gviz} compatible 
24
+\code{\link[Gviz:SequenceTrack-class]{SequenceTrack}} for showing modified 
25
+DNA sequences.
26
+}
27
+\examples{
28
+seq <- ModDNAStringSet(c(chr1 = paste0(alphabet(ModDNAString()),collapse = "")))
29
+st <- ModDNASequenceTrack(seq)
30
+Gviz::plotTracks(st, chromosome = "chr1",from = 1L, to = 20L)
31
+}
... ...
@@ -10,6 +10,8 @@
10 10
 \alias{Modifier,character-method}
11 11
 \alias{Modifier,list-method}
12 12
 \alias{Modifier,BamFileList-method}
13
+\alias{RNAModifier-class}
14
+\alias{DNAModifier-class}
13 15
 \title{The Modifier class}
14 16
 \usage{
15 17
 Modifier(className, x, annotation, sequences, seqinfo, ...)
... ...
@@ -83,8 +85,13 @@ high throughput sequencing data.
83 85
 Each subclass has to implement the following functions:
84 86
 
85 87
 \itemize{
86
-\item{\code{\link{aggregateData}}: }{used for specific data aggregation}
87
-\item{\code{\link{findMod}}: }{used for specific search for modifications}
88
+\item{Slot \code{nucleotide}: } {Either "RNA" or "DNA". For conveniance the
89
+subclasses \code{RNAModifier} and \code{DNAModifier} are already available
90
+and can be inherited from.}
91
+\item{Function \code{\link{aggregateData}}: }{used for specific data 
92
+aggregation}
93
+\item{Function \code{\link{findMod}}: }{used for specific search for 
94
+modifications}
88 95
 }
89 96
 
90 97
 Optionally the function \code{\link[=Modifier-functions]{settings<-}} can be
... ...
@@ -99,9 +106,13 @@ not set to \code{FALSE}.
99 106
 \section{Slots}{
100 107
 
101 108
 \describe{
109
+\item{\code{nucleotide}}{a \code{character} value, which needs to contain "RNA" or 
110
+"DNA"}
111
+
102 112
 \item{\code{mod}}{a \code{character} value, which needs to contain one or more
103 113
 elements from the alphabet of a
104
-\code{\link[Modstrings:ModRNAString]{ModRNAString}} class.}
114
+\code{\link[Modstrings:ModRNAString]{ModRNAString}} or 
115
+\code{\link[Modstrings:ModDNAString]{ModDNAString}} class.}
105 116
 
106 117
 \item{\code{score}}{the main score identifier used for visualizations}
107 118
 
... ...
@@ -23,9 +23,10 @@
23 23
 \alias{names,Modifier-method}
24 24
 \alias{ranges,Modifier-method}
25 25
 \alias{replicates,Modifier-method}
26
+\alias{seqinfo,Modifier-method}
27
+\alias{seqtype,Modifier-method}
26 28
 \alias{sequenceData,Modifier-method}
27 29
 \alias{sequences,Modifier-method}
28
-\alias{seqinfo,Modifier-method}
29 30
 \alias{validAggregate,Modifier-method}
30 31
 \alias{validModification,Modifier-method}
31 32
 \alias{show,ModifierSet-method}
... ...
@@ -39,6 +40,7 @@
39 40
 \alias{ranges,ModifierSet-method}
40 41
 \alias{replicates,ModifierSet-method}
41 42
 \alias{seqinfo,ModifierSet-method}
43
+\alias{seqtype,ModifierSet-method}
42 44
 \alias{sequences,ModifierSet-method}
43 45
 \title{Modifier/ModifierSet functions}
44 46
 \usage{
... ...
@@ -80,12 +82,14 @@ validModification(x)
80 82
 
81 83
 \S4method{replicates}{Modifier}(x)
82 84
 
85
+\S4method{seqinfo}{Modifier}(x)
86
+
87
+\S4method{seqtype}{Modifier}(x)
88
+
83 89
 \S4method{sequenceData}{Modifier}(x)
84 90
 
85 91
 \S4method{sequences}{Modifier}(x, modified = FALSE)
86 92
 
87
-\S4method{seqinfo}{Modifier}(x)
88
-
89 93
 \S4method{validAggregate}{Modifier}(x)
90 94
 
91 95
 \S4method{validModification}{Modifier}(x)
... ...
@@ -112,6 +116,8 @@ validModification(x)
112 116
 
113 117
 \S4method{seqinfo}{ModifierSet}(x)
114 118
 
119
+\S4method{seqtype}{ModifierSet}(x)
120
+
115 121
 \S4method{sequences}{ModifierSet}(x, modified = FALSE)
116 122
 }
117 123
 \arguments{
... ...
@@ -120,8 +126,9 @@ validModification(x)
120 126
 \item{...}{Additional arguments.}
121 127
 
122 128
 \item{modified}{For \code{sequences}: \code{TRUE} or \code{FALSE}: Should
123
-the sequences be returned as a \code{ModRNAString} with the found
124
-modifications added on top of the \code{RNAString}? See
129
+the sequences be returned as a \code{ModRNAString}/\code{ModDNAString} with
130
+the found modifications added on top of the \code{RNAString}/
131
+\code{DNAString}? See 
125 132
 \code{\link[Modstrings:separate]{combineIntoModstrings}}.}
126 133
 
127 134
 \item{perTranscript}{\code{TRUE} or \code{FALSE}: Should the positions shown
... ...
@@ -131,6 +138,10 @@ per transcript? (default: \code{perTranscript = FALSE})}
131 138
 \itemize{
132 139
 \item{\code{modifierType}:} {a character vector with the appropriate class
133 140
 Name of a \code{\link[=Modifier-class]{Modifier}}.}
141
+\item{\code{modType}:} {a character vector with the modifications detected by
142
+the \code{Modifier} class.}
143
+\item{\code{seqtype}:} {a single character value defining if either
144
+"RNA" or "DNA" modifications are detected by the \code{Modifier} class.}
134 145
 \item{\code{mainScore}:} {a character vector.}
135 146
 \item{\code{sequenceData}:} {a \code{SequenceData} object.}
136 147
 \item{\code{modifications}:} {a \code{GRanges} or \code{GRangesList} object
... ...
@@ -159,7 +170,9 @@ loaded. This potentially invalidates them. To update the data, run the
159 170
 data(msi,package="RNAmodR")
160 171
 mi <- msi[[1]]
161 172
 modifierType(mi) # The class name of the Modifier object
162
-modifierType(msi) #
173
+modifierType(msi)
174
+seqtype(mi)
175
+modType(mi)
163 176
 mainScore(mi)
164 177
 sequenceData(mi)
165 178
 modifications(mi)
... ...
@@ -153,7 +153,8 @@ Subsetting of a \code{SequenceDataFrame} returns a \code{SequenceDataFrame} or
153 153
 
154 154
 \describe{
155 155
 \item{\code{sequencesType}}{a \code{character} value for the class name of
156
-\code{sequences}. Either \code{RNAStringSet} or \code{ModRNAStringSet}.}
156
+\code{sequences}. Either \code{RNAStringSet}, \code{ModRNAStringSet},
157
+\code{DNAStringSet} or \code{ModDNAStringSet}.}
157 158
 
158 159
 \item{\code{minQuality}}{a \code{integer} value describing a threshold of the minimum
159 160
 quality of reads to be used.}
... ...
@@ -7,13 +7,15 @@
7 7
 \alias{SequenceData-functions}
8 8
 \alias{replicates}
9 9
 \alias{show,SequenceDataFrame-method}
10
-\alias{sequences,SequenceDataFrame-method}
11
-\alias{ranges,SequenceDataFrame-method}
12
-\alias{replicates,SequenceDataFrame-method}
13 10
 \alias{conditions,SequenceDataFrame-method}
14 11
 \alias{bamfiles,SequenceDataFrame-method}
15
-\alias{seqinfo,SequenceDataFrame-method}
16 12
 \alias{dataType,SequenceDataFrame-method}
13
+\alias{ranges,SequenceDataFrame-method}
14
+\alias{replicates,SequenceDataFrame-method}
15
+\alias{seqinfo,SequenceDataFrame-method}
16
+\alias{seqtype,SequenceDataFrame-method}
17
+\alias{seqtype<-,SequenceDataFrame-method}
18
+\alias{sequences,SequenceDataFrame-method}
17 19
 \alias{show,SequenceData-method}
18 20
 \alias{getData,SequenceData,BamFileList,GRangesList,XStringSet,ScanBamParam-method}
19