From 99d7a890f290db07fd335c93ab68938a3b91e6d9 Mon Sep 17 00:00:00 2001 From: Mikko Marttila <13412395+mikmart@users.noreply.github.com> Date: Fri, 19 Jan 2024 22:02:31 +0000 Subject: [PATCH 1/8] Add server-side support for SearchBuilder --- R/searchBuilder.R | 93 +++++++++++++++++++++++++++++++++++++++++++++++ R/shiny.R | 5 +++ 2 files changed, 98 insertions(+) create mode 100644 R/searchBuilder.R diff --git a/R/searchBuilder.R b/R/searchBuilder.R new file mode 100644 index 00000000..904068bf --- /dev/null +++ b/R/searchBuilder.R @@ -0,0 +1,93 @@ +sbEvaluateSearch <- function(search, data) { + stopifnot(search$logic %in% c("AND", "OR")) + Reduce( + switch(search$logic, AND = `&`, OR = `|`), + lapply(search$criteria, sbEvaluateCriteria, data) + ) +} + +sbEvaluateCriteria <- function(criteria, data) { + # https://datatables.net/reference/option/searchBuilder.preDefined.criteria + if ("logic" %in% names(criteria)) { + # this is a sub-group + sbEvaluateSearch(criteria, data) + } else { + # this is a criteria + cond <- criteria$condition + type <- criteria$type + x <- data[[criteria$origData %||% criteria$data]] + v <- sbParseValue(sbExtractValue(criteria), type) + sbEvaluateCondition(cond, type, x, v) + } +} + +sbExtractValue <- function(criteria) { + if (criteria$condition %in% c("between", "!between")) { + # array values are passed in a funny way to R + c(criteria$value1, criteria$value2) + } else { + criteria$value + } +} + +sbParseValue <- function(value, type) { + if (type %in% c("string", "html")) { + as.character(value) + } else if (type %in% c("num", "num-fmt", "html-num", "html-num-fmt")) { + as.numeric(value) + } else if (type %in% c("date", "moment", "luxon")) { + as.Date(value) + } else { + stop(sprintf('unsupported criteria type "%s"', type)) + } +} + +sbEvaluateCondition <- function(condition, type, x, value) { + # https://datatables.net/reference/option/searchBuilder.preDefined.criteria.condition + if (type %in% c("string", "html")) { + switch( + condition, + "!=" = x != value, + "!null" = !is.na(x) & x != "", + "=" = x == value, + "contains" = grepl(value, x, fixed = TRUE), + "!contains" = !grepl(value, x, fixed = TRUE), + "ends" = endsWith(x, value), + "!ends" = !endsWith(x, value), + "null" = is.na(x) | x == "", + "starts" = startsWith(x, value), + "!starts" = !startsWith(x, value), + stop(sprintf('unsupported condition "%s" for criteria type "%s"', condition, type)) + ) + } else if (type %in% c("num", "num-fmt", "html-num", "html-num-fmt")) { + switch( + condition, + "!=" = x != value, + "!null" = !is.na(x), + "<" = x < value, + "<=" = x <= value, + "=" = x == value, + ">" = x > value, + ">=" = x >= value, + "between" = x >= value[1] & x <= value[2], + "!between" = x < value[1] | x > value[2], + "null" = is.na(x), + stop(sprintf('unsupported condition "%s" for criteria type "%s"', condition, type)) + ) + } else if (type %in% c("date", "moment", "luxon")) { + switch( + condition, + "!=" = x != value, + "!null" = !is.na(x), + "<" = x < value, + "=" = x == value, + ">" = x > value, + "between" = x >= value[1] & x <= value[2], + "!between" = x < value[1] | x > value[2], + "null" = is.na(x), + stop(sprintf('unsupported condition "%s" for criteria type "%s"', condition, type)) + ) + } else { + stop(sprintf('unsupported criteria type "%s"', type)) + } +} diff --git a/R/shiny.R b/R/shiny.R index 3e8b308a..4cf88b5e 100644 --- a/R/shiny.R +++ b/R/shiny.R @@ -649,6 +649,11 @@ dataTablesFilter = function(data, params) { # start searching with all rows i = seq_len(n) + # apply SearchBuilder query if present + if (!is.null(q$searchBuilder)) { + i = which(sbEvaluateSearch(q$searchBuilder, data)) + } + # search by columns if (length(i)) for (j in names(q$columns)) { col = q$columns[[j]] From 1eda45b4c50a3aa6732e51cfc308477247205c82 Mon Sep 17 00:00:00 2001 From: Mikko Marttila <13412395+mikmart@users.noreply.github.com> Date: Fri, 19 Jan 2024 22:05:14 +0000 Subject: [PATCH 2/8] Conform to project style --- R/searchBuilder.R | 93 ++++++++++++++++++++++++----------------------- R/shiny.R | 4 +- 2 files changed, 49 insertions(+), 48 deletions(-) diff --git a/R/searchBuilder.R b/R/searchBuilder.R index 904068bf..0282cd7f 100644 --- a/R/searchBuilder.R +++ b/R/searchBuilder.R @@ -1,28 +1,28 @@ -sbEvaluateSearch <- function(search, data) { - stopifnot(search$logic %in% c("AND", "OR")) +sbEvaluateSearch = function(search, data) { + stopifnot(search$logic %in% c('AND', 'OR')) Reduce( switch(search$logic, AND = `&`, OR = `|`), lapply(search$criteria, sbEvaluateCriteria, data) ) } -sbEvaluateCriteria <- function(criteria, data) { +sbEvaluateCriteria = function(criteria, data) { # https://datatables.net/reference/option/searchBuilder.preDefined.criteria - if ("logic" %in% names(criteria)) { + if ('logic' %in% names(criteria)) { # this is a sub-group sbEvaluateSearch(criteria, data) } else { # this is a criteria - cond <- criteria$condition - type <- criteria$type - x <- data[[criteria$origData %||% criteria$data]] - v <- sbParseValue(sbExtractValue(criteria), type) + cond = criteria$condition + type = criteria$type + x = data[[criteria$origData %||% criteria$data]] + v = sbParseValue(sbExtractValue(criteria), type) sbEvaluateCondition(cond, type, x, v) } } -sbExtractValue <- function(criteria) { - if (criteria$condition %in% c("between", "!between")) { +sbExtractValue = function(criteria) { + if (criteria$condition %in% c('between', '!between')) { # array values are passed in a funny way to R c(criteria$value1, criteria$value2) } else { @@ -30,61 +30,62 @@ sbExtractValue <- function(criteria) { } } -sbParseValue <- function(value, type) { - if (type %in% c("string", "html")) { +sbParseValue = function(value, type) { + # TODO: handle 'moment' and 'luxon' types mentioned in condition reference + if (type %in% c('string', 'html')) { as.character(value) - } else if (type %in% c("num", "num-fmt", "html-num", "html-num-fmt")) { + } else if (type %in% c('num', 'num-fmt', 'html-num', 'html-num-fmt')) { as.numeric(value) - } else if (type %in% c("date", "moment", "luxon")) { + } else if (type %in% c('date')) { as.Date(value) } else { stop(sprintf('unsupported criteria type "%s"', type)) } } -sbEvaluateCondition <- function(condition, type, x, value) { +sbEvaluateCondition = function(condition, type, x, value) { # https://datatables.net/reference/option/searchBuilder.preDefined.criteria.condition - if (type %in% c("string", "html")) { + if (type %in% c('string', 'html')) { switch( condition, - "!=" = x != value, - "!null" = !is.na(x) & x != "", - "=" = x == value, - "contains" = grepl(value, x, fixed = TRUE), - "!contains" = !grepl(value, x, fixed = TRUE), - "ends" = endsWith(x, value), - "!ends" = !endsWith(x, value), - "null" = is.na(x) | x == "", - "starts" = startsWith(x, value), - "!starts" = !startsWith(x, value), + '!=' = x != value, + '!null' = !is.na(x) & x != '', + '=' = x == value, + 'contains' = grepl(value, x, fixed = TRUE), + '!contains' = !grepl(value, x, fixed = TRUE), + 'ends' = endsWith(x, value), + '!ends' = !endsWith(x, value), + 'null' = is.na(x) | x == '', + 'starts' = startsWith(x, value), + '!starts' = !startsWith(x, value), stop(sprintf('unsupported condition "%s" for criteria type "%s"', condition, type)) ) - } else if (type %in% c("num", "num-fmt", "html-num", "html-num-fmt")) { + } else if (type %in% c('num', 'num-fmt', 'html-num', 'html-num-fmt')) { switch( condition, - "!=" = x != value, - "!null" = !is.na(x), - "<" = x < value, - "<=" = x <= value, - "=" = x == value, - ">" = x > value, - ">=" = x >= value, - "between" = x >= value[1] & x <= value[2], - "!between" = x < value[1] | x > value[2], - "null" = is.na(x), + '!=' = x != value, + '!null' = !is.na(x), + '<' = x < value, + '<=' = x <= value, + '=' = x == value, + '>' = x > value, + '>=' = x >= value, + 'between' = x >= value[1] & x <= value[2], + '!between' = x < value[1] | x > value[2], + 'null' = is.na(x), stop(sprintf('unsupported condition "%s" for criteria type "%s"', condition, type)) ) - } else if (type %in% c("date", "moment", "luxon")) { + } else if (type %in% c('date', 'moment', 'luxon')) { switch( condition, - "!=" = x != value, - "!null" = !is.na(x), - "<" = x < value, - "=" = x == value, - ">" = x > value, - "between" = x >= value[1] & x <= value[2], - "!between" = x < value[1] | x > value[2], - "null" = is.na(x), + '!=' = x != value, + '!null' = !is.na(x), + '<' = x < value, + '=' = x == value, + '>' = x > value, + 'between' = x >= value[1] & x <= value[2], + '!between' = x < value[1] | x > value[2], + 'null' = is.na(x), stop(sprintf('unsupported condition "%s" for criteria type "%s"', condition, type)) ) } else { diff --git a/R/shiny.R b/R/shiny.R index 4cf88b5e..7321b0db 100644 --- a/R/shiny.R +++ b/R/shiny.R @@ -650,8 +650,8 @@ dataTablesFilter = function(data, params) { i = seq_len(n) # apply SearchBuilder query if present - if (!is.null(q$searchBuilder)) { - i = which(sbEvaluateSearch(q$searchBuilder, data)) + if (!is.null(s <- q$searchBuilder)) { + i = which(sbEvaluateSearch(s, data)) } # search by columns From f2ad3aa77d18f638d681992c4c191c15d59d0855 Mon Sep 17 00:00:00 2001 From: Mikko Marttila <13412395+mikmart@users.noreply.github.com> Date: Fri, 19 Jan 2024 23:30:03 +0000 Subject: [PATCH 3/8] Add some tests --- R/searchBuilder.R | 4 +++ tests/testit/test-searchbuilder.R | 52 +++++++++++++++++++++++++++++++ 2 files changed, 56 insertions(+) create mode 100644 tests/testit/test-searchbuilder.R diff --git a/R/searchBuilder.R b/R/searchBuilder.R index 0282cd7f..a502a9e3 100644 --- a/R/searchBuilder.R +++ b/R/searchBuilder.R @@ -1,4 +1,8 @@ +# server-side processing for the SearchBuilder extension +# https://datatables.net/extensions/searchbuilder/ + sbEvaluateSearch = function(search, data) { + # https://datatables.net/reference/option/searchBuilder.preDefined stopifnot(search$logic %in% c('AND', 'OR')) Reduce( switch(search$logic, AND = `&`, OR = `|`), diff --git a/tests/testit/test-searchbuilder.R b/tests/testit/test-searchbuilder.R new file mode 100644 index 00000000..e1f928f4 --- /dev/null +++ b/tests/testit/test-searchbuilder.R @@ -0,0 +1,52 @@ +library(testit) + +assert('SearchBuilder condition evaluation works', { + (sbEvaluateCondition('>', 'num', 1:2, 1) == c(FALSE, TRUE)) + (sbEvaluateCondition('between', 'num', 7, c(2, 4)) == FALSE) + (sbEvaluateCondition('starts', 'string', 'foo', 'f') == TRUE) +}) + +assert('SearchBuilder logic evaluation works', { + res = sbEvaluateSearch( + list( + logic = 'AND', + criteria = list( + list(condition = '<=', data = 'a', value = '4', type = 'num'), + list(condition = '>=', data = 'a', value = '2', type = 'num') + ) + ), + data.frame(a = 1:9) + ) + (setequal(which(res), 2:4)) + res = sbEvaluateSearch( + list( + logic = 'OR', + criteria = list( + list(condition = '>', data = 'a', value = '4', type = 'num'), + list(condition = '<', data = 'a', value = '2', type = 'num') + ) + ), + data.frame(a = 1:9) + ) + (setequal(which(res), c(1, 5:9))) +}) + +assert('SearchBuilder complex queries work', { + res = sbEvaluateSearch( + list( + logic = 'OR', + criteria = list( + list(condition = '=', data = 'a', value = '7', type = 'num'), + list( + logic = 'AND', + criteria = list( + list(condition = '<=', data = 'a', value = '4', type = 'num'), + list(condition = '>=', data = 'a', value = '2', type = 'num') + ) + ) + ) + ), + data.frame(a = 1:9) + ) + (setequal(which(res), c(2:4, 7))) +}) From d60b27a9ddeb7463577e47ecc0d412d0b24e378e Mon Sep 17 00:00:00 2001 From: Mikko Marttila <13412395+mikmart@users.noreply.github.com> Date: Fri, 19 Jan 2024 23:30:30 +0000 Subject: [PATCH 4/8] Use lowercase filename --- R/{searchBuilder.R => searchbuilder.R} | 0 1 file changed, 0 insertions(+), 0 deletions(-) rename R/{searchBuilder.R => searchbuilder.R} (100%) diff --git a/R/searchBuilder.R b/R/searchbuilder.R similarity index 100% rename from R/searchBuilder.R rename to R/searchbuilder.R From 927f4d8ff3b04d38d9d89066a2bf12dec23c6857 Mon Sep 17 00:00:00 2001 From: Mikko Marttila <13412395+mikmart@users.noreply.github.com> Date: Fri, 19 Jan 2024 23:57:11 +0000 Subject: [PATCH 5/8] Fix ends and starts for factor columns --- R/searchbuilder.R | 8 ++++---- tests/testit/test-searchbuilder.R | 1 + 2 files changed, 5 insertions(+), 4 deletions(-) diff --git a/R/searchbuilder.R b/R/searchbuilder.R index a502a9e3..6d93887d 100644 --- a/R/searchbuilder.R +++ b/R/searchbuilder.R @@ -57,11 +57,11 @@ sbEvaluateCondition = function(condition, type, x, value) { '=' = x == value, 'contains' = grepl(value, x, fixed = TRUE), '!contains' = !grepl(value, x, fixed = TRUE), - 'ends' = endsWith(x, value), - '!ends' = !endsWith(x, value), + 'ends' = endsWith(as.character(x), value), + '!ends' = !endsWith(as.character(x), value), 'null' = is.na(x) | x == '', - 'starts' = startsWith(x, value), - '!starts' = !startsWith(x, value), + 'starts' = startsWith(as.character(x), value), + '!starts' = !startsWith(as.character(x), value), stop(sprintf('unsupported condition "%s" for criteria type "%s"', condition, type)) ) } else if (type %in% c('num', 'num-fmt', 'html-num', 'html-num-fmt')) { diff --git a/tests/testit/test-searchbuilder.R b/tests/testit/test-searchbuilder.R index e1f928f4..c1d4c369 100644 --- a/tests/testit/test-searchbuilder.R +++ b/tests/testit/test-searchbuilder.R @@ -4,6 +4,7 @@ assert('SearchBuilder condition evaluation works', { (sbEvaluateCondition('>', 'num', 1:2, 1) == c(FALSE, TRUE)) (sbEvaluateCondition('between', 'num', 7, c(2, 4)) == FALSE) (sbEvaluateCondition('starts', 'string', 'foo', 'f') == TRUE) + (sbEvaluateCondition('starts', 'string', factor('foo'), 'f') == TRUE) }) assert('SearchBuilder logic evaluation works', { From 8c2460938938c81b1721597f8f8bc29fdb14511d Mon Sep 17 00:00:00 2001 From: Mikko Marttila <13412395+mikmart@users.noreply.github.com> Date: Sat, 20 Jan 2024 08:59:13 +0000 Subject: [PATCH 6/8] Streamline tests --- tests/testit/test-searchbuilder.R | 12 +----------- 1 file changed, 1 insertion(+), 11 deletions(-) diff --git a/tests/testit/test-searchbuilder.R b/tests/testit/test-searchbuilder.R index c1d4c369..c8c71f51 100644 --- a/tests/testit/test-searchbuilder.R +++ b/tests/testit/test-searchbuilder.R @@ -5,6 +5,7 @@ assert('SearchBuilder condition evaluation works', { (sbEvaluateCondition('between', 'num', 7, c(2, 4)) == FALSE) (sbEvaluateCondition('starts', 'string', 'foo', 'f') == TRUE) (sbEvaluateCondition('starts', 'string', factor('foo'), 'f') == TRUE) + (sbEvaluateCondition('null', 'string', c('', NA)) == c(TRUE, TRUE)) }) assert('SearchBuilder logic evaluation works', { @@ -19,17 +20,6 @@ assert('SearchBuilder logic evaluation works', { data.frame(a = 1:9) ) (setequal(which(res), 2:4)) - res = sbEvaluateSearch( - list( - logic = 'OR', - criteria = list( - list(condition = '>', data = 'a', value = '4', type = 'num'), - list(condition = '<', data = 'a', value = '2', type = 'num') - ) - ), - data.frame(a = 1:9) - ) - (setequal(which(res), c(1, 5:9))) }) assert('SearchBuilder complex queries work', { From fc1b64d6ba7e465a675f39cc5bc92e33d355fa2f Mon Sep 17 00:00:00 2001 From: Mikko Marttila <13412395+mikmart@users.noreply.github.com> Date: Sat, 20 Jan 2024 09:05:25 +0000 Subject: [PATCH 7/8] Update NEWS --- NEWS.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/NEWS.md b/NEWS.md index 9bb6da9b..7b6bdadd 100644 --- a/NEWS.md +++ b/NEWS.md @@ -4,6 +4,8 @@ - `updateSearch()` now sets the slider values based on the new search string for numeric columns (thanks, @mikmart, #1110). +- Added server-side processing support for the [SearchBuilder](https://datatables.net/extensions/searchbuilder/) extension (thanks, @mikmart, #963). + # CHANGES IN DT VERSION 0.31 - Upgraded DataTables version to 1.13.6 (thanks, @stla, #1091). From a1786b3d24f87874836b7cf3be2bf25cd233965c Mon Sep 17 00:00:00 2001 From: Mikko Marttila <13412395+mikmart@users.noreply.github.com> Date: Sat, 20 Jan 2024 12:47:23 +0000 Subject: [PATCH 8/8] Fix NEWS item --- NEWS.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index 7b6bdadd..341664a8 100644 --- a/NEWS.md +++ b/NEWS.md @@ -4,7 +4,7 @@ - `updateSearch()` now sets the slider values based on the new search string for numeric columns (thanks, @mikmart, #1110). -- Added server-side processing support for the [SearchBuilder](https://datatables.net/extensions/searchbuilder/) extension (thanks, @mikmart, #963). +- Added server-side processing support for the [SearchBuilder](https://datatables.net/extensions/searchbuilder/) extension (thanks, @AhmedKhaled945, @shrektan, @mikmart, #963). # CHANGES IN DT VERSION 0.31