inst/source/R/find_missing_doc.R

#' Find Missing Documentation
#'
#' For \pkg{fritools}, we make exhaustive use of categorizing functions into
#' families with the `See also` section of the man pages (which are generated by
#' the @family tags in the code files).
#' @name missing_docs
#' @param path Path to a (package) directory.
#' @param list_families List the function families defined so far.
#' @family searching functions
NULL


#' @export
#' @rdname missing_docs
#' @aliases find_missing_see_also
#' @return For `find_missing_see_also`: a character vector of man pages with
#' missing `See also` sections.
find_missing_see_also <- function(path, list_families = TRUE) {
    files_with_seealso <- search_files("seealso",
                                       path = file.path(path, "man"),
                                       verbose = FALSE)
    files_with_seealso <- summary(files_with_seealso)[["file"]]
    files <- list.files(path = file.path(path, "man"), full.names = TRUE)
    diff <- compare_vectors(files, files_with_seealso, differences_only = TRUE)
    missings <- diff[is.na(diff[, "files_with_seealso"]), "files"]
    result <- strip_off_attributes(missings)
    if (isTRUE(list_families)) {
        families <- NULL
        for (file in files_with_seealso) {
            families <- c(families,
                          fromto(x = readLines(file), from = "^Other.*:",
                                 to = ".*", shift_to = -1))
        }
        message("Families so far: \n",
                paste(unique(sub(": *$", "", families)), collapse = "\n"))
    }
    return(result)
}

#' @export
#' @param clean Remove temporary directory?
#' @rdname missing_docs
#' @aliases find_missing_family
#' @return For `find_missing_family`: a character vector of function names with
#' missing `@family` tags.
find_missing_family <- function(path, list_families = TRUE, clean = TRUE) {
    wdir <- tempfile()
    dir.create(wdir)
    if (isTRUE(clean)) on.exit(unlink(wdir, recursive = TRUE))
    function_files <- NULL
    code_files <- list.files(file.path(path, "R"), full.names = TRUE)
    code_files <- grep("(-package.R|zzz.R)$", code_files, value = TRUE,
                       invert = TRUE)
    for (code_file in code_files) {
        function_files <- c(function_files,
                            split_code_file(code_file, wdir,
                                            write_to_disk = FALSE))
    }
    with_family <- search_files("^#' *@family", path = wdir, verbose = FALSE)
    with_doc <- search_files("^#' ", path = wdir, verbose = FALSE)
    with_rd_name <- search_files("^#' @rdname", path = wdir, verbose = FALSE)
    files_with_family <- summary(with_family)[["file"]]
    files_with_doc_no_rd <- setdiff(summary(with_doc)[["file"]],
                              summary(with_rd_name)[["file"]])
    diff <- compare_vectors(files_with_doc_no_rd, files_with_family,
                            differences_only = TRUE)
    missings <- diff[is.na(diff[, "files_with_family"]), "files_with_doc_no_rd"]
    result <- sub("\\.[rR]$", "", basename(strip_off_attributes(missings)))
    if (isTRUE(list_families)) {
        message("Families so far: \n",
                paste(unique(with_family$matches), collapse = "\n"))
    }
    return(result)
}

Try the fritools package in your browser

Any scripts or data that you put into this service are public.

fritools documentation built on Nov. 19, 2023, 1:06 a.m.