Skip to content

Commit

Permalink
Merge branch 'release/3.11.4'
Browse files Browse the repository at this point in the history
  • Loading branch information
psychelzh committed Jun 10, 2024
2 parents c9f3459 + 8d50900 commit e70974a
Show file tree
Hide file tree
Showing 10 changed files with 59 additions and 47 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: tarflow.iquizoo
Title: Setup "targets" Workflows for "iquizoo" Data Processing
Version: 3.11.3
Version: 3.11.4
Authors@R: c(
person("Liang", "Zhang", , "[email protected]", role = c("aut", "cre"),
comment = c(ORCID = "0000-0001-9041-1150")),
Expand Down
10 changes: 10 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,13 @@
# tarflow.iquizoo 3.11.4

## Breaking Changes

* Let `params` and `contents` arguments be mutually exclusive in `tar_prep_iquizoo()`.

## Upkeep

* Fixed deprecation of `groups` argument in favor of `group`.

# tarflow.iquizoo 3.11.3

* Added `"bit64"` to packages option of targets in order to keep the integer64 class in the output data.
Expand Down
2 changes: 1 addition & 1 deletion R/database.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ fetch_iquizoo <- function(query, ...,
}
# nocov end
if (inherits(source$driver, "MariaDBDriver")) {
con <- DBI::dbConnect(source$driver, groups = source$groups, ...)
con <- DBI::dbConnect(source$driver, group = source$group, ...)
}
on.exit(DBI::dbDisconnect(con))
DBI::dbGetQuery(con, query, params = params)
Expand Down
8 changes: 4 additions & 4 deletions R/setup.R
Original file line number Diff line number Diff line change
Expand Up @@ -45,19 +45,19 @@ setup_templates <- function(contents = NULL,
#' @param dsn The data source name of an **ODBC** database connector. See
#' [odbc::dbConnect()] for more information. Used when `driver` is set as
#' [odbc::odbc()].
#' @param groups Section identifier in the `default.file`. See
#' @param group Section identifier in the `default.file`. See
#' [RMariaDB::MariaDB()] for more information. Used when `driver` is set as
#' [RMariaDB::MariaDB()].
#' @return An S3 class of `tarflow.source` with the options.
#' @export
setup_source <- function(driver = getOption("tarflow.driver"),
dsn = getOption("tarflow.dsn"),
groups = getOption("tarflow.groups")) {
group = getOption("tarflow.group")) {
structure(
list(
driver = driver,
dsn = dsn,
groups = groups
group = group
),
class = "tarflow.source"
)
Expand All @@ -82,7 +82,7 @@ check_source <- function(source = setup_source()) {
}
# nocov end
if (inherits(source$driver, "MariaDBDriver")) {
return(DBI::dbCanConnect(source$driver, groups = source$groups))
return(DBI::dbCanConnect(source$driver, group = source$group))
}
return(FALSE)
}
Expand Down
48 changes: 26 additions & 22 deletions R/targets.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,17 +5,15 @@
#' specific project and task/game combination. Further pre-processing on the
#' fetched data can also be added if requested.
#'
#' @param params A [data.frame] or [list] contains the parameters to be bound to
#' the query. Default templates require specifying `organization_name` and
#' `project_name`, in that order. If `contents` template is specified without
#' any parameters, set it as empty vector or `NULL`. If `contents` argument is
#' specified, this argument is omitted.
#' @param params,contents Used as the configuration of data fetching. These two
#' arguments are mutually exclusive. If `params` is specified, it will be used
#' as parameters to be bound to the query, see [DBI::dbBind()] for more
#' details. The default template requires specifying `organization_name` and
#' `project_name`, in that order. If `contents` is specified, it should be a
#' [data.frame] and will be used directly as the configuration of data
#' fetching. Note `contents` should at least contain `project_id` and
#' `game_id` names.
#' @param ... For future usage. Should be empty.
#' @param contents The contents structure used as the configuration of data
#' fetching. It is typically automatically fetched from database based on the
#' `contents` template in `templates`. If not `NULL`, it will be used directly
#' and ignore that specified in `templates`. Note `contents` should at least
#' contains `project_id` and `game_id` names.
#' @param what What to fetch. There are basically two types of data, i.e., raw
#' data and scores. The former is the logged raw data for each trial of the
#' tasks/games, while the latter is the scores calculated by iQuizoo server.
Expand All @@ -29,23 +27,37 @@
#' done. If set as "none", neither will be done. If `what` is "scores", this
#' argument will be ignored.
#' @param combine Specify which targets to be combined. Note you should only
#' specify names from `c("scores", "raw_data", "raw_data_parsed",
#' "indices")`. If `NULL`, none will be combined.
#' specify names from `c("scores", "raw_data", "raw_data_parsed", "indices")`.
#' If `NULL`, none will be combined.
#' @param templates The SQL template files used to fetch data. See
#' [setup_templates()] for details.
#' @param check_progress Whether to check the progress hash. Set it as `FALSE`
#' if the project is finalized.
#' @return A list of target objects.
#' @export
tar_prep_iquizoo <- function(params, ...,
contents = NULL,
tar_prep_iquizoo <- function(params, contents, ...,
what = c("raw_data", "scores"),
action_raw_data = c("all", "parse", "none"),
combine = NULL,
templates = setup_templates(),
check_progress = TRUE) {
check_dots_empty()
check_templates(templates)
contents <- switch(check_exclusive(params, contents),
params = fetch_iquizoo_mem()(
read_file(templates$contents),
params = unname(
if (!is_empty(params)) as.list(params)
)
),
contents = {
stopifnot(
"`content` must be a `data.frame`." =
is.data.frame(contents)
)
contents
}
)
what <- match.arg(what, several.ok = TRUE)
action_raw_data <- match.arg(action_raw_data)
if (!is.null(combine) && !all(combine %in% objects())) {
Expand All @@ -54,14 +66,6 @@ tar_prep_iquizoo <- function(params, ...,
class = "tarflow_bad_combine"
)
}
if (is.null(contents)) {
contents <- fetch_iquizoo_mem()(
read_file(templates$contents),
params = unname(
if (!is_empty(params)) as.list(params)
)
)
}
if (nrow(contents) == 0) {
cli::cli_abort(
"No contents to fetch.",
Expand Down
2 changes: 1 addition & 1 deletion R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ NULL
if (requireNamespace("RMariaDB", quietly = TRUE)) {
op_tarflow <- list(
tarflow.driver = RMariaDB::MariaDB(),
tarflow.groups = name_db_src_default
tarflow.group = name_db_src_default
)
} else if (requireNamespace("odbc", quietly = TRUE)) {
op_tarflow <- list(
Expand Down
4 changes: 2 additions & 2 deletions man/setup_source.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

24 changes: 11 additions & 13 deletions man/tar_prep_iquizoo.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions tests/testthat/_snaps/targets.md
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@
{
"type": "character",
"attributes": {},
"value": ["陈佳洋", "茹祎", "于胜蓝", "李荟镕", "张忱涵", "连宗鸿", "徐小琳"]
"value": ["徐小琳", "连宗鸿", "张忱涵", "李荟镕", "于胜蓝", "茹祎", "陈佳洋"]
},
{
"type": "integer",
Expand All @@ -58,7 +58,7 @@
"value": ["Date"]
}
},
"value": [-25202, -25201, -25200, -25199, -25198, -25197, -25196]
"value": [-25196, -25197, -25198, -25199, -25200, -25201, -25202]
},
{
"type": "character",
Expand Down
2 changes: 1 addition & 1 deletion tests/testthat/test-targets.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ test_that("Default templates work", {

test_that("Signal error if templates not created correctly", {
templates <- list(contents = "myfile")
tar_prep_iquizoo(templates = templates) |>
tar_prep_iquizoo(NULL, templates = templates) |>
expect_error(class = "tarflow_bad_templates")
})

Expand Down

0 comments on commit e70974a

Please sign in to comment.