Skip to content

Commit

Permalink
#111: opts_regex can now be passed via ...
Browse files Browse the repository at this point in the history
  • Loading branch information
gagolews committed Dec 6, 2014
1 parent 2699ca4 commit f3efe24
Show file tree
Hide file tree
Showing 21 changed files with 77 additions and 40 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: stringi
Version: 0.4-1
Date: 2014-12-06
Date: 2014-12-07
Title: Character String Processing Facilities
Description: stringi allows for fast, correct, consistent, portable,
and convenient character string/text processing in every locale
Expand Down
8 changes: 6 additions & 2 deletions NEWS
Original file line number Diff line number Diff line change
Expand Up @@ -18,9 +18,13 @@
`stri_locate_first_words`, `stri_locate_last_words`,
`stri_extract_first_words`, `stri_extract_last_words`.

(...)
* [IMPORTANT CHANGE] #111: `opts_regex`, `opts_collator`, and
`opts_brkiter` can now be supplied via `...`.
In other words, you may now simply call e.g.
`stri_detect_regex(str, pattern, case_insensitive=TRUE)` instead of
`stri_detect_regex(str, pattern, opts_regex=stri_opts_regex(case_insensitive=TRUE))`.

* [IMPORTANT CHANGE] #111: t.b.d. `opts_regex` as `...` etc.
(...)

* [NEW FEATURE] #110: t.b.d. `*_fixed`: `case_insensitive` + `stri_opts_fixed`

Expand Down
4 changes: 3 additions & 1 deletion R/search_count_4.R
Original file line number Diff line number Diff line change
Expand Up @@ -133,6 +133,8 @@ stri_count_fixed <- function(str, pattern) {

#' @export
#' @rdname stri_count
stri_count_regex <- function(str, pattern, opts_regex=NULL) {
stri_count_regex <- function(str, pattern, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_count_regex, str, pattern, opts_regex)
}
6 changes: 4 additions & 2 deletions R/search_detect_4.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@
#' stri_detect_regex(c("stringi R", "REXAMINE", "123"), '[[:alpha:]]*?')
#' stri_detect_regex(c("stringi R", "REXAMINE", "123"), '[a-zC1]')
#' stri_detect_regex(c("stringi R", "REXAMINE", "123"), '( R|RE)')
#' stri_detect_regex("stringi", "STRING.", opts_regex=stri_opts_regex(case_insensitive=TRUE))
#' stri_detect_regex("stringi", "STRING.", case_insensitive=TRUE)
#'
#' @family search_detect
#' @export
Expand Down Expand Up @@ -126,6 +126,8 @@ stri_detect_coll <- function(str, pattern, ..., opts_collator=NULL) {

#' @export
#' @rdname stri_detect
stri_detect_regex <- function(str, pattern, opts_regex=NULL) {
stri_detect_regex <- function(str, pattern, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_detect_regex, str, pattern, opts_regex)
}
12 changes: 9 additions & 3 deletions R/search_extract_4.R
Original file line number Diff line number Diff line change
Expand Up @@ -242,20 +242,26 @@ stri_extract_last_coll <- function(str, pattern, ..., opts_collator=NULL) {

#' @export
#' @rdname stri_extract
stri_extract_all_regex <- function(str, pattern, simplify=FALSE, omit_no_match=FALSE, opts_regex=NULL) {
stri_extract_all_regex <- function(str, pattern, simplify=FALSE, omit_no_match=FALSE, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_extract_all_regex, str, pattern, simplify, omit_no_match, opts_regex)
}


#' @export
#' @rdname stri_extract
stri_extract_first_regex <- function(str, pattern, opts_regex=NULL) {
stri_extract_first_regex <- function(str, pattern, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_extract_first_regex, str, pattern, opts_regex)
}


#' @export
#' @rdname stri_extract
stri_extract_last_regex <- function(str, pattern, opts_regex=NULL) {
stri_extract_last_regex <- function(str, pattern, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_extract_last_regex, str, pattern, opts_regex)
}
12 changes: 9 additions & 3 deletions R/search_locate_4.R
Original file line number Diff line number Diff line change
Expand Up @@ -261,21 +261,27 @@ stri_locate_last_coll <- function(str, pattern, ..., opts_collator=NULL) {

#' @export
#' @rdname stri_locate
stri_locate_all_regex <- function(str, pattern, omit_no_match=FALSE, opts_regex=NULL) {
stri_locate_all_regex <- function(str, pattern, omit_no_match=FALSE, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_locate_all_regex, str, pattern, omit_no_match, opts_regex)
}


#' @export
#' @rdname stri_locate
stri_locate_first_regex <- function(str, pattern, opts_regex=NULL) {
stri_locate_first_regex <- function(str, pattern, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_locate_first_regex, str, pattern, opts_regex)
}


#' @export
#' @rdname stri_locate
stri_locate_last_regex <- function(str, pattern, opts_regex=NULL) {
stri_locate_last_regex <- function(str, pattern, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_locate_last_regex, str, pattern, opts_regex)
}

Expand Down
12 changes: 9 additions & 3 deletions R/search_match_4.R
Original file line number Diff line number Diff line change
Expand Up @@ -144,22 +144,28 @@ stri_match <- function(str, ..., regex,
#' @export
#' @rdname search_match
stri_match_all_regex <- function(str, pattern, omit_no_match=FALSE,
cg_missing=NA_character_, opts_regex=NULL) {
cg_missing=NA_character_, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_match_all_regex, str, pattern, omit_no_match, cg_missing, opts_regex)
}


#' @export
#' @rdname search_match
stri_match_first_regex <- function(str, pattern,
cg_missing=NA_character_, opts_regex=NULL) {
cg_missing=NA_character_, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_match_first_regex, str, pattern, cg_missing, opts_regex)
}


#' @export
#' @rdname search_match
stri_match_last_regex <- function(str, pattern,
cg_missing=NA_character_, opts_regex=NULL) {
cg_missing=NA_character_, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_match_last_regex, str, pattern, cg_missing, opts_regex)
}
12 changes: 9 additions & 3 deletions R/search_replace_4.R
Original file line number Diff line number Diff line change
Expand Up @@ -273,20 +273,26 @@ stri_replace_last_fixed <- function(str, pattern, replacement) {

#' @export
#' @rdname stri_replace
stri_replace_all_regex <- function(str, pattern, replacement, vectorize_all=TRUE, opts_regex=NULL) {
stri_replace_all_regex <- function(str, pattern, replacement, vectorize_all=TRUE, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_replace_all_regex, str, pattern, replacement, vectorize_all, opts_regex)
}


#' @export
#' @rdname stri_replace
stri_replace_first_regex <- function(str, pattern, replacement, opts_regex=NULL) {
stri_replace_first_regex <- function(str, pattern, replacement, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_replace_first_regex, str, pattern, replacement, opts_regex)
}


#' @export
#' @rdname stri_replace
stri_replace_last_regex <- function(str, pattern, replacement, opts_regex=NULL) {
stri_replace_last_regex <- function(str, pattern, replacement, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_replace_last_regex, str, pattern, replacement, opts_regex)
}
4 changes: 3 additions & 1 deletion R/search_split_4.R
Original file line number Diff line number Diff line change
Expand Up @@ -169,9 +169,11 @@ stri_split_fixed <- function(str, pattern, n=-1L,
#' @export
#' @rdname stri_split
stri_split_regex <- function(str, pattern, n=-1L, omit_empty=FALSE,
tokens_only=FALSE, simplify=FALSE, opts_regex=NULL) {
tokens_only=FALSE, simplify=FALSE, ..., opts_regex=NULL) {
# omit_empty defaults to FALSE for compatibility with the stringr package
# tokens_only defaults to FALSE for compatibility with the stringr package
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_split_regex, str, pattern,
n, omit_empty, tokens_only, simplify, opts_regex)
}
Expand Down
2 changes: 1 addition & 1 deletion R/search_startsendswith_4.R
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,7 @@
#' stri_startswith_coll(c("a1", "A2", "b3", "A4", "C5"), "a", strength=1)
#' pat <- stri_paste("\u0635\u0644\u0649 \u0627\u0644\u0644\u0647 ",
#' "\u0639\u0644\u064a\u0647 \u0648\u0633\u0644\u0645XYZ")
#' stri_endswith_coll("\ufdfa\ufdfa\ufdfaXYZ", pat, strength = 1)
#' stri_endswith_coll("\ufdfa\ufdfa\ufdfaXYZ", pat, strength=1)
#'
#' @family search_detect
#' @export
Expand Down
4 changes: 3 additions & 1 deletion R/search_subset_4.R
Original file line number Diff line number Diff line change
Expand Up @@ -123,6 +123,8 @@ stri_subset_coll <- function(str, pattern, omit_na=FALSE, ..., opts_collator=NUL

#' @export
#' @rdname stri_subset
stri_subset_regex <- function(str, pattern, omit_na=FALSE, opts_regex=NULL) {
stri_subset_regex <- function(str, pattern, omit_na=FALSE, ..., opts_regex=NULL) {
if (!missing(...))
opts_regex <- do.call(stri_opts_regex, as.list(c(opts_regex, ...)))
.Call(C_stri_subset_regex, str, pattern, omit_na, opts_regex)
}
3 changes: 2 additions & 1 deletion devel/testthat/test-subset-regex.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,8 @@ test_that("stri_subset_regex", {
suppressWarnings(expect_identical(stri_subset_regex("a",""), NA_character_))
suppressWarnings(expect_identical(stri_subset_regex("","a"), character(0)))
expect_identical(stri_subset_regex(c("","ala"),"ala"), "ala")
expect_identical(stri_subset_regex(c("","ala","AlA"),"ala", opts=stri_opts_regex(case_insensitive=TRUE)), c("ala", "AlA"))
expect_identical(stri_subset_regex(c("","ala","AlA"),"ala", opts_regex=stri_opts_regex(case_insensitive=TRUE)), c("ala", "AlA"))
expect_identical(stri_subset_regex(c("","ala","AlA"),"ala", case_insensitive=TRUE), c("ala", "AlA"))
expect_identical(stri_subset_regex(c("","ala", "ala", "bbb"),c("ala", "bbb")), c("ala", "bbb"))
expect_identical(stri_subset_regex(c("ala","", "", "bbb"),c("ala", "bbb")), c("ala", "bbb"))
expect_identical(stri_subset_regex(c("a","b", NA, "aaa", ""),c("a")), c("a", NA, "aaa"))
Expand Down
6 changes: 3 additions & 3 deletions man/search_match.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -18,12 +18,12 @@ stri_match_last(str, ..., regex)
stri_match(str, ..., regex, mode = c("first", "all", "last"))

stri_match_all_regex(str, pattern, omit_no_match = FALSE,
cg_missing = NA_character_, opts_regex = NULL)
cg_missing = NA_character_, ..., opts_regex = NULL)

stri_match_first_regex(str, pattern, cg_missing = NA_character_,
stri_match_first_regex(str, pattern, cg_missing = NA_character_, ...,
opts_regex = NULL)

stri_match_last_regex(str, pattern, cg_missing = NA_character_,
stri_match_last_regex(str, pattern, cg_missing = NA_character_, ...,
opts_regex = NULL)
}
\arguments{
Expand Down
2 changes: 1 addition & 1 deletion man/stri_count.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ stri_count_coll(str, pattern, ..., opts_collator = NULL)

stri_count_fixed(str, pattern)

stri_count_regex(str, pattern, opts_regex = NULL)
stri_count_regex(str, pattern, ..., opts_regex = NULL)
}
\arguments{
\item{str}{character vector with strings to search in}
Expand Down
4 changes: 2 additions & 2 deletions man/stri_detect.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ stri_detect_charclass(str, pattern)

stri_detect_coll(str, pattern, ..., opts_collator = NULL)

stri_detect_regex(str, pattern, opts_regex = NULL)
stri_detect_regex(str, pattern, ..., opts_regex = NULL)
}
\arguments{
\item{str}{character vector with strings to search in}
Expand Down Expand Up @@ -70,7 +70,7 @@ stri_detect_regex(c("stringi R", "REXAMINE", "123"), 'R.')
stri_detect_regex(c("stringi R", "REXAMINE", "123"), '[[:alpha:]]*?')
stri_detect_regex(c("stringi R", "REXAMINE", "123"), '[a-zC1]')
stri_detect_regex(c("stringi R", "REXAMINE", "123"), '( R|RE)')
stri_detect_regex("stringi", "STRING.", opts_regex=stri_opts_regex(case_insensitive=TRUE))
stri_detect_regex("stringi", "STRING.", case_insensitive=TRUE)
}
\seealso{
Other search_detect: \code{\link{stri_endswith}},
Expand Down
6 changes: 3 additions & 3 deletions man/stri_extract.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -39,11 +39,11 @@ stri_extract_first_coll(str, pattern, ..., opts_collator = NULL)
stri_extract_last_coll(str, pattern, ..., opts_collator = NULL)

stri_extract_all_regex(str, pattern, simplify = FALSE,
omit_no_match = FALSE, opts_regex = NULL)
omit_no_match = FALSE, ..., opts_regex = NULL)

stri_extract_first_regex(str, pattern, opts_regex = NULL)
stri_extract_first_regex(str, pattern, ..., opts_regex = NULL)

stri_extract_last_regex(str, pattern, opts_regex = NULL)
stri_extract_last_regex(str, pattern, ..., opts_regex = NULL)
}
\arguments{
\item{str}{character vector with strings to search in}
Expand Down
6 changes: 3 additions & 3 deletions man/stri_locate.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -40,12 +40,12 @@ stri_locate_first_coll(str, pattern, ..., opts_collator = NULL)

stri_locate_last_coll(str, pattern, ..., opts_collator = NULL)

stri_locate_all_regex(str, pattern, omit_no_match = FALSE,
stri_locate_all_regex(str, pattern, omit_no_match = FALSE, ...,
opts_regex = NULL)

stri_locate_first_regex(str, pattern, opts_regex = NULL)
stri_locate_first_regex(str, pattern, ..., opts_regex = NULL)

stri_locate_last_regex(str, pattern, opts_regex = NULL)
stri_locate_last_regex(str, pattern, ..., opts_regex = NULL)

stri_locate_all_fixed(str, pattern, omit_no_match = FALSE)

Expand Down
6 changes: 3 additions & 3 deletions man/stri_replace.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -47,12 +47,12 @@ stri_replace_first_fixed(str, pattern, replacement)

stri_replace_last_fixed(str, pattern, replacement)

stri_replace_all_regex(str, pattern, replacement, vectorize_all = TRUE,
stri_replace_all_regex(str, pattern, replacement, vectorize_all = TRUE, ...,
opts_regex = NULL)

stri_replace_first_regex(str, pattern, replacement, opts_regex = NULL)
stri_replace_first_regex(str, pattern, replacement, ..., opts_regex = NULL)

stri_replace_last_regex(str, pattern, replacement, opts_regex = NULL)
stri_replace_last_regex(str, pattern, replacement, ..., opts_regex = NULL)
}
\arguments{
\item{str}{character vector with strings to search in}
Expand Down
2 changes: 1 addition & 1 deletion man/stri_split.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ stri_split_fixed(str, pattern, n = -1L, omit_empty = FALSE,
tokens_only = FALSE, simplify = FALSE)

stri_split_regex(str, pattern, n = -1L, omit_empty = FALSE,
tokens_only = FALSE, simplify = FALSE, opts_regex = NULL)
tokens_only = FALSE, simplify = FALSE, ..., opts_regex = NULL)

stri_split_coll(str, pattern, n = -1L, omit_empty = FALSE,
tokens_only = FALSE, simplify = FALSE, ..., opts_collator = NULL)
Expand Down
2 changes: 1 addition & 1 deletion man/stri_startsendswith.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,7 @@ stri_startswith_fixed("ababa", "ba", from=2)
stri_startswith_coll(c("a1", "A2", "b3", "A4", "C5"), "a", strength=1)
pat <- stri_paste("\\u0635\\u0644\\u0649 \\u0627\\u0644\\u0644\\u0647 ",
"\\u0639\\u0644\\u064a\\u0647 \\u0648\\u0633\\u0644\\u0645XYZ")
stri_endswith_coll("\\ufdfa\\ufdfa\\ufdfaXYZ", pat, strength = 1)
stri_endswith_coll("\\ufdfa\\ufdfa\\ufdfaXYZ", pat, strength=1)
}
\seealso{
Other search_detect: \code{\link{stri_detect}},
Expand Down
2 changes: 1 addition & 1 deletion man/stri_subset.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ stri_subset_charclass(str, pattern, omit_na = FALSE)

stri_subset_coll(str, pattern, omit_na = FALSE, ..., opts_collator = NULL)

stri_subset_regex(str, pattern, omit_na = FALSE, opts_regex = NULL)
stri_subset_regex(str, pattern, omit_na = FALSE, ..., opts_regex = NULL)
}
\arguments{
\item{str}{character vector with strings to search in}
Expand Down

0 comments on commit f3efe24

Please sign in to comment.