Skip to content

Commit 320c6de

Browse files
author
maechler
committed
"normalize" messages, notably for translation, to use "character string"
git-svn-id: https://svn.r-project.org/R/trunk@87255 00db46b3-68df-0310-9c12-caf00c1e9a41
1 parent 32c0a1e commit 320c6de

File tree

8 files changed

+36
-27
lines changed

8 files changed

+36
-27
lines changed

doc/NEWS.Rd

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -110,6 +110,10 @@
110110
methods or class definitions are needed. Consequently, previous
111111
workflows relying on the old behaviour will have to be amended by
112112
adding corresponding \code{library(p)} calls.
113+
114+
\item More R level messages use a common format containing
115+
\code{"character string"} for more consistency and less translation
116+
work.
113117
}
114118
}
115119

src/library/base/R/RNG.R

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
# File src/library/base/R/RNG.R
22
# Part of the R package, https://www.R-project.org
33
#
4-
# Copyright (C) 1995-2019 The R Core Team
4+
# Copyright (C) 1995-2022 The R Core Team
55
#
66
# This program is free software; you can redistribute it and/or modify
77
# it under the terms of the GNU General Public License as published by
@@ -33,7 +33,7 @@ RNGkind <- function(kind = NULL, normal.kind = NULL, sample.kind = NULL)
3333
do.set <- length(kind) > 0L
3434
if(do.set) {
3535
if(!is.character(kind) || length(kind) > 1L)
36-
stop("'kind' must be a character string of length 1 (RNG to be used).")
36+
stop("'kind' must be a character string (RNG to be used).")
3737
if(is.na(i.knd <- pmatch(kind, kinds) - 1L))
3838
stop(gettextf("'%s' is not a valid abbreviation of an RNG", kind),
3939
domain = NA)
@@ -42,7 +42,8 @@ RNGkind <- function(kind = NULL, normal.kind = NULL, sample.kind = NULL)
4242

4343
if(!is.null(normal.kind)) {
4444
if(!is.character(normal.kind) || length(normal.kind) != 1L)
45-
stop("'normal.kind' must be a character string of length 1")
45+
stop(gettextf("'%s' must be a character string", "normal.kind"),
46+
domain = NA)
4647
normal.kind <- pmatch(normal.kind, n.kinds) - 1L
4748
if(is.na(normal.kind))
4849
stop(gettextf("'%s' is not a valid choice", normal.kind),
@@ -55,7 +56,8 @@ RNGkind <- function(kind = NULL, normal.kind = NULL, sample.kind = NULL)
5556

5657
if(!is.null(sample.kind)) {
5758
if(!is.character(sample.kind) || length(sample.kind) != 1L)
58-
stop("'sample.kind' must be a character string of length 1")
59+
stop(gettextf("'%s' must be a character string", "sample.kind"),
60+
domain = NA)
5961
sample.kind <- pmatch(sample.kind, s.kinds) - 1L
6062
if(is.na(sample.kind))
6163
stop(gettextf("'%s' is not a valid choice", sample.kind),
@@ -82,7 +84,7 @@ set.seed <- function(seed, kind = NULL, normal.kind = NULL, sample.kind = NULL)
8284
s.kinds <- c("Rounding", "Rejection", "default")
8385
if(length(kind) ) {
8486
if(!is.character(kind) || length(kind) > 1L)
85-
stop("'kind' must be a character string of length 1 (RNG to be used).")
87+
stop("'kind' must be a character string (RNG to be used).")
8688
if(is.na(i.knd <- pmatch(kind, kinds) - 1L))
8789
stop(gettextf("'%s' is not a valid abbreviation of an RNG", kind),
8890
domain = NA)
@@ -91,7 +93,8 @@ set.seed <- function(seed, kind = NULL, normal.kind = NULL, sample.kind = NULL)
9193

9294
if(!is.null(normal.kind)) {
9395
if(!is.character(normal.kind) || length(normal.kind) != 1L)
94-
stop("'normal.kind' must be a character string of length 1")
96+
stop(gettextf("'%s' must be a character string", "normal.kind"),
97+
domain = NA)
9598
normal.kind <- pmatch(normal.kind, n.kinds) - 1L
9699
if(is.na(normal.kind))
97100
stop(gettextf("'%s' is not a valid choice", normal.kind),
@@ -103,7 +106,8 @@ set.seed <- function(seed, kind = NULL, normal.kind = NULL, sample.kind = NULL)
103106
}
104107
if(!is.null(sample.kind)) {
105108
if(!is.character(sample.kind) || length(sample.kind) != 1L)
106-
stop("'sample.kind' must be a character string of length 1")
109+
stop(gettextf("'%s' must be a character string", "sample.kind"),
110+
domain = NA)
107111
sample.kind <- pmatch(sample.kind, s.kinds) - 1L
108112
if(is.na(sample.kind))
109113
stop(gettextf("'%s' is not a valid choice", sample.kind),

src/library/base/R/load.R

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
# File src/library/base/R/load.R
22
# Part of the R package, https://www.R-project.org
33
#
4-
# Copyright (C) 1995-2022 The R Core Team
4+
# Copyright (C) 1995-2024 The R Core Team
55
#
66
# This program is free software; you can redistribute it and/or modify
77
# it under the terms of the GNU General Public License as published by
@@ -91,7 +91,7 @@ save <- function(..., list = character(),
9191
}
9292
if (is.character(file)) {
9393
if(!nzchar(file))
94-
stop(gettextf("'%s' must be a non-empty string", "file"), domain = NA)
94+
stop(gettextf("'%s' must be a non-empty character string", "file"), domain = NA)
9595
if(!is.character(compress)) {
9696
if(!is.logical(compress))
9797
stop("'compress' must be logical or character")
@@ -130,7 +130,7 @@ save.image <- function (file = ".RData", version = NULL, ascii = FALSE,
130130
compress = !ascii, safe = TRUE)
131131
{
132132
if (!is.character(file) || length(file) != 1 || file == "")
133-
stop(gettextf("'%s' must be a non-empty string", "file"), domain = NA)
133+
stop(gettextf("'%s' must be a non-empty character string", "file"), domain = NA)
134134
opts <- getOption("save.image.defaults")
135135
if(is.null(opts)) opts <- getOption("save.defaults")
136136

src/library/base/R/serialize.R

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
# File src/library/base/R/serialize.R
22
# Part of the R package, https://www.R-project.org
33
#
4-
# Copyright (C) 1995-2023 The R Core Team
4+
# Copyright (C) 1995-2024 The R Core Team
55
#
66
# This program is free software; you can redistribute it and/or modify
77
# it under the terms of the GNU General Public License as published by
@@ -22,7 +22,7 @@ saveRDS <-
2222
{
2323
if(is.character(file)) {
2424
if(length(file) != 1 || file == "")
25-
stop(gettextf("'%s' must be a non-empty string", "file"), domain = NA)
25+
stop(gettextf("'%s' must be a non-empty character string", "file"), domain = NA)
2626
object <- object # do not create corrupt file if object does not exist
2727
mode <- if(ascii %in% FALSE) "wb" else "w"
2828
con <- if (is.logical(compress))

src/library/grDevices/R/postscript.R

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1027,7 +1027,8 @@ embedFonts <- function(file, # The ps or pdf file to convert
10271027
embedGlyphs <- function(file, glyphInfo, outfile = file,
10281028
options = character()) {
10291029
if (!is.character(file) || length(file) != 1L || !nzchar(file))
1030-
stop("'file' must be a non-empty character string")
1030+
stop(gettextf("'%s' must be a non-empty character string", "file"),
1031+
domain = NA)
10311032
infoList <- FALSE
10321033
if (!inherits(glyphInfo, "RGlyphInfo")) {
10331034
if (is.list(glyphInfo)) {

src/library/tools/R/utils.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ function(x)
3737
## Turn a possibly relative file path absolute, performing tilde
3838
## expansion if necessary.
3939
if(length(x) != 1L)
40-
stop("'x' must be a single character string")
40+
stop(gettextf("'%s' must be a character string", "x"), domain=NA)
4141
if(!file.exists(epath <- path.expand(x)))
4242
stop(gettextf("file '%s' does not exist", x),
4343
domain = NA)

src/library/utils/R/help.search.R

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
# File src/library/utils/R/help.search.R
22
# Part of the R package, https://www.R-project.org
33
#
4-
# Copyright (C) 1995-2022 The R Core Team
4+
# Copyright (C) 1995-2024 The R Core Team
55
#
66
# This program is free software; you can redistribute it and/or modify
77
# it under the terms of the GNU General Public License as published by
@@ -121,36 +121,36 @@ function(pattern, fields = c("alias", "concept", "title"),
121121
types = getOption("help.search.types"))
122122
{
123123
### Argument handling.
124-
.wrong_args <- function(args)
125-
gettextf("argument %s must be a character string", sQuote(args))
124+
.wrong_arg <- function(arg)
125+
gettextf("'%s' must be a character string", arg)
126126
if(is.logical(verbose)) verbose <- 2 * as.integer(verbose)
127127
fuzzy <- agrep
128128
if(!missing(pattern)) {
129129
if(!is.character(pattern) || (length(pattern) > 1L))
130-
stop(.wrong_args("pattern"), domain = NA)
130+
stop(.wrong_arg("pattern"), domain = NA)
131131
i <- pmatch(fields, hsearch_db_fields)
132132
if(anyNA(i))
133133
stop("incorrect field specification")
134134
else
135135
fields <- hsearch_db_fields[i]
136136
} else if(!missing(apropos)) {
137137
if(!is.character(apropos) || (length(apropos) > 1L))
138-
stop(.wrong_args("apropos"), domain = NA)
138+
stop(.wrong_arg("apropos"), domain = NA)
139139
else {
140140
pattern <- apropos
141141
fields <- c("alias", "title")
142142
}
143143
} else if(!missing(keyword)) {
144144
if(!is.character(keyword) || (length(keyword) > 1L))
145-
stop(.wrong_args("keyword"), domain = NA)
145+
stop(.wrong_arg("keyword"), domain = NA)
146146
else {
147147
pattern <- keyword
148148
fields <- "keyword"
149149
if(is.null(fuzzy)) fuzzy <- FALSE
150150
}
151151
} else if(!missing(whatis)) {
152152
if(!is.character(whatis) || (length(whatis) > 1))
153-
stop(.wrong_args("whatis"), domain = NA)
153+
stop(.wrong_arg("whatis"), domain = NA)
154154
else {
155155
pattern <- whatis
156156
fields <- "alias"

src/library/utils/R/packages.R

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ function(contriburl = contrib.url(repos, type), method,
2525
quiet = TRUE, ...)
2626
{
2727
if (!is.character(type))
28-
stop("invalid 'type'; must be a character string")
28+
stop(gettextf("'%s' must be a character string", "type"), domain = NA)
2929
requiredFields <-
3030
c(tools:::.get_standard_repository_db_fields(), "File")
3131
if (is.null(fields))
@@ -364,7 +364,7 @@ update.packages <- function(lib.loc = NULL, repos = getOption("repos"),
364364
checkBuilt = FALSE, type = getOption("pkgType"))
365365
{
366366
if (!is.character(type))
367-
stop("invalid 'type'; must be a character string")
367+
stop(gettextf("'%s' must be a character string", "type"), domain = NA)
368368
force(ask) # just a check that it is valid before we start work
369369
text.select <- function(old)
370370
{
@@ -473,7 +473,7 @@ old.packages <- function(lib.loc = NULL, repos = getOption("repos"),
473473
..., type = getOption("pkgType"))
474474
{
475475
if (!is.character(type))
476-
stop("invalid 'type'; must be a character string")
476+
stop(gettextf("'%s' must be a character string", "type"), domain = NA)
477477
if(is.null(lib.loc))
478478
lib.loc <- .libPaths()
479479
if(!missing(instPkgs)) {
@@ -525,7 +525,7 @@ new.packages <- function(lib.loc = NULL, repos = getOption("repos"),
525525
..., type = getOption("pkgType"))
526526
{
527527
if (!is.character(type))
528-
stop("invalid 'type'; must be a character string")
528+
stop(gettextf("'%s' must be a character string", "type"), domain = NA)
529529
ask # just a check that it is valid before we start work
530530
if(type == "both" && (!missing(contriburl) || !is.null(available))) {
531531
stop("specifying 'contriburl' or 'available' requires a single type, not type = \"both\"")
@@ -738,7 +738,7 @@ download.packages <- function(pkgs, destdir, available = NULL,
738738
method, type = getOption("pkgType"), ...)
739739
{
740740
if (!is.character(type))
741-
stop("invalid 'type'; must be a character string")
741+
stop(gettextf("'%s' must be a character string", "type"), domain = NA)
742742
nonlocalcran <- !all(startsWith(contriburl, "file:"))
743743
if(nonlocalcran && !dir.exists(destdir))
744744
stop("'destdir' is not a directory")
@@ -858,7 +858,7 @@ resolvePkgType <- function(type) {
858858
contrib.url <- function(repos, type = getOption("pkgType"))
859859
{
860860
if (!is.character(type))
861-
stop("invalid 'type'; must be a character string")
861+
stop(gettextf("'%s' must be a character string", "type"), domain = NA)
862862
type <- resolvePkgType(type)
863863
if(is.null(repos)) return(NULL)
864864
if(!length(repos)) return(character())

0 commit comments

Comments
 (0)