Un-pack results obtained with a pack()ed group of ranges
unpack-methods.Rd
unpack
returns results obtained with pack()ed ranges
to the geometry of the original, unpacked ranges.
Usage
# S4 method for class 'list,GRangesList'
unpack(flesh, skeleton, ...)
# S4 method for class 'List,GRangesList'
unpack(flesh, skeleton, ...)
Details
unpack
returns a List
obtained with
packed ranges to the geometry and order of the original,
unpacked ranges.
See also
pack
for packing ranges.
Examples
fl <- system.file("extdata", "ex1.bam", package = "Rsamtools")
gr <- GRanges(c(rep("seq2", 3), "seq1"),
IRanges(c(75, 1, 100, 1), width = 2))
## Ranges are packed by order within chromosome and grouped
## around gaps greater than 'inter_range_len'. See ?pack for details.
pk <- pack(gr, inter_range_len = 25)
## FUN computes coverage for the range passed as 'rng'.
FUN <- function(rng, fl, param) {
requireNamespace("GenomicAlignments") ## for bamWhich() and coverage()
Rsamtools::bamWhich(param) <- rng
GenomicAlignments::coverage(Rsamtools::BamFile(fl), param=param)[rng]
}
## Compute coverage on the packed ranges.
dat <- bplapply(as.list(pk), FUN, fl = fl, param = ScanBamParam())
## The result list contains RleLists of coverage.
lapply(dat, class)
#> [[1]]
#> [1] "CompressedRleList"
#> attr(,"package")
#> [1] "IRanges"
#>
#> [[2]]
#> [1] "CompressedRleList"
#> attr(,"package")
#> [1] "IRanges"
#>
#> [[3]]
#> [1] "CompressedRleList"
#> attr(,"package")
#> [1] "IRanges"
#>
## unpack() transforms the results back to the order of
## the original ranges (i.e., unpacked 'gr').
unpack(dat, pk)
#> RleList of length 4
#> $seq2
#> integer-Rle of length 2 with 2 runs
#> Lengths: 1 1
#> Values : 37 35
#>
#> $seq2
#> integer-Rle of length 2 with 2 runs
#> Lengths: 1 1
#> Values : 3 4
#>
#> $seq2
#> integer-Rle of length 2 with 2 runs
#> Lengths: 1 1
#> Values : 32 30
#>
#> $seq1
#> integer-Rle of length 2 with 1 run
#> Lengths: 2
#> Values : 1
#>