Migrate documentation to roxygen2md
Change-Id: If5370cd207770f3e05c6f5cd063bd2a414b92bcb
diff --git a/DESCRIPTION b/DESCRIPTION
index 06285a6..3b8f051 100644
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -62,6 +62,8 @@
'ci.R'
'collocationAnalysis.R'
'collocationScoreQuery.R'
- 'highcharter-helper.R'
+ 'hc_add_onclick_korap_search.R'
+ 'hc_freq_by_year_ci.R'
'misc.R'
'reexports.R'
+Roxygen: list(markdown = TRUE)
diff --git a/R/KorAPConnection.R b/R/KorAPConnection.R
index 83bfd5e..0919d4e 100644
--- a/R/KorAPConnection.R
+++ b/R/KorAPConnection.R
@@ -5,8 +5,8 @@
#' Class KorAPConnection
#'
-#' \code{KorAPConnection} objects represent the connection to a KorAP server.
-#' New \code{KorAPConnection} objects can be created by \code{new("KorAPConnection")}.
+#' `KorAPConnection` objects represent the connection to a KorAP server.
+#' New `KorAPConnection` objects can be created by `new("KorAPConnection")`.
#'
#' @import R.cache
#' @import utils
@@ -20,28 +20,28 @@
#' @param apiUrl URL of the KorAP web service.
#' @param accessToken OAuth2 access token. To use authorization based on an access token
#' in subsequent queries, initialize your KorAP connection with
-#' \code{kco <- new("KorAPConnection", accessToken="<access token>")}.
+#' `kco <- new("KorAPConnection", accessToken="<access token>")`.
#' In order to make the API
-#' token persistent for the currently used \code{KorAPUrl} (you can have one
+#' token persistent for the currently used `KorAPUrl` (you can have one
#' token per KorAPUrl / KorAP server instance), use
-#' \code{persistAccessToken(kco)}. This will store it in your keyring using the
-#' \code{\link{keyring}} package. Subsequent new("KorAPConnection") calls will
+#' `persistAccessToken(kco)`. This will store it in your keyring using the
+#' [keyring()] package. Subsequent new("KorAPConnection") calls will
#' then automatically retrieve the token from your keying. To stop using a
-#' persisted token, call \code{clearAccessToken(kco)}. Please note that for
+#' persisted token, call `clearAccessToken(kco)`. Please note that for
#' DeReKo, authorized queries will behave differently inside and outside the
#' IDS, because of the special license situation. This concerns also cached
#' results which do not take into account from where a request was issued. If
-#' you experience problems or unexpected results, please try \code{kco <-
-#' new("KorAPConnection", cache=FALSE)} or use
-#' \code{\link{clearCache}} to clear the cache completely.
+#' you experience problems or unexpected results, please try `kco <-
+#' new("KorAPConnection", cache=FALSE)` or use
+#' [clearCache()] to clear the cache completely.
#' @param userAgent user agent string.
#' @param timeout time out in seconds.
#' @param verbose logical. Decides whether following operations will default to
#' be verbose.
#' @param cache logical. Decides if API calls are cached locally. You can clear
-#' the cache with \code{\link{clearCache}()}.
-#' @return \code{\link{KorAPConnection}} object that can be used e.g. with
-#' \code{\link{corpusQuery}}
+#' the cache with [clearCache()].
+#' @return [KorAPConnection()] object that can be used e.g. with
+#' [corpusQuery()]
#'
#' @examples
#' \donttest{
diff --git a/R/KorAPCorpusStats.R b/R/KorAPCorpusStats.R
index 8c4ad47..7d299ca 100644
--- a/R/KorAPCorpusStats.R
+++ b/R/KorAPCorpusStats.R
@@ -1,7 +1,7 @@
#' Class KorAPCorpusStats
#'
-#' \code{KorAPCorpusStats} objects can hold information about a corpus or virtual corpus.
-#' \code{KorAPCorpusStats} objects can be obtained by the \code{\link{corpusStats}()} method.
+#' `KorAPCorpusStats` objects can hold information about a corpus or virtual corpus.
+#' `KorAPCorpusStats` objects can be obtained by the [corpusStats()] method.
#'
#' @include KorAPConnection.R
#'
@@ -19,11 +19,11 @@
setGeneric("corpusStats", function(kco, ...) standardGeneric("corpusStats") )
#' Fetch information about a (virtual) corpus
-#' @param kco \code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}
+#' @param kco [KorAPConnection()] object (obtained e.g. from `new("KorAPConnection")`
#' @param vc string describing the virtual corpus. An empty string (default) means the whole corpus, as far as it is license-wise accessible.
-#' @param verbose logical. If \code{TRUE}, additional diagnostics are printed.
+#' @param verbose logical. If `TRUE`, additional diagnostics are printed.
#' @param as.df return result as data frame instead of as S4 object?
-#' @return \code{KorAPCorpusStats} object with the slots \code{documents}, \code{tokens}, \code{sentences}, \code{paragraphs}
+#' @return `KorAPCorpusStats` object with the slots `documents`, `tokens`, `sentences`, `paragraphs`
#'
#' @examples
#' \donttest{corpusStats(new("KorAPConnection"))}
diff --git a/R/KorAPQuery.R b/R/KorAPQuery.R
index 5ef4846..e6f240e 100644
--- a/R/KorAPQuery.R
+++ b/R/KorAPQuery.R
@@ -1,7 +1,7 @@
#' Class KorAPQuery
#'
#' This class provides methods to perform different kinds of queries on the KorAP API server.
-#' \code{KorAPQuery} objects, which are typically created by the \code{\link{corpusQuery}} method,
+#' `KorAPQuery` objects, which are typically created by the [corpusQuery()] method,
#' represent the current state of a query to a KorAP server.
#'
#' @include KorAPConnection.R
@@ -74,7 +74,7 @@
#' Corpus query
#'
-#' \bold{\code{corpusQuery}} performs a corpus query via a connection to a KorAP-API-server
+#' **`corpusQuery`** performs a corpus query via a connection to a KorAP-API-server
#'
#' @rdname KorAPQuery-class
#' @aliases corpusQuery
@@ -83,20 +83,20 @@
#' @importFrom purrr pmap
#' @importFrom dplyr bind_rows
#'
-#' @param kco \code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}
-#' @param query string that contains the corpus query. The query language depends on the \code{ql} parameter. Either \code{query} must be provided or \code{KorAPUrl}.
+#' @param kco [KorAPConnection()] object (obtained e.g. from `new("KorAPConnection")`
+#' @param query string that contains the corpus query. The query language depends on the `ql` parameter. Either `query` must be provided or `KorAPUrl`.
#' @param vc string describing the virtual corpus in which the query should be performed. An empty string (default) means the whole corpus, as far as it is license-wise accessible.
-#' @param KorAPUrl instead of providing the query and vc string parameters, you can also simply copy a KorAP query URL from your browser and use it here (and in \code{KorAPConnection}) to provide all necessary information for the query.
+#' @param KorAPUrl instead of providing the query and vc string parameters, you can also simply copy a KorAP query URL from your browser and use it here (and in `KorAPConnection`) to provide all necessary information for the query.
#' @param metadataOnly logical that determines whether queries should return only metadata without any snippets. This can also be useful to prevent access rewrites. Note that the default value is TRUE, unless the connection is authorized (currently not possible).
-#' @param ql string to choose the query language (see \href{https://github.com/KorAP/Kustvakt/wiki/Service:-Search-GET#user-content-parameters}{section on Query Parameters} in the Kustvakt-Wiki for possible values.
+#' @param ql string to choose the query language (see [section on Query Parameters](https://github.com/KorAP/Kustvakt/wiki/Service:-Search-GET#user-content-parameters) in the Kustvakt-Wiki for possible values.
#' @param fields (meta)data fields that will be fetched for every match.
#' @param accessRewriteFatal abort if query or given vc had to be rewritten due to insufficient rights (not yet implemented).
#' @param verbose print some info
#' @param as.df return result as data frame instead of as S4 object?
-#' @param expand logical that decides if \code{query} and \code{vc} parameters are expanded to all of their combinations
-#' @return Depending on the \code{as.df} parameter, a table or a \code{\link{KorAPQuery}} object that, among other information, contains the total number of results in \code{@totalResults}. The resulting object can be used to fetch all query results (with \code{\link{fetchAll}}) or the next page of results (with \code{\link{fetchNext}}).
-#' A corresponding URL to be used within a web browser is contained in \code{@webUIRequestUrl}
-#' Please make sure to check \code{$collection$rewrites} to see if any unforeseen access rewrites of the query's virtual corpus had to be performed.
+#' @param expand logical that decides if `query` and `vc` parameters are expanded to all of their combinations
+#' @return Depending on the `as.df` parameter, a table or a [KorAPQuery()] object that, among other information, contains the total number of results in `@totalResults`. The resulting object can be used to fetch all query results (with [fetchAll()]) or the next page of results (with [fetchNext()]).
+#' A corresponding URL to be used within a web browser is contained in `@webUIRequestUrl`
+#' Please make sure to check `$collection$rewrites` to see if any unforeseen access rewrites of the query's virtual corpus had to be performed.
#'
#' @examples
#' # Fetch metadata of every query hit for "Ameisenplage" and show a summary
@@ -128,10 +128,10 @@
#' complete(year = min(year):max(year), fill = list(Freq = 0)) %>%
#' plot(type = "l")
#' }
-#' @seealso \code{\link{KorAPConnection}}, \code{\link{fetchNext}}, \code{\link{fetchRest}}, \code{\link{fetchAll}}, \code{\link{corpusStats}}
+#' @seealso [KorAPConnection()], [fetchNext()], [fetchRest()], [fetchAll()], [corpusStats()]
#'
#' @references
-#' \url{https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026}
+#' <https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026>
#'
#' @export
setMethod("corpusQuery", "KorAPConnection",
@@ -214,14 +214,14 @@
#' Fetch the next bunch of results of a KorAP query.
#'
-#' \bold{\code{fetchNext}} fetches the next bunch of results of a KorAP query.
+#' **`fetchNext`** fetches the next bunch of results of a KorAP query.
#'
-#' @param kqo object obtained from \code{\link{corpusQuery}}
+#' @param kqo object obtained from [corpusQuery()]
#' @param offset start offset for query results to fetch
#' @param maxFetch maximum number of query results to fetch
#' @param verbose print progress information if true
-#' @param randomizePageOrder fetch result pages in pseudo random order if true. Use \code{\link{set.seed}} to set seed for reproducible results.
-#' @return The \code{kqo} input object with updated slots \code{collectedMatches}, \code{apiResponse}, \code{nextStartIndex}, \code{hasMoreMatches}
+#' @param randomizePageOrder fetch result pages in pseudo random order if true. Use [set.seed()] to set seed for reproducible results.
+#' @return The `kqo` input object with updated slots `collectedMatches`, `apiResponse`, `nextStartIndex`, `hasMoreMatches`
#'
#' @examples
#' \donttest{q <- new("KorAPConnection") %>% corpusQuery("Ameisenplage") %>% fetchNext()
@@ -229,7 +229,7 @@
#' }
#'
#' @references
-#' \url{https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026}
+#' <https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026>
#'
#' @aliases fetchNext
#' @rdname KorAPQuery-class
@@ -318,7 +318,7 @@
#' Fetch all results of a KorAP query.
#'
-#' \bold{\code{fetchAll}} fetches all results of a KorAP query.
+#' **`fetchAll`** fetches all results of a KorAP query.
#'
#' @examples
#' \donttest{
@@ -350,8 +350,8 @@
#' Query relative frequency of search term(s)
#'
-#' \bold{\code{frequencyQuery}} combines \code{\link{corpusQuery}}, \code{\link{corpusStats}} and
-#' \code{\link{ci}} to compute a table with the relative frequencies and
+#' **`frequencyQuery`** combines [corpusQuery()], [corpusStats()] and
+#' [ci()] to compute a table with the relative frequencies and
#' confidence intervals of one ore multiple search terms across one or multiple
#' virtual corpora.
#'
@@ -363,10 +363,10 @@
#' frequencyQuery(c("Mücke", "Schnake"), paste0("pubDate in ", 2000:2003))
#' }
#'
-#' @param kco \code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}
-#' @param query string that contains the corpus query. The query language depends on the \code{ql} parameter. Either \code{query} must be provided or \code{KorAPUrl}.
-#' @param conf.level confidence level of the returned confidence interval (passed through \code{\link{ci}} to \code{\link{prop.test}}).
-#' @param as.alternatives LOGICAL that specifies if the query terms should be treated as alternatives. If \code{as.alternatives} is TRUE, the sum over all query hits, instead of the respective vc token sizes is used as total for the calculation of relative frequencies.
+#' @param kco [KorAPConnection()] object (obtained e.g. from `new("KorAPConnection")`
+#' @param query string that contains the corpus query. The query language depends on the `ql` parameter. Either `query` must be provided or `KorAPUrl`.
+#' @param conf.level confidence level of the returned confidence interval (passed through [ci()] to [prop.test()]).
+#' @param as.alternatives LOGICAL that specifies if the query terms should be treated as alternatives. If `as.alternatives` is TRUE, the sum over all query hits, instead of the respective vc token sizes is used as total for the calculation of relative frequencies.
#' @export
setMethod("frequencyQuery", "KorAPConnection",
function(kco, query, vc = "", conf.level = 0.95, as.alternatives = FALSE, ...) {
diff --git a/R/association-scores.R b/R/association-scores.R
index fccba98..40599fa 100644
--- a/R/association-scores.R
+++ b/R/association-scores.R
@@ -13,7 +13,7 @@
#' @description
#' Functions to calculate different collocation association scores between
#' a node (target word) and words in a window around the it.
-#' The functions are primarily used by \code{\link{collocationScoreQuery}}.
+#' The functions are primarily used by [collocationScoreQuery()].
NULL
#' NULL
@@ -40,7 +40,7 @@
#' @rdname association-score-functions
#'
#' @description
-#' \bold{pmi}: pointwise mutual information
+#' **pmi**: pointwise mutual information
#'
#' @export
#'
@@ -51,7 +51,7 @@
#' @rdname association-score-functions
#'
#' @description
-#' \bold{mi2}: pointwise mutual information squared (Daille 1994), also referred to as mutual dependency
+#' **mi2**: pointwise mutual information squared (Daille 1994), also referred to as mutual dependency
#' (Thanopoulos et al. 2002)
#' @export
#'
@@ -63,7 +63,7 @@
#' @family association-score-functions
#'
#' @description
-#' \bold{mi3}: pointwise mutual information cubed (Daille 1994), also referred to as log-frequency biased mutual dependency)
+#' **mi3**: pointwise mutual information cubed (Daille 1994), also referred to as log-frequency biased mutual dependency)
#' (Thanopoulos et al. 2002)
#'
#' @export
@@ -80,7 +80,7 @@
#' @rdname association-score-functions
#'
#' @description
-#' \bold{logDice}: log-Dice coefficient, a heuristic measure that is popular in lexicography (Rychlý 2008)
+#' **logDice**: log-Dice coefficient, a heuristic measure that is popular in lexicography (Rychlý 2008)
#' @export
#'
#' @references
@@ -96,7 +96,7 @@
#'
#' @rdname association-score-functions
#' @description
-#' \bold{ll}: log-likelihood (Dunning 1993) using Stefan Evert's (2004) simplified implementation
+#' **ll**: log-likelihood (Dunning 1993) using Stefan Evert's (2004) simplified implementation
#'
#' @export
#'
@@ -106,7 +106,7 @@
#' Dunning, T. (1993): Accurate methods for the statistics of surprise and coincidence. Comput. Linguist. 19, 1 (March 1993), 61-74.
#'
#' Evert, Stefan (2004): The Statistics of Word Cooccurrences: Word Pairs and Collocations. PhD dissertation, IMS, University of Stuttgart. Published in 2005, URN urn:nbn:de:bsz:93-opus-23714.
-#' Free PDF available from \url{http://purl.org/stefan.evert/PUB/Evert2004phd.pdf}
+#' Free PDF available from <http://purl.org/stefan.evert/PUB/Evert2004phd.pdf>
#'
ll <- function(O1, O2, O, N, E, window_size) {
r1 = as.double(O1) * window_size
diff --git a/R/ci.R b/R/ci.R
index 80c45f1..5de87a2 100644
--- a/R/ci.R
+++ b/R/ci.R
@@ -1,13 +1,13 @@
#' Add confidence interval and relative frequency variables
#'
-#' Using \code{\link{prop.test}}, \code{ci} adds three columns to a data frame:
-#' 1. relative frequency (\code{f})
-#' 2. lower bound of a confidence interval (\code{ci.low})
+#' Using [prop.test()], `ci` adds three columns to a data frame:
+#' 1. relative frequency (`f`)
+#' 2. lower bound of a confidence interval (`ci.low`)
#' 3. upper bound of a confidence interval
#'
#'
#' @seealso
-#' \code{ci} is already included in \code{\link{frequencyQuery}}
+#' `ci` is already included in [frequencyQuery()]
#'
#' @param df table with columns for absolute and total frequencies.
#' @param x column with the observed absolute frequency.
diff --git a/R/collocationAnalysis.R b/R/collocationAnalysis.R
index f01c703..88c7845 100644
--- a/R/collocationAnalysis.R
+++ b/R/collocationAnalysis.R
@@ -5,7 +5,7 @@
#' @aliases collocationAnalysis
#'
#' @description
-#' \Sexpr[results=rd, stage=render]{lifecycle::badge("experimental")}
+#' `r lifecycle::badge("experimental")`
#'
#' Performs a collocation analysis for the given node (or query)
#' in the given virtual corpus.
@@ -26,15 +26,15 @@
#'
#' @family collocation analysis functions
#'
-#' @param lemmatizeNodeQuery if TRUE, node query will be lemmatized, i.e. x -> [tt/l=x]
+#' @param lemmatizeNodeQuery if TRUE, node query will be lemmatized, i.e. `x -> [tt/l=x]`
#' @param minOccur minimum absolute number of observed co-occurrences to consider a collocate candidate
#' @param topCollocatesLimit limit analysis to the n most frequent collocates in the search hits sample
#' @param searchHitsSampleLimit limit the size of the search hits sample
#' @param stopwords vector of stopwords not to be considered as collocates
#' @param exactFrequencies if FALSE, extrapolate observed co-occurrence frequencies from frequencies in search hits sample, otherwise retrieve exact co-occurrence frequencies
#' @param seed seed for random page collecting order
-#' @param expand if TRUE, \code{node} and \code{vc} parameters are expanded to all of their combinations
-#' @param ... more arguments will be passed to \code{\link{collocationScoreQuery}}
+#' @param expand if TRUE, `node` and `vc` parameters are expanded to all of their combinations
+#' @param ... more arguments will be passed to [collocationScoreQuery()]
#' @inheritParams collocationScoreQuery,KorAPConnection-method
#' @return Tibble with top collocates, association scores, corresponding URLs for web user interface queries, etc.
#'
@@ -222,7 +222,7 @@
#' Preliminary synsemantic stopwords function
#'
#' @description
-#' \Sexpr[results=rd, stage=render]{lifecycle::badge("experimental")}
+#' `r lifecycle::badge("experimental")`
#'
#' Preliminary synsemantic stopwords function to be used in collocation analysis.
#'
diff --git a/R/collocationScoreQuery.R b/R/collocationScoreQuery.R
index 8ec9bf2..fe3893f 100644
--- a/R/collocationScoreQuery.R
+++ b/R/collocationScoreQuery.R
@@ -10,17 +10,17 @@
#'
#' @description
#' Computes various collocation association scores
-#' based on \code{\link{frequencyQuery}}s for a target word and a collocate.
+#' based on [frequencyQuery()]s for a target word and a collocate.
#'
-#' @param kco \code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}
+#' @param kco [KorAPConnection()] object (obtained e.g. from `new("KorAPConnection")`
#' @param node target word
#' @param collocate collocate of target word
#' @param vc string describing the virtual corpus in which the query should be performed. An empty string (default) means the whole corpus, as far as it is license-wise accessible.
-#' @param lemmatizeNodeQuery logical, set to TRUE if node query should be lemmatized, i.e. x -> [tt/l=x]
-#' @param lemmatizeCollocateQuery logical, set to TRUE if collocate query should be lemmatized, i.e. x -> [tt/l=x]
+#' @param lemmatizeNodeQuery logical, set to TRUE if node query should be lemmatized, i.e. `x -> [tt/l=x]`
+#' @param lemmatizeCollocateQuery logical, set to TRUE if collocate query should be lemmatized, i.e. `x -> [tt/l=x]`
#' @param leftContextSize size of the left context window
#' @param rightContextSize size of the right context window
-#' @param scoreFunctions named list of score functions of the form function(O1, O2, O, N, E, window_size), see e.g. \link{pmi}
+#' @param scoreFunctions named list of score functions of the form function(O1, O2, O, N, E, window_size), see e.g. [pmi]
#' @param smoothingConstant smoothing constant will be added to all observed values
#' @param observed if collocation frequencies are already known (or estimated from a sample) they can be passed as a vector here, otherwise: NA
#' @param ignoreCollocateCase logical, set to TRUE if collocate case should be ignored
diff --git a/R/hc_add_onclick_korap_search.R b/R/hc_add_onclick_korap_search.R
new file mode 100644
index 0000000..24ec37f
--- /dev/null
+++ b/R/hc_add_onclick_korap_search.R
@@ -0,0 +1,39 @@
+#' Add KorAP search click events to highchart plots
+#'
+#' @description
+#' `r lifecycle::badge("experimental")`
+#'
+#' Adds on-click events to data points of highcharts that were constructed with
+#' [frequencyQuery()] or [collocationScoreQuery()]. Clicks on data points
+#' then launch KorAP web UI queries for the given query term and virtual corpus in
+#' a separate tab.
+#'
+#' @family highcharter-helpers
+#'
+#' @param hc higchart object
+#' @export
+#'
+#' @examples
+#' \donttest{
+#' library(highcharter)
+#' library(tidyr)
+#'
+#' new("KorAPConnection", verbose = TRUE) %>%
+#' collocationScoreQuery("Team", "agil", vc = paste("pubDate in", c(2014:2018)),
+#' lemmatizeNodeQuery = TRUE, lemmatizeCollocateQuery = TRUE) %>%
+#' pivot_longer(c("O", "E")) %>%
+#' hchart(type="spline", hcaes(label, value, group=name)) %>%
+#' hc_add_onclick_korap_search()
+#' }
+#'
+hc_add_onclick_korap_search <- function(hc) {
+ hc_plotOptions(
+ hc,
+ series = list(enabled = TRUE),
+ spline = list(cursor = 'pointer', point = list(events = list(
+ click = JS("function() { window.open(this.webUIRequestUrl, 'korap'); }")
+ ))),
+ line = list(cursor = 'pointer', point = list(events = list(
+ click = JS("function() { window.open(this.webUIRequestUrl, 'korap'); }")
+ ))))
+}
diff --git a/R/highcharter-helper.R b/R/hc_freq_by_year_ci.R
similarity index 70%
rename from R/highcharter-helper.R
rename to R/hc_freq_by_year_ci.R
index 29bdc5d..dda6a63 100644
--- a/R/highcharter-helper.R
+++ b/R/hc_freq_by_year_ci.R
@@ -1,26 +1,22 @@
-#' Helper functions for producing highcharts
+#' Plot interactive frequency curves with confidence intervals
#'
-#' @param hc highchart
+#' @description
+#' `r lifecycle::badge("experimental")`
#'
-#' @name highcharter-helpers
-NULL
-#' NULL
-
-#' Experimental: Plot interactive frequency by year graphs with confidence intervals using highcharter
+#' Convenience function for plotting typical frequency by year graphs with confidence intervals using highcharter.
#'
-#' Experimental convenience function for plotting typical frequency by year graphs with confidence intervals using highcharter.
-#' \bold{Warning:} This function may be moved to a new package.
+#' **Warning:** This function may be moved to a new package.
#'
-#' @rdname highcharter-helpers
+#' @family highcharter-helpers
#' @import highcharter
#' @importFrom tibble add_column
#' @export
#'
-#' @param df data frame like the value of a \code{\link{frequencyQuery}}
+#' @param df data frame like the value of a [frequencyQuery()]
#' @param as.alternatives boolean decides whether queries should be treated as mutually exclusive and exhaustive wrt. to some meaningful class (e.g. spelling variants of a certain word form).
-#' @param ylabel defaults to \% if \code{as.alternatives} is \code{true} and to "ipm" otherwise.
+#' @param ylabel defaults to `%` if `as.alternatives` is `TRUE` and to `ipm` otherwise.
#' @param smooth boolean decides whether the graph is smoothed using the highcharts plot types spline and areasplinerange.
-#' @param ... additional arguments passed to \code{\link{hc_add_series}}
+#' @param ... additional arguments passed to [hc_add_series()]
#'
#' @examples
#' \donttest{year <- c(1990:2018)}\dontshow{year <- c(2013:2013)}
@@ -152,47 +148,3 @@
}
hc
}
-
-#' Add KorAP search click events to highchart
-#'
-#' @description
-#' Adds on-click events to data points of highcharts that were constructed with
-#' \code{\link{frequencyQuery}} or \code{\link{collocationScoreQuery}}. Clicks on data points
-#' then launch KorAP web UI queries for the given query term and virtual corpus in
-#' a separate tab.
-#'
-#' @rdname highcharter-helpers
-#' @export
-#'
-#' @examples
-#' \donttest{
-#' library(highcharter)
-#' library(tidyr)
-#'
-#' new("KorAPConnection", verbose = TRUE) %>%
-#' collocationScoreQuery("Team", "agil", vc = paste("pubDate in", c(2014:2018)),
-#' lemmatizeNodeQuery = TRUE, lemmatizeCollocateQuery = TRUE) %>%
-#' pivot_longer(c("O", "E")) %>%
-#' hchart(type="spline", hcaes(label, value, group=name)) %>%
-#' hc_add_onclick_korap_search()
-#' }
-#'
-hc_add_onclick_korap_search <- function(hc) {
- hc_plotOptions(
- hc,
- series = list(enabled = TRUE),
- spline = list(cursor = 'pointer', point = list(events = list(
- click = JS("function() { window.open(this.webUIRequestUrl, 'korap'); }")
- ))),
- line = list(cursor = 'pointer', point = list(events = list(
- click = JS("function() { window.open(this.webUIRequestUrl, 'korap'); }")
- ))))
-}
-
-.onAttach <- function(libname = find.package("RKorAPClient"),
- pkgname = "RKorAPClient") {
- packageStartupMessage(
- "If you intend to use the Highcharts plot options, please note that Highcharts (www.highcharts.com) is a Highsoft software product which is not free for commercial and governmental use."
- )
-}
-
diff --git a/R/misc.R b/R/misc.R
index 0692619..778b6df 100644
--- a/R/misc.R
+++ b/R/misc.R
@@ -9,12 +9,12 @@
#' Convenience function for converting frequency tables to instances per
#' million.
#'
-#' Given a table with columns \code{f}, \code{conf.low}, and \code{conf.high}, \code{ipm} ads a \code{column ipm}
-#' und multiplies conf.low and \code{conf.high} with 10^6.
+#' Given a table with columns `f`, `conf.low`, and `conf.high`, `ipm` ads a `column ipm`
+#' und multiplies conf.low and `conf.high` with 10^6.
#'
-#' @param df table returned from \code{\link{frequencyQuery}}
+#' @param df table returned from [frequencyQuery()]
#'
-#' @return original table with additional column \code{ipm} and converted columns \code{conf.low} and \code{conf.high}
+#' @return original table with additional column `ipm` and converted columns `conf.low` and `conf.high`
#' @export
#'
#' @rdname misc-functions
@@ -32,11 +32,11 @@
#' Convert corpus frequency table of alternatives to percent
#'
#' Convenience function for converting frequency tables of alternative variants
-#' (generated with \code{as.alternatives=TRUE}) to percent.
+#' (generated with `as.alternatives=TRUE`) to percent.
#'
-#' @param df table returned from \code{\link{frequencyQuery}}
+#' @param df table returned from [frequencyQuery()]
#'
-#' @return original table with converted columns \code{f}, \code{conf.low} and \code{conf.high}
+#' @return original table with converted columns `f`, `conf.low` and `conf.high`
#' @export
#'
#' @importFrom dplyr .data
@@ -101,7 +101,7 @@
#' Experimental: Plot frequency by year graphs with confidence intervals
#'
#' Experimental convenience function for plotting typical frequency by year graphs with confidence intervals using ggplot2.
-#' \bold{Warning:} This function may be moved to a new package.
+#' **Warning:** This function may be moved to a new package.
#'
#' @param mapping Set of aesthetic mappings created by aes() or aes_(). If specified and inherit.aes = TRUE (the default), it is combined with the default mapping at the top level of the plot. You must supply mapping if there is no plot mapping.
#' @param ... Other arguments passed to geom_ribbon, geom_line, and geom_click_point.
diff --git a/R/reexports.R b/R/reexports.R
index 1630dd9..1f7e804 100644
--- a/R/reexports.R
+++ b/R/reexports.R
@@ -1,7 +1,7 @@
#' Pipe operator
#'
-#' See \code{magrittr::\link[magrittr:pipe]{\%>\%}} for details.
+#' See `magrittr::[\%>\%][magrittr::pipe]` for details.
#'
#' @name %>%
#' @rdname pipe
diff --git a/man/KorAPConnection-class.Rd b/man/KorAPConnection-class.Rd
index 73e0a6e..33fdb2b 100644
--- a/man/KorAPConnection-class.Rd
+++ b/man/KorAPConnection-class.Rd
@@ -54,15 +54,14 @@
token persistent for the currently used \code{KorAPUrl} (you can have one
token per KorAPUrl / KorAP server instance), use
\code{persistAccessToken(kco)}. This will store it in your keyring using the
-\code{\link{keyring}} package. Subsequent new("KorAPConnection") calls will
+\code{\link[=keyring]{keyring()}} package. Subsequent new("KorAPConnection") calls will
then automatically retrieve the token from your keying. To stop using a
persisted token, call \code{clearAccessToken(kco)}. Please note that for
DeReKo, authorized queries will behave differently inside and outside the
IDS, because of the special license situation. This concerns also cached
results which do not take into account from where a request was issued. If
-you experience problems or unexpected results, please try \code{kco <-
-new("KorAPConnection", cache=FALSE)} or use
-\code{\link{clearCache}} to clear the cache completely.}
+you experience problems or unexpected results, please try \code{kco <- new("KorAPConnection", cache=FALSE)} or use
+\code{\link[=clearCache]{clearCache()}} to clear the cache completely.}
\item{userAgent}{user agent string.}
@@ -72,7 +71,7 @@
be verbose.}
\item{cache}{logical. Decides if API calls are cached locally. You can clear
-the cache with \code{\link{clearCache}()}.}
+the cache with \code{\link[=clearCache]{clearCache()}}.}
\item{kco}{KorAPConnection object}
@@ -85,8 +84,8 @@
\item{object}{KorAPConnection object}
}
\value{
-\code{\link{KorAPConnection}} object that can be used e.g. with
- \code{\link{corpusQuery}}
+\code{\link[=KorAPConnection]{KorAPConnection()}} object that can be used e.g. with
+\code{\link[=corpusQuery]{corpusQuery()}}
}
\description{
\code{KorAPConnection} objects represent the connection to a KorAP server.
diff --git a/man/KorAPCorpusStats-class.Rd b/man/KorAPCorpusStats-class.Rd
index 0d2e46c..243f769 100644
--- a/man/KorAPCorpusStats-class.Rd
+++ b/man/KorAPCorpusStats-class.Rd
@@ -13,7 +13,7 @@
}
\description{
\code{KorAPCorpusStats} objects can hold information about a corpus or virtual corpus.
-\code{KorAPCorpusStats} objects can be obtained by the \code{\link{corpusStats}()} method.
+\code{KorAPCorpusStats} objects can be obtained by the \code{\link[=corpusStats]{corpusStats()}} method.
}
\section{Slots}{
diff --git a/man/KorAPQuery-class.Rd b/man/KorAPQuery-class.Rd
index e5cf68a..13f0337 100644
--- a/man/KorAPQuery-class.Rd
+++ b/man/KorAPQuery-class.Rd
@@ -117,7 +117,7 @@
\item{collectedMatches}{matches already fetched from the KorAP-API-server}
-\item{kco}{\code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}}
+\item{kco}{\code{\link[=KorAPConnection]{KorAPConnection()}} object (obtained e.g. from \code{new("KorAPConnection")}}
\item{query}{string that contains the corpus query. The query language depends on the \code{ql} parameter. Either \code{query} must be provided or \code{KorAPUrl}.}
@@ -135,17 +135,17 @@
\item{as.df}{return result as data frame instead of as S4 object?}
-\item{kqo}{object obtained from \code{\link{corpusQuery}}}
+\item{kqo}{object obtained from \code{\link[=corpusQuery]{corpusQuery()}}}
\item{offset}{start offset for query results to fetch}
\item{maxFetch}{maximum number of query results to fetch}
-\item{randomizePageOrder}{fetch result pages in pseudo random order if true. Use \code{\link{set.seed}} to set seed for reproducible results.}
+\item{randomizePageOrder}{fetch result pages in pseudo random order if true. Use \code{\link[=set.seed]{set.seed()}} to set seed for reproducible results.}
\item{...}{further arguments passed to or from other methods}
-\item{conf.level}{confidence level of the returned confidence interval (passed through \code{\link{ci}} to \code{\link{prop.test}}).}
+\item{conf.level}{confidence level of the returned confidence interval (passed through \code{\link[=ci]{ci()}} to \code{\link[=prop.test]{prop.test()}}).}
\item{as.alternatives}{LOGICAL that specifies if the query terms should be treated as alternatives. If \code{as.alternatives} is TRUE, the sum over all query hits, instead of the respective vc token sizes is used as total for the calculation of relative frequencies.}
@@ -154,25 +154,25 @@
\item{object}{KorAPQuery object}
}
\value{
-Depending on the \code{as.df} parameter, a table or a \code{\link{KorAPQuery}} object that, among other information, contains the total number of results in \code{@totalResults}. The resulting object can be used to fetch all query results (with \code{\link{fetchAll}}) or the next page of results (with \code{\link{fetchNext}}).
-A corresponding URL to be used within a web browser is contained in \code{@webUIRequestUrl}
-Please make sure to check \code{$collection$rewrites} to see if any unforeseen access rewrites of the query's virtual corpus had to be performed.
+Depending on the \code{as.df} parameter, a table or a \code{\link[=KorAPQuery]{KorAPQuery()}} object that, among other information, contains the total number of results in \verb{@totalResults}. The resulting object can be used to fetch all query results (with \code{\link[=fetchAll]{fetchAll()}}) or the next page of results (with \code{\link[=fetchNext]{fetchNext()}}).
+A corresponding URL to be used within a web browser is contained in \verb{@webUIRequestUrl}
+Please make sure to check \verb{$collection$rewrites} to see if any unforeseen access rewrites of the query's virtual corpus had to be performed.
The \code{kqo} input object with updated slots \code{collectedMatches}, \code{apiResponse}, \code{nextStartIndex}, \code{hasMoreMatches}
}
\description{
This class provides methods to perform different kinds of queries on the KorAP API server.
-\code{KorAPQuery} objects, which are typically created by the \code{\link{corpusQuery}} method,
+\code{KorAPQuery} objects, which are typically created by the \code{\link[=corpusQuery]{corpusQuery()}} method,
represent the current state of a query to a KorAP server.
-\bold{\code{corpusQuery}} performs a corpus query via a connection to a KorAP-API-server
+\strong{\code{corpusQuery}} performs a corpus query via a connection to a KorAP-API-server
-\bold{\code{fetchNext}} fetches the next bunch of results of a KorAP query.
+\strong{\code{fetchNext}} fetches the next bunch of results of a KorAP query.
-\bold{\code{fetchAll}} fetches all results of a KorAP query.
+\strong{\code{fetchAll}} fetches all results of a KorAP query.
-\bold{\code{frequencyQuery}} combines \code{\link{corpusQuery}}, \code{\link{corpusStats}} and
-\code{\link{ci}} to compute a table with the relative frequencies and
+\strong{\code{frequencyQuery}} combines \code{\link[=corpusQuery]{corpusQuery()}}, \code{\link[=corpusStats]{corpusStats()}} and
+\code{\link[=ci]{ci()}} to compute a table with the relative frequencies and
confidence intervals of one ore multiple search terms across one or multiple
virtual corpora.
}
@@ -232,5 +232,5 @@
\url{https://ids-pub.bsz-bw.de/frontdoor/index/index/docId/9026}
}
\seealso{
-\code{\link{KorAPConnection}}, \code{\link{fetchNext}}, \code{\link{fetchRest}}, \code{\link{fetchAll}}, \code{\link{corpusStats}}
+\code{\link[=KorAPConnection]{KorAPConnection()}}, \code{\link[=fetchNext]{fetchNext()}}, \code{\link[=fetchRest]{fetchRest()}}, \code{\link[=fetchAll]{fetchAll()}}, \code{\link[=corpusStats]{corpusStats()}}
}
diff --git a/man/RKorAPClient-package.Rd b/man/RKorAPClient-package.Rd
index e60c721..e59738e 100644
--- a/man/RKorAPClient-package.Rd
+++ b/man/RKorAPClient-package.Rd
@@ -33,7 +33,7 @@
\itemize{
\item \url{https://github.com/KorAP/RKorAPClient/}
\item \url{https://korap.ids-mannheim.de/}
- \item \url{https://www1.ids-mannheim.de/kl/projekte/korap.html}
+ \item \url{https://www.ids-mannheim.de/digspra/kl/projekte/korap}
\item Report bugs at \url{https://github.com/KorAP/RKorAPClient/issues}
}
diff --git a/man/association-score-functions.Rd b/man/association-score-functions.Rd
index fda531a..1443bd8 100644
--- a/man/association-score-functions.Rd
+++ b/man/association-score-functions.Rd
@@ -36,24 +36,25 @@
\item{window_size}{total window size around node (left neighbour count + right neighbour count)}
}
\value{
-association score
+\preformatted{ association score
+}
}
\description{
Functions to calculate different collocation association scores between
a node (target word) and words in a window around the it.
-The functions are primarily used by \code{\link{collocationScoreQuery}}.
+The functions are primarily used by \code{\link[=collocationScoreQuery]{collocationScoreQuery()}}.
-\bold{pmi}: pointwise mutual information
+\strong{pmi}: pointwise mutual information
-\bold{mi2}: pointwise mutual information squared (Daille 1994), also referred to as mutual dependency
+\strong{mi2}: pointwise mutual information squared (Daille 1994), also referred to as mutual dependency
(Thanopoulos et al. 2002)
-\bold{mi3}: pointwise mutual information cubed (Daille 1994), also referred to as log-frequency biased mutual dependency)
+\strong{mi3}: pointwise mutual information cubed (Daille 1994), also referred to as log-frequency biased mutual dependency)
(Thanopoulos et al. 2002)
-\bold{logDice}: log-Dice coefficient, a heuristic measure that is popular in lexicography (Rychlý 2008)
+\strong{logDice}: log-Dice coefficient, a heuristic measure that is popular in lexicography (Rychlý 2008)
-\bold{ll}: log-likelihood (Dunning 1993) using Stefan Evert's (2004) simplified implementation
+\strong{ll}: log-likelihood (Dunning 1993) using Stefan Evert's (2004) simplified implementation
}
\examples{
\donttest{
@@ -71,7 +72,7 @@
Thanopoulos, A., Fakotakis, N., Kokkinakis, G. (2002): Comparative evaluation of collocation extraction metrics. In: Proc. of LREC 2002: 620–625.
-Rychlý, Pavel (2008): A lexicographer-friendly association score. In Proceedings of Recent Advances in Slavonic Natural Language Processing, RASLAN, 6–9. <http://www.fi.muni.cz/usr/sojka/download/raslan2008/13.pdf>.
+Rychlý, Pavel (2008): A lexicographer-friendly association score. In Proceedings of Recent Advances in Slavonic Natural Language Processing, RASLAN, 6–9. \url{http://www.fi.muni.cz/usr/sojka/download/raslan2008/13.pdf}.
Dunning, T. (1993): Accurate methods for the statistics of surprise and coincidence. Comput. Linguist. 19, 1 (March 1993), 61-74.
diff --git a/man/collocationAnalysis-KorAPConnection-method.Rd b/man/collocationAnalysis-KorAPConnection-method.Rd
index bcfe99e..840cd47 100644
--- a/man/collocationAnalysis-KorAPConnection-method.Rd
+++ b/man/collocationAnalysis-KorAPConnection-method.Rd
@@ -25,13 +25,13 @@
)
}
\arguments{
-\item{kco}{\code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}}
+\item{kco}{\code{\link[=KorAPConnection]{KorAPConnection()}} object (obtained e.g. from \code{new("KorAPConnection")}}
\item{node}{target word}
\item{vc}{string describing the virtual corpus in which the query should be performed. An empty string (default) means the whole corpus, as far as it is license-wise accessible.}
-\item{lemmatizeNodeQuery}{if TRUE, node query will be lemmatized, i.e. x -> [tt/l=x]}
+\item{lemmatizeNodeQuery}{if TRUE, node query will be lemmatized, i.e. \verb{x -> [tt/l=x]}}
\item{minOccur}{minimum absolute number of observed co-occurrences to consider a collocate candidate}
@@ -55,13 +55,13 @@
\item{expand}{if TRUE, \code{node} and \code{vc} parameters are expanded to all of their combinations}
-\item{...}{more arguments will be passed to \code{\link{collocationScoreQuery}}}
+\item{...}{more arguments will be passed to \code{\link[=collocationScoreQuery]{collocationScoreQuery()}}}
}
\value{
Tibble with top collocates, association scores, corresponding URLs for web user interface queries, etc.
}
\description{
-\Sexpr[results=rd, stage=render]{lifecycle::badge("experimental")}
+\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}}
Performs a collocation analysis for the given node (or query)
in the given virtual corpus.
diff --git a/man/collocationScoreQuery-KorAPConnection-method.Rd b/man/collocationScoreQuery-KorAPConnection-method.Rd
index 605caf4..4aec265 100644
--- a/man/collocationScoreQuery-KorAPConnection-method.Rd
+++ b/man/collocationScoreQuery-KorAPConnection-method.Rd
@@ -22,7 +22,7 @@
)
}
\arguments{
-\item{kco}{\code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}}
+\item{kco}{\code{\link[=KorAPConnection]{KorAPConnection()}} object (obtained e.g. from \code{new("KorAPConnection")}}
\item{node}{target word}
@@ -30,9 +30,9 @@
\item{vc}{string describing the virtual corpus in which the query should be performed. An empty string (default) means the whole corpus, as far as it is license-wise accessible.}
-\item{lemmatizeNodeQuery}{logical, set to TRUE if node query should be lemmatized, i.e. x -> [tt/l=x]}
+\item{lemmatizeNodeQuery}{logical, set to TRUE if node query should be lemmatized, i.e. \verb{x -> [tt/l=x]}}
-\item{lemmatizeCollocateQuery}{logical, set to TRUE if collocate query should be lemmatized, i.e. x -> [tt/l=x]}
+\item{lemmatizeCollocateQuery}{logical, set to TRUE if collocate query should be lemmatized, i.e. \verb{x -> [tt/l=x]}}
\item{leftContextSize}{size of the left context window}
@@ -53,7 +53,7 @@
}
\description{
Computes various collocation association scores
-based on \code{\link{frequencyQuery}}s for a target word and a collocate.
+based on \code{\link[=frequencyQuery]{frequencyQuery()}}s for a target word and a collocate.
}
\examples{
\donttest{
diff --git a/man/corpusStats-KorAPConnection-method.Rd b/man/corpusStats-KorAPConnection-method.Rd
index f514830..24f6fa0 100644
--- a/man/corpusStats-KorAPConnection-method.Rd
+++ b/man/corpusStats-KorAPConnection-method.Rd
@@ -8,7 +8,7 @@
\S4method{corpusStats}{KorAPConnection}(kco, vc = "", verbose = kco@verbose, as.df = FALSE)
}
\arguments{
-\item{kco}{\code{\link{KorAPConnection}} object (obtained e.g. from \code{new("KorAPConnection")}}
+\item{kco}{\code{\link[=KorAPConnection]{KorAPConnection()}} object (obtained e.g. from \code{new("KorAPConnection")}}
\item{vc}{string describing the virtual corpus. An empty string (default) means the whole corpus, as far as it is license-wise accessible.}
diff --git a/man/hc_add_onclick_korap_search.Rd b/man/hc_add_onclick_korap_search.Rd
new file mode 100644
index 0000000..805ff11
--- /dev/null
+++ b/man/hc_add_onclick_korap_search.Rd
@@ -0,0 +1,38 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/hc_add_onclick_korap_search.R
+\name{hc_add_onclick_korap_search}
+\alias{hc_add_onclick_korap_search}
+\title{Add KorAP search click events to highchart plots}
+\usage{
+hc_add_onclick_korap_search(hc)
+}
+\arguments{
+\item{hc}{higchart object}
+}
+\description{
+\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}}
+
+Adds on-click events to data points of highcharts that were constructed with
+\code{\link[=frequencyQuery]{frequencyQuery()}} or \code{\link[=collocationScoreQuery]{collocationScoreQuery()}}. Clicks on data points
+then launch KorAP web UI queries for the given query term and virtual corpus in
+a separate tab.
+}
+\examples{
+\donttest{
+library(highcharter)
+library(tidyr)
+
+new("KorAPConnection", verbose = TRUE) \%>\%
+ collocationScoreQuery("Team", "agil", vc = paste("pubDate in", c(2014:2018)),
+ lemmatizeNodeQuery = TRUE, lemmatizeCollocateQuery = TRUE) \%>\%
+ pivot_longer(c("O", "E")) \%>\%
+ hchart(type="spline", hcaes(label, value, group=name)) \%>\%
+ hc_add_onclick_korap_search()
+}
+
+}
+\seealso{
+Other highcharter-helpers:
+\code{\link{hc_freq_by_year_ci}()}
+}
+\concept{highcharter-helpers}
diff --git a/man/hc_freq_by_year_ci.Rd b/man/hc_freq_by_year_ci.Rd
new file mode 100644
index 0000000..dae39e7
--- /dev/null
+++ b/man/hc_freq_by_year_ci.Rd
@@ -0,0 +1,61 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/hc_freq_by_year_ci.R
+\name{hc_freq_by_year_ci}
+\alias{hc_freq_by_year_ci}
+\title{Plot interactive frequency curves with confidence intervals}
+\usage{
+hc_freq_by_year_ci(
+ df,
+ as.alternatives = FALSE,
+ ylabel = if (as.alternatives) "\%" else "ipm",
+ smooth = FALSE,
+ ...
+)
+}
+\arguments{
+\item{df}{data frame like the value of a \code{\link[=frequencyQuery]{frequencyQuery()}}}
+
+\item{as.alternatives}{boolean decides whether queries should be treated as mutually exclusive and exhaustive wrt. to some meaningful class (e.g. spelling variants of a certain word form).}
+
+\item{ylabel}{defaults to \verb{\%} if \code{as.alternatives} is \code{TRUE} and to \code{ipm} otherwise.}
+
+\item{smooth}{boolean decides whether the graph is smoothed using the highcharts plot types spline and areasplinerange.}
+
+\item{...}{additional arguments passed to \code{\link[=hc_add_series]{hc_add_series()}}}
+}
+\description{
+\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}}
+
+Convenience function for plotting typical frequency by year graphs with confidence intervals using highcharter.
+
+\strong{Warning:} This function may be moved to a new package.
+}
+\examples{
+\donttest{year <- c(1990:2018)}\dontshow{year <- c(2013:2013)}
+\donttest{alternatives <- c("macht []{0,3} Sinn", "ergibt []{0,3} Sinn")}\dontshow{alternatives <- c("macht []{0,3} Sinn")}
+new("KorAPConnection", verbose = TRUE) \%>\%
+ frequencyQuery(query = alternatives,
+ vc = paste("textType = /Zeit.*/ & pubDate in", year),
+ as.alternatives = TRUE) \%>\%
+ hc_freq_by_year_ci(as.alternatives = TRUE)
+
+\donttest{
+kco <- new("KorAPConnection", verbose = TRUE)
+expand_grid(
+ condition = c("textDomain = /Wirtschaft.*/", "textDomain != /Wirtschaft.*/"),
+ year = (2005:2011)
+) \%>\%
+ cbind(frequencyQuery(
+ kco,
+ "[tt/l=Heuschrecke]",
+ paste0(.$condition, " & pubDate in ", .$year)
+ )) \%>\%
+ hc_freq_by_year_ci()
+}
+
+}
+\seealso{
+Other highcharter-helpers:
+\code{\link{hc_add_onclick_korap_search}()}
+}
+\concept{highcharter-helpers}
diff --git a/man/highcharter-helpers.Rd b/man/highcharter-helpers.Rd
deleted file mode 100644
index 94716c8..0000000
--- a/man/highcharter-helpers.Rd
+++ /dev/null
@@ -1,76 +0,0 @@
-% Generated by roxygen2: do not edit by hand
-% Please edit documentation in R/highcharter-helper.R
-\name{highcharter-helpers}
-\alias{highcharter-helpers}
-\alias{hc_freq_by_year_ci}
-\alias{hc_add_onclick_korap_search}
-\title{Helper functions for producing highcharts}
-\usage{
-hc_freq_by_year_ci(
- df,
- as.alternatives = FALSE,
- ylabel = if (as.alternatives) "\%" else "ipm",
- smooth = FALSE,
- ...
-)
-
-hc_add_onclick_korap_search(hc)
-}
-\arguments{
-\item{df}{data frame like the value of a \code{\link{frequencyQuery}}}
-
-\item{as.alternatives}{boolean decides whether queries should be treated as mutually exclusive and exhaustive wrt. to some meaningful class (e.g. spelling variants of a certain word form).}
-
-\item{ylabel}{defaults to \% if \code{as.alternatives} is \code{true} and to "ipm" otherwise.}
-
-\item{smooth}{boolean decides whether the graph is smoothed using the highcharts plot types spline and areasplinerange.}
-
-\item{...}{additional arguments passed to \code{\link{hc_add_series}}}
-
-\item{hc}{highchart}
-}
-\description{
-Experimental convenience function for plotting typical frequency by year graphs with confidence intervals using highcharter.
-\bold{Warning:} This function may be moved to a new package.
-
-Adds on-click events to data points of highcharts that were constructed with
-\code{\link{frequencyQuery}} or \code{\link{collocationScoreQuery}}. Clicks on data points
-then launch KorAP web UI queries for the given query term and virtual corpus in
-a separate tab.
-}
-\examples{
-\donttest{year <- c(1990:2018)}\dontshow{year <- c(2013:2013)}
-\donttest{alternatives <- c("macht []{0,3} Sinn", "ergibt []{0,3} Sinn")}\dontshow{alternatives <- c("macht []{0,3} Sinn")}
-new("KorAPConnection", verbose = TRUE) \%>\%
- frequencyQuery(query = alternatives,
- vc = paste("textType = /Zeit.*/ & pubDate in", year),
- as.alternatives = TRUE) \%>\%
- hc_freq_by_year_ci(as.alternatives = TRUE)
-
-\donttest{
-kco <- new("KorAPConnection", verbose = TRUE)
-expand_grid(
- condition = c("textDomain = /Wirtschaft.*/", "textDomain != /Wirtschaft.*/"),
- year = (2005:2011)
-) \%>\%
- cbind(frequencyQuery(
- kco,
- "[tt/l=Heuschrecke]",
- paste0(.$condition, " & pubDate in ", .$year)
- )) \%>\%
- hc_freq_by_year_ci()
-}
-
-\donttest{
-library(highcharter)
-library(tidyr)
-
-new("KorAPConnection", verbose = TRUE) \%>\%
- collocationScoreQuery("Team", "agil", vc = paste("pubDate in", c(2014:2018)),
- lemmatizeNodeQuery = TRUE, lemmatizeCollocateQuery = TRUE) \%>\%
- pivot_longer(c("O", "E")) \%>\%
- hchart(type="spline", hcaes(label, value, group=name)) \%>\%
- hc_add_onclick_korap_search()
-}
-
-}
diff --git a/man/misc-functions.Rd b/man/misc-functions.Rd
index e3c0630..aad5c80 100644
--- a/man/misc-functions.Rd
+++ b/man/misc-functions.Rd
@@ -20,7 +20,7 @@
geom_freq_by_year_ci(mapping = aes(ymin = conf.low, ymax = conf.high), ...)
}
\arguments{
-\item{df}{table returned from \code{\link{frequencyQuery}}}
+\item{df}{table returned from \code{\link[=frequencyQuery]{frequencyQuery()}}}
\item{x}{column with the observed absolute frequency.}
@@ -47,10 +47,12 @@
string or vector of strings with clipped off common prefixes and suffixes
}
\description{
-Using \code{\link{prop.test}}, \code{ci} adds three columns to a data frame:
-1. relative frequency (\code{f})
-2. lower bound of a confidence interval (\code{ci.low})
-3. upper bound of a confidence interval
+Using \code{\link[=prop.test]{prop.test()}}, \code{ci} adds three columns to a data frame:
+\enumerate{
+\item relative frequency (\code{f})
+\item lower bound of a confidence interval (\code{ci.low})
+\item upper bound of a confidence interval
+}
Convenience function for converting frequency tables to instances per
million.
@@ -62,10 +64,10 @@
by clipping off prefixes and suffixes that are common to all query strings.
Experimental convenience function for plotting typical frequency by year graphs with confidence intervals using ggplot2.
-\bold{Warning:} This function may be moved to a new package.
+\strong{Warning:} This function may be moved to a new package.
}
\details{
-Given a table with columns \code{f}, \code{conf.low}, and \code{conf.high}, \code{ipm} ads a \code{column ipm}
+Given a table with columns \code{f}, \code{conf.low}, and \code{conf.high}, \code{ipm} ads a \verb{column ipm}
und multiplies conf.low and \code{conf.high} with 10^6.
}
\examples{
@@ -106,5 +108,5 @@
}
}
\seealso{
-\code{ci} is already included in \code{\link{frequencyQuery}}
+\code{ci} is already included in \code{\link[=frequencyQuery]{frequencyQuery()}}
}
diff --git a/man/pipe.Rd b/man/pipe.Rd
index 32004dc..07c1c18 100644
--- a/man/pipe.Rd
+++ b/man/pipe.Rd
@@ -7,6 +7,6 @@
lhs \%>\% rhs
}
\description{
-See \code{magrittr::\link[magrittr:pipe]{\%>\%}} for details.
+See \verb{magrittr::[\\\%>\\\%][magrittr::pipe]} for details.
}
\keyword{internal}
diff --git a/man/synsemanticStopwords.Rd b/man/synsemanticStopwords.Rd
index 54b82ad..560e53f 100644
--- a/man/synsemanticStopwords.Rd
+++ b/man/synsemanticStopwords.Rd
@@ -13,7 +13,7 @@
Vector of synsemantic stopwords.
}
\description{
-\Sexpr[results=rd, stage=render]{lifecycle::badge("experimental")}
+\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}}
Preliminary synsemantic stopwords function to be used in collocation analysis.
}