Skip to content

Commit 4cd066d

Browse files
committedMar 1, 2025·
💄 Start switching to base R pipe
Change-Id: I9a7cadb089e150deb1e58f33b8944ea789cd612f
1 parent 617266d commit 4cd066d

File tree

3 files changed

+47
-47
lines changed

3 files changed

+47
-47
lines changed
 

‎R/collocationAnalysis.R

+27-27
Original file line numberDiff line numberDiff line change
@@ -53,17 +53,17 @@ setGeneric("collocationAnalysis", function(kco, ...) standardGeneric("collocati
5353
#' \dontrun{
5454
#'
5555
#' # Find top collocates of "Packung" inside and outside the sports domain.
56-
#' KorAPConnection(verbose = TRUE) %>%
56+
#' KorAPConnection(verbose = TRUE) |>
5757
#' collocationAnalysis("Packung", vc=c("textClass=sport", "textClass!=sport"),
58-
#' leftContextSize=1, rightContextSize=1, topCollocatesLimit=20) %>%
58+
#' leftContextSize=1, rightContextSize=1, topCollocatesLimit=20) |>
5959
#' dplyr::filter(logDice >= 5)
6060
#' }
6161
#'
6262
#' \dontrun{
6363
#'
6464
#' # Identify the most prominent light verb construction with "in ... setzen".
6565
#' # Note that, currently, the use of focus function disallows exactFrequencies.
66-
#' KorAPConnection(verbose = TRUE) %>%
66+
#' KorAPConnection(verbose = TRUE) |>
6767
#' collocationAnalysis("focus(in [tt/p=NN] {[tt/l=setzen]})",
6868
#' leftContextSize=1, rightContextSize=0, exactFrequencies=FALSE, topCollocatesLimit=20)
6969
#' }
@@ -124,7 +124,7 @@ setMethod("collocationAnalysis", "KorAPConnection",
124124
localStopwords = localStopwords,
125125
seed = seed,
126126
expand = expand,
127-
...) ) %>%
127+
...) ) |>
128128
bind_rows()
129129
} else {
130130
set.seed(seed)
@@ -142,8 +142,8 @@ setMethod("collocationAnalysis", "KorAPConnection",
142142
)
143143

144144
if (nrow(candidates) > 0) {
145-
candidates <- candidates %>%
146-
filter(frequency >= minOccur) %>%
145+
candidates <- candidates |>
146+
filter(frequency >= minOccur) |>
147147
slice_head(n=topCollocatesLimit)
148148
collocationScoreQuery(
149149
kco,
@@ -164,7 +164,7 @@ setMethod("collocationAnalysis", "KorAPConnection",
164164
}
165165
}
166166
if (maxRecurse > 0 & length(result) > 0 && any(!!thresholdScore >= threshold)) {
167-
recurseWith <- result %>%
167+
recurseWith <- result |>
168168
filter(!!as.name(thresholdScore) >= threshold)
169169
result <- collocationAnalysis(
170170
kco,
@@ -262,10 +262,10 @@ matches2FreqTable <- function(matches,
262262
)
263263
}
264264
log_info(verbose, paste("Aggregating", length(oldTable$word), "tokens\n"))
265-
oldTable %>%
266-
group_by(word) %>%
267-
mutate(word = dplyr::case_when(ignoreCollocateCase ~ tolower(word), TRUE ~ word)) %>%
268-
summarise(frequency=sum(frequency), .groups = "drop") %>%
265+
oldTable |>
266+
group_by(word) |>
267+
mutate(word = dplyr::case_when(ignoreCollocateCase ~ tolower(word), TRUE ~ word)) |>
268+
summarise(frequency=sum(frequency), .groups = "drop") |>
269269
arrange(desc(frequency))
270270
} else {
271271
stopwordsTable <- dplyr::tibble(word=stopwords)
@@ -281,11 +281,11 @@ matches2FreqTable <- function(matches,
281281
if(length(left) + length(right) == 0) {
282282
oldTable
283283
} else {
284-
table(c(left, right)) %>%
285-
dplyr::as_tibble(.name_repair = "minimal") %>%
286-
dplyr::rename(word = 1, frequency = 2) %>%
287-
dplyr::filter(str_detect(word, collocateFilterRegex)) %>%
288-
dplyr::anti_join(stopwordsTable, by="word") %>%
284+
table(c(left, right)) |>
285+
dplyr::as_tibble(.name_repair = "minimal") |>
286+
dplyr::rename(word = 1, frequency = 2) |>
287+
dplyr::filter(str_detect(word, collocateFilterRegex)) |>
288+
dplyr::anti_join(stopwordsTable, by="word") |>
289289
dplyr::bind_rows(oldTable)
290290
}
291291
}
@@ -323,10 +323,10 @@ snippet2FreqTable <- function(snippet,
323323
)
324324
}
325325
log_info(verbose, paste("Aggregating", length(oldTable$word), "tokens\n"))
326-
oldTable %>%
327-
group_by(word) %>%
328-
mutate(word = dplyr::case_when(ignoreCollocateCase ~ tolower(word), TRUE ~ word)) %>%
329-
summarise(frequency=sum(frequency), .groups = "drop") %>%
326+
oldTable |>
327+
group_by(word) |>
328+
mutate(word = dplyr::case_when(ignoreCollocateCase ~ tolower(word), TRUE ~ word)) |>
329+
summarise(frequency=sum(frequency), .groups = "drop") |>
330330
arrange(desc(frequency))
331331
} else {
332332
stopwordsTable <- dplyr::tibble(word=stopwords)
@@ -351,11 +351,11 @@ snippet2FreqTable <- function(snippet,
351351
if(is.na(left[1]) || is.na(right[1]) || length(left) + length(right) == 0) {
352352
oldTable
353353
} else {
354-
table(c(left, right)) %>%
355-
dplyr::as_tibble(.name_repair = "minimal") %>%
356-
dplyr::rename(word = 1, frequency = 2) %>%
357-
dplyr::filter(str_detect(word, collocateFilterRegex)) %>%
358-
dplyr::anti_join(stopwordsTable, by="word") %>%
354+
table(c(left, right)) |>
355+
dplyr::as_tibble(.name_repair = "minimal") |>
356+
dplyr::rename(word = 1, frequency = 2) |>
357+
dplyr::filter(str_detect(word, collocateFilterRegex)) |>
358+
dplyr::anti_join(stopwordsTable, by="word") |>
359359
dplyr::bind_rows(oldTable)
360360
}
361361
}
@@ -487,8 +487,8 @@ collocatesQuery <-
487487
ignoreCollocateCase = ignoreCollocateCase,
488488
stopwords = stopwords,
489489
...,
490-
verbose = kco@verbose) %>%
491-
mutate(frequency = frequency * q@totalResults / min(q@totalResults, searchHitsSampleLimit)) %>%
490+
verbose = kco@verbose) |>
491+
mutate(frequency = frequency * q@totalResults / min(q@totalResults, searchHitsSampleLimit)) |>
492492
filter(frequency >= minOccur)
493493
}
494494
}

‎R/collocationScoreQuery.R

+9-9
Original file line numberDiff line numberDiff line change
@@ -33,13 +33,13 @@ utils::globalVariables(c("."))
3333
#' @examples
3434
#' \dontrun{
3535
#'
36-
#' KorAPConnection(verbose = TRUE) %>%
36+
#' KorAPConnection(verbose = TRUE) |>
3737
#' collocationScoreQuery("Grund", "triftiger")
3838
#' }
3939
#'
4040
#' \dontrun{
4141
#'
42-
#' KorAPConnection(verbose = TRUE) %>%
42+
#' KorAPConnection(verbose = TRUE) |>
4343
#' collocationScoreQuery("Grund", c("guter", "triftiger"),
4444
#' scoreFunctions = list(localMI = function(O1, O2, O, N, E, window_size) { O * log2(O/E) }) )
4545
#' }
@@ -48,11 +48,11 @@ utils::globalVariables(c("."))
4848
#'
4949
#' library(highcharter)
5050
#' library(tidyr)
51-
#' KorAPConnection(verbose = TRUE) %>%
51+
#' KorAPConnection(verbose = TRUE) |>
5252
#' collocationScoreQuery("Team", "agil", vc = paste("pubDate in", c(2014:2018)),
53-
#' lemmatizeNodeQuery = TRUE, lemmatizeCollocateQuery = TRUE) %>%
54-
#' pivot_longer(14:last_col(), names_to = "measure", values_to = "score") %>%
55-
#' hchart(type="spline", hcaes(label, score, group=measure)) %>%
53+
#' lemmatizeNodeQuery = TRUE, lemmatizeCollocateQuery = TRUE) |>
54+
#' pivot_longer(14:last_col(), names_to = "measure", values_to = "score") |>
55+
#' hchart(type="spline", hcaes(label, score, group=measure)) |>
5656
#' hc_add_onclick_korap_search()
5757
#' }
5858
#'
@@ -202,8 +202,8 @@ mergeDuplicateCollocates <- function(..., smoothingConstant = .5) {
202202
korapUrl <- combined_df$webUIRequestUrl[1] |> httr2::url_modify(query="")
203203

204204
# Group by collocate and summarize
205-
combined_df %>%
206-
group_by(collocate, O2, N) %>%
205+
combined_df |>
206+
group_by(collocate, O2, N) |>
207207
summarise(
208208
O = sum(O) - smoothingConstant * (n()-1),
209209
O1 = sum(O1) - smoothingConstant * (n()-1),
@@ -219,7 +219,7 @@ mergeDuplicateCollocates <- function(..., smoothingConstant = .5) {
219219
query = paste(query, collapse = " | "),
220220
webUIRequestUrl = buildWebUIRequestUrlFromString(korapUrl, query = paste(query, collapse = " | "), vc = first(vc)),
221221
across(everything(), first),
222-
) %>%
222+
) |>
223223
ungroup()
224224
}
225225

‎Readme.md

+11-11
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ R client package to access the [web service API](https://github.com/KorAP/Kustva
2121

2222
```R
2323
library(RKorAPClient)
24-
KorAPConnection(verbose=TRUE) %>% corpusQuery("Hello world") %>% fetchAll()
24+
KorAPConnection(verbose=TRUE) |> corpusQuery("Hello world") |> fetchAll()
2525
```
2626

2727
### Frequencies over time and domains using ggplot2
@@ -49,8 +49,8 @@ query = c("macht []{0,3} Sinn", "ergibt []{0,3} Sinn")
4949
years = c(1980:2010)
5050
as.alternatives = TRUE
5151
vc = "textType = /Zeit.*/ & pubDate in"
52-
KorAPConnection(verbose=T) %>%
53-
frequencyQuery(query, paste(vc, years), as.alternatives = as.alternatives) %>%
52+
KorAPConnection(verbose=T) |>
53+
frequencyQuery(query, paste(vc, years), as.alternatives = as.alternatives) |>
5454
hc_freq_by_year_ci(as.alternatives)
5555
```
5656

@@ -62,18 +62,18 @@ KorAPConnection(verbose=T) %>%
6262
```r
6363
library(RKorAPClient)
6464
library(knitr)
65-
KorAPConnection(verbose = TRUE) %>% auth() %>%
65+
KorAPConnection(verbose = TRUE) |> auth() |>
6666
collocationAnalysis(
6767
"focus(in [tt/p=NN] {[tt/l=setzen]})",
6868
leftContextSize = 1,
6969
rightContextSize = 0,
7070
exactFrequencies = FALSE,
7171
searchHitsSampleLimit = 1000,
7272
topCollocatesLimit = 20
73-
) %>%
74-
mutate(LVC = sprintf("[in %s setzen](%s)", collocate, webUIRequestUrl)) %>%
75-
select(LVC, logDice, pmi, ll) %>%
76-
head(10) %>%
73+
) |>
74+
mutate(LVC = sprintf("[in %s setzen](%s)", collocate, webUIRequestUrl)) |>
75+
select(LVC, logDice, pmi, ll) |>
76+
head(10) |>
7777
kable(format="pipe", digits=2)
7878
```
7979

@@ -101,7 +101,7 @@ In the case of DeReKo, this can be done in three different ways.
101101
Authorize your RKorAPClient application via the usual OAuth browser flow *using the default application id* and the `auth` method:
102102

103103
```R
104-
kco <- KorAPConnection() %>% auth()
104+
kco <- KorAPConnection() |> auth()
105105
```
106106

107107
#### 2. The old way: Authorize your RKorAPClient application manually
@@ -131,7 +131,7 @@ Authorize your RKorAPClient application via the usual OAuth browser flow, using
131131
2. Click on the copy symbol ⎘ behind the ID of your client application.
132132
3. Paste your clipboard content overwriting `<application ID>` in the following example code:
133133
```R
134-
kco <- KorAPConnection() %>% auth(app_id = "<application ID>")
134+
kco <- KorAPConnection() |> auth(app_id = "<application ID>")
135135
```
136136

137137
#### Storing and testing your authorized access
@@ -150,7 +150,7 @@ Piping the result through the `auth()` function `kco <- KorAPConnection() |> aut
150150
To use the access token for simple corpus queries, i.e. to make `corpusQuery` return KWIC snippets, the `metadataOnly` parameter must be set to `FALSE`, for example:
151151

152152
```R
153-
corpusQuery(kco, "Ameisenplage", metadataOnly = FALSE) %>% fetchAll()
153+
corpusQuery(kco, "Ameisenplage", metadataOnly = FALSE) |> fetchAll()
154154
```
155155

156156
should return KWIC snippets, if you have authorized your application successfully.

0 commit comments

Comments
 (0)
Please sign in to comment.