This file is indexed.

/usr/lib/R/site-library/IRanges/unitTests/test_AtomicList.R is in r-bioc-iranges 2.4.1-1.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

  1
  2
  3
  4
  5
  6
  7
  8
  9
 10
 11
 12
 13
 14
 15
 16
 17
 18
 19
 20
 21
 22
 23
 24
 25
 26
 27
 28
 29
 30
 31
 32
 33
 34
 35
 36
 37
 38
 39
 40
 41
 42
 43
 44
 45
 46
 47
 48
 49
 50
 51
 52
 53
 54
 55
 56
 57
 58
 59
 60
 61
 62
 63
 64
 65
 66
 67
 68
 69
 70
 71
 72
 73
 74
 75
 76
 77
 78
 79
 80
 81
 82
 83
 84
 85
 86
 87
 88
 89
 90
 91
 92
 93
 94
 95
 96
 97
 98
 99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
test_AtomicList_constructors <- function() {
    subclasses <- c(logical="LogicalList",
                    integer="IntegerList",
                    #double="NumericList",
                    numeric="NumericList",
                    complex="ComplexList",
                    character="CharacterList",
                    raw="RawList",
                    Rle="RleList")
    for (elt_type in names(subclasses)) {
        subclass <- subclasses[[elt_type]]
        constructor <- get(subclass)
        vec1 <- get(elt_type)(6)
        vec2 <- get(elt_type)(8)
        target <- list(A=vec1, B=vec2)
        for (compress in c(TRUE, FALSE)) {
            current <- constructor(A=vec1, B=vec2, compress=compress)
            checkTrue(is(current, subclass))
            checkIdentical(compress, is(current, "CompressedList"))
            checkIdentical(elt_type, elementType(current))
            checkIdentical(target, as.list(current))
            checkIdentical(unname(target), as.list(current, use.names=FALSE))
        }
    }
}

test_AtomicList_GroupGenerics <- function() {
    vec1 <- c(1L,2L,3L,5L,2L,8L)
    vec2 <- c(15L,45L,20L,1L,15L,100L,80L,5L)
    for (compress in c(TRUE, FALSE)) {
        for (type in c("IntegerList", "RleList")) {
            list1 <- do.call(type, list(one = vec1, vec2, compress = compress))
            checkIdentical(as.list(list1 + list1), Map("+", list1, list1))
            checkIdentical(as.list(log(list1)), lapply(list1, log))
            checkIdentical(as.list(round(sqrt(list1))),
                           lapply(list1, function(x) round(sqrt(x))))
            checkIdentical(sum(list1), sapply(list1, sum))
        }
    }
}

test_AtomicList_general <- function() {
    vec1 <- c(1L,2L,NA,3L,NA,5L,2L,8L)
    vec2 <- c(NA,15L,45L,20L,NA,1L,15L,100L,80L,5L,NA)
    for (compress in c(TRUE, FALSE)) {
        for (type in c("IntegerList", "RleList")) {
            list1 <- do.call(type, list(one = vec1, vec2, compress = compress))
            checkIdentical(as.list(list1 %in% c(1L, 5L)),
                           lapply(list1, "%in%", c(1L, 5L)))
            checkIdentical(lapply(list1 %in%
                                  IntegerList(one = vec1, vec2,
                                              compress = compress),
                                  as.vector),
                           mapply("%in%", lapply(list1, as.vector),
                                  list(one = vec1, vec2)))
            checkIdentical(as.list(is.na(list1)), lapply(list1, is.na))
            checkIdentical(as.list(match(list1, c(1L, 5L))),
                           lapply(list1, match, c(1L, 5L)))
            checkIdentical(lapply(match(list1,
                                        IntegerList(one = vec1, vec2,
                                                    compress = compress)),
                                  as.vector),
                           mapply(match, lapply(list1, as.vector),
                                  list(one = vec1, vec2)))
            checkIdentical(as.list(sort(list1)), lapply(list1, sort))
            checkIdentical(as.list(unique(list1)), lapply(list1, unique))
        }
    }
}

test_AtomicList_logical <- function() {
    vec1 <- c(TRUE,NA,FALSE, NA)
    vec2 <- c(TRUE,TRUE,FALSE,FALSE,TRUE,FALSE,TRUE,TRUE,TRUE)
    for (compress in c(TRUE, FALSE)) {
        for (type in c("LogicalList", "RleList")) {
            list1 <- do.call(type, list(one = vec1, vec2, compress = compress))
            checkIdentical(as.list(!list1), lapply(list1, "!"))
            checkIdentical(as.list(which(list1)), lapply(list1, which))
        }
    }
}

test_AtomicList_numerical <- function() {
    vec1 <- c(1L,2L,NA,3L,NA,5L,2L,8L)
    vec2 <- c(NA,15L,45L,20L,NA,1L,15L,100L,80L,5L,NA)
    for (compress in c(TRUE, FALSE)) {
        for (type in c("IntegerList", "RleList")) {
            list1 <- do.call(type, list(one = vec1, vec2, compress = compress))
            list2 <- endoapply(list1, rev)
            checkIdentical(as.list(diff(list1)), lapply(list1, diff))
            checkIdentical(as.list(pmax(list1, list2)),
                           mapply(pmax, list1, list2))
            checkIdentical(as.list(pmin(list1, list2)),
                           mapply(pmin, list1, list2))
            checkIdentical(as.list(pmax.int(list1, list2)),
                           mapply(pmax.int, list1, list2))
            checkIdentical(as.list(pmin.int(list1, list2)),
                           mapply(pmin.int, list1, list2))
            checkIdentical(mean(list1, na.rm=TRUE),
                           sapply(list1, mean, na.rm=TRUE))
            checkIdentical(var(list1, na.rm=TRUE),
                           sapply(list1, var, na.rm=TRUE))
            checkIdentical(cov(list1, list2, use="complete.obs"),
                           mapply(cov, list1, list2,
                                  MoreArgs = list(use="complete.obs")))
            checkIdentical(cor(list1, list2, use="complete.obs"),
                           mapply(cor, list1, list2,
                                  MoreArgs = list(use="complete.obs")))
            checkIdentical(sd(list1, na.rm=TRUE),
                           sapply(list1, sd, na.rm=TRUE))
            checkIdentical(median(list1, na.rm=TRUE),
                           sapply(list1, median, na.rm=TRUE))
            checkIdentical(quantile(list1, na.rm=TRUE),
                           sapply(list1, quantile, na.rm=TRUE))
            checkIdentical(mad(list1, na.rm=TRUE),
                           sapply(list1, mad, na.rm=TRUE))
            checkIdentical(IQR(list1, na.rm=TRUE),
                           sapply(list1, IQR, na.rm=TRUE))

            vec3 <- (-20:20)^2
            vec3[c(1,10,21,41)] <- c(100L, 30L, 400L, 470L)
            list3 <- do.call(type, list(one = vec3, rev(vec3), compress = compress))
            checkIdentical(as.list(smoothEnds(list3)), lapply(list3, smoothEnds))
            checkIdentical(as.list(runmed(list3, 7)),
                           lapply(list3, function(x) {
                                      y <- runmed(x, 7)
                                      if (type != "RleList")
                                          y <- as.vector(y)
                                      y
                                  }))
        }
    }
}

test_AtomicList_character <- function() {
    txt <- c("The", "licenses", "for", "most", "software", "are",
             "designed", "to", "take", "away", "your", "freedom",
             "to", "share", "and", "change", "it.",
             "", "By", "contrast,", "the", "GNU", "General", "Public", "License",
             "is", "intended", "to", "guarantee", "your", "freedom", "to",
             "share", "and", "change", "free", "software", "--",
             "to", "make", "sure", "the", "software", "is",
             "free", "for", "all", "its", "users")
     for (compress in c(TRUE, FALSE)) {
         for (type in c("CharacterList", "RleList")) {
             list1 <- do.call(type, list(one = txt, rev(txt), compress = compress))
             checkIdentical(as.list(nchar(list1)), lapply(list1, nchar))
             checkIdentical(as.list(chartr("@!*", "alo", list1)),
                            lapply(list1, chartr, old="@!*", new="alo"))
             checkIdentical(as.list(tolower(list1)), lapply(list1, tolower))
             checkIdentical(as.list(toupper(list1)), lapply(list1, toupper))
             checkIdentical(as.list(sub("[b-e]",".", list1)),
                            lapply(list1, sub, pattern="[b-e]", replacement="."))
             checkIdentical(as.list(gsub("[b-e]",".", list1)),
                            lapply(list1, gsub, pattern="[b-e]", replacement="."))
        }
    }
}

test_RleList_methods <- function() {
    x1 <- RleList(11:15, 15L, integer(0), 15:16, compress=FALSE)
    x2 <- RleList(11:15, 15L, integer(0), 15:16, compress=TRUE)
    checkIdentical(as(runValue(x1), "CompressedIntegerList"), runValue(x2))
    checkIdentical(as(runLength(x1), "CompressedIntegerList"), runLength(x2))
    checkIdentical(as(ranges(x1), "CompressedIRangesList"), ranges(x2))

    ## na.rm
    x <- RleList(c(NA,1,1), 
                 c(1L,NA_integer_,1L), 
                 c(1,Inf,1,-Inf),compress=TRUE)

    target <- RleList(c(1,2), c(1L,1L), c(Inf,Inf,-Inf))
    current <- runsum(x,2, na.rm = TRUE)
    checkIdentical(target, current)
    target <- RleList(c(NA,2), c(NA_integer_,NA_integer_), c(Inf,Inf,-Inf))
    current <- runsum(x,2, na.rm = FALSE)
    checkIdentical(target, current)

    target <- RleList(c(2,4), c(2,2), c(Inf, Inf, -Inf))
    current <- runwtsum(x,2, c(2,2), na.rm = TRUE)
    checkIdentical(target, current)
    target <- RleList(c(NA,4), c(NA_real_,NA_real_), c(Inf,Inf,-Inf))
    current <- runwtsum(x,2, c(2,2), na.rm = FALSE)
    checkIdentical(target, current)

    target <- RleList(c(1,1), c(1,1), c(Inf,Inf,-Inf))
    current <- runmean(x, 2, na.rm = TRUE)
    checkIdentical(target, current)
    target <- RleList(c(NA,1), c(NA_real_, NA_real_), c(Inf, Inf, -Inf))
    current <- runmean(x, 2, na.rm = FALSE)
    checkIdentical(target, current)

    x <- RleList(c(NA,1,2), 
                 c(2L,NA_integer_,1L), 
                 c(1,Inf,1,-Inf),compress=TRUE)
    target <- RleList(c(1,2), c(2L,1L), c(Inf,Inf,1))
    current <- runq(x, 2, 2, na.rm = TRUE)
    checkIdentical(target, current)
    target <- RleList(c(NA,2), c(NA_integer_, NA_integer_), c(Inf, Inf, 1))
    current <- runq(x, 2, 2, na.rm = FALSE)
    checkIdentical(target, current)

    ## Binary operations between an RleList and an atomic vector:
    a1 <- Rle(1, 999722111)
    a2 <- 20 * a1
    a <- RleList(a1, a2, compress=TRUE)
    b1 <- c(a1, a1)
    b2 <- 20 * b1
    b <- RleList(b1, b2, compress=FALSE)
    ## FIXME: 'a1 <= 19:21' is taking forever and eats up all the memory in
    ## BioC <= 2.12! Seems like 'a1' is expanded to integer vector first, which
    ## is not good :-/
    #for (y in list(8L, 8, 19:21)) {
    for (y in list(8L, 8)) {
        ## With a CompressedRleList
        target <- RleList(a1 <= y, a2 <= y, compress=TRUE)
        current <- a <= y
        checkIdentical(target, current)
        target <- RleList(a1 + y, a2 + y, compress=TRUE)
        current <- a + y
        checkIdentical(target, current)
        target <- RleList(a1 * y, a2 * y, compress=TRUE)
        current <- a * y
        checkIdentical(target, current)
        target <- RleList(a1 / y, a2 / y, compress=TRUE)
        current <- a / y
        checkIdentical(target, current)
        ## With a SimpleRleList
        target <- RleList(b1 <= y, b2 <= y, compress=FALSE)
        current <- b <= y
        checkIdentical(target, current)
        target <- RleList(b1 + y, b2 + y, compress=FALSE)
        current <- b + y
        checkIdentical(target, current)
        target <- RleList(b1 * y, b2 * y, compress=FALSE)
        current <- b * y
        checkIdentical(target, current)
        target <- RleList(b1 / y, b2 / y, compress=FALSE)
        current <- b / y
        checkIdentical(target, current)
    }
}