Skip to content

Commit

Permalink
Add suffix to get_author_list()
Browse files Browse the repository at this point in the history
  • Loading branch information
arnaudgallou committed Dec 8, 2023
1 parent 248c5ea commit 122ab6c
Show file tree
Hide file tree
Showing 8 changed files with 59 additions and 51 deletions.
3 changes: 2 additions & 1 deletion R/checkers.R
Original file line number Diff line number Diff line change
Expand Up @@ -243,11 +243,12 @@ check_args <- function(type, x, ...) {
})
}

check_suffix_format <- function(x, allowed, arg = caller_arg(x)) {
check_suffix_format <- function(x, arg = caller_arg(x)) {
check_string(x, allow_null = TRUE, arg = arg)
if (is.null(x)) {
return(invisible(NULL))
}
allowed <- c("a", "c", "n", "o", "^", ",")
pattern <- to_chr_class(allowed, negate = TRUE)
keys <- als_extract_keys(x)
has_dup_keys <- vec_duplicate_any(keys)
Expand Down
15 changes: 9 additions & 6 deletions R/plume.R
Original file line number Diff line number Diff line change
Expand Up @@ -111,10 +111,13 @@ Plume <- R6Class(
},

#' @description Get author list.
#' @param format A character string defining the format of symbols suffixing
#' @param suffix A character string defining the format of symbols suffixing
#' author names. See details.
#' @param format `r lifecycle::badge("deprecated")`
#'
#' Please use the parameter `suffix` instead.
#' @details
#' `format` lets you choose which symbol categories to suffix authors with,
#' `suffix` lets you choose which symbol categories to suffix authors with,
#' using the following keys:
#' * `a` for affiliations
#' * `c` for corresponding authors
Expand All @@ -127,13 +130,13 @@ Plume <- R6Class(
#' Use `","` to separate and `"^"` to superscript symbols.
#' Use `NULL` or an empty string to list author names without suffixes.
#' @return A character vector.
get_author_list = function(format = NULL) {
check_suffix_format(format, allowed = c("a", "c", "n", "o", "^", ","))
get_author_list = function(suffix = NULL, format = deprecated()) {
authors <- private$get("literal_name")
if (is_empty(format)) {
if (is_empty(suffix)) {
out <- authors
} else {
suffixes <- private$get_author_list_suffixes(format)
check_suffix_format(suffix)
suffixes <- private$get_author_list_suffixes(suffix)
out <- paste0(authors, suffixes)
}
as_plm(out)
Expand Down
4 changes: 2 additions & 2 deletions README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ Alternatively, you can generate author information as character strings using `P
aut <- Plume$new(encyclopedists)
aut$set_corresponding_authors(diderot, .by = "family_name")
aut$get_author_list(format = "^a,^cn") |> enumerate(last = ",\n")
aut$get_author_list(suffix = "^a,^cn") |> enumerate(last = ",\n")
aut$get_contact_details()
Expand All @@ -113,7 +113,7 @@ aut2 <- Plume$new(
symbols = list(affiliation = letters)
)
aut2$get_author_list(format = "^a^") |> enumerate(last = ",\n")
aut2$get_author_list("^a^") |> enumerate(last = ",\n")
aut2$get_contributions(roles_first = FALSE, divider = " ")
```
Expand Down
4 changes: 2 additions & 2 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -169,7 +169,7 @@ using `Plume`:
aut <- Plume$new(encyclopedists)
aut$set_corresponding_authors(diderot, .by = "family_name")

aut$get_author_list(format = "^a,^cn") |> enumerate(last = ",\n")
aut$get_author_list(suffix = "^a,^cn") |> enumerate(last = ",\n")
#> Denis Diderot^1,^\*†, Jean-Jacques Rousseau^2^, François-Marie Arouet^2^‡,
#> Jean Le Rond d'Alembert^1,3^§

Expand Down Expand Up @@ -199,7 +199,7 @@ aut2 <- Plume$new(
symbols = list(affiliation = letters)
)

aut2$get_author_list(format = "^a^") |> enumerate(last = ",\n")
aut2$get_author_list("^a^") |> enumerate(last = ",\n")
#> Denis Diderot^a^, Jean-Jacques Rousseau^b^, François-Marie Arouet^b^,
#> Jean Le Rond d'Alembert^a,c^

Expand Down
10 changes: 7 additions & 3 deletions man/Plume.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

16 changes: 8 additions & 8 deletions tests/testthat/_snaps/get-author-list.md
Original file line number Diff line number Diff line change
Expand Up @@ -10,31 +10,31 @@
# get_author_list() gives meaningful error messages

Code
(expect_error(aut$get_author_list(format = 1)))
(expect_error(aut$get_author_list(1)))
Output
<error/rlang_error>
Error:
! `format` must be a character string.
! `suffix` must be a character string.
Code
(expect_error(aut$get_author_list(format = "anca")))
(expect_error(aut$get_author_list("anca")))
Output
<error/rlang_error>
Error:
! `format` must have unique keys.
! `suffix` must have unique keys.
Code
(expect_error(aut$get_author_list(format = "az")))
(expect_error(aut$get_author_list("az")))
Output
<error/rlang_error>
Error:
! `format` must only contain any of `a`, `c`, `n`, `o`, `^` or `,`.
! `suffix` must only contain any of `a`, `c`, `n`, `o`, `^` or `,`.
Code
(expect_error(aut$get_author_list(format = "ac")))
(expect_error(aut$get_author_list("ac")))
Output
<error/rlang_error>
Error:
! Column `corresponding` doesn't exist.
Code
(expect_error(aut$get_author_list(format = "o")))
(expect_error(aut$get_author_list("o")))
Output
<error/purrr_error_indexed>
Error in `map2()`:
Expand Down
44 changes: 22 additions & 22 deletions tests/testthat/test-get-author-list.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,11 @@ test_that("get_author_list() returns author list", {

expect_s3_class(aut$get_author_list(), "plm")
expect_equal(
aut$get_author_list(format = NULL),
aut$get_author_list(NULL),
c("Zip Zap", "Ric Rac", "Pim-Pam Pom")
)
expect_equal(
aut$get_author_list(format = ""),
aut$get_author_list(""),
c("Zip Zap", "Ric Rac", "Pim-Pam Pom")
)

Expand All @@ -21,58 +21,58 @@ test_that("get_author_list() returns author list", {
.n <- c("†,‡", "", "§")

expect_equal(
aut$get_author_list(format = "a"),
aut$get_author_list("a"),
affix_to_authors(.a)
)
expect_equal(
aut$get_author_list(format = "c"),
aut$get_author_list("c"),
affix_to_authors(.c)
)
expect_equal(
aut$get_author_list(format = "n"),
aut$get_author_list("n"),
affix_to_authors(.n)
)
expect_equal(
aut$get_author_list(format = "anc"),
aut$get_author_list("anc"),
affix_to_authors(.a, .n, .c)
)
expect_equal(
aut$get_author_list(format = "acn"),
affix_to_authors(.a, .c, .n)
aut$get_author_list("can"),
affix_to_authors(.c, .a, .n)
)
expect_equal(
aut$get_author_list(format = "^ac^n"),
aut$get_author_list("^ac^n"),
affix_to_authors("^", .a, .c, "^", .n)
)

.seps <- c(",", "", ",")

expect_equal(
aut$get_author_list(format = "a,c"),
aut$get_author_list("a,c"),
affix_to_authors(.a, .seps, .c)
)
expect_equal(
aut$get_author_list(format = "^a,^c"),
aut$get_author_list("^a,^c"),
affix_to_authors("^", .a, .seps, "^", .c)
)

expect_equal(
aut$get_author_list(format = "a,,c"),
aut$get_author_list("a,,c"),
affix_to_authors(.a, .seps, .c)
)
expect_equal(
aut$get_author_list(format = ",ac,"),
aut$get_author_list(",ac,"),
affix_to_authors(.a, .c)
)
expect_equal(
aut$get_author_list(format = "^^ac^^"),
aut$get_author_list("^^ac^^"),
affix_to_authors("^", .a, .c, "^")
)

.hats <- c("^", "", "^")

expect_equal(
aut$get_author_list(format = "^a^c^n^"),
aut$get_author_list("^a^c^n^"),
affix_to_authors("^", .a, .hats, .c, .hats, .n, "^")
)

Expand All @@ -90,7 +90,7 @@ test_that("get_author_list() returns author list", {
.n <- c("1,2", "", "3")

expect_equal(
aut$get_author_list(format = "anc"),
aut$get_author_list("anc"),
affix_to_authors(.a, .n, .c)
)

Expand All @@ -102,7 +102,7 @@ test_that("get_author_list() returns author list", {
)

expect_equal(
aut$get_author_list(format = "a"),
aut$get_author_list("a"),
"X Y1,2"
)
})
Expand All @@ -120,19 +120,19 @@ test_that("get_author_list() gives meaningful error messages", {

expect_snapshot({
(expect_error(
aut$get_author_list(format = 1)
aut$get_author_list(1)
))
(expect_error(
aut$get_author_list(format = "anca")
aut$get_author_list("anca")
))
(expect_error(
aut$get_author_list(format = "az")
aut$get_author_list("az")
))
(expect_error(
aut$get_author_list(format = "ac")
aut$get_author_list("ac")
))
(expect_error(
aut$get_author_list(format = "o")
aut$get_author_list("o")
))
})
})
14 changes: 7 additions & 7 deletions vignettes/plume.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -259,7 +259,7 @@ cat(read_file(tmp_file))

### Author lists

`get_author_list()` generates author lists. You can control the formatting of author suffixes (symbols linking authors to affiliations, notes and other metadata) using the `format` parameter. `format` takes a character string as argument and allows you to choose which symbol categories to suffix authors with, using the following keys:
`get_author_list()` generates author lists. You can control the formatting of author suffixes (symbols linking authors to affiliations, notes and other metadata) using the `suffix` parameter. `suffix` takes a character string as argument and allows you to choose which symbol categories to suffix authors with, using the following keys:

- `a` for affiliations

Expand All @@ -275,23 +275,23 @@ The order of the keys determines the order of symbol categories.
aut <- Plume$new(encyclopedists)
aut$set_corresponding_authors(everyone())
aut$get_author_list(format = "ac") |> enumerate(last = ",\n")
aut$get_author_list(suffix = "ac") |> enumerate(last = ",\n")
aut$get_author_list(format = "ca") |> enumerate(last = ",\n")
aut$get_author_list(suffix = "ca") |> enumerate(last = ",\n")
```

In addition, you can use `^` to superscript and `,` to separate symbols:

```{r}
aut$set_corresponding_authors(1, 4)
aut$get_author_list(format = "^a,^cn") |> enumerate(last = ",\n")
aut$get_author_list("^a,^cn") |> enumerate(last = ",\n")
```

Use `format = NULL` or `format = ""` to ignore suffixes:
Use `suffix = NULL` or `suffix = ""` to ignore suffixes:

```{r}
aut$get_author_list(format = NULL) |> enumerate()
aut$get_author_list(suffix = NULL) |> enumerate()
```

### Affiliations & notes
Expand Down Expand Up @@ -385,7 +385,7 @@ Use `NULL` to display numbers:
```{r}
aut <- Plume$new(encyclopedists, symbols = list(affiliation = letters, note = NULL))
aut$get_author_list(format = "^a,n^") |> enumerate(last = ",\n")
aut$get_author_list("^a,n^") |> enumerate(last = ",\n")
```

Use `NULL` as much as possible for symbols using numerous unique items (typically affiliations). If you have to use letters for a given category that has more unique items than letters, you can control the sequencing behaviour using the `sequential()` modifier, as shown below:
Expand Down

0 comments on commit 122ab6c

Please sign in to comment.