[Rd] [EXTERNAL] Re: NOTE: multiple local function definitions for ?fun? with different formal arguments

Chris Black chr|@ @end|ng |rom ckb|@ck@org
Mon Oct 21 21:28:51 CEST 2024


I’m replying 8 months later to say a proper thanks to Duncan for the function below. It’s been helping me clean up duplicate (and not-quite duplicate!) function definitions in amateur code ever since, and I’m reminded to say so now because I just passed it along to Ben Zipperer in response to a very similar question[1] on Mastodon. 

In the Mastodon thread there were several R experts expecting the existing package checks to catch this and being surprised to realize they don't, which I think mostly goes to highlight that it really is a corner case… but in any case thank you for your help to keep the “bitten by function redefinition” club a small one.

Thanks,
Chris

[1] https://mastodon.social/@benzipperer/113328761897124440



> On Feb 7, 2024, at 11:53 AM, Duncan Murdoch <murdoch.duncan using gmail.com> wrote:
> 
> I put the idea below into a function that gives nicer looking results. Here's the new code:
> 
> dupnames <- function(path = ".") {
> 
>  Rfiles <- pkgload:::find_code(path)
>  allnames <- data.frame(names=character(), filename=character(), line = numeric())
>  result <- NULL
>  for (f in Rfiles) {
>    exprs <- parse(f, keep.source = TRUE)
>    locs <- getSrcLocation(exprs)
>    names <- character(length(exprs))
>    lines <- numeric(length(exprs))
>    for (i in seq_along(exprs)) {
>      expr <- exprs[[i]]
>      if (is.name(expr[[1]]) &&
>          deparse(expr[[1]]) %in% c("<-", "=") &&
>          is.name(expr[[2]])) {
>        names[i] <- deparse(expr[[2]])
>        lines[i] <- locs[i]
>      }
>    }
>    keep <- names != ""
>    if (any(keep)) {
>      names <- names[keep]
>      lines <- lines[keep]
> 
>      prev <- nrow(allnames)
>      allnames <- rbind(allnames, data.frame(name = names, filename = basename(f), line = lines))
>      dups <- which(duplicated(allnames$name))
>      dups <- dups[dups > prev]
>      if (any(dups)) {
>        origfile <- character(length(dups))
>        origline <- numeric(length(dups))
>        for (i in seq_along(dups)) {
>          prev <- which(allnames$name == allnames$name[dups[i]])[1]
>          origfile[i] <- allnames$filename[prev]
>          origline[i] <- allnames$line[prev]
>        }
> 
>        result <- rbind(result,
>                        data.frame(name = allnames$name[dups],
>                                   first = paste(origfile, origline, sep=":"),
>                                   dup = paste(allnames$filename[dups], allnames$line[dups], sep = ":")))
>      }
>    }
>  }
>  result
> }
> 
> 
> And here's what I get when I run it on rgl:
> 
> dupnames("rgl")
>  name      first          dup
> 1  fns knitr.R:12  knitr.R:165
> 2  fns knitr.R:12 pkgdown.R:14
> 3  fns knitr.R:12    shiny.R:8
> 
> Those are okay; the fns object is a temporary that is later removed in each case.
> 
> Duncan Murdoch



More information about the R-devel mailing list