1 Introduction

Most nucleic acids, regardless of their being DNA or RNA, contain modified nucleotides, which enhances the normal function of encoding genetic information. They have usually a regulatory function and/or modify folding behavior and molecular interactions.

RNA are nearly always post-transcriptionally modified. Most prominent examples are of course ribsomal RNA (rRNA) and transfer RNA (tRNA), but in recent years mRNA was also discovered to be post-transcriptionally modified. In addition, many small and long non-coding RNAs are also modified.

In many resources, like the tRNAdb (Jühling et al. 2009) or the modomics database (Boccaletto et al. 2018), modified nucleotides are repertoried. However in the Bioconductor context these information were not accessible, since they rely extensively on special characters in the RNA modification alphabet.

Therefore, the ModRNAString class was implemented extending the BString class from the Biostrings (H. Pagès, P. Aboyoun, R. Gentleman, and S. DebRoy 2017) package. It can store RNA sequences containing special characters of the RNA modification alphabet and thus can store location and identity of modifications. Functions for conversion to a tabular format are implemented as well.

The implemented classes inherit most of the functions from the parental BString class and it derivatives, which allows them to behave like the normal XString classes within the Bioconductor context. Most of the functionality is directly inherited and derived from the Biostrings package.

Since a DNA modification alphabet also exists, a ModDNAString class was implemented as well. For details on the available letters have a look at the RNA modification and [DNA modification](ModDNAString-alphabet.html alphabet vignettes.

2 Creating a ModRNAString object

In principle ModRNAString and ModDNAString objects can be created as any other XString object. However encoding issue will most certainly come into play, depending on the modification, the operation system and probably the R version. This is not a problem of how the data is internally used, but how the letter is transfered from the console to R and back.

library(Modstrings)
library(GenomicRanges)
# This works
mr <- ModRNAString("ACGU7")
# This might work on Linux, but does not on Windows
ModRNAString("ACGU≈")
##   5-letter "ModRNAString" instance
## seq: ACGU≈
# This cause a misinterpretation on Windows. Omega gets added as O. 
# This modifys the information from yW-72 (7-aminocarboxypropylwyosine) to 
# m1I (1-methylinosine)
ModRNAString("ACGUΩ")
##   5-letter "ModRNAString" instance
## seq: ACGUΩ

To eliminate this issue the function modifyNucleotide() is implemented, which can use short names or the nomenclature of a modification to add it at the desired position.

head(shortName(ModRNAString()))
## [1] "m1Am"    "m1Gm"    "m1Im"    "m1acp3Y" "m1A"     "m1G"
head(nomenclature(ModRNAString()))
## [1] "01A"   "01G"   "019A"  "1309U" "1A"    "1G"
r <- RNAString("ACGUG")
mr2 <- modifyNucleotides(r,5,"m7G")
mr2
##   5-letter "ModRNAString" instance
## seq: ACGU7
mr3 <- modifyNucleotides(r,5,"7G",nc.type = "nc")
mr3
##   5-letter "ModRNAString" instance
## seq: ACGU7

In addition, one can also use the alphabet() function and subset to the desired modifications.

mr4 <- ModRNAString(paste0("ACGU",alphabet(ModRNAString())[33]))
mr4
##   5-letter "ModRNAString" instance
## seq: ACGUB

3 Streamlining objection creation and modification

To offer a more streamlined functionality, which can take more information as input, the function combineIntoModstrings() is implemented. It takes a XString object and a GRanges object with a mod column and returns a ModString object. The information in the mod column must match the short name or nomenclature of the particular modification of interest as returned by the shortName() or nomenclature() functions as seen above.

gr <- GRanges("1:5", mod = "m7G")
mr5 <- combineIntoModstrings(r, gr)
mr5
##   5-letter "ModRNAString" instance
## seq: ACGU7

combineIntoModstrings() is also implemented for ModStringSet objects.

rs <- RNAStringSet(list(r,r,r,r,r))
names(rs) <- paste0("Sequence", seq_along(rs))
gr2 <- GRanges(seqnames = names(rs)[c(1,1,2,3,3,4,5,5)],
               ranges = IRanges(start = c(4,5,5,4,5,5,4,5),width = 1),
               mod = c("D","m7G","m7G","D","m7G","m7G","D","m7G"))
gr2
## GRanges object with 8 ranges and 1 metadata column:
##        seqnames    ranges strand |         mod
##           <Rle> <IRanges>  <Rle> | <character>
##   [1] Sequence1         4      * |           D
##   [2] Sequence1         5      * |         m7G
##   [3] Sequence2         5      * |         m7G
##   [4] Sequence3         4      * |           D
##   [5] Sequence3         5      * |         m7G
##   [6] Sequence4         5      * |         m7G
##   [7] Sequence5         4      * |           D
##   [8] Sequence5         5      * |         m7G
##   -------
##   seqinfo: 5 sequences from an unspecified genome; no seqlengths
mrs <- combineIntoModstrings(rs, gr2)
mrs
##   A ModRNAStringSet instance of length 5
##     width seq                                               names               
## [1]     5 ACGD7                                             Sequence1
## [2]     5 ACGU7                                             Sequence2
## [3]     5 ACGD7                                             Sequence3
## [4]     5 ACGU7                                             Sequence4
## [5]     5 ACGD7                                             Sequence5

The reverse operation is also available via the function separate(), which allows the positions of modifications to be transfered into a tabular format.

gr3 <- separate(mrs)
rs2 <- RNAStringSet(mrs)
gr3
## GRanges object with 8 ranges and 1 metadata column:
##        seqnames    ranges strand |         mod
##           <Rle> <IRanges>  <Rle> | <character>
##   [1] Sequence1         4      + |           D
##   [2] Sequence1         5      + |         m7G
##   [3] Sequence2         5      + |         m7G
##   [4] Sequence3         4      + |           D
##   [5] Sequence3         5      + |         m7G
##   [6] Sequence4         5      + |         m7G
##   [7] Sequence5         4      + |           D
##   [8] Sequence5         5      + |         m7G
##   -------
##   seqinfo: 5 sequences from an unspecified genome; no seqlengths
rs2
##   A RNAStringSet instance of length 5
##     width seq                                               names               
## [1]     5 ACGUG                                             Sequence1
## [2]     5 ACGUG                                             Sequence2
## [3]     5 ACGUG                                             Sequence3
## [4]     5 ACGUG                                             Sequence4
## [5]     5 ACGUG                                             Sequence5

modifyNucleotides() and therefore also combineIntoModstrings() requires, that the nucleotides to be modified match the originating base for the modification. The next chunk fails, since the originating base for m7G is of course G.

modifyNucleotides(r,4,"m7G")
## Error: Modification type does not match the originating base:
##  U != G  for  m7G

Calls for both functions check the sanity for this operation, so that the next bit is always TRUE.

r <- RNAString("ACGUG")
mr2 <- modifyNucleotides(r,5,"m7G")
r == RNAString(mr2)
## [1] TRUE

4 Comparing ModString objects

ModString objects can be directly compared to RNAString or DNAString objects depending on the type (ModRNA to RNA and ModDNA to DNA).

r == ModRNAString(r)
## [1] TRUE
r == mr
## [1] FALSE
rs == ModRNAStringSet(rs)
## [1] TRUE TRUE TRUE TRUE TRUE
rs == c(mrs[1:3],rs[4:5])
## [1] FALSE FALSE FALSE  TRUE  TRUE

5 Conversion of ModString objects

ModString objects can be converted into each other. However any conversion will remove any information on modifications and revert each nucleotide back to its originating nucleotide.

RNAString(mr)
##   5-letter "RNAString" instance
## seq: ACGUG

6 Quality scaled ModString

Quality information can be encoded alongside ModString objects by combining it with a XStringQuality object inside a QualityScaledModStringSet object. Two class are implemented: QualityScaledModRNAStringSet and QualityScaledModDNAStringSet. They are usable as expected from a QualityScaledXStringSet object.

qmrs <- QualityScaledModRNAStringSet(mrs,
                                     PhredQuality(c("!!!!h","!!!!h","!!!!h",
                                                    "!!!!h","!!!!h")))
qmrs
##   A QualityScaledModRNAStringSet instance containing:
## 
##   A ModRNAStringSet instance of length 5
##     width seq                                               names               
## [1]     5 ACGD7                                             Sequence1
## [2]     5 ACGU7                                             Sequence2
## [3]     5 ACGD7                                             Sequence3
## [4]     5 ACGU7                                             Sequence4
## [5]     5 ACGD7                                             Sequence5
## 
##   A PhredQuality instance of length 5
##     width seq
## [1]     5 !!!!h
## [2]     5 !!!!h
## [3]     5 !!!!h
## [4]     5 !!!!h
## [5]     5 !!!!h

They can also be constructed/deconstructed using the functions combineIntoModstrings() and separate() and use an additional metadata column named quality. For quality information to persist during construction, set the argument with.qualities = TRUE. If a QualityScaledModStringSet is used as an input to separate, the quality information are returned in the quality column. We choose to avoid clashes with the score column and not to recycle it.

qgr <- separate(qmrs)
qgr
## GRanges object with 8 ranges and 2 metadata columns:
##        seqnames    ranges strand |         mod   quality
##           <Rle> <IRanges>  <Rle> | <character> <integer>
##   [1] Sequence1         4      + |           D         0
##   [2] Sequence1         5      + |         m7G        71
##   [3] Sequence2         5      + |         m7G        71
##   [4] Sequence3         4      + |           D         0
##   [5] Sequence3         5      + |         m7G        71
##   [6] Sequence4         5      + |         m7G        71
##   [7] Sequence5         4      + |           D         0
##   [8] Sequence5         5      + |         m7G        71
##   -------
##   seqinfo: 5 sequences from an unspecified genome; no seqlengths
combineIntoModstrings(mrs,qgr, with.qualities = TRUE)
##   A QualityScaledModRNAStringSet instance containing:
## 
##   A ModRNAStringSet instance of length 5
##     width seq                                               names               
## [1]     5 ACGD7                                             Sequence1
## [2]     5 ACGU7                                             Sequence2
## [3]     5 ACGD7                                             Sequence3
## [4]     5 ACGU7                                             Sequence4
## [5]     5 ACGD7                                             Sequence5
## 
##   A PhredQuality instance of length 5
##     width seq
## [1]     5 !!!!h
## [2]     5 !!!!h
## [3]     5 !!!!h
## [4]     5 !!!!h
## [5]     5 !!!!h

7 Saving and reading ModString objects to file

The nucleotide sequences with modifications can be saved to a fasta or fastq file using the functions writeModStringSet(). Reading of these files is achieved using readModRNAStringSet() or readModDNAStringSet(). In case of fastq files, the sequences can be automatically read as a QualityScaledModRNAStringSet using readQualityScaledModRNAStringSet() function.

writeModStringSet(mrs, file = "test.fasta")
# note the different function name. Otherwise empty qualities will be written
writeQualityScaledModStringSet(qmrs, file = "test.fastq")
mrs2 <- readModRNAStringSet("test.fasta", format = "fasta")
mrs2
##   A ModRNAStringSet instance of length 5
##     width seq                                               names               
## [1]     5 ACGD7                                             Sequence1
## [2]     5 ACGU7                                             Sequence2
## [3]     5 ACGD7                                             Sequence3
## [4]     5 ACGU7                                             Sequence4
## [5]     5 ACGD7                                             Sequence5
qmrs2 <- readQualityScaledModRNAStringSet("test.fastq")
qmrs2
##   A QualityScaledModRNAStringSet instance containing:
## 
##   A ModRNAStringSet instance of length 5
##     width seq                                               names               
## [1]     5 ACGD7                                             Sequence1
## [2]     5 ACGU7                                             Sequence2
## [3]     5 ACGD7                                             Sequence3
## [4]     5 ACGU7                                             Sequence4
## [5]     5 ACGD7                                             Sequence5
## 
##   A PhredQuality instance of length 5
##     width seq
## [1]     5 !!!!h
## [2]     5 !!!!h
## [3]     5 !!!!h
## [4]     5 !!!!h
## [5]     5 !!!!h

8 Pattern matching

Pattern matching is implemented as well as expected for XString objects.

matchPattern("U7",mr)
##   Views on a 5-letter ModRNAString subject
## subject: ACGU7
## views:
##     start end width
## [1]     4   5     2 [U7]
vmatchPattern("D7",mrs)
## MIndex object of length 5
## $Sequence1
## IRanges object with 1 range and 0 metadata columns:
##           start       end     width
##       <integer> <integer> <integer>
##   [1]         4         5         2
## 
## $Sequence2
## IRanges object with 0 ranges and 0 metadata columns:
##        start       end     width
##    <integer> <integer> <integer>
## 
## $Sequence3
## IRanges object with 1 range and 0 metadata columns:
##           start       end     width
##       <integer> <integer> <integer>
##   [1]         4         5         2
## 
## $Sequence4
## IRanges object with 0 ranges and 0 metadata columns:
##        start       end     width
##    <integer> <integer> <integer>
## 
## $Sequence5
## IRanges object with 1 range and 0 metadata columns:
##           start       end     width
##       <integer> <integer> <integer>
##   [1]         4         5         2
mrl <- unlist(mrs)
matchLRPatterns("7ACGU","U7ACG",100,mrl)
##   Views on a 25-letter ModRNAString subject
## subject: ACGD7ACGU7ACGD7ACGU7ACGD7
## views:
##     start end width
## [1]     5  23    19 [7ACGU7ACGD7ACGU7ACG]

9 Future development

In principle post-translational modifications of proteins could also be implemented. However, a one letter alphabet of post-translational modifications must be developed first. If you are already aware of such an alphabet and want to use it in a Bioconductor context, let us know.

10 Import example

This is a quick example showing how sequence information containing modified nucleotides can be imported into an R session using the Modstrings package. The file needs to be UTF-8 encoded.

# read the lines
test <- readLines(system.file("extdata","test.fasta",package = "Modstrings"),
                      encoding = "UTF-8")
head(test,2)
## [1] "> tRNA | Ala | AGC | Saccharomyces cerevisiae | cytosolic"                                          
## [2] "-GGGCGUGUKGCGUAGDC-GGD--AGCGCRCUCCCUUIGCOPGGGAGAG-------------------GDCUCCGGTPCGAUUCCGGACUCGUCCACCA"
# keep every second line as sequence, the other one as name
names <- test[seq.int(from = 1, to = 104, by = 2)]
seq <- test[seq.int(from = 2, to = 104, by = 2)]
# sanitize input. This needs to be adapt to the individual case
names <- gsub(" ","_",
              gsub("> ","",
                   gsub(" \\| ","-",
                        names)))
seq <- gsub("-","",gsub("_","",seq))
names(seq) <- names

# sanitize special characters to Modstrings equivalent
seq <- sanitizeFromModomics(seq)
seq <- ModRNAStringSet(seq)
seq
##   A ModRNAStringSet instance of length 52
##      width seq                                              names               
##  [1]    76 GGGCGUGUKGCGUAGDCGGDAGC...PCGAUUCCGGACUCGUCCACCA tRNA-Ala-AGC-Sacc...
##  [2]    75 GCUCGCGUKLCGUAADGGCAACG...PCG"CCCCCAUCGUGAGUGCCA tRNA-Arg-UCU-Sacc...
##  [3]    76 PUCCUCGUKLCCCAADGGDCACG...PCA"GUCCUGGCGGGGAAGCCA tRNA-Arg-ICG-Sacc...
##  [4]    77 GACUCCAUGLCCAAGDDGGDDAA...PCA"CCCUCACUGGGGUCGCCA tRNA-Asn-GUU-Sacc...
##  [5]    75 UCCGUGAUAGUUPAADGGDCAGA...PCAAUUCCCCGUCGCGGAGCCA tRNA-Asp-GUC-Sacc...
##  ...   ... ...
## [48]    76 GCUCUCUUAGCUUAADGGDUAAA...PCAAAUCAUGGAGAGAGUACCA tRNA-Arg-NCU-Sacc...
## [49]    90 GGAUGGUUGACUGAGDGGDUUAA...PCAAAUCCUACAUCAUCCGCCA tRNA-Ser-UGA-Sacc...
## [50]    90 GGAUGGUUGACUGAGDGGDUUAA...PCAAAUCCUACAUCAUCCGCCA tRNA-Ser-UGA-Sacc...
## [51]    73 GUAAAUAUAAUUUAADGGDAAAA...PCAAAUCUUAGUAUUUACACCA tRNA-Thr-UAG-Sacc...
## [52]    74 AAGGAUAUAGUUUAADGGDAAAA...PCGAAUCUCUUUAUCCUUGCCA tRNA-Trp-!CA-Sacc...
# convert the contained modifications into a tabular format
separate(seq)
## GRanges object with 567 ranges and 1 metadata column:
##                                                    seqnames    ranges strand |
##                                                       <Rle> <IRanges>  <Rle> |
##     [1]     tRNA-Arg-UCU-Saccharomyces_cerevisiae-cytosolic         9      + |
##     [2]     tRNA-Arg-UCU-Saccharomyces_cerevisiae-cytosolic        10      + |
##     [3]     tRNA-Arg-UCU-Saccharomyces_cerevisiae-cytosolic        16      + |
##     [4]     tRNA-Arg-UCU-Saccharomyces_cerevisiae-cytosolic        25      + |
##     [5]     tRNA-Arg-UCU-Saccharomyces_cerevisiae-cytosolic        26      + |
##     ...                                                 ...       ...    ... .
##   [563] tRNA-Arg-NCU-Saccharomyces_cerevisiae-mitochondrial        34      + |
##   [564] tRNA-Arg-NCU-Saccharomyces_cerevisiae-mitochondrial        37      + |
##   [565] tRNA-Arg-NCU-Saccharomyces_cerevisiae-mitochondrial        39      + |
##   [566] tRNA-Arg-NCU-Saccharomyces_cerevisiae-mitochondrial        54      + |
##   [567] tRNA-Arg-NCU-Saccharomyces_cerevisiae-mitochondrial        55      + |
##                 mod
##         <character>
##     [1]         m1G
##     [2]         m2G
##     [3]           D
##     [4]       m2,2G
##     [5]           Y
##     ...         ...
##   [563]          xU
##   [564]         t6A
##   [565]           Y
##   [566]         m5U
##   [567]           Y
##   -------
##   seqinfo: 47 sequences from an unspecified genome; no seqlengths

11 Sessioninfo

sessioninfo::session_info()
## ─ Session info ───────────────────────────────────────────────────────────────
##  setting  value                       
##  version  R version 3.6.2 (2019-12-12)
##  os       Ubuntu 18.04.3 LTS          
##  system   x86_64, linux-gnu           
##  ui       X11                         
##  language (EN)                        
##  collate  C                           
##  ctype    en_US.UTF-8                 
##  tz       America/New_York            
##  date     2020-02-01                  
## 
## ─ Packages ───────────────────────────────────────────────────────────────────
##  package              * version  date       lib source                      
##  assertive              0.3-5    2016-12-31 [2] CRAN (R 3.6.2)              
##  assertive.base         0.0-7    2016-12-30 [2] CRAN (R 3.6.2)              
##  assertive.code         0.0-3    2018-10-21 [2] CRAN (R 3.6.2)              
##  assertive.data         0.0-3    2018-11-21 [2] CRAN (R 3.6.2)              
##  assertive.data.uk      0.0-2    2018-10-21 [2] CRAN (R 3.6.2)              
##  assertive.data.us      0.0-2    2018-10-21 [2] CRAN (R 3.6.2)              
##  assertive.datetimes    0.0-2    2016-05-10 [2] CRAN (R 3.6.2)              
##  assertive.files        0.0-2    2016-05-10 [2] CRAN (R 3.6.2)              
##  assertive.matrices     0.0-2    2018-11-20 [2] CRAN (R 3.6.2)              
##  assertive.models       0.0-2    2018-10-21 [2] CRAN (R 3.6.2)              
##  assertive.numbers      0.0-2    2016-05-09 [2] CRAN (R 3.6.2)              
##  assertive.properties   0.0-4    2016-12-30 [2] CRAN (R 3.6.2)              
##  assertive.reflection   0.0-4    2016-12-30 [2] CRAN (R 3.6.2)              
##  assertive.sets         0.0-3    2016-12-30 [2] CRAN (R 3.6.2)              
##  assertive.strings      0.0-3    2016-05-10 [2] CRAN (R 3.6.2)              
##  assertive.types        0.0-3    2016-12-30 [2] CRAN (R 3.6.2)              
##  assertthat             0.2.1    2019-03-21 [2] CRAN (R 3.6.2)              
##  BiocGenerics         * 0.32.0   2020-02-01 [2] Bioconductor                
##  BiocManager            1.30.10  2019-11-16 [2] CRAN (R 3.6.2)              
##  BiocStyle            * 2.14.4   2020-02-01 [2] Bioconductor                
##  Biostrings           * 2.54.0   2020-02-01 [2] Bioconductor                
##  bitops                 1.0-6    2013-08-17 [2] CRAN (R 3.6.2)              
##  bookdown               0.17     2020-01-11 [2] CRAN (R 3.6.2)              
##  cli                    2.0.1    2020-01-08 [2] CRAN (R 3.6.2)              
##  codetools              0.2-16   2018-12-24 [2] CRAN (R 3.6.2)              
##  crayon                 1.3.4    2017-09-16 [2] CRAN (R 3.6.2)              
##  digest                 0.6.23   2019-11-23 [2] CRAN (R 3.6.2)              
##  evaluate               0.14     2019-05-28 [2] CRAN (R 3.6.2)              
##  fansi                  0.4.1    2020-01-08 [2] CRAN (R 3.6.2)              
##  GenomeInfoDb         * 1.22.0   2020-02-01 [2] Bioconductor                
##  GenomeInfoDbData       1.2.2    2019-12-18 [2] Bioconductor                
##  GenomicRanges        * 1.38.0   2020-02-01 [2] Bioconductor                
##  glue                   1.3.1    2019-03-12 [2] CRAN (R 3.6.2)              
##  highr                  0.8      2019-03-20 [2] CRAN (R 3.6.2)              
##  htmltools              0.4.0    2019-10-04 [2] CRAN (R 3.6.2)              
##  IRanges              * 2.20.2   2020-02-01 [2] Bioconductor                
##  knitr                  1.27.2   2020-01-21 [2] Github (yihui/knitr@ab191b0)
##  magrittr               1.5      2014-11-22 [2] CRAN (R 3.6.2)              
##  Modstrings           * 1.2.1    2020-02-01 [1] Bioconductor                
##  Rcpp                   1.0.3    2019-11-08 [2] CRAN (R 3.6.2)              
##  RCurl                  1.98-1.1 2020-01-19 [2] CRAN (R 3.6.2)              
##  rlang                  0.4.4    2020-01-28 [2] CRAN (R 3.6.2)              
##  rmarkdown              2.1      2020-01-20 [2] CRAN (R 3.6.2)              
##  S4Vectors            * 0.24.3   2020-02-01 [2] Bioconductor                
##  sessioninfo            1.1.1    2018-11-05 [2] CRAN (R 3.6.2)              
##  stringi                1.4.5    2020-01-11 [2] CRAN (R 3.6.2)              
##  stringr                1.4.0    2019-02-10 [2] CRAN (R 3.6.2)              
##  withr                  2.1.2    2018-03-15 [2] CRAN (R 3.6.2)              
##  xfun                   0.12     2020-01-13 [2] CRAN (R 3.6.2)              
##  XVector              * 0.26.0   2020-02-01 [2] Bioconductor                
##  yaml                   2.2.1    2020-02-01 [2] CRAN (R 3.6.2)              
##  zlibbioc               1.32.0   2020-02-01 [2] Bioconductor                
## 
## [1] /tmp/RtmpHRrcOz/Rinst69262c0fbf1
## [2] /home/biocbuild/bbs-3.10-bioc/R/library

References

Boccaletto, Pietro, Magdalena A. Machnicka, Elzbieta Purta, Pawel Piatkowski, Blazej Baginski, Tomasz K. Wirecki, Valérie de Crécy-Lagard, et al. 2018. “MODOMICS: A Database of Rna Modification Pathways. 2017 Update.” Nucleic Acids Research 46 (D1):D303–D307. https://doi.org/10.1093/nar/gkx1030.

H. Pagès, P. Aboyoun, R. Gentleman, and S. DebRoy. 2017. “Biostrings.” Bioconductor. https://doi.org/10.18129/B9.bioc.Biostrings.

Jühling, Frank, Mario Mörl, Roland K. Hartmann, Mathias Sprinzl, Peter F. Stadler, and Joern Pütz. 2009. “TRNAdb 2009: Compilation of tRNA Sequences and tRNA Genes.” Nucleic Acids Research 37:D159–D162. https://doi.org/10.1093/nar/gkn772.