DFplyr 1.2.0
DFplyrDFplyr is a R package available via the
Bioconductor repository for packages and can be
downloaded via BiocManager::install():
if (!requireNamespace("BiocManager", quietly = TRUE)) {
    install.packages("BiocManager")
}
BiocManager::install("DFplyr")
## Check that you have a valid Bioconductor installation
BiocManager::valid()DFplyr is inspired by dplyr which implements a
wide variety of common data manipulations (mutate, select, filter) but
which only operates on objects of class data.frame or tibble (from r CRANpkg("tibble")).
When working with S4Vectors DataFrames - which are frequently
used as components of, for example SummarizedExperiment objects -
a common workaround is to convert the DataFrame to a tibble in order to then
use dplyr functions to manipulate the contents, before converting
back to a DataFrame.
This has several drawbacks, including the fact that tibble does not support
rownames (and dplyr frequently does not preserve them), does not
support S4 columns (e.g. IRanges vectors), and requires the back
and forth transformation any time manipulation is desired.
DFplyrlibrary("DFplyr")To being with, we create an S4Vectors DataFrame, including some
S4 columns
library(S4Vectors)
m <- mtcars[, c("cyl", "hp", "am", "gear", "disp")]
d <- as(m, "DataFrame")
d$grX <- GenomicRanges::GRanges("chrX", IRanges::IRanges(1:32, width = 10))
d$grY <- GenomicRanges::GRanges("chrY", IRanges::IRanges(1:32, width = 10))
d$nl <- IRanges::NumericList(lapply(d$gear, function(n) round(rnorm(n), 2)))
d
#> DataFrame with 32 rows and 8 columns
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Mazda RX4                 6       110         1         4       160  chrX:1-10
#> Mazda RX4 Wag             6       110         1         4       160  chrX:2-11
#> Datsun 710                4        93         1         4       108  chrX:3-12
#> Hornet 4 Drive            6       110         0         3       258  chrX:4-13
#> Hornet Sportabout         8       175         0         3       360  chrX:5-14
#> ...                     ...       ...       ...       ...       ...        ...
#> Lotus Europa              4       113         1         5      95.1 chrX:28-37
#> Ford Pantera L            8       264         1         5     351.0 chrX:29-38
#> Ferrari Dino              6       175         1         5     145.0 chrX:30-39
#> Maserati Bora             8       335         1         5     301.0 chrX:31-40
#> Volvo 142E                4       109         1         4     121.0 chrX:32-41
#>                          grY                      nl
#>                    <GRanges> <CompressedNumericList>
#> Mazda RX4          chrY:1-10    0.71,-1.10, 0.21,...
#> Mazda RX4 Wag      chrY:2-11   -0.16,-0.70,-0.35,...
#> Datsun 710         chrY:3-12   -0.82,-1.20, 1.14,...
#> Hornet 4 Drive     chrY:4-13        0.21,-0.81, 0.57
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22
#> ...                      ...                     ...
#> Lotus Europa      chrY:28-37   -1.39, 1.91,-0.96,...
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...
#> Ferrari Dino      chrY:30-39    1.01,-1.00, 0.59,...
#> Maserati Bora     chrY:31-40   -0.21,-0.91,-0.59,...
#> Volvo 142E        chrY:32-41   -0.96,-0.16,-0.61,...This will appear in RStudio’s environment pane as a
Formal class DataFrame (dplyr-compatible)when using DFplyr. No interference with the actual object is required, but this helps identify that dplyr-compatibility is available.
DataFrames can then be used in dplyr-like calls the same as
data.frame or tibble objects. Support for working with S4 columns is enabled
provided they have appropriate functions. Adding multiple columns will result in
the new columns being created in alphabetical order. For example, adding a new
column newvar which is the sum of the cyl and hp columns
mutate(d, newvar = cyl + hp)
#> DataFrame with 32 rows and 9 columns
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Mazda RX4                 6       110         1         4       160  chrX:1-10
#> Mazda RX4 Wag             6       110         1         4       160  chrX:2-11
#> Datsun 710                4        93         1         4       108  chrX:3-12
#> Hornet 4 Drive            6       110         0         3       258  chrX:4-13
#> Hornet Sportabout         8       175         0         3       360  chrX:5-14
#> ...                     ...       ...       ...       ...       ...        ...
#> Lotus Europa              4       113         1         5      95.1 chrX:28-37
#> Ford Pantera L            8       264         1         5     351.0 chrX:29-38
#> Ferrari Dino              6       175         1         5     145.0 chrX:30-39
#> Maserati Bora             8       335         1         5     301.0 chrX:31-40
#> Volvo 142E                4       109         1         4     121.0 chrX:32-41
#>                          grY                      nl    newvar
#>                    <GRanges> <CompressedNumericList> <numeric>
#> Mazda RX4          chrY:1-10    0.71,-1.10, 0.21,...       116
#> Mazda RX4 Wag      chrY:2-11   -0.16,-0.70,-0.35,...       116
#> Datsun 710         chrY:3-12   -0.82,-1.20, 1.14,...        97
#> Hornet 4 Drive     chrY:4-13        0.21,-0.81, 0.57       116
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22       183
#> ...                      ...                     ...       ...
#> Lotus Europa      chrY:28-37   -1.39, 1.91,-0.96,...       117
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...       272
#> Ferrari Dino      chrY:30-39    1.01,-1.00, 0.59,...       181
#> Maserati Bora     chrY:31-40   -0.21,-0.91,-0.59,...       343
#> Volvo 142E        chrY:32-41   -0.96,-0.16,-0.61,...       113or doubling the nl column as nl2
mutate(d, nl2 = nl * 2)
#> DataFrame with 32 rows and 9 columns
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Mazda RX4                 6       110         1         4       160  chrX:1-10
#> Mazda RX4 Wag             6       110         1         4       160  chrX:2-11
#> Datsun 710                4        93         1         4       108  chrX:3-12
#> Hornet 4 Drive            6       110         0         3       258  chrX:4-13
#> Hornet Sportabout         8       175         0         3       360  chrX:5-14
#> ...                     ...       ...       ...       ...       ...        ...
#> Lotus Europa              4       113         1         5      95.1 chrX:28-37
#> Ford Pantera L            8       264         1         5     351.0 chrX:29-38
#> Ferrari Dino              6       175         1         5     145.0 chrX:30-39
#> Maserati Bora             8       335         1         5     301.0 chrX:31-40
#> Volvo 142E                4       109         1         4     121.0 chrX:32-41
#>                          grY                      nl                     nl2
#>                    <GRanges> <CompressedNumericList> <CompressedNumericList>
#> Mazda RX4          chrY:1-10    0.71,-1.10, 0.21,...    1.42,-2.20, 0.42,...
#> Mazda RX4 Wag      chrY:2-11   -0.16,-0.70,-0.35,...   -0.32,-1.40,-0.70,...
#> Datsun 710         chrY:3-12   -0.82,-1.20, 1.14,...   -1.64,-2.40, 2.28,...
#> Hornet 4 Drive     chrY:4-13        0.21,-0.81, 0.57        0.42,-1.62, 1.14
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22       -1.66,-1.98,-0.44
#> ...                      ...                     ...                     ...
#> Lotus Europa      chrY:28-37   -1.39, 1.91,-0.96,...   -2.78, 3.82,-1.92,...
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...   -0.26,-3.24,-3.60,...
#> Ferrari Dino      chrY:30-39    1.01,-1.00, 0.59,...    2.02,-2.00, 1.18,...
#> Maserati Bora     chrY:31-40   -0.21,-0.91,-0.59,...   -0.42,-1.82,-1.18,...
#> Volvo 142E        chrY:32-41   -0.96,-0.16,-0.61,...   -1.92,-0.32,-1.22,...or calculating the length() of the nl column cells as length_nl
mutate(d, length_nl = lengths(nl))
#> DataFrame with 32 rows and 9 columns
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Mazda RX4                 6       110         1         4       160  chrX:1-10
#> Mazda RX4 Wag             6       110         1         4       160  chrX:2-11
#> Datsun 710                4        93         1         4       108  chrX:3-12
#> Hornet 4 Drive            6       110         0         3       258  chrX:4-13
#> Hornet Sportabout         8       175         0         3       360  chrX:5-14
#> ...                     ...       ...       ...       ...       ...        ...
#> Lotus Europa              4       113         1         5      95.1 chrX:28-37
#> Ford Pantera L            8       264         1         5     351.0 chrX:29-38
#> Ferrari Dino              6       175         1         5     145.0 chrX:30-39
#> Maserati Bora             8       335         1         5     301.0 chrX:31-40
#> Volvo 142E                4       109         1         4     121.0 chrX:32-41
#>                          grY                      nl length_nl
#>                    <GRanges> <CompressedNumericList> <integer>
#> Mazda RX4          chrY:1-10    0.71,-1.10, 0.21,...         4
#> Mazda RX4 Wag      chrY:2-11   -0.16,-0.70,-0.35,...         4
#> Datsun 710         chrY:3-12   -0.82,-1.20, 1.14,...         4
#> Hornet 4 Drive     chrY:4-13        0.21,-0.81, 0.57         3
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22         3
#> ...                      ...                     ...       ...
#> Lotus Europa      chrY:28-37   -1.39, 1.91,-0.96,...         5
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...         5
#> Ferrari Dino      chrY:30-39    1.01,-1.00, 0.59,...         5
#> Maserati Bora     chrY:31-40   -0.21,-0.91,-0.59,...         5
#> Volvo 142E        chrY:32-41   -0.96,-0.16,-0.61,...         4Transformations can involve S4-related functions, such as extracting the
seqnames(), strand(), and end() of the grX column
mutate(d,
    chr = GenomeInfoDb::seqnames(grX),
    strand_X = BiocGenerics::strand(grX),
    end_X = BiocGenerics::end(grX)
)
#> DataFrame with 32 rows and 11 columns
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Mazda RX4                 6       110         1         4       160  chrX:1-10
#> Mazda RX4 Wag             6       110         1         4       160  chrX:2-11
#> Datsun 710                4        93         1         4       108  chrX:3-12
#> Hornet 4 Drive            6       110         0         3       258  chrX:4-13
#> Hornet Sportabout         8       175         0         3       360  chrX:5-14
#> ...                     ...       ...       ...       ...       ...        ...
#> Lotus Europa              4       113         1         5      95.1 chrX:28-37
#> Ford Pantera L            8       264         1         5     351.0 chrX:29-38
#> Ferrari Dino              6       175         1         5     145.0 chrX:30-39
#> Maserati Bora             8       335         1         5     301.0 chrX:31-40
#> Volvo 142E                4       109         1         4     121.0 chrX:32-41
#>                          grY                      nl   chr     end_X strand_X
#>                    <GRanges> <CompressedNumericList> <Rle> <integer>    <Rle>
#> Mazda RX4          chrY:1-10    0.71,-1.10, 0.21,...  chrX        10        *
#> Mazda RX4 Wag      chrY:2-11   -0.16,-0.70,-0.35,...  chrX        11        *
#> Datsun 710         chrY:3-12   -0.82,-1.20, 1.14,...  chrX        12        *
#> Hornet 4 Drive     chrY:4-13        0.21,-0.81, 0.57  chrX        13        *
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22  chrX        14        *
#> ...                      ...                     ...   ...       ...      ...
#> Lotus Europa      chrY:28-37   -1.39, 1.91,-0.96,...  chrX        37        *
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...  chrX        38        *
#> Ferrari Dino      chrY:30-39    1.01,-1.00, 0.59,...  chrX        39        *
#> Maserati Bora     chrY:31-40   -0.21,-0.91,-0.59,...  chrX        40        *
#> Volvo 142E        chrY:32-41   -0.96,-0.16,-0.61,...  chrX        41        *the object returned remains a standard DataFrame, and further calls can be
piped with %>%, in this case extracting the newly created newvar column
mutate(d, newvar = cyl + hp) %>%
    pull(newvar)
#>  [1] 116 116  97 116 183 111 253  66  99 129 129 188 188 188 213 223 238  70  56
#> [20]  69 101 158 158 253 183  70  95 117 272 181 343 113Some of the variants of the dplyr verbs also work, such as transforming the
numeric columns using a quosure style lambda function, in this case squaring
them
mutate_if(d, is.numeric, ~ .^2)
#> DataFrame with 32 rows and 8 columns
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Mazda RX4                36     12100         1        16     25600  chrX:1-10
#> Mazda RX4 Wag            36     12100         1        16     25600  chrX:2-11
#> Datsun 710               16      8649         1        16     11664  chrX:3-12
#> Hornet 4 Drive           36     12100         0         9     66564  chrX:4-13
#> Hornet Sportabout        64     30625         0         9    129600  chrX:5-14
#> ...                     ...       ...       ...       ...       ...        ...
#> Lotus Europa             16     12769         1        25   9044.01 chrX:28-37
#> Ford Pantera L           64     69696         1        25 123201.00 chrX:29-38
#> Ferrari Dino             36     30625         1        25  21025.00 chrX:30-39
#> Maserati Bora            64    112225         1        25  90601.00 chrX:31-40
#> Volvo 142E               16     11881         1        16  14641.00 chrX:32-41
#>                          grY                      nl
#>                    <GRanges> <CompressedNumericList>
#> Mazda RX4          chrY:1-10    0.71,-1.10, 0.21,...
#> Mazda RX4 Wag      chrY:2-11   -0.16,-0.70,-0.35,...
#> Datsun 710         chrY:3-12   -0.82,-1.20, 1.14,...
#> Hornet 4 Drive     chrY:4-13        0.21,-0.81, 0.57
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22
#> ...                      ...                     ...
#> Lotus Europa      chrY:28-37   -1.39, 1.91,-0.96,...
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...
#> Ferrari Dino      chrY:30-39    1.01,-1.00, 0.59,...
#> Maserati Bora     chrY:31-40   -0.21,-0.91,-0.59,...
#> Volvo 142E        chrY:32-41   -0.96,-0.16,-0.61,...or extracting the start of all of the "GRanges" columns
mutate_if(d, ~ isa(., "GRanges"), BiocGenerics::start)
#> DataFrame with 32 rows and 8 columns
#>                         cyl        hp        am      gear      disp       grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric> <integer>
#> Mazda RX4                 6       110         1         4       160         1
#> Mazda RX4 Wag             6       110         1         4       160         2
#> Datsun 710                4        93         1         4       108         3
#> Hornet 4 Drive            6       110         0         3       258         4
#> Hornet Sportabout         8       175         0         3       360         5
#> ...                     ...       ...       ...       ...       ...       ...
#> Lotus Europa              4       113         1         5      95.1        28
#> Ford Pantera L            8       264         1         5     351.0        29
#> Ferrari Dino              6       175         1         5     145.0        30
#> Maserati Bora             8       335         1         5     301.0        31
#> Volvo 142E                4       109         1         4     121.0        32
#>                         grY                      nl
#>                   <integer> <CompressedNumericList>
#> Mazda RX4                 1    0.71,-1.10, 0.21,...
#> Mazda RX4 Wag             2   -0.16,-0.70,-0.35,...
#> Datsun 710                3   -0.82,-1.20, 1.14,...
#> Hornet 4 Drive            4        0.21,-0.81, 0.57
#> Hornet Sportabout         5       -0.83,-0.99,-0.22
#> ...                     ...                     ...
#> Lotus Europa             28   -1.39, 1.91,-0.96,...
#> Ford Pantera L           29   -0.13,-1.62,-1.80,...
#> Ferrari Dino             30    1.01,-1.00, 0.59,...
#> Maserati Bora            31   -0.21,-0.91,-0.59,...
#> Volvo 142E               32   -0.96,-0.16,-0.61,...Use of tidyselect helpers is limited to within vars()
calls and using the _at variants
mutate_at(d, vars(starts_with("c")), ~ .^2)
#> DataFrame with 32 rows and 8 columns
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Mazda RX4                36       110         1         4       160  chrX:1-10
#> Mazda RX4 Wag            36       110         1         4       160  chrX:2-11
#> Datsun 710               16        93         1         4       108  chrX:3-12
#> Hornet 4 Drive           36       110         0         3       258  chrX:4-13
#> Hornet Sportabout        64       175         0         3       360  chrX:5-14
#> ...                     ...       ...       ...       ...       ...        ...
#> Lotus Europa             16       113         1         5      95.1 chrX:28-37
#> Ford Pantera L           64       264         1         5     351.0 chrX:29-38
#> Ferrari Dino             36       175         1         5     145.0 chrX:30-39
#> Maserati Bora            64       335         1         5     301.0 chrX:31-40
#> Volvo 142E               16       109         1         4     121.0 chrX:32-41
#>                          grY                      nl
#>                    <GRanges> <CompressedNumericList>
#> Mazda RX4          chrY:1-10    0.71,-1.10, 0.21,...
#> Mazda RX4 Wag      chrY:2-11   -0.16,-0.70,-0.35,...
#> Datsun 710         chrY:3-12   -0.82,-1.20, 1.14,...
#> Hornet 4 Drive     chrY:4-13        0.21,-0.81, 0.57
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22
#> ...                      ...                     ...
#> Lotus Europa      chrY:28-37   -1.39, 1.91,-0.96,...
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...
#> Ferrari Dino      chrY:30-39    1.01,-1.00, 0.59,...
#> Maserati Bora     chrY:31-40   -0.21,-0.91,-0.59,...
#> Volvo 142E        chrY:32-41   -0.96,-0.16,-0.61,...and also works with other verbs
select_at(d, vars(starts_with("gr")))
#> DataFrame with 32 rows and 2 columns
#>                          grX        grY
#>                    <GRanges>  <GRanges>
#> Mazda RX4          chrX:1-10  chrY:1-10
#> Mazda RX4 Wag      chrX:2-11  chrY:2-11
#> Datsun 710         chrX:3-12  chrY:3-12
#> Hornet 4 Drive     chrX:4-13  chrY:4-13
#> Hornet Sportabout  chrX:5-14  chrY:5-14
#> ...                      ...        ...
#> Lotus Europa      chrX:28-37 chrY:28-37
#> Ford Pantera L    chrX:29-38 chrY:29-38
#> Ferrari Dino      chrX:30-39 chrY:30-39
#> Maserati Bora     chrX:31-40 chrY:31-40
#> Volvo 142E        chrX:32-41 chrY:32-41Importantly, grouped operations are supported. DataFrame does not
natively support groups (the same way that data.frame does not) so these
are implemented specifically for DFplyr with group information shown at the
top of the printed output
group_by(d, cyl, am)
#> DataFrame with 32 rows and 8 columns
#> Groups:  cyl, am 
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Mazda RX4                 6       110         1         4       160  chrX:1-10
#> Mazda RX4 Wag             6       110         1         4       160  chrX:2-11
#> Datsun 710                4        93         1         4       108  chrX:3-12
#> Hornet 4 Drive            6       110         0         3       258  chrX:4-13
#> Hornet Sportabout         8       175         0         3       360  chrX:5-14
#> ...                     ...       ...       ...       ...       ...        ...
#> Lotus Europa              4       113         1         5      95.1 chrX:28-37
#> Ford Pantera L            8       264         1         5     351.0 chrX:29-38
#> Ferrari Dino              6       175         1         5     145.0 chrX:30-39
#> Maserati Bora             8       335         1         5     301.0 chrX:31-40
#> Volvo 142E                4       109         1         4     121.0 chrX:32-41
#>                          grY                      nl
#>                    <GRanges> <CompressedNumericList>
#> Mazda RX4          chrY:1-10    0.71,-1.10, 0.21,...
#> Mazda RX4 Wag      chrY:2-11   -0.16,-0.70,-0.35,...
#> Datsun 710         chrY:3-12   -0.82,-1.20, 1.14,...
#> Hornet 4 Drive     chrY:4-13        0.21,-0.81, 0.57
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22
#> ...                      ...                     ...
#> Lotus Europa      chrY:28-37   -1.39, 1.91,-0.96,...
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...
#> Ferrari Dino      chrY:30-39    1.01,-1.00, 0.59,...
#> Maserati Bora     chrY:31-40   -0.21,-0.91,-0.59,...
#> Volvo 142E        chrY:32-41   -0.96,-0.16,-0.61,...Other verbs are similarly implemented, and preserve row names where possible. For example, selecting a limited set of columns using non-standard evaluation (NSE)
select(d, am, cyl)
#> DataFrame with 32 rows and 2 columns
#>                          am       cyl
#>                   <numeric> <numeric>
#> Mazda RX4                 1         6
#> Mazda RX4 Wag             1         6
#> Datsun 710                1         4
#> Hornet 4 Drive            0         6
#> Hornet Sportabout         0         8
#> ...                     ...       ...
#> Lotus Europa              1         4
#> Ford Pantera L            1         8
#> Ferrari Dino              1         6
#> Maserati Bora             1         8
#> Volvo 142E                1         4Arranging rows according to the ordering of a column
arrange(d, desc(hp))
#> DataFrame with 32 rows and 8 columns
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Maserati Bora             8       335         1         5       301 chrX:31-40
#> Ford Pantera L            8       264         1         5       351 chrX:29-38
#> Duster 360                8       245         0         3       360  chrX:7-16
#> Camaro Z28                8       245         0         3       350 chrX:24-33
#> Chrysler Imperial         8       230         0         3       440 chrX:17-26
#> ...                     ...       ...       ...       ...       ...        ...
#> Fiat 128                  4        66         1         4      78.7 chrX:18-27
#> Fiat X1-9                 4        66         1         4      79.0 chrX:26-35
#> Toyota Corolla            4        65         1         4      71.1 chrX:20-29
#> Merc 240D                 4        62         0         4     146.7  chrX:8-17
#> Honda Civic               4        52         1         4      75.7 chrX:19-28
#>                          grY                      nl
#>                    <GRanges> <CompressedNumericList>
#> Maserati Bora     chrY:31-40   -0.21,-0.91,-0.59,...
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...
#> Duster 360         chrY:7-16       -0.46,-0.15,-0.99
#> Camaro Z28        chrY:24-33        0.77, 1.20,-1.62
#> Chrysler Imperial chrY:17-26       -0.18, 1.48, 0.18
#> ...                      ...                     ...
#> Fiat 128          chrY:18-27   -1.50,-0.64, 0.68,...
#> Fiat X1-9         chrY:26-35      0.45,0.73,0.28,...
#> Toyota Corolla    chrY:20-29   -1.42, 0.11,-1.12,...
#> Merc 240D          chrY:8-17    0.52,-1.05, 0.75,...
#> Honda Civic       chrY:19-28    0.73,-2.05,-1.27,...Filtering to only specific values appearing in a column
filter(d, am == 0)
#> DataFrame with 19 rows and 8 columns
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Hornet 4 Drive            6       110         0         3     258.0  chrX:4-13
#> Hornet Sportabout         8       175         0         3     360.0  chrX:5-14
#> Valiant                   6       105         0         3     225.0  chrX:6-15
#> Duster 360                8       245         0         3     360.0  chrX:7-16
#> Merc 240D                 4        62         0         4     146.7  chrX:8-17
#> ...                     ...       ...       ...       ...       ...        ...
#> Toyota Corona             4        97         0         3     120.1 chrX:21-30
#> Dodge Challenger          8       150         0         3     318.0 chrX:22-31
#> AMC Javelin               8       150         0         3     304.0 chrX:23-32
#> Camaro Z28                8       245         0         3     350.0 chrX:24-33
#> Pontiac Firebird          8       175         0         3     400.0 chrX:25-34
#>                          grY                      nl
#>                    <GRanges> <CompressedNumericList>
#> Hornet 4 Drive     chrY:4-13        0.21,-0.81, 0.57
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22
#> Valiant            chrY:6-15       -2.11, 1.28,-0.18
#> Duster 360         chrY:7-16       -0.46,-0.15,-0.99
#> Merc 240D          chrY:8-17    0.52,-1.05, 0.75,...
#> ...                      ...                     ...
#> Toyota Corona     chrY:21-30          0.87,0.11,0.90
#> Dodge Challenger  chrY:22-31       -1.03, 1.35, 1.55
#> AMC Javelin       chrY:23-32          0.28,0.57,1.75
#> Camaro Z28        chrY:24-33        0.77, 1.20,-1.62
#> Pontiac Firebird  chrY:25-34        0.85,-0.01, 2.05Selecting specific rows by index
slice(d, 3:6)
#> DataFrame with 4 rows and 8 columns
#>                         cyl        hp        am      gear      disp       grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric> <GRanges>
#> Datsun 710                4        93         1         4       108 chrX:3-12
#> Hornet 4 Drive            6       110         0         3       258 chrX:4-13
#> Hornet Sportabout         8       175         0         3       360 chrX:5-14
#> Valiant                   6       105         0         3       225 chrX:6-15
#>                         grY                      nl
#>                   <GRanges> <CompressedNumericList>
#> Datsun 710        chrY:3-12   -0.82,-1.20, 1.14,...
#> Hornet 4 Drive    chrY:4-13        0.21,-0.81, 0.57
#> Hornet Sportabout chrY:5-14       -0.83,-0.99,-0.22
#> Valiant           chrY:6-15       -2.11, 1.28,-0.18These also work for grouped objects, and also preserve the rownames, e.g.
selecting the first two rows from each group of gear
group_by(d, gear) %>%
    slice(1:2)
#> DataFrame with 6 rows and 8 columns
#> Groups:  gear 
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Hornet Sportabout         8       175         0         3     360.0  chrX:5-14
#> Merc 450SL                8       180         0         3     275.8 chrX:13-22
#> Mazda RX4                 6       110         1         4     160.0  chrX:1-10
#> Mazda RX4 Wag             6       110         1         4     160.0  chrX:2-11
#> Porsche 914-2             4        91         1         5     120.3 chrX:27-36
#> Ford Pantera L            8       264         1         5     351.0 chrX:29-38
#>                          grY                      nl
#>                    <GRanges> <CompressedNumericList>
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22
#> Merc 450SL        chrY:13-22          0.55,0.37,1.61
#> Mazda RX4          chrY:1-10    0.71,-1.10, 0.21,...
#> Mazda RX4 Wag      chrY:2-11   -0.16,-0.70,-0.35,...
#> Porsche 914-2     chrY:27-36    1.76,-0.73,-0.52,...
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...rename is itself renamed to rename2 due to conflicts between
dplyr and S4Vectors, but works in the
dplyr sense of taking new = old replacements with NSE syntax
select(d, am, cyl) %>%
    rename2(foo = am)
#> DataFrame with 32 rows and 2 columns
#>                         foo       cyl
#>                   <numeric> <numeric>
#> Mazda RX4                 1         6
#> Mazda RX4 Wag             1         6
#> Datsun 710                1         4
#> Hornet 4 Drive            0         6
#> Hornet Sportabout         0         8
#> ...                     ...       ...
#> Lotus Europa              1         4
#> Ford Pantera L            1         8
#> Ferrari Dino              1         6
#> Maserati Bora             1         8
#> Volvo 142E                1         4Row names are not preserved when there may be duplicates or they don’t make
sense, otherwise the first label (according to the current de-duplication
method, in the case of distinct, this is via BiocGenerics::duplicated). This
may have complications for S4 columns.
distinct(d)
#> DataFrame with 32 rows and 8 columns
#>                         cyl        hp        am      gear      disp        grX
#>                   <numeric> <numeric> <numeric> <numeric> <numeric>  <GRanges>
#> Mazda RX4                 6       110         1         4       160  chrX:1-10
#> Mazda RX4 Wag             6       110         1         4       160  chrX:2-11
#> Datsun 710                4        93         1         4       108  chrX:3-12
#> Hornet 4 Drive            6       110         0         3       258  chrX:4-13
#> Hornet Sportabout         8       175         0         3       360  chrX:5-14
#> ...                     ...       ...       ...       ...       ...        ...
#> Lotus Europa              4       113         1         5      95.1 chrX:28-37
#> Ford Pantera L            8       264         1         5     351.0 chrX:29-38
#> Ferrari Dino              6       175         1         5     145.0 chrX:30-39
#> Maserati Bora             8       335         1         5     301.0 chrX:31-40
#> Volvo 142E                4       109         1         4     121.0 chrX:32-41
#>                          grY                      nl
#>                    <GRanges> <CompressedNumericList>
#> Mazda RX4          chrY:1-10    0.71,-1.10, 0.21,...
#> Mazda RX4 Wag      chrY:2-11   -0.16,-0.70,-0.35,...
#> Datsun 710         chrY:3-12   -0.82,-1.20, 1.14,...
#> Hornet 4 Drive     chrY:4-13        0.21,-0.81, 0.57
#> Hornet Sportabout  chrY:5-14       -0.83,-0.99,-0.22
#> ...                      ...                     ...
#> Lotus Europa      chrY:28-37   -1.39, 1.91,-0.96,...
#> Ford Pantera L    chrY:29-38   -0.13,-1.62,-1.80,...
#> Ferrari Dino      chrY:30-39    1.01,-1.00, 0.59,...
#> Maserati Bora     chrY:31-40   -0.21,-0.91,-0.59,...
#> Volvo 142E        chrY:32-41   -0.96,-0.16,-0.61,...Behaviours are ideally the same as those of dplyr wherever possible, for example a grouped tally
group_by(d, cyl, am) %>%
    tally(gear)
#> DataFrame with 6 rows and 3 columns
#>         cyl        am         n
#>   <numeric> <numeric> <numeric>
#> 1         4         0        11
#> 2         4         1        34
#> 3         6         0        14
#> 4         6         1        13
#> 5         8         0        36
#> 6         8         1        10or a count with weights
count(d, gear, am, cyl)
#> DataFrame with 10 rows and 4 columns
#>        gear    am   cyl         n
#>    <factor> <Rle> <Rle> <integer>
#> 1         3     0     4         1
#> 2         3     0     6         2
#> 3         3     0     8        12
#> 4         4     0     4         2
#> 5         4     0     6         2
#> 6         4     1     4         6
#> 7         4     1     6         2
#> 8         5     1     4         2
#> 9         5     1     6         1
#> 10        5     1     8         2DFplyrWe hope that DFplyr will be useful for your research. Please use the following information to cite the package and the overall approach. Thank you!
citation("DFplyr")
#> To cite package 'DFplyr' in publications use:
#> 
#>   Carroll J (2025). _DFplyr: A `DataFrame` (`S4Vectors`) backend for
#>   `dplyr`_. doi:10.18129/B9.bioc.DFplyr
#>   <https://doi.org/10.18129/B9.bioc.DFplyr>, R package version 1.2.0,
#>   <https://bioconductor.org/packages/DFplyr>.
#> 
#> A BibTeX entry for LaTeX users is
#> 
#>   @Manual{,
#>     title = {DFplyr: A `DataFrame` (`S4Vectors`) backend for `dplyr`},
#>     author = {Jonathan Carroll},
#>     year = {2025},
#>     note = {R package version 1.2.0},
#>     url = {https://bioconductor.org/packages/DFplyr},
#>     doi = {10.18129/B9.bioc.DFplyr},
#>   }#> ─ Session info ───────────────────────────────────────────────────────────────────────────────────────────────────────
#>  setting  value
#>  version  R version 4.5.0 RC (2025-04-04 r88126)
#>  os       Ubuntu 24.04.2 LTS
#>  system   x86_64, linux-gnu
#>  ui       X11
#>  language (EN)
#>  collate  C
#>  ctype    en_US.UTF-8
#>  tz       America/New_York
#>  date     2025-04-15
#>  pandoc   2.7.3 @ /usr/bin/ (via rmarkdown)
#>  quarto   1.5.57 @ /usr/local/bin/quarto
#> 
#> ─ Packages ───────────────────────────────────────────────────────────────────────────────────────────────────────────
#>  package          * version date (UTC) lib source
#>  BiocGenerics     * 0.54.0  2025-04-15 [2] Bioconductor 3.21 (R 4.5.0)
#>  BiocManager        1.30.25 2024-08-28 [2] CRAN (R 4.5.0)
#>  BiocStyle        * 2.36.0  2025-04-15 [2] Bioconductor 3.21 (R 4.5.0)
#>  bookdown           0.43    2025-04-15 [2] CRAN (R 4.5.0)
#>  bslib              0.9.0   2025-01-30 [2] CRAN (R 4.5.0)
#>  cachem             1.1.0   2024-05-16 [2] CRAN (R 4.5.0)
#>  cli                3.6.4   2025-02-13 [2] CRAN (R 4.5.0)
#>  DFplyr           * 1.2.0   2025-04-15 [1] Bioconductor 3.21 (R 4.5.0)
#>  digest             0.6.37  2024-08-19 [2] CRAN (R 4.5.0)
#>  dplyr            * 1.1.4   2023-11-17 [2] CRAN (R 4.5.0)
#>  evaluate           1.0.3   2025-01-10 [2] CRAN (R 4.5.0)
#>  fastmap            1.2.0   2024-05-15 [2] CRAN (R 4.5.0)
#>  generics         * 0.1.3   2022-07-05 [2] CRAN (R 4.5.0)
#>  GenomeInfoDb       1.44.0  2025-04-15 [2] Bioconductor 3.21 (R 4.5.0)
#>  GenomeInfoDbData   1.2.14  2025-04-10 [2] Bioconductor
#>  GenomicRanges      1.60.0  2025-04-15 [2] Bioconductor 3.21 (R 4.5.0)
#>  glue               1.8.0   2024-09-30 [2] CRAN (R 4.5.0)
#>  htmltools          0.5.8.1 2024-04-04 [2] CRAN (R 4.5.0)
#>  httr               1.4.7   2023-08-15 [2] CRAN (R 4.5.0)
#>  IRanges            2.42.0  2025-04-15 [2] Bioconductor 3.21 (R 4.5.0)
#>  jquerylib          0.1.4   2021-04-26 [2] CRAN (R 4.5.0)
#>  jsonlite           2.0.0   2025-03-27 [2] CRAN (R 4.5.0)
#>  knitr              1.50    2025-03-16 [2] CRAN (R 4.5.0)
#>  lifecycle          1.0.4   2023-11-07 [2] CRAN (R 4.5.0)
#>  magrittr           2.0.3   2022-03-30 [2] CRAN (R 4.5.0)
#>  pillar             1.10.2  2025-04-05 [2] CRAN (R 4.5.0)
#>  pkgconfig          2.0.3   2019-09-22 [2] CRAN (R 4.5.0)
#>  R6                 2.6.1   2025-02-15 [2] CRAN (R 4.5.0)
#>  rlang              1.1.6   2025-04-11 [2] CRAN (R 4.5.0)
#>  rmarkdown          2.29    2024-11-04 [2] CRAN (R 4.5.0)
#>  S4Vectors        * 0.46.0  2025-04-15 [2] Bioconductor 3.21 (R 4.5.0)
#>  sass               0.4.10  2025-04-11 [2] CRAN (R 4.5.0)
#>  sessioninfo        1.2.3   2025-02-05 [2] CRAN (R 4.5.0)
#>  tibble             3.2.1   2023-03-20 [2] CRAN (R 4.5.0)
#>  tidyselect         1.2.1   2024-03-11 [2] CRAN (R 4.5.0)
#>  UCSC.utils         1.4.0   2025-04-15 [2] Bioconductor 3.21 (R 4.5.0)
#>  vctrs              0.6.5   2023-12-01 [2] CRAN (R 4.5.0)
#>  withr              3.0.2   2024-10-28 [2] CRAN (R 4.5.0)
#>  xfun               0.52    2025-04-02 [2] CRAN (R 4.5.0)
#>  XVector            0.48.0  2025-04-15 [2] Bioconductor 3.21 (R 4.5.0)
#>  yaml               2.3.10  2024-07-26 [2] CRAN (R 4.5.0)
#> 
#>  [1] /tmp/RtmpHexoHG/Rinst1759ee115f3328
#>  [2] /home/biocbuild/bbs-3.21-bioc/R/site-library
#>  [3] /home/biocbuild/bbs-3.21-bioc/R/library
#>  * ── Packages attached to the search path.
#> 
#> ──────────────────────────────────────────────────────────────────────────────────────────────────────────────────────