Skip to content

Commit 4acda17

Browse files
authored
Fix list_combine(list(NA), default =) and add vec_ptype_common(.finalise=)
1 parent 523ec0f commit 4acda17

File tree

17 files changed

+364
-81
lines changed

17 files changed

+364
-81
lines changed

NEWS.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
# vctrs (development version)
22

3+
* `vec_ptype_common()` has gained a `.finalise` argument that defaults to `TRUE`. Setting this to `FALSE` lets you opt out of prototype finalisation, which allows `vec_ptype_common()` to act like `vec_ptype()` and `vec_ptype2()`, which don't finalise. This can be useful in some advanced common type determination cases (#2100).
4+
35
* New `vec_pany()` and `vec_pall()`, parallel variants of `any()` and `all()` (in the same way that `pmin()` and `pmax()` are parallel variants of `min()` and `max()`).
46

57
* The deprecated C callable for `vec_is_vector()` has been removed.

R/type-unspecified.R

Lines changed: 28 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,28 @@
1-
#' A 1d vector of unspecified type
1+
#' Unspecified vectors and prototype finalisation
22
#'
33
#' @description
4-
#' This is the underlying type used to represent logical vectors that only
5-
#' contain `NA`. These require special handling because we want to allow logical
6-
#' `NA` to specify missingness that can be cast to any other type.
7-
#'
8-
#' [vec_ptype()] and [vec_ptype2()] convert a logical vector of `NA` into an
9-
#' empty `<unspecified>` type. This type can combine with any other type.
4+
#' `unspecified()` is the underlying type used to represent logical vectors that
5+
#' only contain `NA`. These require special handling because we want to allow
6+
#' logical `NA` to specify missingness that can be cast to any other type.
7+
#'
8+
#' In vctrs, the `<unspecified>` type is considered _unfinalised_ and is not
9+
#' suitable for use in most vctrs functions that take a `ptype` argument, like
10+
#' [vec_c()]. The purpose of `vec_ptype_finalise()` is to finalise any
11+
#' `<unspecified>` types into `<logical>` after common type determination
12+
#' has been completed.
13+
#'
14+
#' [vec_ptype()] and [vec_ptype2()] return _unfinalised_ types, and will convert
15+
#' a logical vector of `NA` into an empty `<unspecified>` type that can combine
16+
#' with any other type. It is unlikely that you will call these yourself, but,
17+
#' if you do, you'll need to manually finalise with `vec_ptype_finalise()` to
18+
#' take care of any `<unspecified>` types.
1019
#'
1120
#' [vec_ptype_common()] uses both [vec_ptype()] and [vec_ptype2()] to compute
12-
#' the common type, but then returns a _finalised_ type using
13-
#' [vec_ptype_finalise()]. The purpose of `vec_ptype_finalise()` is to turn any
14-
#' remaining `<unspecified>` types back into `<logical>`, which is the more
15-
#' useful type for callers of `vec_ptype_common()`.
21+
#' the common type, but typically returns a _finalised_ type for immediate usage
22+
#' in other vctrs functions. You can optionally skip finalisation by setting
23+
#' `.finalise = FALSE`, in which case `vec_ptype_common()` can return
24+
#' `<unspecified>` and you'll need to manually call `vec_ptype_finalise()`
25+
#' yourself.
1626
#'
1727
#' `vec_ptype_finalise()` is an S3 generic, but it is extremely rare to need to
1828
#' write an S3 method for this. Data frames (and data frame subclasses) are
@@ -63,6 +73,10 @@
6373
#' vec_ptype_common(NA)
6474
#' vec_ptype_common(NA, NA)
6575
#' vec_ptype_show(vec_ptype_common(df))
76+
#'
77+
#' # `vec_ptype_common()` lets you opt out of finalisation using `.finalise`
78+
#' vec_ptype_common(NA, .finalise = FALSE)
79+
#' vec_ptype_show(vec_ptype_common(df, .finalise = FALSE))
6680
NULL
6781

6882
#' @param n Length of vector
@@ -102,8 +116,9 @@ ununspecify <- function(x) {
102116

103117
#' @inheritParams rlang::args_dots_empty
104118
#'
105-
#' @param x A `ptype` to finalize, typically a result of [vec_ptype()] or
106-
#' [vec_ptype2()].
119+
#' @param x A `ptype` to finalize, typically a result of [vec_ptype()],
120+
#' [vec_ptype2()], or [`vec_ptype_common(.finalise =
121+
#' FALSE)`][vec_ptype_common].
107122
#'
108123
#' @rdname vctrs-unspecified
109124
#' @export

R/type.R

Lines changed: 72 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,29 +1,53 @@
11
#' Find the prototype of a set of vectors
22
#'
3-
#' `vec_ptype()` returns the unfinalised prototype of a single vector.
4-
#' `vec_ptype_common()` finds the common type of multiple vectors.
5-
#' `vec_ptype_show()` nicely prints the common type of any number of
6-
#' inputs, and is designed for interactive exploration.
3+
#' @description
4+
#' - `vec_ptype()` returns the [unfinalised][vec_ptype_finalise] prototype of a
5+
#' single vector.
6+
#'
7+
#' - `vec_ptype_common()` returns the common type of multiple vectors. By
8+
#' default, this is [finalised][vec_ptype_finalise] for immediate usage, but
9+
#' can optionally be left unfinalised for advanced common type determination.
10+
#'
11+
#' - `vec_ptype_show()` nicely prints the common type of any number of inputs,
12+
#' and is designed for interactive exploration.
713
#'
814
#' @inheritParams rlang::args_error_context
915
#'
1016
#' @param x A vector
17+
#'
1118
#' @param ... For `vec_ptype()`, these dots are for future extensions and must
1219
#' be empty.
1320
#'
1421
#' For `vec_ptype_common()` and `vec_ptype_show()`, vector inputs.
22+
#'
1523
#' @param x_arg Argument name for `x`. This is used in error messages to inform
1624
#' the user about the locations of incompatible types.
25+
#'
1726
#' @param .ptype If `NULL`, the default, the output type is determined by
1827
#' computing the common type across all elements of `...`.
1928
#'
2029
#' Alternatively, you can supply `.ptype` to give the output known type.
2130
#' If `getOption("vctrs.no_guessing")` is `TRUE` you must supply this value:
2231
#' this is a convenient way to make production code demand fixed types.
32+
#'
33+
#' @param .finalise Should `vec_ptype_common()` [finalise][vec_ptype_finalise]
34+
#' its output?
35+
#'
36+
#' - If `TRUE`, [vec_ptype_finalise()] is called on the final `ptype` before
37+
#' it is returned. Practically this has the effect of converting any
38+
#' types from [unspecified] to logical.
39+
#'
40+
#' - If `FALSE`, [unspecified] types are left unfinalised, which can be useful
41+
#' for advanced cases where you combine one common type result with another
42+
#' type via [vec_ptype2()]. Note that you must manually call
43+
#' [vec_ptype_finalise()] on the final `ptype` before supplying it to any
44+
#' other vctrs functions.
45+
#'
2346
#' @return `vec_ptype()` and `vec_ptype_common()` return a prototype
24-
#' (a size-0 vector)
47+
#' (a size-0 vector).
2548
#'
2649
#' @section `vec_ptype()`:
50+
#'
2751
#' `vec_ptype()` returns [size][vec_size] 0 vectors potentially
2852
#' containing attributes but no data. Generally, this is just
2953
#' `vec_slice(x, 0L)`, but some inputs require special
@@ -36,7 +60,8 @@
3660
#' * The prototype of logical vectors that only contain missing values
3761
#' is the special [unspecified] type, which can be coerced to any
3862
#' other 1d type. This allows bare `NA`s to represent missing values
39-
#' for any 1d vector type.
63+
#' for any 1d vector type. [Finalising][vec_ptype_finalise] this type
64+
#' converts it from unspecified back to logical.
4065
#'
4166
#' See [internal-faq-ptype2-identity] for more information about
4267
#' identity values.
@@ -49,15 +74,16 @@
4974
#' improve the performance of your class in many cases ([common
5075
#' type][vec_ptype2] imputation in particular).
5176
#'
52-
#' Because it may contain unspecified vectors, the prototype returned
53-
#' by `vec_ptype()` is said to be __unfinalised__. Call
54-
#' [vec_ptype_finalise()] to finalise it. Commonly you will need the
55-
#' finalised prototype as returned by `vec_slice(x, 0L)`.
77+
#' Because it may contain unspecified vectors, the prototype returned by
78+
#' `vec_ptype()` is said to be __unfinalised__. Call [vec_ptype_finalise()] to
79+
#' finalise it.
5680
#'
5781
#' @section `vec_ptype_common()`:
82+
#'
5883
#' `vec_ptype_common()` first finds the prototype of each input, then
59-
#' successively calls [vec_ptype2()] to find a common type. It returns
60-
#' a [finalised][vec_ptype_finalise] prototype.
84+
#' successively calls [vec_ptype2()] to find a common type. It returns a
85+
#' [finalised][vec_ptype_finalise] prototype by default, but can optionally be
86+
#' left unfinalised for advanced common type determination.
6187
#'
6288
#' @section Dependencies of `vec_ptype()`:
6389
#' - [vec_slice()] for returning an empty slice
@@ -70,7 +96,6 @@
7096
#' @examples
7197
#' # Unknown types ------------------------------------------
7298
#' vec_ptype_show()
73-
#' vec_ptype_show(NA)
7499
#' vec_ptype_show(NULL)
75100
#'
76101
#' # Vectors ------------------------------------------------
@@ -100,6 +125,30 @@
100125
#' data.frame(y = 2),
101126
#' data.frame(z = "a")
102127
#' )
128+
#'
129+
#' # Finalisation -------------------------------------------
130+
#'
131+
#' # `vec_ptype()` and `vec_ptype2()` return unfinalised ptypes so that they
132+
#' # can be coerced to any other type
133+
#' vec_ptype(NA)
134+
#' vec_ptype2(NA, NA)
135+
#'
136+
#' # By default `vec_ptype_common()` finalises so that you can use its result
137+
#' # directly in other vctrs functions
138+
#' vec_ptype_common(NA, NA)
139+
#'
140+
#' # You can opt out of finalisation to make it work like `vec_ptype()` and
141+
#' # `vec_ptype2()` with `.finalise = FALSE`, but don't forget that you must
142+
#' # call `vec_ptype_finalise()` manually if you do so!
143+
#' vec_ptype_common(NA, NA, .finalise = FALSE)
144+
#' vec_ptype_finalise(vec_ptype_common(NA, NA, .finalise = FALSE))
145+
#'
146+
#' # This can be useful in rare scenarios, like including a separate `default`
147+
#' # argument in the ptype computation
148+
#' xs <- list(NA, NA)
149+
#' default <- "a"
150+
#' try(vec_ptype2(vec_ptype_common(!!!xs), default))
151+
#' vec_ptype2(vec_ptype_common(!!!xs, .finalise = FALSE), default)
103152
vec_ptype <- function(x, ..., x_arg = "", call = caller_env()) {
104153
check_dots_empty0(...)
105154
return(.Call(ffi_ptype, x, x_arg, environment()))
@@ -111,20 +160,28 @@ vec_ptype <- function(x, ..., x_arg = "", call = caller_env()) {
111160
vec_ptype_common <- function(
112161
...,
113162
.ptype = NULL,
163+
.finalise = TRUE,
114164
.arg = "",
115165
.call = caller_env()
116166
) {
117-
.External2(ffi_ptype_common, list2(...), .ptype)
167+
.External2(ffi_ptype_common, list2(...), .ptype, .finalise)
118168
}
119169

120170
vec_ptype_common_params <- function(
121171
...,
122172
.ptype = NULL,
173+
.finalise = TRUE,
123174
.fallback_opts = fallback_opts(),
124175
.arg = "",
125176
.call = caller_env()
126177
) {
127-
.External2(ffi_ptype_common_params, list2(...), .ptype, .fallback_opts)
178+
.External2(
179+
ffi_ptype_common_params,
180+
list2(...),
181+
.ptype,
182+
.finalise,
183+
.fallback_opts
184+
)
128185
}
129186

130187
vec_ptype_common_fallback <- function(

man/vctrs-unspecified.Rd

Lines changed: 26 additions & 12 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

0 commit comments

Comments
 (0)