Replace our log.info with log_info to avoid name clashes

Change-Id: Ib2d9b4a22d4d4e761b7b22fc8ad2b377658742d4
diff --git a/NEWS.md b/NEWS.md
index 6e3866c..8d9df68 100644
--- a/NEWS.md
+++ b/NEWS.md
@@ -7,6 +7,7 @@
 - added context parameter to corpusQuery
 - updated GitHub workflows
 - in collocationAnalysis: given withinSpan parameters are now correctly passed to queries for examples
+- replaced our log.info function with log_info to avoid name clashes
 
 # RKorAPClient 0.7.5 (CRAN release)
 
diff --git a/R/KorAPCorpusStats.R b/R/KorAPCorpusStats.R
index 4056ded..2390d6b 100644
--- a/R/KorAPCorpusStats.R
+++ b/R/KorAPCorpusStats.R
@@ -13,7 +13,7 @@
 #' @slot paragraphs number of paragraphs
 setClass("KorAPCorpusStats", slots=c(vc="character", documents="numeric", tokens="numeric", sentences="numeric", paragraphs="numeric"))
 
-log.info <- function(v,  ...) {
+log_info <- function(v,  ...) {
   cat(ifelse(v, paste0(...), ""))
 }
 setGeneric("corpusStats", function(kco, ...)  standardGeneric("corpusStats") )
@@ -45,12 +45,12 @@
       paste0(kco@apiUrl,
              'statistics?cq=',
              URLencode(enc2utf8(vc), reserved = TRUE))
-    log.info(verbose, "Getting size of virtual corpus \"", vc, "\"", sep = "")
+    log_info(verbose, "Getting size of virtual corpus \"", vc, "\"", sep = "")
     res <- apiCall(kco, url)
     if(is.null(res)) {
       res <- data.frame(documents=NA, tokens=NA, sentences=NA, paragraphs=NA)
     }
-    log.info(verbose, ": ", res$tokens, " tokens\n")
+    log_info(verbose, ": ", res$tokens, " tokens\n")
     if (as.df)
       data.frame(vc = vc, res, stringsAsFactors = FALSE)
     else
diff --git a/R/KorAPQuery.R b/R/KorAPQuery.R
index b6ed0da..d5894b2 100644
--- a/R/KorAPQuery.R
+++ b/R/KorAPQuery.R
@@ -198,20 +198,20 @@
         paste(fields, collapse = ","),
         if (metadataOnly) '&access-rewrite-disabled=true' else ''
       )
-      log.info(verbose, "Searching \"", query, "\" in \"", vc, "\"", sep =
+      log_info(verbose, "Searching \"", query, "\" in \"", vc, "\"", sep =
                  "")
       res = apiCall(kco, paste0(requestUrl, '&count=0'))
       if (is.null(res)) {
-        log.info(verbose, " [failed]\n")
+        log_info(verbose, " [failed]\n")
         message("API call failed.")
         totalResults <- 0
       } else {
         totalResults <-res$meta$totalResults
-        log.info(verbose, ": ", totalResults, " hits")
+        log_info(verbose, ": ", totalResults, " hits")
         if(!is.null(res$meta$cached))
-          log.info(verbose, " [cached]\n")
+          log_info(verbose, " [cached]\n")
         else
-          log.info(verbose, ", took ", res$meta$benchmark, "\n", sep = "")
+          log_info(verbose, ", took ", res$meta$benchmark, "\n", sep = "")
       }
       if (as.df)
         data.frame(
diff --git a/R/collocationAnalysis.R b/R/collocationAnalysis.R
index edc427d..fcc80c1 100644
--- a/R/collocationAnalysis.R
+++ b/R/collocationAnalysis.R
@@ -243,7 +243,7 @@
   if (length(snippet) < 1) {
     dplyr::tibble(word=c(), frequency=c())
   } else if (length(snippet) > 1) {
-    log.info(verbose, paste("Joining", length(snippet), "kwics\n"))
+    log_info(verbose, paste("Joining", length(snippet), "kwics\n"))
     for (s in snippet) {
       oldTable <- snippet2FreqTable(
         s,
@@ -254,7 +254,7 @@
         stopwords = stopwords
       )
     }
-    log.info(verbose, paste("Aggregating", length(oldTable$word), "tokens\n"))
+    log_info(verbose, paste("Aggregating", length(oldTable$word), "tokens\n"))
     oldTable  %>%
       group_by(word) %>%
       mutate(word = dplyr::case_when(ignoreCollocateCase ~ tolower(word), TRUE ~ word)) %>%
diff --git a/cran-comments.md b/cran-comments.md
index 69866ff..9864f87 100644
--- a/cran-comments.md
+++ b/cran-comments.md
@@ -24,6 +24,7 @@
   by gracefully failing on invalid json api responses, via:
   <https://github.com/KorAP/RKorAPClient/commit/04814f2be215f08a3777310af2202d14457c2e7c>,
   <https://github.com/KorAP/RKorAPClient/commit/f650629fa69ab10979f2ffe2652da77599caaf70>
+* Replaced our log.info function with log_info to avoid name clashes
 
 ### Old Notes
 
diff --git a/inst/shiny-apps/frequency_curves/server.R b/inst/shiny-apps/frequency_curves/server.R
index 67c0cf8..2094490 100644
--- a/inst/shiny-apps/frequency_curves/server.R
+++ b/inst/shiny-apps/frequency_curves/server.R
@@ -11,8 +11,8 @@
 query <- "Aluhut"
 logfile <- file("frequency_curves.log", open = "a")
 
-# override log.info in RKorAPClient to get some progress info
-log.info <- function(v,  ...) {
+# override log_info in RKorAPClient to get some progress info
+log_info <- function(v,  ...) {
   original = paste0(...)
   detail <- if (str_detect(original, "Searching.*in ([0-9]{4})")) {
     str_replace(original, ".*in ([0-9]{4}).*", "Suche in \\1")
@@ -26,7 +26,7 @@
   flush(logfile)
 }
 
-assignInNamespace("log.info", log.info, "RKorAPClient")
+assignInNamespace("log_info", log_info, "RKorAPClient")
 
 plotHighchart <- function(query = c("Tolpatsch", "Tollpatsch"),
                           vc = "(textType = /Zeit.*/ | textTypeRef=Plenarprotokoll) & availability!=QAO-NC-LOC:ids & creationDate in"