7 | Description: An interface to embeded R in IBM SPSS CF based application
8 | License: GPL-2
--------------------------------------------------------------------------------
/src/NAMESPACE:
--------------------------------------------------------------------------------
1 | useDynLib(ibmspsscf83)
2 |
3 | export(
4 | ibmspsscfpkg.preaction,
5 | ibmspsscfpkg.postaction,
6 | ibmspsscfpkg.startprocedure,
7 | ibmspsscfpkg.stopprocedure,
8 | ibmspsscfoutput.SetHTMLWithAllGraphs,
9 | ibmspsscfoutput.SinkOn,
10 | ibmspsscfoutput.SinkOff,
11 | ibmspsscfoutput.GetModel,
12 | ibmspsscfoutput.SetModel,
13 | ibmspsscfdatamodel.GetDataModel,
14 | ibmspsscfdatamodel.SetDataModel,
15 | ibmspsscfdata.GetData,
16 | ibmspsscfdata.GetDataFromTemp,
17 | ibmspsscfdata.SetDataToTemp,
18 | ibmspsscfdata.HasMoreData,
19 | ibmspsscfdata.SetData
20 | )
--------------------------------------------------------------------------------
/src/R/action.R:
--------------------------------------------------------------------------------
1 | #############################################
2 | # IBM?SPSS?Statistics - Essentials for R
3 | # (c) Copyright IBM Corp. 1989, 2012
4 | #
5 | #This program is free software; you can redistribute it and/or modify
6 | #it under the terms of the GNU General Public License version 2 as published by
7 | #the Free Software Foundation.
8 | #
9 | #This program is distributed in the hope that it will be useful,
10 | #but WITHOUT ANY WARRANTY; without even the implied warranty of
11 | #MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 | #GNU General Public License for more details.
13 | #
14 | #You should have received a copy of the GNU General Public License version 2
15 | #along with this program; if not, write to the Free Software
16 | #Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
17 | #############################################
18 |
19 | ibmspsscfpkg.startprocedure <- function()
20 | {
21 | options(hasBrowser = FALSE)
22 | .C("ext_StartProcedure", as.integer(0),PACKAGE=ibmspsscf_package)
23 | }
24 |
25 | ibmspsscfpkg.preaction <- function()
26 | {
27 | ## the output file names list
28 | ibmspsscfpkg.fileNamesList <<- list()
29 | ibmspsscfpkg.fileNamesList <<- c(ibmspsscfpkg.fileNamesList, "R_result.txt")
30 | ibmspsscfpkg.zipFileNames <<- list()
31 | ibmspsscfpkg.htmlFilesCount <<- as.integer(0)
32 |
33 | outputPath <- ibmspsscfoutput.GetOutputDir()
34 | ##set the temp workspace, put the console result and graphs in this dir
35 | ibmspsscfpkg.oldwd <<- getwd()
36 | setwd(outputPath)
37 |
38 |
39 | # Stop all existing error message diversion if any.
40 | if(sink.number(type = "message") > 0)
41 | {
42 | for( i in 1:sink.number(type = "message") )
43 | {
44 | sink(type = "message")
45 | }
46 | }
47 |
48 | # Stop all existing output diversion if any.
49 | if(sink.number() > 0)
50 | {
51 | for( i in 1:sink.number() )
52 | {
53 | sink()
54 | }
55 | }
56 |
57 | ##Sys.setlocale("LC_ALL","ja_JP.utf8")
58 | ## set the locale of embedding R in Linux
59 | out <- .C("ext_GetSystemLocale", as.character(""),as.integer(0),PACKAGE=ibmspsscf_package)
60 | Sys.setlocale("LC_ALL",out[[1]])
61 |
62 | out <- .C("ext_IsDisplayTextOutput",as.integer(0),as.integer(0),PACKAGE=ibmspsscf_package)
63 | last.SpssCfError <<- out[[2]]
64 | if(last.SpssCfError != 0)
65 | processSpssCFError(last.SpssCfError)
66 |
67 | consoleOutputFileName <- file.path(outputPath, "R_result.txt")
68 | fp <- file(consoleOutputFileName, open="at", encoding="UTF-8")
69 | ibmspsscfpkg.connections <<- vector()
70 | ibmspsscfpkg.connections <<- c(ibmspsscfpkg.connections, fp)
71 |
72 | # move the sink text output from output.R to here
73 | if(out[[1]])
74 | {
75 | textOutputFileName <- file.path(outputPath, "TextOutput.txt")
76 | textFile <- file(textOutputFileName, open="at", encoding="UTF-8")
77 | sink(fp, append = TRUE, type = "message")
78 | sink(textFile, append = TRUE)
79 | ibmspsscfpkg.fileNamesList <<- c(ibmspsscfpkg.fileNamesList, "TextOutput.txt")
80 | ibmspsscfpkg.connections <<- c(ibmspsscfpkg.connections, textFile)
81 | } else {
82 | ##sink all output to the console output
83 | sink(fp, append = TRUE, type = "message")
84 | sink(fp, append = TRUE)
85 | }
86 | tryCatch({png(filename="Rplot%03d.png")}, error=function(ex) {warning(ex)},finally= {})
87 | }
88 |
89 | ibmspsscfpkg.postaction <- function()
90 | {
91 | tryCatch(
92 | {
93 | if(sink.number(type = "message") > 0)
94 | {
95 | for( i in 1:sink.number(type = "message") )
96 | {
97 | sink(type = "message")
98 | }
99 | }
100 | # Stop all existing output diversion if any.
101 | if(sink.number() > 0)
102 | {
103 | for( i in 1:sink.number() )
104 | {
105 | sink()
106 | }
107 | }
108 |
109 | if(length(ibmspsscfpkg.zipFileNames) > 0)
110 | {
111 | zip("HTMLOutput", as.character(ibmspsscfpkg.zipFileNames))
112 | ibmspsscfpkg.fileNamesList <<- c(ibmspsscfpkg.fileNamesList, "HTMLOutput.zip")
113 | }
114 | else
115 | {
116 | ## if there is ibmspsscfpkg.zipFileNames, the dev.off has been called in SetHTMLWithAllGraphs
117 | tryCatch({dev.off()}, error=function(ex) {},finally= {})
118 | }
119 |
120 | # Close all open connections
121 | for( i in ibmspsscfpkg.connections)
122 | {
123 | if(isOpen(i))
124 | {
125 | close(getConnection(i))
126 | }
127 | }
128 | },
129 | error=function(ex) {
130 | ##checkoutput<-'File did not exist or invalid!'
131 | print(ex)
132 | },
133 | finally= {
134 | .C("ext_PostOutput", as.character(ibmspsscfpkg.fileNamesList),length(ibmspsscfpkg.fileNamesList),as.integer(0),PACKAGE=ibmspsscf_package)
135 | }
136 | )
137 | }
138 |
139 | ibmspsscfpkg.stopprocedure <- function()
140 | {
141 | setwd(ibmspsscfpkg.oldwd)
142 | .C("ext_StopProcedure",as.integer(0),PACKAGE=ibmspsscf_package)
143 | }
144 |
--------------------------------------------------------------------------------
/src/R/attach.R:
--------------------------------------------------------------------------------
1 | #############################################
2 | # IBM?SPSS?Statistics - Essentials for R
3 | # (c) Copyright IBM Corp. 1989, 2012
4 | #
5 | #This program is free software; you can redistribute it and/or modify
6 | #it under the terms of the GNU General Public License version 2 as published by
7 | #the Free Software Foundation.
8 | #
9 | #This program is distributed in the hope that it will be useful,
10 | #but WITHOUT ANY WARRANTY; without even the implied warranty of
11 | #MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 | #GNU General Public License for more details.
13 | #
14 | #You should have received a copy of the GNU General Public License version 2
15 | #along with this program; if not, write to the Free Software
16 | #Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
17 | #############################################
18 |
19 | ibmspsscf.errtable <- NULL
20 | ibmspsscf.generalErr <- NULL
21 | ibmspsscf.language <- NULL
22 | ibmspsscf_package <- NULL
23 | ibmspsscf_version <- NULL
24 | plugin_version <- NULL
25 | ibmspsscf.lib <- NULL
26 | ibmspsscfNamespace <- "ibmspsscf83"
27 | last.SpssCfError <- 0
28 | ## when the package is attached(via library), the hook function .onAttach is called
29 | ## before the package environment is sealed
30 | .onAttach <- function(lib, pkg)
31 | {
32 | if(bindingIsLocked("ibmspsscf_package", asNamespace(ibmspsscfNamespace)))
33 | {
34 | unlockBinding("ibmspsscf_package", asNamespace(ibmspsscfNamespace))
35 | }
36 |
37 | ## modeler version
38 | if(bindingIsLocked("ibmspsscf_version", asNamespace(ibmspsscfNamespace)))
39 | {
40 | unlockBinding("ibmspsscf_version", asNamespace(ibmspsscfNamespace))
41 | }
42 |
43 | ## plugin version, get from discription file
44 | if(bindingIsLocked("plugin_version", asNamespace(ibmspsscfNamespace)))
45 | {
46 | unlockBinding("plugin_version", asNamespace(ibmspsscfNamespace))
47 | }
48 |
49 | if(bindingIsLocked("ibmspsscf.errtable", asNamespace(ibmspsscfNamespace)))
50 | unlockBinding("ibmspsscf.errtable", asNamespace(ibmspsscfNamespace))
51 |
52 | if(bindingIsLocked("ibmspsscf.generalErr", asNamespace(ibmspsscfNamespace)))
53 | unlockBinding("ibmspsscf.generalErr", asNamespace(ibmspsscfNamespace))
54 |
55 | if(bindingIsLocked("ibmspsscf.lib", asNamespace(ibmspsscfNamespace)))
56 | {
57 | unlockBinding("ibmspsscf.lib", asNamespace(ibmspsscfNamespace))
58 | }
59 |
60 | if(bindingIsLocked("last.SpssCfError", asNamespace(ibmspsscfNamespace)))
61 | unlockBinding("last.SpssCfError", asNamespace(ibmspsscfNamespace))
62 |
63 | #if(bindingIsLocked("spss.language", asNamespace(ibmspsscfNamespace)))
64 | #{
65 | #unlockBinding("spss.language", asNamespace(ibmspsscfNamespace))
66 | #}
67 |
68 | ibmspsscf_package <<- pkg
69 | ibmspsscf.lib <<- lib
70 | plugin_version <<- getPkgVersion(lib, pkg)
71 | ibmspsscf.errtable <<- getErrTable(ibmspsscf.language,lib,pkg)
72 | ibmspsscf.generalErr <<- getGeneralErr(ibmspsscf.language,lib,pkg)
73 | ##this storages will be set in SetDataModel
74 | ##and used in SetData
75 | outputStorages <<- NULL
76 | ##ibmspsscf_version <<- readSpssVersion()
77 | ##plugin_version <<- readPkgVersion(lib, pkg)
78 | }
79 |
80 | getPkgVersion <- function(lib, pkg)
81 | {
82 | ver <- NULL
83 | pfile <- file.path(lib, pkg, "Meta", "package.rds")
84 | if(file.exists(pfile))
85 | {
86 | # Read version from package.rds file
87 | ver <- readRDS(pfile)$DESCRIPTION["Version"]
88 | }
89 | else
90 | {
91 | # Read version from DESCRIPTION file
92 | dfile <- file.path(lib, pkg, "DESCRIPTION")
93 | if(!file.exists(dfile))
94 | {
95 | stop(gettextf("There is no 'DESCRIPTION' file in '%s'",file.path(lib, pkg)))
96 | }
97 | ver <- read.dcf(dfile,"Version")[1, ]
98 | }
99 | ver
100 | }
101 |
102 | ibmspsscfpkg.GetPkgVersion <- function()
103 | {
104 | plugin_version
105 | }
--------------------------------------------------------------------------------
/src/R/convert.R:
--------------------------------------------------------------------------------
https://raw.githubusercontent.com/IBMPredictiveAnalytics/R_Essentials_Modeler/41c86d65df56f1cd10e2fad2e1ef0fbc29494fc8/src/R/convert.R
--------------------------------------------------------------------------------
/src/R/data.R:
--------------------------------------------------------------------------------
1 | #############################################
2 | # IBM?SPSS?Statistics - Essentials for R
3 | # (c) Copyright IBM Corp. 1989, 2012
4 | #
5 | #This program is free software; you can redistribute it and/or modify
6 | #it under the terms of the GNU General Public License version 2 as published by
7 | #the Free Software Foundation.
8 | #
9 | #This program is distributed in the hope that it will be useful,
10 | #but WITHOUT ANY WARRANTY; without even the implied warranty of
11 | #MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 | #GNU General Public License for more details.
13 | #
14 | #You should have received a copy of the GNU General Public License version 2
15 | #along with this program; if not, write to the Free Software
16 | #Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
17 | #############################################
18 |
19 | ## These constants represent the display formats that are supported
20 | ## for SPSS variables. Internal use only.
21 |
22 |
23 | ## format set which could be transformed into POSIXt
24 | dataFormatSet <- c("D-M-Y","M-D-Y","Y-M-D","Q-Y","W-Y","D-monthName-Y",
25 | "monthName-Y","Y-dayNo","dayName","monthName")
26 | timeFormatSetTest <- c("H-M","H-M-S","M-S")
27 |
28 | ibmspsscfdata.GetData <- function(fields=NULL,
29 | rowCount=NULL,
30 | missingValue = NA,
31 | factorMode = "levels",
32 | rDate = "None",
33 | logicalFields=FALSE)
34 |
35 | {
36 | spssError.reset()
37 | err <- 0
38 | fields <- unlist(fields)
39 | if(is.null(fields))
40 | {
41 | fieldCount <- ibmspsscfdatamodel.GetFieldCount()
42 | if(fieldCount > 0)
43 | {
44 | fields <- 0:(fieldCount-1)
45 | }
46 | else
47 | {
48 | return(NULL)
49 | }
50 | }
51 | else if(is.character(fields))
52 | {
53 | ## need to look
54 | fields <- ibmspsscfpkg.ParseFieldNames(fields)
55 | }
56 |
57 | if(length(fields) == 0)
58 | {
59 | return(NULL)
60 | }
61 |
62 | if(rDate != "None" && rDate != "POSIXct" && rDate != "POSIXlt")
63 | {
64 | last.SpssCfError <<- 1009
65 | processSpssCFError(last.SpssCfError)
66 | }
67 |
68 | if(factorMode != "none" && factorMode != "labels" && factorMode != "levels")
69 | {
70 | last.SpssCfError <<- 1008
71 | processSpssCFError(last.SpssCfError)
72 | }
73 |
74 | if(is.null(rowCount) || rowCount <= 0)
75 | {
76 | rowCount <- ibmspsscfdata.GetRecordCount()
77 | }
78 |
79 | missSign <- ibmspsscfdata.CheckMissArgument(missingValue)
80 | out <- .Call("ext_GetData",as.list(fields),as.integer(rowCount),
81 | as.integer(missSign),
82 | as.integer(err),
83 | PACKAGE=ibmspsscf_package)
84 |
85 | n <- length(out)
86 | last.SpssCfError <<- out[[n]]
87 | if(last.SpssCfError !=0)
88 | {
89 | processSpssCFError(last.SpssCfError)
90 | }
91 |
92 | result <- out[1:(n-1)]
93 | rm(out)
94 | n <- length(result)
95 |
96 | fieldFormatTypes <- modelerDataModel[5,]
97 | fieldStorages <- modelerDataModel[3,]
98 | fieldMeasure <- modelerDataModel[4,]
99 | fieldNames <- modelerDataModel[1,]
100 |
101 | ## transform spss datetime into POSIXct which is supported by R
102 | if(rDate != "None")
103 | {
104 | dateFields <- 1:length(fields)
105 |
106 | for(i in dateFields)
107 | {
108 | if(fieldStorages[i]== "date" || fieldStorages[i]== "timestamp" )
109 | {
110 | ## the date in CF is days since Jan 1st 1970
111 | ## the datetime in CF seconds since midnight Jan 1st 1970
112 | ## this code is to convert days to seconds
113 | if(fieldStorages[i] != "timestamp")
114 | {
115 | result[[i]] <- result[[i]]*(24*60*60)
116 | }
117 |
118 | if(rDate == "POSIXct")
119 | {
120 | result[[i]] <- as.POSIXct(result[[i]],origin="1970-01-01 00:00:00", tz="GMT")
121 | }
122 | else if(rDate == "POSIXlt")
123 | {
124 | result[[i]] <- as.POSIXlt(result[[i]],origin="1970-01-01 00:00:00", tz="GMT")
125 | }
126 | }
127 | }
128 | }
129 |
130 | if(factorMode != "none")
131 | {
132 | j<-1
133 | for(i in fields)
134 | {
135 | if("nominal" == fieldMeasure[[j]]
136 | || "discrete" == fieldMeasure[[j]]
137 | || (logicalFields == FALSE && "flag" == fieldMeasure[[j]] && "string"==fieldStorages[[j]]))
138 | {
139 | if(factorMode == "labels")
140 | {
141 | valueLabels <- ibmspsscfdatamodel.GetValueLabels(i)
142 | if(length(valueLabels$values) == 0)
143 | {
144 | result[[j]] <- factor(result[[j]], ordered = FALSE)
145 | }
146 | else
147 | {
148 | result[[j]] <- factor(result[[j]],levels = valueLabels$values, labels = valueLabels$labels, ordered = FALSE)
149 | }
150 | }
151 | else if(factorMode == "levels")
152 | {
153 | # let it has the same behaviour of read.table
154 | result[[j]] <- factor(result[[j]], ordered = FALSE)
155 | }
156 | }
157 | if("ordinal" == fieldMeasure[[j]])
158 | {
159 | valueLabels <- ibmspsscfdatamodel.GetValueLabels(i)
160 | if(factorMode == "labels")
161 | {
162 | if(length(valueLabels$values) == 0) {
163 | result[[j]] <- factor(result[[j]], ordered=TRUE)
164 | }
165 | else {
166 | result[[j]] <- factor(result[[j]],levels = valueLabels$values, labels= valueLabels$labels, ordered=TRUE)
167 | }
168 | }
169 | else if(factorMode == "levels")
170 | {
171 | if(length(valueLabels$values) == 0)
172 | {
173 | result[[j]] <- factor(result[[j]], ordered=TRUE)
174 | }
175 | else
176 | {
177 | result[[j]] <- factor(result[[j]],levels = valueLabels$values, ordered=TRUE)
178 | }
179 | }
180 | }
181 | j<-j+1
182 | }
183 | }
184 |
185 | ## process converting flag fields to logical fields
186 | if(logicalFields == TRUE)
187 | {
188 | j<-1
189 | for(i in fields)
190 | {
191 | if("flag" == fieldMeasure[[j]])
192 | {
193 | ## flagValues[1] is true value, flagValues[2] is false value
194 | flagValues <- ibmspsscfdatamodel.GetFlagValues(i)
195 | if(length(flagValues) == 0)
196 | {
197 | last.SpssCfError <<- 1022
198 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(3), as.list(fieldNames[[j]]), as.integer(err),PACKAGE=ibmspsscf_package)
199 | stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
200 | }
201 |
202 | for(index in 1:length(result[[j]]))
203 | {
204 | if(!is.na(result[[j]][index])) {
205 | if(result[[j]][index] == flagValues[1])
206 | {
207 | result[[j]][index] <- TRUE
208 | } else if(result[[j]][index] == flagValues[2])
209 | {
210 | result[[j]][index] <- FALSE
211 | } else
212 | {
213 | result[[j]][index] <- NA
214 | }
215 | }
216 | }
217 | result[[j]] <- as.logical(result[[j]])
218 | }
219 | j <- j+1
220 | }
221 | }
222 |
223 | #this is a tricky way to work around as.data.frame
224 | #as.data.frame has a bad performance
225 | rowNum <- length(result[[1]])
226 | class(result) <- "data.frame"
227 | attr(result, "row.names") <- 1:rowNum
228 | names(result) <- fieldNames
229 |
230 | result
231 | }
232 |
233 | ibmspsscfdata.CheckMissArgument <- function(missingValue)
234 | {
235 | missSign <- 0
236 | if(is.nan(missingValue))
237 | {
238 | missSign <- 1
239 | } else if(is.na(missingValue))
240 | {
241 | missSign <- 0
242 | } else if("asis" == missingValue)
243 | {
244 | missSign <- 2
245 | } else
246 | {
247 | last.SpssCfError <<- 1010
248 | processSpssCFError(last.SpssCfError)
249 | }
250 | missSign
251 | }
252 |
253 |
254 | # this function is to solve batch issue, it uses read.table to get data
255 | # from temp data file created by R component
256 | ibmspsscfdata.GetDataFromTemp <- function(missingValue = NA,
257 | factorMode = "levels",
258 | rDate = "None",
259 | logicalFields=FALSE)
260 | {
261 | spssError.reset()
262 | ## 1. Convert missing values
263 | ## check argument: missingValue
264 | missSign <- ibmspsscfdata.CheckMissArgument(missingValue)
265 |
266 | out <- .C("ext_GetTempDataFile",as.character(""),as.integer(missSign),as.integer(0),PACKAGE=ibmspsscf_package)
267 | dataFileName <- out[[1]]
268 |
269 | ## need to give colClasses, it will treat "F" as logical by default
270 | fieldStorages <- modelerDataModel[3,]
271 | colClassesVec <- vector(mode="character")
272 | for(i in fieldStorages)
273 | {
274 | if("string" == i)
275 | {
276 | colClassesVec <- c(colClassesVec, "factor")
277 | } else if("integer" == i)
278 | {
279 | colClassesVec <- c(colClassesVec, "integer")
280 | } else
281 | {
282 | colClassesVec <- c(colClassesVec, "numeric")
283 | }
284 | }
285 | dataFromTempFile <- read.table(dataFileName, header=TRUE, sep=" ",colClasses=colClassesVec,fileEncoding="UTF-8")
286 | unlink(dataFileName)
287 |
288 |
289 | ## 2. Convert flag fields
290 | ## process converting flag fields to logical fields
291 | fieldMeasure <- modelerDataModel[4,]
292 | fieldNames <- modelerDataModel[1,]
293 | fieldCount <- ibmspsscfdatamodel.GetFieldCount()
294 | fields <- 0:(fieldCount-1)
295 | if(logicalFields == TRUE)
296 | {
297 | j<-1
298 | for(i in fields)
299 | {
300 | if("flag" == fieldMeasure[[j]])
301 | {
302 | ## flagValues[1] is true value, flagValues[2] is false value
303 | flagValues <- ibmspsscfdatamodel.GetFlagValues(i)
304 | if(length(flagValues) == 0)
305 | {
306 | last.SpssCfError <<- 1022
307 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(3), as.list(fieldNames[[j]]), as.integer(0),PACKAGE=ibmspsscf_package)
308 | stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
309 | }
310 |
311 | ## need to convert character firstly, factor will have value check
312 | dataFromTempFile[[j]] <- as.character(dataFromTempFile[[j]])
313 | for(index in 1:length(dataFromTempFile[[j]]))
314 | {
315 | if(!is.na(dataFromTempFile[[j]][index])) {
316 | if(dataFromTempFile[[j]][index] == flagValues[1])
317 | {
318 | dataFromTempFile[[j]][index] <- TRUE
319 | } else if(dataFromTempFile[[j]][index] == flagValues[2])
320 | {
321 | dataFromTempFile[[j]][index] <- FALSE
322 | } else
323 | {
324 | dataFromTempFile[[j]][index] <- NA
325 | }
326 | }
327 | }
328 | dataFromTempFile[[j]] <- as.logical(dataFromTempFile[[j]])
329 | }
330 | j <- j+1
331 | }
332 | }
333 |
334 | ## 3. Convert date/time fields
335 | fieldStorages <- modelerDataModel[3,]
336 | if(rDate != "None")
337 | {
338 | dateFields <- 1:length(fields)
339 | for(i in dateFields)
340 | {
341 | if(fieldStorages[i]== "date" || fieldStorages[i]== "timestamp" )
342 | {
343 | ## the date in CF is days since Jan 1st 1970
344 | ## the datetime in CF seconds since midnight Jan 1st 1970
345 | ## this code is to convert days to seconds
346 | if(fieldStorages[i] != "timestamp")
347 | {
348 | dataFromTempFile[[i]] <- dataFromTempFile[[i]]*(24*60*60)
349 | }
350 | if(rDate == "POSIXct")
351 | {
352 | dataFromTempFile[[i]] <- as.POSIXct(dataFromTempFile[[i]],origin="1970-01-01 00:00:00", tz="GMT")
353 | }
354 | else if(rDate == "POSIXlt")
355 | {
356 | dataFromTempFile[[i]] <- as.POSIXlt(dataFromTempFile[[i]],origin="1970-01-01 00:00:00", tz="GMT")
357 | }
358 | }
359 | }
360 | }
361 |
362 |
363 | ## 4. Convert factor
364 | ## now in this package, it just supports factorMode == "levels" and
365 | ## it means factor levels are values of the fields
366 | if(factorMode != "none")
367 | {
368 | j<-1
369 | for(i in fields)
370 | {
371 | # only convert storage is not string, string has been converted in read.table
372 | if("string" != fieldStorages[[j]] && ("nominal" == fieldMeasure[[j]]
373 | || "discrete" == fieldMeasure[[j]]))
374 | {
375 | if(factorMode == "levels")
376 | {
377 | dataFromTempFile[[j]] <- factor(dataFromTempFile[[j]], ordered=FALSE)
378 | }
379 | }
380 |
381 | if("ordinal" == fieldMeasure[[j]])
382 | {
383 | valueLabels <- ibmspsscfdatamodel.GetValueLabels(i)
384 | if(factorMode == "levels")
385 | {
386 | if(length(valueLabels$values) == 0)
387 | {
388 | dataFromTempFile[[j]] <- factor(dataFromTempFile[[j]], ordered=TRUE)
389 | }
390 | else
391 | {
392 | dataFromTempFile[[j]] <- factor(dataFromTempFile[[j]],levels = valueLabels$values, ordered=TRUE)
393 | }
394 | }
395 | }
396 | j<-j+1
397 | }
398 | }
399 |
400 | dataFromTempFile
401 | }
402 |
403 | ibmspsscfdata.GetRecordCount <- function()
404 | {
405 | err <- 0
406 | out <- .C("ext_GetRecordCount",as.integer(0), as.integer(err),PACKAGE=ibmspsscf_package)
407 | last.SpssCfError <<- out[[2]]
408 | if(last.SpssCfError !=0)
409 | processSpssCFError(last.SpssCfError)
410 |
411 | records <- out[[1]]
412 | records
413 | }
414 |
415 | ibmspsscfdata.HasMoreData <- function()
416 | {
417 | err <- 0
418 | out <- .C("ext_HasMoreData",as.logical(0), as.integer(err),PACKAGE=ibmspsscf_package)
419 |
420 | last.SpssCfError <<- out[[2]]
421 | if(last.SpssCfError !=0)
422 | processSpssCFError(last.SpssCfError)
423 |
424 | hasMoreData <- out[[1]]
425 | hasMoreData
426 | }
427 |
428 | ibmspsscfdata.SetDataToTemp <- function(x)
429 | {
430 | ibmspsscfdata.DataModelCheck(x)
431 | fieldStorages <- outputStorages
432 | fieldNums <- ncol(x)
433 |
434 | for(i in 1:fieldNums)
435 | {
436 | fieldStorage <- fieldStorages[[i]]
437 | if("POSIXt"%in%class(x[[i]]))
438 | {
439 | x[[i]]<-as.double(difftime(as.POSIXct(x[[i]]),as.POSIXct(0,origin="1970-01-01 00:00:00",tz="GMT"),units = "secs"))
440 | if("date" == fieldStorage)
441 | {
442 | ## convert seconds to days
443 | x[[i]] <- x[[i]]/((24*60*60))
444 | }
445 | }
446 |
447 | # check if the variable is a list type
448 | # if a list, report a warning to cf R component
449 | if(is.list(x[[i]])) {
450 | last.SpssCfError <<- 1014
451 | fieldNames <- names(x)
452 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(4), as.list(fieldNames[i]), as.integer(err),PACKAGE=ibmspsscf_package)
453 | #stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
454 | }
455 |
456 | # factor and with numeric storage needs convert
457 | if("string" != fieldStorage) {
458 | if(is.factor(x[[i]])) {
459 | x[[i]] <- sapply(x[[i]], as.character)
460 | if("integer" == fieldStorage) {
461 | x[[i]] <- sapply(x[[i]],as.integer)
462 | } else {
463 | x[[i]] <- sapply(x[[i]],as.double)
464 | }
465 | }
466 | }
467 |
468 | if("string" == fieldStorage) {
469 | if(is.factor(x[[i]]) || is.character(x[[i]])) {
470 | # do not need to convert
471 | } else {
472 | x[[i]] <- sapply(x[[i]],as.character)
473 | }
474 | }
475 | else if("integer" == fieldStorage && !is.integer(x[[i]])) {
476 | x[[i]] <- sapply(x[[i]],as.integer)
477 | } else if(!is.numeric(x[[i]])){
478 | x[[i]] <- sapply(x[[i]],as.double)
479 | }
480 |
481 | }
482 |
483 | outputPath <- ibmspsscfoutput.GetOutputDir()
484 | temp <- paste("r_to_modeler", Sys.getpid(), sep="_")
485 | dataFileName <- file.path(outputPath, temp)
486 | write.table(x, file=dataFileName, col.names = FALSE, row.names = FALSE, qmethod ="double", fileEncoding ="UTF-8")
487 | out <- .C("ext_SetDataToTemp",as.character(dataFileName),as.integer(0),PACKAGE=ibmspsscf_package)
488 | }
489 |
490 | ibmspsscfdata.DataModelCheck <- function(x)
491 | {
492 | ## the outputDataModel get in ibmspsscfdatamodel.SetDataModel
493 | if(is.null(outputStorages))
494 | {
495 | last.SpssCfError <<- 1011
496 | if(is.SpssCfError(last.SpssCfError))
497 | {
498 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(3), as.list(""), as.integer(0),PACKAGE=ibmspsscf_package)
499 | stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
500 | }
501 | } else if(0 == length(outputStorages))
502 | {
503 | return(NULL)
504 | }
505 |
506 | ## check the length of modelerData and outputStorages
507 | if(ncol(modelerData) != length(outputStorages))
508 | {
509 | last.SpssCfError <<- 1012
510 | if(is.SpssCfError(last.SpssCfError))
511 | {
512 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(3), as.list(""), as.integer(0),PACKAGE=ibmspsscf_package)
513 | stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
514 | }
515 | }
516 | }
517 |
518 | ibmspsscfdata.SetData <- function(x)
519 | {
520 | ##spssError.reset()
521 | ##if( !getOption("is.dataStepRunning") )
522 | ##{
523 | ## last.SpssError <<- 1009
524 | ## if( is.SpssError(last.SpssError))
525 | ## stop(printSpssError(last.SpssError),call. = FALSE, domain = NA)
526 | ##}
527 | err <- 0
528 | x <- data.frame(x)
529 | x <- as.list(x)
530 |
531 | ibmspsscfdata.DataModelCheck(x)
532 | fieldStorages <- outputStorages
533 | fieldNums <- length(x)
534 | for(i in 1:fieldNums)
535 | {
536 | fieldStorage <- fieldStorages[[i]]
537 | if("POSIXt"%in%class(x[[i]]))
538 | {
539 | x[[i]]<-as.double(difftime(as.POSIXct(x[[i]]),as.POSIXct(0,origin="1970-01-01 00:00:00",tz="GMT"),units = "secs"))
540 | if("date" == fieldStorage)
541 | {
542 | ## convert seconds to days
543 | x[[i]] <- x[[i]]/((24*60*60))
544 | }
545 | }
546 |
547 | # check if the variable is a list type
548 | # if a list, report a warning to cf R component
549 | if(is.list(x[[i]])) {
550 | last.SpssCfError <<- 1014
551 | fieldNames <- names(x)
552 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(4), as.list(fieldNames[i]), as.integer(err),PACKAGE=ibmspsscf_package)
553 | #stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
554 | }
555 |
556 | x[[i]] <- unlist(x[[i]])
557 | x[[i]] <- as.vector(x[[i]])
558 |
559 | if( "string" == fieldStorage) {
560 | x[[i]] <- sapply(x[[i]],as.character)
561 | }
562 | else if("integer" == fieldStorage) {
563 | x[[i]] <- sapply(x[[i]],as.integer)
564 | } else {
565 | x[[i]] <- sapply(x[[i]],as.double)
566 | }
567 |
568 | }
569 |
570 | for(i in 1:fieldNums)
571 | x[i] <- UnicodeConverterInput(x[i])
572 |
573 | out <- .Call("ext_SetData",x,as.list(fieldStorages),as.integer(err),PACKAGE=ibmspsscf_package)
574 | ##last.SpssError <<- out[1]
575 | ##if( is.SpssError(last.SpssError))
576 | ## stop(printSpssError(last.SpssError),call. = FALSE, domain = NA)
577 | }
578 |
--------------------------------------------------------------------------------
/src/R/datamodel.R:
--------------------------------------------------------------------------------
1 | #############################################
2 | # IBM?SPSS?Statistics - Essentials for R
3 | # (c) Copyright IBM Corp. 1989, 2012
4 | #
5 | #This program is free software; you can redistribute it and/or modify
6 | #it under the terms of the GNU General Public License version 2 as published by
7 | #the Free Software Foundation.
8 | #
9 | #This program is distributed in the hope that it will be useful,
10 | #but WITHOUT ANY WARRANTY; without even the implied warranty of
11 | #MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 | #GNU General Public License for more details.
13 | #
14 | #You should have received a copy of the GNU General Public License version 2
15 | #along with this program; if not, write to the Free Software
16 | #Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
17 | #############################################
18 |
19 | baseInfo <- c("fieldName","fieldLabel","fieldStorage","fieldMeasure","fieldFormat","fieldRole")
20 |
21 | checkBaseInfo <- function(x)
22 | {
23 | check <- TRUE
24 | if(is.data.frame(x))
25 | {
26 | info <- row.names(x)
27 | if( !is.null(info) && 6 == length(info) )
28 | check <- any(info != baseInfo)
29 | }
30 | !check
31 | }
32 |
33 | ibmspsscfdatamodel.GetDataModel <- function(fields=NULL)
34 | {
35 | err <- 0
36 | if( is.null(fields) )
37 | {
38 | fieldNum <- ibmspsscfdatamodel.GetFieldCount()
39 | if(fieldNum > 0)
40 | {
41 | fields <- 0:(fieldNum-1)
42 | }
43 | else
44 | {
45 | return(NULL)
46 | }
47 | }
48 | ##else if( is.character(variables) )
49 | ## variables <- ParseVarNames(variables)
50 |
51 | if(length(fields)==0)
52 | {
53 | return(NULL)
54 | }
55 | ## get field names
56 | out <- .Call("ext_GetFieldNames",as.list(fields),as.integer(err),
57 | PACKAGE=ibmspsscf_package)
58 | n <- length(out)
59 | last.SpssCfError <<- out[n]
60 | if(last.SpssCfError !=0)
61 | processSpssCFError(last.SpssCfError)
62 | ##varName <- unicodeConverterOutput(out[1:n-1])
63 | fieldName <- out[1:n-1]
64 |
65 |
66 | ## get field name label
67 | out <- .Call("ext_GetFieldLabels",as.list(fields),as.integer(err),
68 | PACKAGE=ibmspsscf_package)
69 | n <- length(out)
70 | last.SpssCfError <<- out[n]
71 | if(last.SpssCfError !=0)
72 | processSpssCFError(last.SpssCfError)
73 | fieldLabel <- out[1:n-1]
74 |
75 | ## get field storage
76 | out <- .Call("ext_GetFieldStorages",as.list(fields),as.integer(err),
77 | PACKAGE=ibmspsscf_package)
78 | n <- length(out)
79 | last.SpssCfError <<- out[n]
80 | if(last.SpssCfError !=0)
81 | processSpssCFError(last.SpssCfError)
82 | fieldStorage <- out[1:n-1]
83 |
84 |
85 | ## get field measure
86 | out <- .Call("ext_GetFieldMeasures",as.list(fields),as.integer(err),
87 | PACKAGE=ibmspsscf_package)
88 | n <- length(out)
89 | last.SpssCfError <<- out[n]
90 | if(last.SpssCfError !=0)
91 | processSpssCFError(last.SpssCfError)
92 | fieldMeasure <- out[1:n-1]
93 | ## get field format
94 | out <- .Call("ext_GetFieldFormats",as.list(fields),as.integer(err),
95 | PACKAGE=ibmspsscf_package)
96 | n <- length(out)
97 | last.SpssCfError <<- out[n]
98 | if(last.SpssCfError !=0)
99 | processSpssCFError(last.SpssCfError)
100 | fieldFormat <- out[1:n-1]
101 |
102 | out <- .Call("ext_GetFieldRoles",as.list(fields),as.integer(err),
103 | PACKAGE=ibmspsscf_package)
104 | n <- length(out)
105 | last.SpssCfError <<- out[n]
106 | if(last.SpssCfError !=0)
107 | processSpssCFError(last.SpssCfError)
108 | fieldRole <- out[1:n-1]
109 |
110 | fields <- rbind(fieldName,fieldLabel,fieldStorage,fieldMeasure,fieldFormat,fieldRole)
111 | value <- data.frame(fields,stringsAsFactors=FALSE)
112 | value
113 | }
114 |
115 | ibmspsscfdatamodel.GetFieldCount <- function()
116 | {
117 | err <- 0
118 | out <- .C("ext_GetFieldCount",as.integer(0), as.integer(err),PACKAGE=ibmspsscf_package)
119 | last.SpssCfError <<- out[[2]]
120 | if(last.SpssCfError)
121 | processSpssCFError(last.SpssCfError)
122 |
123 | columns <- out[[1]]
124 | columns
125 | }
126 |
127 | ## the parameter field should be a numeric
128 | GetFieldName <- function(field)
129 | {
130 | ##spssError.reset()
131 | if(!is.numeric(field))
132 | {
133 | last.SpssCfError <<- 1017
134 | processSpssCFError(last.SpssCfError)
135 | }
136 | fieldIndex <- field
137 |
138 | err <- 0
139 | out <- .C("ext_GetFieldName",as.character(""), as.integer(fieldIndex),as.integer(err),PACKAGE=ibmspsscf_package)
140 |
141 | last.SpssCfError <<- out[[3]]
142 | if(last.SpssCfError)
143 | processSpssCFError(last.SpssCfError)
144 |
145 | fieldName <- out[[1]]
146 | ##varName <- unicodeConverterOutput(varName)
147 | fieldName
148 | }
149 |
150 | GetFieldStorage <- function(field)
151 | {
152 | ##spssError.reset()
153 | fieldIndex <- GetFieldIndex(field)
154 |
155 | err <- 0
156 | out <- .C("ext_GetFieldStorage",as.character(""), as.integer(fieldIndex),as.integer(err),PACKAGE=ibmspsscf_package)
157 |
158 | last.SpssCfError <<- out[[3]]
159 | if(last.SpssCfError)
160 | processSpssCFError(last.SpssCfError)
161 |
162 | fieldStorage <- out[[1]]
163 | fieldStorage
164 | }
165 |
166 | GetFieldIndex <- function(field)
167 | {
168 | ##oldwarn = getOption("warn")
169 | ##options(warn = -1)
170 | try(temp <- as.integer(field),TRUE)
171 | ##options(warn = oldwarn)
172 | if(is.na(temp))
173 | {
174 | temp <- field
175 | }
176 |
177 | field <- temp
178 | result <- NULL
179 | if(is.numeric(field))
180 | {
181 | result <- field
182 | }
183 | else
184 | {
185 | fieldNum <- ibmspsscfdatamodel.GetFieldCount()
186 | for(i in 0:(fieldNum-1))
187 | {
188 | fieldName <- GetFieldName(i)
189 | if(nchar(fieldName) == nchar(field) && !is.na(charmatch(fieldName,field)))
190 | {
191 | result <- i
192 | break
193 | }
194 | }
195 | }
196 | if( is.null(result))
197 | {
198 | ## can not match the parameter field with field names in data
199 | last.SpssCfError <<- 1020
200 | processSpssCFError(last.SpssCfError)
201 | }
202 | result
203 | }
204 |
205 | ibmspsscfdatamodel.GetValueLabels <- function(field)
206 | {
207 | ##spssError.reset()
208 | field <- GetFieldIndex(field)
209 | fieldIndex <- field
210 |
211 | err <- 0
212 | out <- NULL
213 | fieldStorage <- GetFieldStorage(fieldIndex)
214 | out <- .Call("ext_GetValueLabels",as.integer(fieldIndex),as.integer(err),PACKAGE=ibmspsscf_package)
215 |
216 | last.SpssCfError <<- out[[3]][1]
217 | if(last.SpssCfError)
218 | processSpssCFError(last.SpssCfError)
219 |
220 | result <- out[1:2]
221 | names(result) <- c("values","labels")
222 |
223 | ##last.SpssCfError <<- out[[3]][1]
224 | ##if(is.SpssWarning(last.SpssCfError))
225 | ##{
226 | ##warning(gettextf("%s %d", "Warning of Field:", fieldIndex),call. = FALSE, domain = NA)
227 | ##warning(printSpssWarning(last.SpssCfError),call. = FALSE, domain = NA)
228 | ##if(getData)
229 | ##result$labels <- list()
230 | ##}
231 |
232 | if("string" != fieldStorage) {
233 | result$values <- as.numeric(result$values)
234 | } else {
235 | result$values <- result$values
236 | }
237 | result
238 | }
239 |
240 | ## this function does not finish, related with data mapping
241 | ibmspsscfdatamodel.GetMissingValues <- function(field)
242 | {
243 | ##spssError.reset()
244 | fieldIndex <- GetFieldIndex(field)
245 | ##missingType <- c("Discrete","Range","Range Discrete")
246 | err <- 0
247 | ##missingFormat <- 0
248 | value <- NULL
249 | fieldStorage <- GetFieldStorage(fieldIndex)
250 |
251 | out <- .Call("ext_GetMissingValues",as.integer(fieldIndex),
252 | as.integer(err),
253 | PACKAGE=ibmspsscf_package)
254 |
255 | last.SpssCfError <<- out[[2]][1]
256 | if(last.SpssCfError)
257 | processSpssCFError(last.SpssCfError)
258 |
259 |
260 | if("string" == fieldStorage)
261 | {
262 | value <- out[[1]]
263 | } else if("integer" == fieldStorage){
264 | value <- as.integer(out[[1]])
265 | } else {
266 | value <- as.double(out[[1]])
267 | }
268 | value
269 | }
270 |
271 | ibmspsscfdatamodel.GetFlagValues <- function(field)
272 | {
273 | ##spssError.reset()
274 | fieldIndex <- GetFieldIndex(field)
275 | err <- 0
276 | value <- NULL
277 | fieldStorage <- GetFieldStorage(fieldIndex)
278 |
279 | out <- .Call("ext_GetFlagValues",as.integer(fieldIndex),
280 | as.integer(err),
281 | PACKAGE=ibmspsscf_package)
282 |
283 | last.SpssCfError <<- out[[2]][1]
284 | if(last.SpssCfError)
285 | processSpssCFError(last.SpssCfError)
286 |
287 | if("string" == fieldStorage)
288 | {
289 | value <- out[[1]]
290 | } else if("integer" == fieldStorage){
291 | value <- as.integer(out[[1]])
292 | } else {
293 | value <- as.double(out[[1]])
294 | }
295 | value
296 | }
297 |
298 | ibmspsscfdatamodel.SetDataModel <- function(dataModel)
299 | {
300 | ##spssError.reset()
301 | outputStorages <<- vector()
302 | err <- 0
303 | if(!checkBaseInfo(dataModel) )
304 | {
305 | last.SpssCfError <<- 1001
306 | if(is.SpssCfError(last.SpssCfError))
307 | {
308 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(3), as.list(""), as.integer(err),PACKAGE=ibmspsscf_package)
309 | stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
310 | }
311 | }
312 |
313 |
314 | fieldName <- vector()
315 | fieldLabel <- vector()
316 | fieldStorage <- vector()
317 | fieldMeasure <- vector()
318 | fieldFormat <- vector()
319 | fieldRole <- vector()
320 | fieldNums <- length(dataModel)
321 |
322 | for(i in 1:fieldNums)
323 | {
324 | fieldName <- c(fieldName, UnicodeConverterInput(as.character(dataModel[1, i])))
325 | fieldLabel <- c(fieldLabel, UnicodeConverterInput(as.character(dataModel[2, i])))
326 |
327 | ##check the storage
328 | if(dataModel[3, i] == "string" || dataModel[3, i] == "integer" || dataModel[3, i] == "real"
329 | || dataModel[3, i] == "date" || dataModel[3, i] == "time" || dataModel[3, i] == "timestamp")
330 | {}
331 | else
332 | {
333 | last.SpssCfError <<- 1004
334 | if(is.SpssCfError(last.SpssCfError))
335 | {
336 | invalidStorage <- as.character(dataModel[3, i])
337 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(3), as.list(invalidStorage), as.integer(err),PACKAGE=ibmspsscf_package)
338 | stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
339 | }
340 | }
341 | fieldStorage <- c(fieldStorage, as.character(dataModel[3, i]))
342 |
343 | ##check the measure
344 | if(dataModel[4, i] =="" || dataModel[4, i] == "continuous" || dataModel[4, i] == "discrete"
345 | || dataModel[4, i] == "flag"|| dataModel[4, i] == "nominal" || dataModel[4, i] == "ordinal"
346 | || dataModel[4, i] == "typeless" || dataModel[4, i] == "unknown")
347 | {}
348 | else
349 | {
350 | last.SpssCfError <<- 1005
351 | if(is.SpssCfError(last.SpssCfError))
352 | {
353 | invalidMeasure <- as.character(dataModel[4, i])
354 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(3), as.list(invalidMeasure), as.integer(err),PACKAGE=ibmspsscf_package)
355 | stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
356 | }
357 | }
358 | fieldMeasure <- c(fieldMeasure, as.character(dataModel[4, i]))
359 | fieldFormat <- c(fieldFormat, as.character(dataModel[5, i]))
360 |
361 | ##check the role
362 | dataModelRole <- dataModel[6, i]
363 | if(dataModelRole =="" || dataModelRole == "input" ||dataModelRole == "target"
364 | || dataModelRole == "both"|| dataModelRole == "partition" || dataModelRole == "split"
365 | || dataModelRole == "freqWeight" || dataModelRole == "recordId" || dataModelRole == "none")
366 | {}
367 | else
368 | {
369 | last.SpssCfError <<- 1007
370 | if(is.SpssCfError(last.SpssCfError))
371 | {
372 | invalidRole <- as.character(dataModelRole)
373 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(3), as.list(invalidRole), as.integer(err),PACKAGE=ibmspsscf_package)
374 | stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
375 | }
376 | }
377 | fieldRole <- c(fieldRole, as.character(dataModel[6, i]))
378 | }
379 |
380 | ##check if fieldNames have duplicated
381 | if(0 != anyDuplicated(fieldName))
382 | {
383 | last.SpssCfError <<- 1002
384 | if(is.SpssCfError(last.SpssCfError))
385 | {
386 | duplicatedFieldName <- fieldName[anyDuplicated(fieldName)]
387 | .Call("ext_SendErrorCode",as.integer(last.SpssCfError), as.integer(3), as.list(duplicatedFieldName), as.integer(err),PACKAGE=ibmspsscf_package)
388 | stop(printSpssError(last.SpssCfError),call. = FALSE, domain = NA)
389 | }
390 | }
391 |
392 |
393 | fields <- rbind(fieldName,fieldLabel,fieldStorage,fieldMeasure,fieldFormat,fieldRole)
394 | value <- data.frame(fields,stringsAsFactors=FALSE)
395 |
396 | out <- .Call("ext_SetDataModel", value, as.integer(err), PACKAGE=ibmspsscf_package)
397 | outputStorages <<- fieldStorage
398 | }
399 |
400 | UnicodeConverterInput <- function(x)
401 | {
402 | if(is.character(x))
403 | {
404 | if(length(x)>0)
405 | {
406 | for(i in 1:length(x))
407 | {
408 | if(Encoding(x[[i]])!="UTF-8")
409 | {
410 | x[[i]] <- iconv(x[[i]],to="UTF-8")
411 | }
412 | }
413 | }
414 | }
415 | x
416 | }
417 |
418 |
--------------------------------------------------------------------------------
/src/R/error.R:
--------------------------------------------------------------------------------
https://raw.githubusercontent.com/IBMPredictiveAnalytics/R_Essentials_Modeler/41c86d65df56f1cd10e2fad2e1ef0fbc29494fc8/src/R/error.R
--------------------------------------------------------------------------------
/src/R/output.R:
--------------------------------------------------------------------------------
1 | #############################################
2 | # IBM?SPSS?Statistics - Essentials for R
3 | # (c) Copyright IBM Corp. 1989, 2012
4 | #
5 | #This program is free software; you can redistribute it and/or modify
6 | #it under the terms of the GNU General Public License version 2 as published by
7 | #the Free Software Foundation.
8 | #
9 | #This program is distributed in the hope that it will be useful,
10 | #but WITHOUT ANY WARRANTY; without even the implied warranty of
11 | #MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 | #GNU General Public License for more details.
13 | #
14 | #You should have received a copy of the GNU General Public License version 2
15 | #along with this program; if not, write to the Free Software
16 | #Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
17 | #############################################
18 |
19 | ibmspsscfoutput.GetOutputDir <- function()
20 | {
21 | out <- .C("ext_GetOutputDir",as.character(""),as.integer(0),PACKAGE=ibmspsscf_package)
22 | last.SpssCfError <<- out[[2]]
23 | if(last.SpssCfError)
24 | processSpssCFError(last.SpssCfError)
25 |
26 | dir <- out[[1]]
27 | outputPath <- file.path(dirname(dir), basename(dir), 'ROutput')
28 | if (!file.exists(outputPath))
29 | {
30 | dir.create(outputPath, showWarnings = TRUE, recursive = TRUE)
31 | }
32 | outputPath
33 | }
34 |
35 | ibmspsscfoutput.SetHTML <- function(htmlOutput, imageNames=NULL)
36 | {
37 | if(is.null(htmlOutput)) {
38 | warning("No html output provided")
39 | return
40 | }
41 | ibmspsscfpkg.htmlFilesCount <<- ibmspsscfpkg.htmlFilesCount + 1
42 | outputPath <- ibmspsscfoutput.GetOutputDir()
43 | tempFileName <- paste("Output", sprintf("%03d", ibmspsscfpkg.htmlFilesCount), ".html", sep="")
44 | fileName <- file.path(outputPath, tempFileName)
45 | if(file.exists(fileName))
46 | {
47 | warning("Existing file is overwrited")
48 | }
49 | write(htmlOutput, fileName)
50 | ibmspsscfpkg.zipFileNames <<- c(ibmspsscfpkg.zipFileNames, tempFileName)
51 | for(imageName in imageNames)
52 | {
53 | ibmspsscfpkg.zipFileNames <<- c(ibmspsscfpkg.zipFileNames, imageName)
54 | }
55 | }
56 |
57 | ibmspsscfoutput.SetHTMLWithAllGraphs <- function()
58 | {
59 | ## get all graph names
60 | tryCatch({dev.off()}, error=function(ex) {},finally= {})
61 | count <- ibmspsscfoutput.GetOutputCount()
62 | graphNames <- ibmspsscfoutput.GetOutputNames()
63 |
64 |
65 | if(is.null(graphNames)) {
66 | warning("No graph output provided")
67 | return
68 | }
69 |
70 | htmlBegin <- ""
71 | htmlEnd <- ""
72 |
73 | for(name in graphNames)
74 | {
75 | temp <- NULL
76 | temp1 <- paste("", as.character(name))
77 | temp2 <- "
"
80 | temp <- paste(temp1, temp2, temp3, temp4)
81 | htmlBegin <- paste(htmlBegin, temp)
82 | }
83 |
84 | html <- paste(htmlBegin, htmlEnd)
85 |
86 | ibmspsscfpkg.htmlFilesCount <<- ibmspsscfpkg.htmlFilesCount + 1
87 | outputPath <- ibmspsscfoutput.GetOutputDir()
88 | tempFileName <- paste("Output", sprintf("%03d", ibmspsscfpkg.htmlFilesCount), ".html", sep="")
89 | fileName <- file.path(outputPath, tempFileName)
90 | if(file.exists(fileName))
91 | {
92 | warning("Existing file is overwrited")
93 | }
94 | write(html, fileName)
95 | ibmspsscfpkg.zipFileNames <<- c(ibmspsscfpkg.zipFileNames, tempFileName)
96 | for(imageName in graphNames)
97 | {
98 | ibmspsscfpkg.zipFileNames <<- c(ibmspsscfpkg.zipFileNames, imageName)
99 | }
100 | }
101 |
102 | ibmspsscfoutput.SinkOn <- function()
103 | {
104 | outputPath <-ibmspsscfoutput.GetOutputDir()
105 | fileName <- file.path(outputPath, "TextOutput.txt")
106 | sink(fileName, FALSE, "output", FALSE)
107 | }
108 |
109 | ibmspsscfoutput.SinkOff <- function()
110 | {
111 | ibmspsscfpkg.fileNamesList <<- c(ibmspsscfpkg.fileNamesList, "TextOutput.txt")
112 | sink()
113 | }
114 |
115 | ibmspsscfoutput.SetPMML <- function(PMML, statsXML=NULL)
116 | {
117 | if(is.null(PMML))
118 | {
119 | warning("No PMML provided")
120 | return
121 | }
122 | outputPath <- ibmspsscfoutput.GetOutputDir()
123 | pmmlFileName <- file.path(outputPath, "PMML.xml")
124 | if(file.exists(pmmlFileName))
125 | {
126 | warning("Existing PMML output is overwrited")
127 | }
128 | write(PMML, pmmlFileName)
129 | ibmspsscfpkg.fileNamesList <<- c(ibmspsscfpkg.fileNamesList, "PMML.xml")
130 | if(!is.null(statsXML))
131 | {
132 | statsFileName <- file.path(outputPath, "StatsXML.xml")
133 | if(file.exists(statsFileName))
134 | {
135 | warning("Existing Statistics XML is overwrited")
136 | }
137 | write(statsXML, statsFileName)
138 | ibmspsscfpkg.fileNamesList <<- c(ibmspsscfpkg.fileNamesList, "StatsXML.xml")
139 | }
140 | }
141 |
142 | ibmspsscfoutput.GetModel <- function()
143 | {
144 | out <- .C("ext_GetModel",as.character(""),as.integer(0),PACKAGE=ibmspsscf_package)
145 | last.SpssCfError <<- out[[2]]
146 | if(last.SpssCfError)
147 | processSpssCFError(last.SpssCfError)
148 |
149 | modelFileName <- out[[1]]
150 | modelFile <- file(modelFileName, "r+")
151 | model <- unserialize(modelFile)
152 | close(modelFile)
153 | model
154 | }
155 |
156 | ibmspsscfoutput.SetModel <- function(model)
157 | {
158 | if(is.null(model))
159 | {
160 | warning("No Model provided")
161 | return
162 | }
163 | outputPath <- ibmspsscfoutput.GetOutputDir()
164 | modelFileName <- file.path(outputPath, "model")
165 | modelFile <- file(modelFileName, "w")
166 | serialize(model, modelFile)
167 | flush(modelFile)
168 | close(modelFile)
169 | ibmspsscfpkg.fileNamesList <<- c(ibmspsscfpkg.fileNamesList, "model")
170 | ##write(tempModel, modelFileName)
171 | ##.C("ext_SetModel",as.character(""),0,PACKAGE=ibmspsscf_package)
172 | }
173 |
174 | ibmspsscfoutput.GetOutputCount <- function()
175 | {
176 | outputPath <- ibmspsscfoutput.GetOutputDir()
177 | outputFiles <- list.files(outputPath, pattern = "*.png")
178 |
179 | if (length(outputFiles) == 1)
180 | {
181 | if(file.info(outputFiles[1])$size < 500 )
182 | {
183 | file.remove(outputFiles[1])
184 | return(0)
185 | }
186 | }
187 |
188 | length(outputFiles)
189 | }
190 |
191 | ibmspsscfoutput.GetOutputNames <- function(indices=NULL)
192 | {
193 | outputPath <- ibmspsscfoutput.GetOutputDir()
194 | outputFiles <- list.files(outputPath, pattern = "*.png")
195 |
196 | if(!is.null(indices))
197 | {
198 | resultFiles <- list()
199 | for(index in indices)
200 | {
201 | if(index < 1 || index > length(outputFiles))
202 | {
203 | last.SpssCfError <<- 1013
204 | processSpssCFError(last.SpssCfError)
205 | }
206 | resultFiles <- c(resultFiles, outputFiles[[index]])
207 | }
208 | resultFiles
209 | }
210 | else
211 | {
212 | outputFiles
213 | }
214 | }
215 |
--------------------------------------------------------------------------------
/src/inst/lang/de/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # Errors come from IBM SPSS Statistics backend.
9 | [ok]_0 = Kein Fehler.
10 | [ok]_1 = Kommentar.
11 | [warning]_2 = Warnung.
12 | [error]_3 = Schwerer Fehler.
13 | [error]_4 = Schwerwiegender Fehler.
14 | [error]_5 = Katastrophaler Fehler.
15 | [error]_6 = Befehlssyntaxfehler.
16 | [error]_10 = Ung\u00fcltiger Index.
17 | [error]_11 = Objekt kann XML-Arbeitsfl\u00e4che nicht hinzugef\u00fcgt werden.
18 | [error]_12 = Ung\u00fcltige Objektbehandlung.
19 | [error]_13 = XML-Arbeitsfl\u00e4chenobjekt kann nicht entfernt werden.
20 | [error]_15 = Ergebnis kann nicht abgerufen werden.
21 | [error]_16 = Ung\u00fcltiger Wert.
22 | [warning]_20 = Eine bestehende XML-Arbeitsfl\u00e4chenbehandlung wurde \u00fcberschrieben.
23 | [error]_21 = Ung\u00fcltiger XPath-Ausdruck.
24 | [error]_22 = XML-Fehler.
25 | [warning]_23 = Weitere Daten k\u00f6nnen nicht gelesen werden.
26 | [error]_24 = Ung\u00fcltiger Datentyp.
27 | [error]_25 = Mehrfach vorhandener Variablenname.
28 | [error]_26 = Ung\u00fcltiger Variablentyp.
29 | [error]_27 = Ung\u00fcltiger Variablenname.
30 | [error]_30 = Ung\u00fcltiger Fall.
31 | [error]_31 = Diese Aktion kann nicht abgeschlossen werden, solange eine Datenverbindung f\u00fcr die Verarbeitung aufgeteilter Dateien ge\u00f6ffnet ist.
32 | [error]_32 = Eine Benutzerprozedur wird ausgef\u00fchrt.
33 | [error]_34 = Ung\u00fcltiges Messniveau.
34 | [error]_36 = Ung\u00fcltiges Format von fehlenden Werten.
35 | [error]_40 = Es ist eine Prozedur-Datenquelle erforderlich.
36 | [error]_44 = Das aktive Daten-Set ist leer.
37 | [error]_47 = Ung\u00fcltiger Formattyp.
38 | [error]_48 = Ung\u00fcltige Formatbreite.
39 | [error]_49 = Ung\u00fcltiger Dezimalpunkt.
40 | [error]_54 = Im aktiven Daten-Set sind keine weiteren Daten vorhanden.
41 | [error]_56 = Es sind nur String-Variablen zul\u00e4ssig.
42 | [error]_57 = Es sind nur numerische Variablen zul\u00e4ssig.
43 | [error]_58 = Ung\u00fcltiger Attributname.
44 | [error]_59 = Der benutzerdefiniert fehlende Wert f\u00fcr eine String-Variable darf h\u00f6chstens 8 Zeichen lang sein.
45 | [error]_61 = Der Datenwert ist zu lang.
46 | [error]_62 = Die L\u00e4nge einer String-Variablen darf 32767 Byte nicht \u00fcberschreiten.
47 | [error]_64 = Datenwerte oder Variableninformationen k\u00f6nnen im Original-Daten-Set nicht ge\u00e4ndert werden.
48 | [warning]_67 = Das Ende der aktuellen Aufteilung wurde erreicht.
49 | [error]_70 = Die Bezeichnung ist zu lang.
50 | [error]_71 = Der Wert ist zu lang.
51 | [error]_82 = Die Variable befindet sich nicht im aktiven Daten-Set.
52 | [error]_86 = Zum Abschluss dieser Aktion ist eine aktive Datenquelle erforderlich.
53 | [error]_87 = Ung\u00fcltiger Daten-Set-Name.
54 | [error]_88 = Diese Methode kann nur zwischen SetDictionaryToSPSS und EndDataStep aufgerufen werden.
55 | [error]_89 = Ung\u00fcltiger Funktionsaufruf. Die Funktion kann nur bei der Daten-Set-Erstellung oder innerhalb einer Benutzerprozedur aufgerufen werden.
56 | [error]_90 = Innerhalb einer Benutzerprozedur kann kein aktives Daten-Set erstellt werden.
57 | [error]_91 = Ein Daten-Set mit dem gleichen Namen ist bereits vorhanden.
58 | [error]_92 = Diese Aktion kann nicht abgeschlossen werden, solange ein Daten-Set erstellt wird.
59 | [error]_94 = Ein Daten-Set kann bei noch ausstehenden Transformationen nicht erstellt werden.
60 | [error]_96 = Der angegebene Attributname kann nicht gefunden werden.
61 | [error]_99 = Das angegebene Daten-Set kann nicht erstellt werden.
62 | [error]_100 = Ung\u00fcltige Definition eines Mehrfach-Antworten-Sets.
63 | [error]_999999997 = Unbekannter Fehler.
64 | [error]_999999998 = Die Verarbeitung wurde vom Benutzer unterbrochen.
65 | [error]_999999999 = Unbekannter Fehler.
66 |
67 | # Errors come from R plug-in.
68 | [warning]_1000 = Es sind keine weiteren Aufteilungsgruppen vorhanden.
69 | [RError]_1001 = Eine Aufteilungsdatenverbindung ist ge\u00f6ffnet. Schlie\u00dfen Sie die Verbindung, bevor Sie eine beliebige Funktion au\u00dfer GetSplitDataFromSPSS aufrufen.
70 | [RError]_1002 = Ung\u00fcltiges IBM SPSS Statistics-W\u00f6rterbuchformat.
71 | [warning]_1003 = Ung\u00fcltige Zeilenbeschriftung. Werte sind mehrfach vorhanden.
72 | [warning]_1004 = Unbekanntes Messniveau.
73 | [RError]_1005 = Ung\u00fcltiger Vorlagenname der Pivot-Tabelle (Name muss mit einem Buchstaben beginnen und maximal 64 Byte lang sein).
74 | [RError]_1006 = Ung\u00fcltiges Format.
75 | [RError]_1007 = Ung\u00fcltiger Typ von fehlenden Werten.
76 | [RError]_1008 = Ung\u00fcltige Variable; sie muss numerisch sein.
77 | [RError]_1009 = Ung\u00fcltiger Funktionsaufruf. Die Funktion kann nur nach dem Aufruf von SetDictionaryToSPSS aufgerufen werden.
78 | [RError]_1010 = Ung\u00fcltiger Variablenname.
79 | [RError]_1011 = Argumentvariablen m\u00fcssen ein String, ein Vektor oder eine Liste sein.
80 | [RError]_1012 = Ung\u00fcltiger Typ eines Mehrfach-Antworten-Sets; es muss entweder Dichotomies oder Categories sein.
81 | [RError]_1013 = Das Argument countedValue muss angegeben werden, wenn der Typ eines Mehrfach-Antworten-Sets Dichotomies ist.
82 | [RError]_1014 = Ung\u00fcltiger Grafikname oder Pfad.
83 | [RError]_1015 = Ung\u00fcltiges Grafikformat (muss "JPG", "PNG" oder "BMP" sein).
84 | [RError]_1016 = Ung\u00fcltiger Variablenwert (muss "ON" oder "OFF" sein).
85 | [RError]_1017 = Die Form VARX TO VARY, mit der auf einen Variablenbereich verwiesen wird, wurde nicht korrekt verwendet.
86 | [RError]_1018 = Ung\u00fcltiger Wert f\u00fcr Argument factorMode (muss "none", "levels" oder "labels" sein).
87 | [RError]_1019 = Ung\u00fcltiger Wert f\u00fcr Argument rDate (muss "none", "POSIXct" oder "POSIXlt" sein).
88 | [RError]_1020 = Ung\u00fcltiger Wert f\u00fcr Argument newName (muss genauso lang sein wie das Argument categoryDictionary).
89 | [RError]_1021 = Ung\u00fcltiger Wert f\u00fcr Argument categoryDictionary.
90 | [RError]_1022 = Es wird ein numerisches Argument erwartet.
91 | [RError]_1032 = Die Zellenl\u00e4nge stimmt nicht mit der Anzahl an Kategorien der Zeilen-/Spaltendimensionen \u00fcberein.
92 | [RError]_1031 = Ung\u00fcltige Dimensionsposition.
93 | [RError]_1036 = Ung\u00fcltiger Vorlagenname der Pivot-Tabelle (Name muss mit einem Buchstaben beginnen und maximal 64 Byte lang sein).
94 | [RError]_1037 = Es wird ein spss.Dimension-Objekt erwartet.
95 | [RError]_1038 = Die Anzahl der Pivot-Tabellenkategorien stimmt nicht mit der Dimensionsgr\u00f6\u00dfe \u00fcberein.
96 | [RError]_1039 = Es wird ein CellText-Objekt erwartet.
97 | [RError]_1040 = Eine Dimension kann nicht mehr gel\u00f6scht werden, nachdem sie einer Pivot-Tabelle hinzugef\u00fcgt wurde.
98 | [RError]_1041 = Der Zellenwert muss eingestellt werden, bevor seine Fu\u00dfnoten hinzugef\u00fcgt werden.
99 | [RError]_1042 = Ung\u00fcltiger Dimensionsort.
100 | [RError]_1043 = Ung\u00fcltiger Dimensionsname.
101 | [RError]_1044 = Zelle f\u00fcr mehrere Zeilendimensionen konnte nicht gesetzt werden.
102 | [RError]_1045 = Zelle f\u00fcr mehrere Spaltendimensionen konnte nicht gesetzt werden.
103 | [RError]_1046 = Sie sollten der Pivot-Tabelle eine Dimension hinzuf\u00fcgen, bevor Sie ihr Kategorien hinzuf\u00fcgen.
104 | [RError]_1047 = Eine Kategorie kann nicht mehr gel\u00f6scht werden, nachdem sie einer Dimension hinzugef\u00fcgt wurde.
105 | [RError]_1048 = Eine Kategorie kann nicht mehr ge\u00e4ndert werden, nachdem sie einer Dimension hinzugef\u00fcgt wurde.
106 | [RError]_1049 = Ung\u00fcltiger Wert f\u00fcr Argument FormatSpec.
107 | [RError]_1050 = F\u00fcr den abgegebenen FormatSpec-Typ ist ein varIndex-Wert erforderlich.
108 | [RError]_1051 = Das Objekt CellText.VarValue erwartet einen numerischen oder einen String-Wert.
109 | [RError]_1068 = Ung\u00fcltiger Argumenttyp.
110 | [RError]_1069 = Es wird ein ganzzahliges Argument erwartet.
111 | [RError]_1070 = Es wird ein boolesches Argument erwartet.
112 | [RError]_1071 = Argumentvariablen m\u00fcssen ein String, ein Vektor oder eine Liste sein.
113 | [RError]_1072 = Ung\u00fcltiger Objekttyp (muss "BasePivotTable", "spss.Dimension", "CellText.Number", "CellText.String", "CellText.VarName" oder "CellText.VarValue" sein).
114 | [RError]_1073 = Ung\u00fcltiger Argumenttyp (kann nicht logisch sein).
115 | [RError]_1074 = Ung\u00fcltige Einstellung der Ausgabesprache (muss "English", "French", "German", "Italian", "Japanese", "Korean", "Polish", "Russian", "Simplified Chinese", "Spanish" oder "Traditional Chinese" sein).
116 | [RError]_1075 = Ung\u00fcltiger Wert f\u00fcr Argument footnotes (kann nicht null sein).
117 | [RError]_1076 = Ung\u00fcltige Argumentkategorien. Sie sollten in der gleichen Reihenfolge vorliegen wie die Dimensionen der Pivot-Tabelle.
118 | [RError]_1077 = Gebietsschemaeinstellung in R-Plugin fehlgeschlagen. Es wurde kein passendes Gebietsschema auf Ihrem System gefunden. Installieren Sie das entsprechende Gebietsschema auf Ihrem System.
119 |
120 | # General errors
121 | SPSSError = IBM SPSS Statistics-Fehler
122 | SPSSWarning = IBM SPSS Statistics-Warnung
123 | error_code = Der Fehlercode lautet
124 | with_message = Mit Meldung
125 |
--------------------------------------------------------------------------------
/src/inst/lang/en/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = No error.
13 | [ok]_1 = Comment.
14 | [warning]_2 = Warning.
15 | [error]_3 = Serious error.
16 | [error]_4 = Fatal error.
17 | [error]_5 = Catastrophic error.
18 | [error]_6 = Command syntax error.
19 | [error]_401 = Invalid index.
20 | [error]_11 = Cannot add object to XML workspace.
21 | [error]_12 = Invalid handle object.
22 | [error]_13 = Cannot remove XML workspace object.
23 | [error]_15 = Cannot get the result.
24 | [error]_16 = Invalid value.
25 | [warning]_20 = An existing XML workspace handle has been overwritten.
26 | [error]_21 = Invalid XPath expression.
27 | [error]_22 = XML error.
28 | [warning]_23 = Cannot read more data.
29 | [error]_24 = Invalid data type.
30 | [error]_25 = Duplicate variable name.
31 | [error]_26 = Invalid variable type.
32 | [error]_27 = Invalid variable name.
33 | [error]_30 = Invalid case.
34 | [error]_31 = Cannot complete this action while a data connection for processing split files is open.
35 | [error]_32 = A User Procedure is running.
36 | [error]_34 = Invalid measurement level.
37 | [error]_36 = Invalid missing value format.
38 | [error]_40 = A Procedure Data Source is required.
39 | [error]_44 = The active dataset is empty.
40 | [error]_47 = Invalid format type.
41 | [error]_48 = Invalid format width.
42 | [error]_49 = Invalid decimal point.
43 | [error]_54 = No more data is available in the active dataset.
44 | [error]_56 = Only string variables are allowed.
45 | [error]_57 = Only numeric variables are allowed.
46 | [error]_58 = Invalid attribute name.
47 | [error]_59 = The length of user-missing value for a string variable must be 8 characters or less.
48 | [error]_61 = The data value is too long.
49 | [error]_62 = The length of a string variable cannot exceed 32767 bytes.
50 | [error]_64 = Cannot change data values or variable information in the original dataset.
51 | [warning]_67 = The end of the current split has been reached.
52 | [error]_70 = The label length is too long.
53 | [error]_71 = The value length is too long.
54 | [error]_82 = The variable is not in the active dataset.
55 | [error]_86 = An active data source is required to complete this action.
56 | [error]_87 = Invalid dataset name.
57 | [error]_88 = This method can only be called between SetDictionaryToSPSS and EndDataStep.
58 | [error]_89 = Invalid function call. Function can only be called during dataset creation or within a User Procedure.
59 | [error]_90 = Cannot create an active dataset within a User Procedure.
60 | [error]_91 = A dataset with the same name already exists.
61 | [error]_92 = Cannot complete this action while dataset creation is in process.
62 | [error]_94 = Cannot create a dataset while there are pending transformations.
63 | [error]_96 = Cannot find specified attribute name.
64 | [error]_99 = Cannot create specified dataset.
65 | [error]_100 = Invalid multiple response set definition.
66 | [error]_301 = No model in CF Applier Node,please make sure SetModel in Builder Node.
67 | [error]_402 = Invalid field index.
68 | [warning]_404 = Field does not have labels.
69 | [warning]_403 = Field labels and values do not match.
70 | [error]_999999997 = Unknown error.
71 | [error]_999999998 = Processing was interrupted by the user.
72 | [error]_999999999 = Unknown error.
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = Invalid R CF Component Data Model format.
78 | [RError]_1002 = Invalid field name in data model. Duplicate values are present.
79 | [warning]_1003 = Duplicate values are present for value labels.
80 | [RError]_1004 = Invalid field storage for SetDataModel.
81 | [RError]_1005 = Invalid field measure for SetDataModel.
82 | [RError]_1006 = Invalid field format for SetDataModel.
83 | [RError]_1007 = Invalid field role for SetDataModel.
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = Invalid field name in argument.
88 | [RError]_1021 = Invalid field missing value.
89 | [RError]_1022 = Flag field does not have values.
90 |
91 | ## data
92 | [RError]_1008 = Invalid value for argument factorMode (must be "none", "levels" or "labels").
93 | [RError]_1009 = Invalid value for argument rDate (must be "none", "POSIXct" or "POSIXlt").
94 | [RError]_1010 = Invalid value for argument missingValue (must be NA, NaN or "asis").
95 | [RError]_1011 = Invalid function call. Function can only be called after calling SetDataModel.
96 | [RError]_1012 = Data and data model does not match.
97 |
98 | [RError]_1013 = Invalid index for GetOutputsNames.
99 | [RError]_1014 = Invalid graphic name or path.
100 | [RError]_1015 = Invalid graphic format (must be "JPG", "PNG" or "BMP").
101 | [RError]_1016 = Expects a numeric argument.
102 | [RError]_1017 = Expects an integer argument.
103 | [RError]_1018 = Expects a boolean argument.
104 | [RError]_1019 = Argument variables must be string, vector or list.
105 |
106 | # General errors
107 | SPSSError = IBM SPSS CF error
108 | SPSSWarning = IBM SPSS CF warning
109 | error_code = The error code is
110 | with_message = With message
111 |
--------------------------------------------------------------------------------
/src/inst/lang/es/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # Errors come from IBM SPSS Statistics backend.
9 | [ok]_0 = No error.
10 | [ok]_1 = Comment.
11 | [warning]_2 = Warning.
12 | [error]_3 = Serious error.
13 | [error]_4 = Fatal error.
14 | [error]_5 = Catastrophic error.
15 | [error]_6 = Command syntax error.
16 | [error]_401 = Invalid index.
17 | [error]_11 = Cannot add object to XML workspace.
18 | [error]_12 = Invalid handle object.
19 | [error]_13 = Cannot remove XML workspace object.
20 | [error]_15 = Cannot get the result.
21 | [error]_16 = Invalid value.
22 | [warning]_20 = An existing XML workspace handle has been overwritten.
23 | [error]_21 = Invalid XPath expression.
24 | [error]_22 = XML error.
25 | [warning]_23 = Cannot read more data.
26 | [error]_24 = Invalid data type.
27 | [error]_25 = Duplicate variable name.
28 | [error]_26 = Invalid variable type.
29 | [error]_27 = Invalid variable name.
30 | [error]_30 = Invalid case.
31 | [error]_31 = Cannot complete this action while a data connection for processing split files is open.
32 | [error]_32 = A User Procedure is running.
33 | [error]_34 = Invalid measurement level.
34 | [error]_36 = Invalid missing value format.
35 | [error]_40 = A Procedure Data Source is required.
36 | [error]_44 = The active dataset is empty.
37 | [error]_47 = Invalid format type.
38 | [error]_48 = Invalid format width.
39 | [error]_49 = Invalid decimal point.
40 | [error]_54 = No more data is available in the active dataset.
41 | [error]_56 = Only string variables are allowed.
42 | [error]_57 = Only numeric variables are allowed.
43 | [error]_58 = Invalid attribute name.
44 | [error]_59 = The length of user-missing value for a string variable must be 8 characters or less.
45 | [error]_61 = The data value is too long.
46 | [error]_62 = The length of a string variable cannot exceed 32767 bytes.
47 | [error]_64 = Cannot change data values or variable information in the original dataset.
48 | [warning]_67 = The end of the current split has been reached.
49 | [error]_70 = The label length is too long.
50 | [error]_71 = The value length is too long.
51 | [error]_82 = The variable is not in the active dataset.
52 | [error]_86 = An active data source is required to complete this action.
53 | [error]_87 = Invalid dataset name.
54 | [error]_88 = This method can only be called between SetDictionaryToSPSS and EndDataStep.
55 | [error]_89 = Invalid function call. Function can only be called during dataset creation or within a User Procedure.
56 | [error]_90 = Cannot create an active dataset within a User Procedure.
57 | [error]_91 = A dataset with the same name already exists.
58 | [error]_92 = Cannot complete this action while dataset creation is in process.
59 | [error]_94 = Cannot create a dataset while there are pending transformations.
60 | [error]_96 = Cannot find specified attribute name.
61 | [error]_99 = Cannot create specified dataset.
62 | [error]_100 = Invalid multiple response set definition.
63 | [error]_301 = No model in CF Applier Node,please make sure SetModel in Builder Node.
64 | [error]_402 = Invalid field index.
65 | [warning]_404 = Field does not have labels.
66 | [warning]_403 = Field labels and values do not match.
67 | [error]_999999997 = Unknown error.
68 | [error]_999999998 = Processing was interrupted by the user.
69 | [error]_999999999 = Unknown error.
70 |
71 | # Errors come from R plug-in.
72 | #[warning]_1000 = There are no more split groups.
73 | ## data model
74 | [RError]_1001 = Invalid R CF Component Data Model format.
75 | [RError]_1002 = Invalid field name in data model. Duplicate values are present.
76 | [warning]_1003 = Duplicate values are present for value labels.
77 | [RError]_1004 = Invalid field storage for SetDataModel.
78 | [RError]_1005 = Invalid field measure for SetDataModel.
79 | [RError]_1006 = Invalid field format for SetDataModel.
80 | [RError]_1007 = Invalid field role for SetDataModel.
81 |
82 | [RError]_1021 = Invalid field missing value.
83 | ##this is for GetDataModel or GetData
84 | [RError]_1020 = Invalid field name in argument.
85 |
86 | ## data
87 | [RError]_1008 = Invalid value for argument factorMode (must be "none", "levels" or "labels").
88 | [RError]_1009 = Invalid value for argument rDate (must be "none", "POSIXct" or "POSIXlt").
89 | [RError]_1010 = Invalid value for argument missingValue (must be NA, NaN or "asis").
90 | [RError]_1011 = Invalid function call. Function can only be called after calling SetDataModel.
91 | [RError]_1012 = Data and data model does not match.
92 |
93 | [RError]_1013 = Invalid index for GetOutputsNames.
94 | [RError]_1014 = Invalid graphic name or path.
95 | [RError]_1015 = Invalid graphic format (must be "JPG", "PNG" or "BMP").
96 | [RError]_1016 = Expects a numeric argument.
97 | [RError]_1017 = Expects an integer argument.
98 | [RError]_1018 = Expects a boolean argument.
99 | [RError]_1019 = Argument variables must be string, vector or list.
100 |
101 | # General errors
102 | SPSSError = IBM SPSS CF error
103 | SPSSWarning = IBM SPSS CF warning
104 | error_code = The error code is
105 | with_message = With message
106 |
--------------------------------------------------------------------------------
/src/inst/lang/fr/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # Errors come from IBM SPSS Statistics backend.
9 | [ok]_0 = No error.
10 | [ok]_1 = Comment.
11 | [warning]_2 = Warning.
12 | [error]_3 = Serious error.
13 | [error]_4 = Fatal error.
14 | [error]_5 = Catastrophic error.
15 | [error]_6 = Command syntax error.
16 | [error]_401 = Invalid index.
17 | [error]_11 = Cannot add object to XML workspace.
18 | [error]_12 = Invalid handle object.
19 | [error]_13 = Cannot remove XML workspace object.
20 | [error]_15 = Cannot get the result.
21 | [error]_16 = Invalid value.
22 | [warning]_20 = An existing XML workspace handle has been overwritten.
23 | [error]_21 = Invalid XPath expression.
24 | [error]_22 = XML error.
25 | [warning]_23 = Cannot read more data.
26 | [error]_24 = Invalid data type.
27 | [error]_25 = Duplicate variable name.
28 | [error]_26 = Invalid variable type.
29 | [error]_27 = Invalid variable name.
30 | [error]_30 = Invalid case.
31 | [error]_31 = Cannot complete this action while a data connection for processing split files is open.
32 | [error]_32 = A User Procedure is running.
33 | [error]_34 = Invalid measurement level.
34 | [error]_36 = Invalid missing value format.
35 | [error]_40 = A Procedure Data Source is required.
36 | [error]_44 = The active dataset is empty.
37 | [error]_47 = Invalid format type.
38 | [error]_48 = Invalid format width.
39 | [error]_49 = Invalid decimal point.
40 | [error]_54 = No more data is available in the active dataset.
41 | [error]_56 = Only string variables are allowed.
42 | [error]_57 = Only numeric variables are allowed.
43 | [error]_58 = Invalid attribute name.
44 | [error]_59 = The length of user-missing value for a string variable must be 8 characters or less.
45 | [error]_61 = The data value is too long.
46 | [error]_62 = The length of a string variable cannot exceed 32767 bytes.
47 | [error]_64 = Cannot change data values or variable information in the original dataset.
48 | [warning]_67 = The end of the current split has been reached.
49 | [error]_70 = The label length is too long.
50 | [error]_71 = The value length is too long.
51 | [error]_82 = The variable is not in the active dataset.
52 | [error]_86 = An active data source is required to complete this action.
53 | [error]_87 = Invalid dataset name.
54 | [error]_88 = This method can only be called between SetDictionaryToSPSS and EndDataStep.
55 | [error]_89 = Invalid function call. Function can only be called during dataset creation or within a User Procedure.
56 | [error]_90 = Cannot create an active dataset within a User Procedure.
57 | [error]_91 = A dataset with the same name already exists.
58 | [error]_92 = Cannot complete this action while dataset creation is in process.
59 | [error]_94 = Cannot create a dataset while there are pending transformations.
60 | [error]_96 = Cannot find specified attribute name.
61 | [error]_99 = Cannot create specified dataset.
62 | [error]_100 = Invalid multiple response set definition.
63 | [error]_301 = No model in CF Applier Node,please make sure SetModel in Builder Node.
64 | [error]_402 = Invalid field index.
65 | [warning]_404 = Field does not have labels.
66 | [warning]_403 = Field labels and values do not match.
67 | [error]_999999997 = Unknown error.
68 | [error]_999999998 = Processing was interrupted by the user.
69 | [error]_999999999 = Unknown error.
70 |
71 | # Errors come from R plug-in.
72 | #[warning]_1000 = There are no more split groups.
73 | ## data model
74 | [RError]_1001 = Invalid R CF Component Data Model format.
75 | [RError]_1002 = Invalid field name in data model. Duplicate values are present.
76 | [warning]_1003 = Duplicate values are present for value labels.
77 | [RError]_1004 = Invalid field storage for SetDataModel.
78 | [RError]_1005 = Invalid field measure for SetDataModel.
79 | [RError]_1006 = Invalid field format for SetDataModel.
80 | [RError]_1007 = Invalid field role for SetDataModel.
81 |
82 | [RError]_1021 = Invalid field missing value.
83 | ##this is for GetDataModel or GetData
84 | [RError]_1020 = Invalid field name in argument.
85 |
86 | ## data
87 | [RError]_1008 = Invalid value for argument factorMode (must be "none", "levels" or "labels").
88 | [RError]_1009 = Invalid value for argument rDate (must be "none", "POSIXct" or "POSIXlt").
89 | [RError]_1010 = Invalid value for argument missingValue (must be NA, NaN or "asis").
90 | [RError]_1011 = Invalid function call. Function can only be called after calling SetDataModel.
91 | [RError]_1012 = Data and data model does not match.
92 |
93 | [RError]_1013 = Invalid index for GetOutputsNames.
94 | [RError]_1014 = Invalid graphic name or path.
95 | [RError]_1015 = Invalid graphic format (must be "JPG", "PNG" or "BMP").
96 | [RError]_1016 = Expects a numeric argument.
97 | [RError]_1017 = Expects an integer argument.
98 | [RError]_1018 = Expects a boolean argument.
99 | [RError]_1019 = Argument variables must be string, vector or list.
100 |
101 | # General errors
102 | SPSSError = IBM SPSS CF error
103 | SPSSWarning = IBM SPSS CF warning
104 | error_code = The error code is
105 | with_message = With message
106 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_de.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = Kein Fehler.
13 | [ok]_1 = Kommentar.
14 | [warning]_2 = Warnung.
15 | [error]_3 = Schwerwiegender Fehler.
16 | [error]_4 = Fataler Fehler.
17 | [error]_5 = Nicht behebbarer Fehler.
18 | [error]_6 = Befehlssyntaxfehler.
19 | [error]_401 = Ung\u00fcltiger Index.
20 | [error]_11 = Objekt kann XML-Arbeitsbereich nicht hinzugef\u00fcgt werden.
21 | [error]_12 = Ung\u00fcltiges Handleobjekt.
22 | [error]_13 = XML-Arbeitsbereichsobjekt kann nicht entfernt werden.
23 | [error]_15 = Das Ergebnis kann nicht abgerufen werden.
24 | [error]_16 = Ung\u00fcltiger Wert.
25 | [warning]_20 = Ein vorhandenes XML-Arbeitsbereichshandle wurde \u00fcberschrieben.
26 | [error]_21 = Ung\u00fcltiger XPath-Ausdruck.
27 | [error]_22 = XML-Fehler.
28 | [warning]_23 = Es k\u00f6nnen keine weiteren Daten gelesen werden.
29 | [error]_24 = Ung\u00fcltiger Datentyp.
30 | [error]_25 = Doppelter Variablenname.
31 | [error]_26 = Ung\u00fcltiger Variablentyp.
32 | [error]_27 = Ung\u00fcltiger Variablenname.
33 | [error]_30 = Ung\u00fcltiger Fall.
34 | [error]_31 = Diese Aktion kann nicht abgeschlossen werden, solange eine Datenverbindung f\u00fcr die Verarbeitung aufgeteilter Dateien ge\u00f6ffnet ist.
35 | [error]_32 = Eine Benutzerprozedur wird ausgef\u00fchrt.
36 | [error]_34 = Ung\u00fcltiges Messniveau.
37 | [error]_36 = Ung\u00fcltiges Format von fehlenden Werten.
38 | [error]_40 = Eine Prozedurendatenquelle ist erforderlich.
39 | [error]_44 = Das aktive Dataset ist leer.
40 | [error]_47 = Ung\u00fcltiger Formattyp.
41 | [error]_48 = Ung\u00fcltige Formatbreite.
42 | [error]_49 = Ung\u00fcltiges Dezimaltrennzeichen.
43 | [error]_54 = Im aktiven Dataset sind keine weiteren Daten verf\u00fcgbar.
44 | [error]_56 = Nur Zeichenfolgevariablen sind zul\u00e4ssig.
45 | [error]_57 = Nur numerische Variablen sind zul\u00e4ssig.
46 | [error]_58 = Ung\u00fcltiger Attributname.
47 | [error]_59 = Der benutzerdefiniert fehlende Wert f\u00fcr eine Zeichenfolgevariable darf maximal 8 Zeichen lang sein.
48 | [error]_61 = Der Datenwert ist zu lang.
49 | [error]_62 = Eine Zeichenfolgevariable darf nicht l\u00e4nger als 32.767 Byte sein.
50 | [error]_64 = Die Datenwerte oder Variableninformationen im urspr\u00fcnglichen Dataset k\u00f6nnen nicht ge\u00e4ndert werden.
51 | [warning]_67 = Das Ende der aktuellen Aufteilung wurde erreicht.
52 | [error]_70 = Die Beschriftung ist zu lang.
53 | [error]_71 = Die Wertel\u00e4nge ist zu gro\u00df.
54 | [error]_82 = Die Variable befindet sich nicht im aktiven Dataset.
55 | [error]_86 = Damit diese Aktion abgeschlossen werden kann, ist eine aktive Datenquelle erforderlich.
56 | [error]_87 = Ung\u00fcltiger Datasetname.
57 | [error]_88 = Diese Methode kann nur zwischen SetDictionaryToSPSS und EndDataStep aufgerufen werden.
58 | [error]_89 = Ung\u00fcltiger Funktionsaufruf. Die Funktion kann nur w\u00e4hrend der Erstellung eines Datasets oder im Rahmen einer Benutzerprozedur aufgerufen werden.
59 | [error]_90 = Ein aktives Dataset kann nicht im Rahmen einer Benutzerprozedur erstellt werden.
60 | [error]_91 = Ein Dataset mit demselben Namen ist bereits vorhanden.
61 | [error]_92 = Diese Aktion kann nicht abgeschlossen werden, w\u00e4hrend ein Dataset erstellt wird.
62 | [error]_94 = Ein Dataset kann nicht erstellt werden, w\u00e4hrend Transformationen anstehen.
63 | [error]_96 = Der angegebene Attributname wurde nicht gefunden.
64 | [error]_99 = Das angegebene Dataset kann nicht erstellt werden.
65 | [error]_100 = Ung\u00fcltige Definition f\u00fcr Mehrfachantwortset.
66 | [error]_301 = Kein Modell in CF-Anwenderknoten. Stellen Sie sicher, dass SetModel im Builder-Knoten vorhanden ist.
67 | [error]_402 = Ung\u00fcltiger Feldindex.
68 | [warning]_404 = Das Feld weist keine Beschriftungen auf.
69 | [warning]_403 = Die Feldbeschriftungen und -werte stimmen nicht \u00fcberein.
70 | [error]_999999997 = Unbekannter Fehler.
71 | [error]_999999998 = Die Verarbeitung wurde vom Benutzer unterbrochen.
72 | [error]_999999999 = Unbekannter Fehler.
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = Ung\u00fcltiges Datenmodellformat f\u00fcr CF-Komponente f\u00fcr R.
78 | [RError]_1002 = Ung\u00fcltiger Feldname in Datenmodell. Es sind doppelte Werte vorhanden.
79 | [warning]_1003 = F\u00fcr Wertbeschriftungen liegen doppelte Werte vor.
80 | [RError]_1004 = Ung\u00fcltiger Feldspeicher f\u00fcr SetDataModel.
81 | [RError]_1005 = Ung\u00fcltiges Feldma\u00df f\u00fcr SetDataModel.
82 | [RError]_1006 = Ung\u00fcltiges Feldformat f\u00fcr SetDataModel.
83 | [RError]_1007 = Ung\u00fcltige Feldrolle f\u00fcr SetDataModel.
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = Ung\u00fcltiger Feldname in Argument.
88 | [RError]_1021 = Ung\u00fcltiger Wert f\u00fcr fehlendes Feld.
89 | [RError]_1022 = Flagfeld enth\u00e4lt keine Werte.
90 |
91 | ## data
92 | [RError]_1008 = Ung\u00fcltiger Wert f\u00fcr Argument factorMode (muss "none", "levels" oder "labels" sein).
93 | [RError]_1009 = Ung\u00fcltiger Wert f\u00fcr Argument rDate (muss "none", "POSIXct" oder "POSIXlt" sein).
94 | [RError]_1010 = Ung\u00fcltiger Wert f\u00fcr Argument missingValue (muss NA, NaN oder "asis" sein).
95 | [RError]_1011 = Ung\u00fcltiger Funktionsaufruf. Funktion kann nur nach dem Aufruf von SetDataModel aufgerufen werden.
96 | [RError]_1012 = Daten und Datenmodell stimmen nicht \u00fcberein.
97 |
98 | [RError]_1013 = Ung\u00fcltiger Index f\u00fcr GetOutputsNames.
99 | [RError]_1014 = Ung\u00fcltiger Grafikname oder Pfad.
100 | [RError]_1015 = Ung\u00fcltiges Grafikformat (erforderlich ist "JPG", "PNG" oder "BMP").
101 | [RError]_1016 = Erwartet ein numerisches Argument.
102 | [RError]_1017 = Erwartet ein ganzzahliges Argument.
103 | [RError]_1018 = Erwartet ein boolesches Argument.
104 | [RError]_1019 = Variablen f\u00fcr Argumente m\u00fcssen eine Zeichenfolge, ein Vektor oder eine Liste sein.
105 |
106 | # General errors
107 | SPSSError = IBM SPSS CF - Fehler
108 | SPSSWarning = IBM SPSS CF - Warnung
109 | error_code = Fehlercode:
110 | with_message = Mit Nachricht
111 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_es.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = Ning\u00fan error.
13 | [ok]_1 = Comentario.
14 | [warning]_2 = Aviso.
15 | [error]_3 = Error grave.
16 | [error]_4 = Error muy grave.
17 | [error]_5 = Error catastr\u00f3fico.
18 | [error]_6 = Error de sintaxis del mandato.
19 | [error]_401 = \u00cdndice no v\u00e1lido.
20 | [error]_11 = No se puede agregar un objeto al espacio de trabajo XML.
21 | [error]_12 = Objeto de controlador no v\u00e1lido.
22 | [error]_13 = No se puede eliminar el objeto del espacio de trabajo XML.
23 | [error]_15 = No se puede obtener el resultado.
24 | [error]_16 = Valor no v\u00e1lido.
25 | [warning]_20 = Se ha sobrescrito un controlador de un espacio de trabajo XML existente.
26 | [error]_21 = Expresi\u00f3n XPath no v\u00e1lida.
27 | [error]_22 = Error de XML.
28 | [warning]_23 = No se pueden leer m\u00e1s datos.
29 | [error]_24 = Tipo de datos no v\u00e1lido.
30 | [error]_25 = Nombre de variable duplicado.
31 | [error]_26 = Tipo de variable no v\u00e1lida.
32 | [error]_27 = Nombre de variable no v\u00e1lido.
33 | [error]_30 = Caso no v\u00e1lido.
34 | [error]_31 = No se puede completar esta acci\u00f3n mientras est\u00e9 abierta una conexi\u00f3n de datos para procesar archivos divididos.
35 | [error]_32 = Se est\u00e1 ejecutando un procedimiento de usuario.
36 | [error]_34 = Nivel de medici\u00f3n no v\u00e1lido.
37 | [error]_36 = Formato de valor perdido no v\u00e1lido.
38 | [error]_40 = Se requiere un origen de datos de procedimiento.
39 | [error]_44 = El conjunto de datos activo est\u00e1 vac\u00edo.
40 | [error]_47 = Tipo de formato no v\u00e1lido.
41 | [error]_48 = Ancho de formato no v\u00e1lido.
42 | [error]_49 = Separador decimal no v\u00e1lido.
43 | [error]_54 = No hay m\u00e1s datos disponibles en el conjunto de datos activo.
44 | [error]_56 = S\u00f3lo se permiten variables de cadena.
45 | [error]_57 = S\u00f3lo se permiten variables num\u00e9ricas.
46 | [error]_58 = Nombre de atributo no v\u00e1lido.
47 | [error]_59 = La longitud de un valor perdido del usuario para una variable de cadena debe ser de 8 caracteres o menos.
48 | [error]_61 = El valor de datos es demasiado largo.
49 | [error]_62 = La longitud de una variable de cadena no puede exceder 32767 bytes.
50 | [error]_64 = No se pueden cambiar valores de datos o informaci\u00f3n de variable en el conjunto de datos original.
51 | [warning]_67 = Se ha alcanzado el final de la divisi\u00f3n actual.
52 | [error]_70 = La longitud de la etiqueta es demasiado larga.
53 | [error]_71 = La longitud del valor es demasiado larga.
54 | [error]_82 = La variable no est\u00e1 en el conjunto de datos activo.
55 | [error]_86 = Se requiere un origen de datos activo para completar esta acci\u00f3n.
56 | [error]_87 = Nombre de conjunto de datos no v\u00e1lido.
57 | [error]_88 = S\u00f3lo se puede llamar a este m\u00e9todo entre SetDictionaryToSPSS y EndDataStep.
58 | [error]_89 = Llamada a funci\u00f3n no v\u00e1lida. S\u00f3lo se puede llamar a la funci\u00f3n durante la creaci\u00f3n del conjunto de datos o en un procedimiento de usuario.
59 | [error]_90 = No se puede crear un conjunto de datos activo en un procedimiento de usuario.
60 | [error]_91 = Ya existe un conjunto de datos con el mismo nombre.
61 | [error]_92 = No se puede completar esta acci\u00f3n mientras est\u00e1 en curso la creaci\u00f3n del conjunto de datos.
62 | [error]_94 = No se puede crear un conjunto de datos mientras hay transformaciones pendientes.
63 | [error]_96 = No se puede encontrar el nombre de atributo especificado.
64 | [error]_99 = No se puede crear el conjunto de datos especificado.
65 | [error]_100 = Definici\u00f3n de conjunto de respuesta m\u00faltiples no v\u00e1lida.
66 | [error]_301 = No hay ning\u00fan modelo en el nodo aplicador de CF, aseg\u00farese de definir el Modelo en el nodo Generador.
67 | [error]_402 = \u00cdndice de campos no v\u00e1lido.
68 | [warning]_404 = El campo no tiene etiquetas.
69 | [warning]_403 = Las etiquetas y los valores de campo no coinciden.
70 | [error]_999999997 = Error desconocido.
71 | [error]_999999998 = El proceso ha sido interrumpido por el usuario.
72 | [error]_999999999 = Error desconocido.
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = Formato de modelo de datos de componente CF de R no v\u00e1lido.
78 | [RError]_1002 = Nombre de campo no v\u00e1lido en el modelo de datos. Hay valores duplicados.
79 | [warning]_1003 = Hay valores duplicados en las etiquetas de valor.
80 | [RError]_1004 = Almacenamiento de campo no v\u00e1lido para SetDataModel.
81 | [RError]_1005 = Medida de campo no v\u00e1lida para SetDataModel.
82 | [RError]_1006 = Formato de campo no v\u00e1lido para SetDataModel.
83 | [RError]_1007 = Rol de campo no v\u00e1lido para SetDataModel.
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = Nombre de campo no v\u00e1lido en el argumento.
88 | [RError]_1021 = Valor perdido de campo no v\u00e1lido.
89 | [RError]_1022 = El campo de distintivo no tiene valores.
90 |
91 | ## data
92 | [RError]_1008 = Valor no v\u00e1lido para el argumento factorMode (debe ser "none", "levels" o "labels").
93 | [RError]_1009 = Valor no v\u00e1lido para el argumento rDate (debe ser "none", "POSIXct" o "POSIXlt").
94 | [RError]_1010 = Valor no v\u00e1lido para el argumento missingValue (debe ser NA, NaN o "asis").
95 | [RError]_1011 = Llamada a funci\u00f3n no v\u00e1lida. S\u00f3lo se puede llamar a la funci\u00f3n despu\u00e9s de llamar a SetDataModel.
96 | [RError]_1012 = Los datos y el modelo de datos no coinciden.
97 |
98 | [RError]_1013 = \u00cdndice no v\u00e1lido para GetOutputsNames.
99 | [RError]_1014 = Nombre o ruta de gr\u00e1fico no v\u00e1lido.
100 | [RError]_1015 = Formato de gr\u00e1fico no v\u00e1lido (debe ser "JPG", "PNG" o "BMP").
101 | [RError]_1016 = Se espera un argumento num\u00e9rico.
102 | [RError]_1017 = Se espera un argumento de entero.
103 | [RError]_1018 = Se espera un argumento booleano.
104 | [RError]_1019 = Las variables de argumento deben ser cadenas, vectores o listas.
105 |
106 | # General errors
107 | SPSSError = Error de IBM SPSS CF
108 | SPSSWarning = Aviso de IBM SPSS CF
109 | error_code = El c\u00f3digo de error es
110 | with_message = Con el mensaje
111 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_fr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = Aucune erreur.
13 | [ok]_1 = Commentaire.
14 | [warning]_2 = Avertissement.
15 | [error]_3 = Erreur grave.
16 | [error]_4 = Erreur fatale.
17 | [error]_5 = Erreur catastrophique.
18 | [error]_6 = Erreur de syntaxe de commande.
19 | [error]_401 = Index non valide.
20 | [error]_11 = Impossible d'ajouter l'objet \u00e0 l'espace de travail XML.
21 | [error]_12 = Objet de descripteur non valide.
22 | [error]_13 = Impossible de supprimer l'objet d'espace de travail XML.
23 | [error]_15 = Impossible d'obtenir le r\u00e9sultat.
24 | [error]_16 = Valeur non valide.
25 | [warning]_20 = Un descripteur d'espace de travail XML existant a \u00e9t\u00e9 supprim\u00e9 et remplac\u00e9.
26 | [error]_21 = Expression XPath non valide.
27 | [error]_22 = Erreur XML.
28 | [warning]_23 = Impossible de lire plus de donn\u00e9es.
29 | [error]_24 = Type de donn\u00e9es non valide.
30 | [error]_25 = Nom de variable en double.
31 | [error]_26 = Type de variable non valide.
32 | [error]_27 = Nom de variable non valide.
33 | [error]_30 = Observation non valide.
34 | [error]_31 = Impossible de compl\u00e9ter cette action si une connexion de donn\u00e9es pour le traitement des fichiers scind\u00e9s est ouverte.
35 | [error]_32 = Une proc\u00e9dure utilisateur est en cours d'ex\u00e9cution.
36 | [error]_34 = Niveau de mesure non valide.
37 | [error]_36 = Format de valeur manquante non valide.
38 | [error]_40 = Une source de donn\u00e9es de proc\u00e9dure est requise.
39 | [error]_44 = Le jeu de donn\u00e9es actif est vide.
40 | [error]_47 = Type de format non valide.
41 | [error]_48 = Format de largeur non valide.
42 | [error]_49 = S\u00e9parateur d\u00e9cimal non valide.
43 | [error]_54 = Plus de donn\u00e9es disponibles dans le jeu de donn\u00e9es actif.
44 | [error]_56 = Seules les variables de cha\u00eene sont autoris\u00e9es.
45 | [error]_57 = Seules les variables num\u00e9riques sont autoris\u00e9es.
46 | [error]_58 = Nom d'attribut non valide.
47 | [error]_59 = Les valeurs manquantes de l'utilisateur pour les variables de cha\u00eene doivent \u00eatre \u00e9gales ou inf\u00e9rieures \u00e0 8 caract\u00e8res.
48 | [error]_61 = La valeur des donn\u00e9es est trop longue.
49 | [error]_62 = La longueur d\u00e9finie de la variable de cha\u00eene ne doit pas d\u00e9passer 32\u00a0767 octets.
50 | [error]_64 = Impossible de modifier les valeurs de donn\u00e9es ou les informations sur la variable dans le jeu de donn\u00e9es d'origine.
51 | [warning]_67 = La fin de la scission actuelle a \u00e9t\u00e9 atteinte.
52 | [error]_70 = Le libell\u00e9 est trop long.
53 | [error]_71 = La valeur est trop longue.
54 | [error]_82 = La variable ne se trouve pas dans le jeu de donn\u00e9es actif.
55 | [error]_86 = Une source de donn\u00e9s active est requise pour compl\u00e9ter cette action.
56 | [error]_87 = Nom du jeu de donn\u00e9es non valide.
57 | [error]_88 = Cette m\u00e9thode ne peut \u00eatre appel\u00e9e qu'entre SetDictionaryToSPSS et EndDataStep.
58 | [error]_89 = Appel de fonction non valide. La fonction ne peut \u00eatre appel\u00e9e que pendant la cr\u00e9ation du jeu de donn\u00e9es ou dans une proc\u00e9dure utilisateur.
59 | [error]_90 = Impossible de cr\u00e9er un jeu de donn\u00e9es actif dans une proc\u00e9dure utilisateur.
60 | [error]_91 = Un jeu de donn\u00e9es avec le nom sp\u00e9cifi\u00e9 existe d\u00e9j\u00e0.
61 | [error]_92 = Impossible de compl\u00e9ter cette action si la cr\u00e9ation du jeu de donn\u00e9es est en cours.
62 | [error]_94 = Impossible de cr\u00e9er un jeu de donn\u00e9es alors que des transformations sont en attente.
63 | [error]_96 = Impossible de trouver le nom d'attribut sp\u00e9cifi\u00e9.
64 | [error]_99 = Impossible de cr\u00e9er le jeu de donn\u00e9es sp\u00e9cifi\u00e9.
65 | [error]_100 = D\u00e9finition de l'ensemble de r\u00e9ponses multiples non valide.
66 | [error]_301 = Aucun mod\u00e8le dans le noeud applicateur CF. V\u00e9rifiez SetModel dans le noeud cr\u00e9ation.
67 | [error]_402 = Index de champ non valide.
68 | [warning]_404 = Le champ n'a pas de libell\u00e9s.
69 | [warning]_403 = Les valeurs et les libell\u00e9s de champ ne correspondent pas.
70 | [error]_999999997 = Erreur inconnue.
71 | [error]_999999998 = Le traitement a \u00e9t\u00e9 interrompu par l'utilisateur.
72 | [error]_999999999 = Erreur inconnue.
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = Format de mod\u00e8le de donn\u00e9es de composant R CF non valide.
78 | [RError]_1002 = Nom de champ non valide dans le mod\u00e8le de donn\u00e9es. Des valeurs en double sont pr\u00e9sentes.
79 | [warning]_1003 = Des valeurs en double sont pr\u00e9sentes pour les libell\u00e9s de valeur.
80 | [RError]_1004 = Stockage de champ non valide pour SetDataModel.
81 | [RError]_1005 = Mesure non valide pour SetDataModel.
82 | [RError]_1006 = Format de champ non valide pour SetDataModel.
83 | [RError]_1007 = R\u00f4le de champ non valide pour SetDataModel.
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = Nom de champ non valide dans l'argument.
88 | [RError]_1021 = Valeur manquante de champ non valide.
89 | [RError]_1022 = Le champ indicateur ne poss\u00e8de pas de valeur.
90 |
91 | ## data
92 | [RError]_1008 = Valeur non valide pour l'argument factorMode (doit \u00eatre "none", "levels" ou "labels").
93 | [RError]_1009 = Valeur non valide pour l'argument rDate (doit \u00eatre "none", "POSIXct" ou "POSIXlt").
94 | [RError]_1010 = Valeur non valide pour l'argument missingValue (doit \u00eatre NA, NaN ou "asis").
95 | [RError]_1011 = Appel de fonction non valide. La fonction ne peut \u00eatre appel\u00e9e que lorsque SetDataModel a \u00e9t\u00e9 appel\u00e9e.
96 | [RError]_1012 = Les donn\u00e9es et le mod\u00e8le de donn\u00e9es ne correspondent pas.
97 |
98 | [RError]_1013 = Index non valide pour GetOutputsNames.
99 | [RError]_1014 = Nom ou chemin de graphique non valide.
100 | [RError]_1015 = Format de graphique non valide (doit \u00eatre "JPG", "PNG" ou "BMP").
101 | [RError]_1016 = Attend un argument num\u00e9rique.
102 | [RError]_1017 = Attend un argument entier.
103 | [RError]_1018 = Attend un argument bool\u00e9en.
104 | [RError]_1019 = Les variables d'argument doivent \u00eatre une cha\u00eene, un vecteur ou une liste.
105 |
106 | # General errors
107 | SPSSError = Erreur d'IBM SPSS CF
108 | SPSSWarning = Avertissement d'IBM SPSS CF
109 | error_code = Le code d'erreur est
110 | with_message = avec le message
111 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_it.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = Nessun errore.
13 | [ok]_1 = Commento.
14 | [warning]_2 = Avviso.
15 | [error]_3 = Errore grave.
16 | [error]_4 = Errore irreversibile.
17 | [error]_5 = Errore catastrofico.
18 | [error]_6 = Errore di sintassi del comando.
19 | [error]_401 = Indice non valido.
20 | [error]_11 = Impossibile aggiungere oggetto allo spazio di lavoro XML.
21 | [error]_12 = Oggetto handle non valido.
22 | [error]_13 = Impossibile rimuovere oggetto dello spazio di lavoro XML.
23 | [error]_15 = Impossibile acquisire il risultato.
24 | [error]_16 = Valore non valido.
25 | [warning]_20 = Un handle dello spazio di lavoro XML esistente \u00e8 stato sovrascritto.
26 | [error]_21 = Espressione XPath non valida.
27 | [error]_22 = Errore XML.
28 | [warning]_23 = Impossibile leggere ulteriori dati.
29 | [error]_24 = Tipo di dati non valido.
30 | [error]_25 = Nome variabile duplicato.
31 | [error]_26 = Tipo di variabile non valido.
32 | [error]_27 = Nome variabile non valido.
33 | [error]_30 = Caso non valido.
34 | [error]_31 = Impossibile completare l'azione mentre \u00e8 aperta una connessione dati per l'elaborazione dei file di suddivisione.
35 | [error]_32 = Procedura utente in esecuzione.
36 | [error]_34 = Livello di misurazione non valido.
37 | [error]_36 = Formato valore mancante non valido.
38 | [error]_40 = \u00c8 obbligatoria un'origine dati per la procedura.
39 | [error]_44 = Il dataset attivo \u00e8 vuoto.
40 | [error]_47 = Tipo di formato non valido.
41 | [error]_48 = Larghezza formato non valida.
42 | [error]_49 = Punto decimale non valido.
43 | [error]_54 = Non sono disponibili ulteriori dati nel dataset attivo.
44 | [error]_56 = Sono consentite solo variabili di stringa.
45 | [error]_57 = Sono consentite solo variabili numeriche.
46 | [error]_58 = Nome di attributo non valido.
47 | [error]_59 = La lunghezza di un valore mancante definito dall'utente per una variabile di stringa deve essere al massimo di 8 caratteri.
48 | [error]_61 = Il valore dati \u00e8 troppo lungo.
49 | [error]_62 = La lunghezza di una variabile di stringa non pu\u00f2 superare 32767 byte.
50 | [error]_64 = Impossibile modificare i valori dei dati o le informazioni sulla variabile nel dataset originale.
51 | [warning]_67 = \u00c8 stata raggiunta la fine della suddivisione corrente.
52 | [error]_70 = Lunghezza eccessiva dell'etichetta.
53 | [error]_71 = Lunghezza eccessiva del valore.
54 | [error]_82 = La variabile non \u00e8 nel dataset attivo.
55 | [error]_86 = Per completare questa azione \u00e8 necessaria un'origine dati attiva.
56 | [error]_87 = Nome dataset non valido.
57 | [error]_88 = Questo metodo pu\u00f2 essere richiamato solo tra SetDictionaryToSPSS ed EndDataStep.
58 | [error]_89 = Chiamata funzione non valida. La funzione pu\u00f2 essere richiamata solo durante la creazione del dataset o all'interno di una procedura utente.
59 | [error]_90 = Impossibile creare un dataset attivo all'interno di una procedura utente.
60 | [error]_91 = Esiste gi\u00e0 un dataset con lo stesso nome.
61 | [error]_92 = Impossibile completare l'azione se \u00e8 in corso la creazione di un dataset.
62 | [error]_94 = Impossibile creare un dataset mentre sono in sospeso trasformazioni.
63 | [error]_96 = Impossibile trovare il nome dell'attributo specificato.
64 | [error]_99 = Impossibile creare il dataset specificato.
65 | [error]_100 = Definizione insieme a risposta multipla non valida.
66 | [error]_301 = Nessun modello nel nodo applicatore CF, verificare che SetModel sia presente nel nodo Builder.
67 | [error]_402 = Indica campo non valido.
68 | [warning]_404 = Il campo non dispone di etichette.
69 | [warning]_403 = I valori e le etichette di campo non corrispondono.
70 | [error]_999999997 = Errore sconosciuto.
71 | [error]_999999998 = Elaborazione interrotta dall'utente.
72 | [error]_999999999 = Errore sconosciuto.
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = Formato del modello dati del componente CF R non valido.
78 | [RError]_1002 = Nome campo non valido nel modello dati. Sono presenti valori duplicati.
79 | [warning]_1003 = Sono presenti valori duplicati per le etichette valore.
80 | [RError]_1004 = Archiviazione campo non valida per SetDataModel.
81 | [RError]_1005 = Misura campo non valida per SetDataModel.
82 | [RError]_1006 = Formato campo non valido per SetDataModel.
83 | [RError]_1007 = Ruolo campo non valido per SetDataModel.
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = Nome campo non valido nell'argomento.
88 | [RError]_1021 = Valore mancante campo non valido.
89 | [RError]_1022 = Il campo indicatore non dispone di alcun valore.
90 |
91 | ## data
92 | [RError]_1008 = Valore non valido per l'argomento factorMode (deve essere "none", "levels" o "labels").
93 | [RError]_1009 = Valore non valido per l'argomento rDate (deve essere "none", "POSIXct" o "POSIXlt").
94 | [RError]_1010 = Valore non valido per l'argomento missingValue (deve essere NA, NaN o "asis").
95 | [RError]_1011 = Chiamata funzione non valida. La funzione pu\u00f2 essere richiamata solo dopo aver richiamato SetDataModel.
96 | [RError]_1012 = Dati e modello dati non corrispondenti.
97 |
98 | [RError]_1013 = Indice non valido per GetOutputsNames.
99 | [RError]_1014 = Percorso o nome grafico non valido.
100 | [RError]_1015 = Formato grafico non valido (deve essere "JPG", "PNG" o "BMP").
101 | [RError]_1016 = \u00c8 previsto un argomento numerico.
102 | [RError]_1017 = \u00c8 previsto un argomento intero.
103 | [RError]_1018 = \u00c8 previsto un argomento booleano.
104 | [RError]_1019 = Le variabili degli argomenti devono essere stringa, vettore o elenco.
105 |
106 | # General errors
107 | SPSSError = Errore IBM SPSS CF
108 | SPSSWarning = Avviso di IBM SPSS CF
109 | error_code = Il codice di errore \u00e8
110 | with_message = Con messaggio
111 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_ja.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = \u30a8\u30e9\u30fc\u306f\u3042\u308a\u307e\u305b\u3093\u3002
13 | [ok]_1 = \u30b3\u30e1\u30f3\u30c8\u3002
14 | [warning]_2 = \u8b66\u544a\u3002
15 | [error]_3 = \u6df1\u523b\u306a\u30a8\u30e9\u30fc\u3002
16 | [error]_4 = \u81f4\u547d\u7684\u306a\u30a8\u30e9\u30fc\u3002
17 | [error]_5 = \u58ca\u6ec5\u7684\u306a\u30a8\u30e9\u30fc\u3002
18 | [error]_6 = \u30b3\u30de\u30f3\u30c9 \u30b7\u30f3\u30bf\u30c3\u30af\u30b9\u306e\u30a8\u30e9\u30fc
19 | [error]_401 = \u30a4\u30f3\u30c7\u30c3\u30af\u30b9\u304c\u7121\u52b9\u3067\u3059\u3002
20 | [error]_11 = \u30aa\u30d6\u30b8\u30a7\u30af\u30c8\u3092 XML \u30ef\u30fc\u30af\u30b9\u30da\u30fc\u30b9\u306b\u8ffd\u52a0\u3067\u304d\u307e\u305b\u3093\u3002
21 | [error]_12 = \u30cf\u30f3\u30c9\u30eb \u30aa\u30d6\u30b8\u30a7\u30af\u30c8\u304c\u7121\u52b9\u3067\u3059\u3002
22 | [error]_13 = XML \u30ef\u30fc\u30af\u30b9\u30da\u30fc\u30b9 \u30aa\u30d6\u30b8\u30a7\u30af\u30c8\u3092\u524a\u9664\u3067\u304d\u307e\u305b\u3093\u3002
23 | [error]_15 = \u7d50\u679c\u3092\u53d6\u5f97\u3067\u304d\u307e\u305b\u3093\u3002
24 | [error]_16 = \u5024\u304c\u7121\u52b9\u3067\u3059\u3002
25 | [warning]_20 = \u65e2\u5b58\u306e XML \u30ef\u30fc\u30af\u30b9\u30da\u30fc\u30b9 \u30cf\u30f3\u30c9\u30eb\u304c\u4e0a\u66f8\u304d\u3055\u308c\u307e\u3057\u305f\u3002
26 | [error]_21 = XPath \u5f0f\u304c\u7121\u52b9\u3067\u3059\u3002
27 | [error]_22 = XML \u30a8\u30e9\u30fc\u3002
28 | [warning]_23 = \u3053\u308c\u4ee5\u4e0a\u30c7\u30fc\u30bf\u3092\u8aad\u307f\u8fbc\u3080\u3053\u3068\u306f\u3067\u304d\u307e\u305b\u3093\u3002
29 | [error]_24 = \u30c7\u30fc\u30bf\u578b\u304c\u7121\u52b9\u3067\u3059\u3002
30 | [error]_25 = \u5909\u6570\u540d\u304c\u91cd\u8907\u3057\u3066\u3044\u307e\u3059\u3002
31 | [error]_26 = \u5909\u6570\u306e\u578b\u304c\u7121\u52b9\u3067\u3059\u3002
32 | [error]_27 = \u5909\u6570\u540d\u304c\u7121\u52b9\u3067\u3059\u3002
33 | [error]_30 = \u30b1\u30fc\u30b9\u304c\u7121\u52b9\u3067\u3059\u3002
34 | [error]_31 = "\u5206\u5272\u30d5\u30a1\u30a4\u30eb\u3092\u51e6\u7406\u3059\u308b\u305f\u3081\u306e\u30c7\u30fc\u30bf\u63a5\u7d9a\u304c\u958b\u3044\u3066\u3044\u308b\u9593\u306f\u3053\u306e\u64cd\u4f5c\u3092\u5b9f\u884c\u3067\u304d\u307e\u305b\u3093\u3002
35 | [error]_32 = \u30e6\u30fc\u30b6\u30fc\u624b\u9806\u304c\u5b9f\u884c\u4e2d\u3067\u3059\u3002
36 | [error]_34 = \u6e2c\u5b9a\u306e\u5c3a\u5ea6\u304c\u7121\u52b9\u3067\u3059\u3002
37 | [error]_36 = \u6b20\u640d\u5024\u306e\u5f62\u5f0f\u304c\u7121\u52b9\u3067\u3059\u3002
38 | [error]_40 = \u624b\u7d9a\u304d\u30c7\u30fc\u30bf \u30bd\u30fc\u30b9\u304c\u5fc5\u8981\u3067\u3059\u3002
39 | [error]_44 = \u30a2\u30af\u30c6\u30a3\u30d6 \u30c7\u30fc\u30bf \u30bb\u30c3\u30c8\u304c\u7a7a\u3067\u3059\u3002
40 | [error]_47 = \u5f62\u5f0f\u306e\u30bf\u30a4\u30d7\u304c\u7121\u52b9\u3067\u3059\u3002
41 | [error]_48 = \u5f62\u5f0f\u306e\u5e45\u304c\u7121\u52b9\u3067\u3059\u3002
42 | [error]_49 = \u5c0f\u6570\u70b9\u304c\u7121\u52b9\u3067\u3059\u3002
43 | [error]_54 = \u30a2\u30af\u30c6\u30a3\u30d6 \u30c7\u30fc\u30bf \u30bb\u30c3\u30c8\u306b\u306f\u3001\u3053\u308c\u4ee5\u4e0a\u4f7f\u7528\u53ef\u80fd\u306a\u30c7\u30fc\u30bf\u306f\u3042\u308a\u307e\u305b\u3093\u3002
44 | [error]_56 = \u4f7f\u7528\u3067\u304d\u308b\u306e\u306f\u6587\u5b57\u5217\u5909\u6570\u3060\u3051\u3067\u3059\u3002
45 | [error]_57 = \u4f7f\u7528\u3067\u304d\u308b\u306e\u306f\u6570\u5024\u5909\u6570\u3060\u3051\u3067\u3059\u3002
46 | [error]_58 = \u5c5e\u6027\u540d\u304c\u7121\u52b9\u3067\u3059\u3002
47 | [error]_59 = \u6587\u5b57\u5217\u5909\u6570\u306e\u30e6\u30fc\u30b6\u30fc\u6b20\u640d\u5024\u306e\u9577\u3055\u306f 8 \u6587\u5b57\u4ee5\u4e0b\u3067\u306a\u3051\u308c\u3070\u306a\u308a\u307e\u305b\u3093\u3002
48 | [error]_61 = \u30c7\u30fc\u30bf\u5024\u304c\u9577\u3059\u304e\u307e\u3059\u3002
49 | [error]_62 = \u6587\u5b57\u5217\u5909\u6570\u306e\u9577\u3055\u306f\u300132767 \u30d0\u30a4\u30c8\u3092\u8d85\u3048\u308b\u3053\u3068\u306f\u3067\u304d\u307e\u305b\u3093\u3002
50 | [error]_64 = \u5143\u306e\u30c7\u30fc\u30bf \u30bb\u30c3\u30c8\u306e\u30c7\u30fc\u30bf\u5024\u3084\u5909\u6570\u60c5\u5831\u3092\u5909\u66f4\u3059\u308b\u3053\u3068\u306f\u3067\u304d\u307e\u305b\u3093\u3002
51 | [warning]_67 = \u73fe\u5728\u306e\u5206\u5272\u306e\u6700\u5f8c\u306b\u5230\u9054\u3057\u307e\u3057\u305f\u3002
52 | [error]_70 = \u30e9\u30d9\u30eb\u306e\u9577\u3055\u304c\u9577\u3059\u304e\u307e\u3059\u3002
53 | [error]_71 = \u5024\u306e\u9577\u3055\u304c\u9577\u3059\u304e\u307e\u3059\u3002
54 | [error]_82 = \u30a2\u30af\u30c6\u30a3\u30d6 \u30c7\u30fc\u30bf\u30bb\u30c3\u30c8\u306b\u5909\u6570\u304c\u3042\u308a\u307e\u305b\u3093\u3002
55 | [error]_86 = \u3053\u306e\u64cd\u4f5c\u3092\u5b9f\u884c\u3059\u308b\u306b\u306f\u30a2\u30af\u30c6\u30a3\u30d6 \u30c7\u30fc\u30bf \u30bd\u30fc\u30b9\u304c\u5fc5\u8981\u3067\u3059\u3002
56 | [error]_87 = \u30c7\u30fc\u30bf \u30bb\u30c3\u30c8\u540d\u304c\u7121\u52b9\u3067\u3059\u3002
57 | [error]_88 = \u3053\u306e\u30e1\u30bd\u30c3\u30c9\u306f SetDictionaryToSPSS \u3068 EndDataStep \u306e\u9593\u3067\u306e\u307f\u547c\u3073\u51fa\u3059\u3053\u3068\u304c\u3067\u304d\u307e\u3059\u3002
58 | [error]_89 = \u95a2\u6570\u547c\u3073\u51fa\u3057\u304c\u7121\u52b9\u3067\u3059\u3002 \u95a2\u6570\u306f\u3001\u30c7\u30fc\u30bf \u30bb\u30c3\u30c8\u4f5c\u6210\u6642\u3001\u307e\u305f\u306f\u30e6\u30fc\u30b6\u30fc\u624b\u9806\u3067\u306e\u307f\u547c\u3073\u51fa\u3059\u3053\u3068\u304c\u3067\u304d\u307e\u3059\u3002
59 | [error]_90 = \u30e6\u30fc\u30b6\u30fc\u624b\u9806\u5185\u3067\u30a2\u30af\u30c6\u30a3\u30d6 \u30c7\u30fc\u30bf \u30bb\u30c3\u30c8\u3092\u4f5c\u6210\u3067\u304d\u307e\u305b\u3093\u3002
60 | [error]_91 = \u540c\u3058\u540d\u524d\u306e\u30c7\u30fc\u30bf \u30bb\u30c3\u30c8\u304c\u3059\u3067\u306b\u5b58\u5728\u3057\u3066\u3044\u307e\u3059\u3002
61 | [error]_92 = \u30c7\u30fc\u30bf \u30bb\u30c3\u30c8\u306e\u4f5c\u6210\u4e2d\u306f\u3001\u3053\u306e\u30a2\u30af\u30b7\u30e7\u30f3\u3092\u5b9f\u884c\u3059\u308b\u3053\u3068\u306f\u3067\u304d\u307e\u305b\u3093\u3002
62 | [error]_94 = \u4fdd\u7559\u4e2d\u306e\u5909\u63db\u304c\u3042\u308b\u5834\u5408\u3001\u30c7\u30fc\u30bf \u30bb\u30c3\u30c8\u3092\u4f5c\u6210\u3059\u308b\u3053\u3068\u306f\u3067\u304d\u307e\u305b\u3093\u3002
63 | [error]_96 = \u6307\u5b9a\u3055\u308c\u305f\u5c5e\u6027\u540d\u304c\u898b\u3064\u304b\u308a\u307e\u305b\u3093\u3002
64 | [error]_99 = \u6307\u5b9a\u3055\u308c\u305f\u30c7\u30fc\u30bf \u30bb\u30c3\u30c8\u3092\u4f5c\u6210\u3067\u304d\u307e\u305b\u3093\u3002
65 | [error]_100 = \u591a\u91cd\u56de\u7b54\u30bb\u30c3\u30c8\u306e\u5b9a\u7fa9\u304c\u7121\u52b9\u3067\u3059\u3002
66 | [error]_301 = CF \u30a2\u30d7\u30e9\u30a4\u30e4\u30fc \u30ce\u30fc\u30c9\u306b\u30e2\u30c7\u30eb\u304c\u3042\u308a\u307e\u305b\u3093\u3002\u30d3\u30eb\u30c0\u30fc \u30ce\u30fc\u30c9\u306e SetModel \u3092\u78ba\u8a8d\u3057\u3066\u304f\u3060\u3055\u3044\u3002
67 | [error]_402 = \u30d5\u30a3\u30fc\u30eb\u30c9 \u30a4\u30f3\u30c7\u30c3\u30af\u30b9\u304c\u7121\u52b9\u3067\u3059\u3002
68 | [warning]_404 = \u30d5\u30a3\u30fc\u30eb\u30c9\u306b\u30e9\u30d9\u30eb\u304c\u3042\u308a\u307e\u305b\u3093\u3002
69 | [warning]_403 = \u30d5\u30a3\u30fc\u30eb\u30c9\u306e\u30e9\u30d9\u30eb\u3068\u5024\u304c\u4e00\u81f4\u3057\u307e\u305b\u3093\u3002
70 | [error]_999999997 = \u4e0d\u660e\u306a\u30a8\u30e9\u30fc\u3002
71 | [error]_999999998 = \u51e6\u7406\u304c\u30e6\u30fc\u30b6\u30fc\u306b\u3088\u3063\u3066\u4e2d\u65ad\u3055\u308c\u307e\u3057\u305f\u3002
72 | [error]_999999999 = \u4e0d\u660e\u306a\u30a8\u30e9\u30fc\u3002
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = R CF \u30b3\u30f3\u30dd\u30fc\u30cd\u30f3\u30c8\u306e\u30c7\u30fc\u30bf \u30e2\u30c7\u30eb\u5f62\u5f0f\u304c\u7121\u52b9\u3067\u3059\u3002
78 | [RError]_1002 = \u30c7\u30fc\u30bf \u30e2\u30c7\u30eb\u5185\u306e\u30d5\u30a3\u30fc\u30eb\u30c9\u540d\u304c\u7121\u52b9\u3067\u3059\u3002 \u91cd\u8907\u3057\u305f\u5024\u304c\u5b58\u5728\u3057\u307e\u3059\u3002
79 | [warning]_1003 = \u5024\u306e\u30e9\u30d9\u30eb\u3067\u91cd\u8907\u3057\u305f\u5024\u304c\u5b58\u5728\u3057\u307e\u3059\u3002
80 | [RError]_1004 = SetDataModel \u306e\u30d5\u30a3\u30fc\u30eb\u30c9 \u30b9\u30c8\u30ec\u30fc\u30b8\u304c\u7121\u52b9\u3067\u3059\u3002
81 | [RError]_1005 = SetDataModel \u306e\u30d5\u30a3\u30fc\u30eb\u30c9\u6307\u6a19\u304c\u7121\u52b9\u3067\u3059\u3002
82 | [RError]_1006 = SetDataModel \u306e\u30d5\u30a3\u30fc\u30eb\u30c9\u5f62\u5f0f\u304c\u7121\u52b9\u3067\u3059\u3002
83 | [RError]_1007 = SetDataModel \u306e\u30d5\u30a3\u30fc\u30eb\u30c9\u306e\u5f79\u5272\u304c\u7121\u52b9\u3067\u3059\u3002
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = \u5f15\u6570\u5185\u306e\u30d5\u30a3\u30fc\u30eb\u30c9\u540d\u304c\u7121\u52b9\u3067\u3059\u3002
88 | [RError]_1021 = \u30d5\u30a3\u30fc\u30eb\u30c9\u306e\u6b20\u640d\u5024\u304c\u7121\u52b9\u3067\u3059\u3002
89 | [RError]_1022 = \u30d5\u30e9\u30b0\u578b\u30d5\u30a3\u30fc\u30eb\u30c9\u306b\u5024\u304c\u3042\u308a\u307e\u305b\u3093\u3002
90 |
91 | ## data
92 | [RError]_1008 = \u5f15\u6570 factorMode \u306e\u5024\u304c\u7121\u52b9\u3067\u3059 (\u300cnone\u300d\u3001\u300clevels\u300d\u3001\u300clabels\u300d\u306e\u3044\u305a\u308c\u304b\u3067\u306a\u3051\u308c\u3070\u306a\u308a\u307e\u305b\u3093)\u3002
93 | [RError]_1009 = \u5f15\u6570 rDate \u306e\u5024\u304c\u7121\u52b9\u3067\u3059 (\u300cnone\u300d\u3001\u300cPOSIXct\u300d\u3001\u300cPOSIXlt\u300d\u306e\u3044\u305a\u308c\u304b\u3067\u306a\u3051\u308c\u3070\u306a\u308a\u307e\u305b\u3093)\u3002
94 | [RError]_1010 = \u5f15\u6570 missingValue \u306e\u5024\u304c\u7121\u52b9\u3067\u3059 (NA\u3001NaN\u3001\u300casis\u300d\u306e\u3044\u305a\u308c\u304b\u3067\u306a\u3051\u308c\u3070\u306a\u308a\u307e\u305b\u3093)\u3002
95 | [RError]_1011 = \u95a2\u6570\u547c\u3073\u51fa\u3057\u304c\u7121\u52b9\u3067\u3059\u3002 \u95a2\u6570\u3092\u547c\u3073\u51fa\u3059\u306b\u306f\u3001\u6700\u521d\u306b SetDataModel \u3092\u547c\u3073\u51fa\u3059\u5fc5\u8981\u304c\u3042\u308a\u307e\u3059\u3002
96 | [RError]_1012 = \u30c7\u30fc\u30bf\u3068\u30c7\u30fc\u30bf \u30e2\u30c7\u30eb\u304c\u4e00\u81f4\u3057\u307e\u305b\u3093\u3002
97 |
98 | [RError]_1013 = GetOutputsNames \u306e\u30a4\u30f3\u30c7\u30c3\u30af\u30b9\u304c\u7121\u52b9\u3067\u3059\u3002
99 | [RError]_1014 = \u30b0\u30e9\u30d5\u30a3\u30c3\u30af\u540d\u307e\u305f\u306f\u30d1\u30b9\u304c\u7121\u52b9\u3067\u3059\u3002
100 | [RError]_1015 = \u30b0\u30e9\u30d5\u30a3\u30c3\u30af\u306e\u5f62\u5f0f\u304c\u7121\u52b9\u3067\u3059 (\u300cJPG\u300d\u3001\u300cPNG\u300d\u3001\u300cBMP\u300d\u306e\u3044\u305a\u308c\u304b\u3067\u306a\u3051\u308c\u3070\u306a\u308a\u307e\u305b\u3093)\u3002
101 | [RError]_1016 = \u6570\u5024\u578b\u306e\u5f15\u6570\u304c\u5fc5\u8981\u3067\u3059\u3002
102 | [RError]_1017 = \u6574\u6570\u306e\u5f15\u6570\u304c\u5fc5\u8981\u3067\u3059\u3002
103 | [RError]_1018 = \u30d6\u30fc\u30eb\u578b\u306e\u5f15\u6570\u304c\u5fc5\u8981\u3067\u3059\u3002
104 | [RError]_1019 = \u5f15\u6570\u306e\u5909\u6570\u306f\u3001\u6587\u5b57\u5217\u3001\u30d9\u30af\u30c8\u30eb\u3001\u307e\u305f\u306f\u30ea\u30b9\u30c8\u3067\u306a\u3051\u308c\u3070\u306a\u308a\u307e\u305b\u3093\u3002
105 |
106 | # General errors
107 | SPSSError = IBM SPSS CF \u30a8\u30e9\u30fc
108 | SPSSWarning = IBM SPSS CF \u8b66\u544a
109 | error_code = \u30a8\u30e9\u30fc \u30b3\u30fc\u30c9
110 | with_message = \u30e1\u30c3\u30bb\u30fc\u30b8\u3042\u308a
111 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_ko.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = \uc624\ub958 \uc5c6\uc74c.
13 | [ok]_1 = \uc8fc\uc11d.
14 | [warning]_2 = \uacbd\uace0.
15 | [error]_3 = \uc2ec\uac01\ud55c \uc624\ub958.
16 | [error]_4 = \uce58\uba85\uc801 \uc624\ub958.
17 | [error]_5 = \ubcf5\uad6c\ud560 \uc218 \uc5c6\ub294 \uc624\ub958.
18 | [error]_6 = \uba85\uacbd \uad6c\ubb38 \uc624\ub958.
19 | [error]_401 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \uc9c0\uc218.
20 | [error]_11 = XML \uc791\uc5c5\uacf5\uac04\uc5d0 \uc624\ube0c\uc81d\ud2b8\ub97c \ucd94\uac00\ud560 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
21 | [error]_12 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud578\ub4e4 \uc624\ube0c\uc81d\ud2b8.
22 | [error]_13 = XMl \uc791\uc5c5\uacf5\uac04 \uc624\ube0c\uc81d\ud2b8\ub97c \uc81c\uac70\ud560 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
23 | [error]_15 = \uacb0\uacfc\ub97c \uac00\uc838\uc62c \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
24 | [error]_16 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \uac12.
25 | [warning]_20 = \uae30\uc874 XML \uc791\uc5c5 \uacf5\uac04 \ud578\ub4e4\uc744 \uacb9\uccd0\uc37c\uc2b5\ub2c8\ub2e4.
26 | [error]_21 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 XPath \ud45c\ud604\uc2dd.
27 | [error]_22 = XML \uc624\ub958.
28 | [warning]_23 = \ucd94\uac00 \ub370\uc774\ud130\ub97c \uc77d\uc744 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
29 | [error]_24 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ub370\uc774\ud130 \uc720\ud615.
30 | [error]_25 = \uc911\ubcf5\ubcc0\uc218 \uc774\ub984.
31 | [error]_26 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ubcc0\uc218 \uc720\ud615.
32 | [error]_27 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ubcc0\uc218 \uc774\ub984.
33 | [error]_30 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ucf00\uc774\uc2a4.
34 | [error]_31 = \ubd84\ud560 \ud30c\uc77c \ucc98\ub9ac\ub97c \uc704\ud55c \ub370\uc774\ud130 \uc5f0\uacb0\uc774 \uc5f4\ub824 \uc788\uc73c\uba74 \uc774 \uc870\uce58\ub97c \uc644\ub8cc\ud560 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
35 | [error]_32 = \uc0ac\uc6a9\uc790 \ud504\ub85c\uc2dc\uc800\uac00 \uc2e4\ud589\ub418\uace0 \uc788\uc2b5\ub2c8\ub2e4.
36 | [error]_34 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \uce21\uc815 \uc218\uc900.
37 | [error]_36 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \uacb0\uce21\uac12 \ud615\uc2dd.
38 | [error]_40 = \ud504\ub85c\uc2dc\uc800 \ub370\uc774\ud130 \uc18c\uc2a4\uac00 \ud544\uc694\ud569\ub2c8\ub2e4.
39 | [error]_44 = \ud65c\uc131 \ub370\uc774\ud130 \uc138\ud2b8\uac00 \ube44\uc5b4 \uc788\uc2b5\ub2c8\ub2e4.
40 | [error]_47 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud615\uc2dd \uc720\ud615.
41 | [error]_48 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud615\uc2dd \ub108\ube44.
42 | [error]_49 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \uc18c\uc218\uc810.
43 | [error]_54 = \ud65c\uc131 \ub370\uc774\ud130 \uc138\ud2b8\uc5d0 \uc0ac\uc6a9 \uac00\ub2a5\ud55c \ub370\uc774\ud130\uac00 \ub354 \uc5c6\uc2b5\ub2c8\ub2e4.
44 | [error]_56 = \ubb38\uc790\uc5f4 \ubcc0\uc218\ub9cc \ud5c8\uc6a9\ub429\ub2c8\ub2e4.
45 | [error]_57 = \uc22b\uc790 \ubcc0\uc218\ub9cc \ud5c8\uc6a9\ub429\ub2c8\ub2e4.
46 | [error]_58 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \uc18d\uc131 \uc774\ub984.
47 | [error]_59 = \ubb38\uc790\uc5f4 \ubcc0\uc218\uc758 \uc0ac\uc6a9\uc790 \uacb0\uce21\uac12 \uae38\uc774\ub294 8\uc790 \uc774\ud558\uc5ec\uc57c \ud569\ub2c8\ub2e4.
48 | [error]_61 = \ub370\uc774\ud130 \uac12\uc774 \ub108\ubb34 \uae41\ub2c8\ub2e4.
49 | [error]_62 = \ubb38\uc790\uc5f4 \ubcc0\uc218\uc758 \uae38\uc774\ub294 32767\ubc14\uc774\ud2b8\ub97c \ucd08\uacfc\ud560 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
50 | [error]_64 = \uc6d0\ub798 \ub370\uc774\ud130 \uc138\ud2b8\uc5d0\uc11c \ub370\uc774\ud130 \uac12 \ub610\ub294 \ubcc0\uc218 \uc815\ubcf4\ub97c \ubcc0\uacbd\ud560 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
51 | [warning]_67 = \ud604\uc7ac \ubd84\ud560\uc758 \ub05d\uc5d0 \ub3c4\ub2ec\ud588\uc2b5\ub2c8\ub2e4.
52 | [error]_70 = \ub808\uc774\ube14 \uae38\uc774\uac00 \ub108\ubb34 \uae41\ub2c8\ub2e4.
53 | [error]_71 = \uac12 \uae38\uc774\uac00 \ub108\ubb34 \uae41\ub2c8\ub2e4.
54 | [error]_82 = \ud574\ub2f9 \ubcc0\uc218\uac00 \ud65c\uc131 \ub370\uc774\ud130 \uc138\ud2b8\uc5d0 \uc5c6\uc2b5\ub2c8\ub2e4.
55 | [error]_86 = \uc774 \uc870\uce58\ub97c \uc644\ub8cc\ud558\ub824\uba74 \ud65c\uc131 \ub370\uc774\ud130 \uc18c\uc2a4\uac00 \ud544\uc694\ud569\ub2c8\ub2e4.
56 | [error]_87 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ub370\uc774\ud130 \uc138\ud2b8 \uc774\ub984.
57 | [error]_88 = \uc774 \uba54\uc18c\ub4dc\ub294 SetDictionaryToSPSS \ubc0f EndDataStep \uc0ac\uc774\uc5d0\uc11c\ub9cc \ud638\ucd9c\ud560 \uc218 \uc788\uc2b5\ub2c8\ub2e4.
58 | [error]_89 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud568\uc218 \ud638\ucd9c. \ud568\uc218\ub294 \ub370\uc774\ud130 \uc138\ud2b8\ub97c \uc791\uc131\ud558\ub294 \ub3d9\uc548 \ub610\ub294 \uc0ac\uc6a9\uc790 \ud504\ub85c\uc2dc\uc800 \ub0b4\uc5d0\uc11c\ub9cc \ud638\ucd9c\ud560 \uc218 \uc788\uc2b5\ub2c8\ub2e4.
59 | [error]_90 = \uc0ac\uc6a9\uc790 \ud504\ub85c\uc2dc\uc800 \ub0b4\uc5d0 \ud65c\uc131 \ub370\uc774\ud130 \uc138\ud2b8\ub97c \uc791\uc131\ud560 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
60 | [error]_91 = \ub3d9\uc77c\ud55c \uc774\ub984\uc758 \ub370\uc774\ud130 \uc138\ud2b8\uac00 \uc774\ubbf8 \uc788\uc2b5\ub2c8\ub2e4.
61 | [error]_92 = \ub370\uc774\ud130 \uc138\ud2b8 \uc791\uc131\uc774 \uc9c4\ud589 \uc911\uc778 \ub3d9\uc548 \uc774 \uc870\uce58\ub97c \uc644\ub8cc\ud560 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
62 | [error]_94 = \ubcf4\ub958 \uc911\uc778 \ubcc0\ud658\uc774 \uc788\uc73c\uba74 \ub370\uc774\ud130 \uc138\ud2b8\ub97c \uc791\uc131\ud560 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
63 | [error]_96 = \uc9c0\uc815\ub41c \uc18d\uc131 \uc774\ub984\uc744 \ucc3e\uc744 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
64 | [error]_99 = \uc9c0\uc815\ub41c \ub370\uc774\ud130 \uc138\ud2b8\ub97c \uc791\uc131\ud560 \uc218 \uc5c6\uc2b5\ub2c8\ub2e4.
65 | [error]_100 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ub2e4\uc911 \uc751\ub2f5 \uc138\ud2b8 \uc815\uc758\uc785\ub2c8\ub2e4.
66 | [error]_301 = CF \uc801\uc6a9\uc790 \ub178\ub4dc\uc5d0 \ubaa8\ub378\uc774 \uc5c6\uc2b5\ub2c8\ub2e4. \uc791\uc131\uae30 \ub178\ub4dc\uc5d0 SetModel\uc774 \uc788\ub294\uc9c0 \ud655\uc778\ud558\uc2ed\uc2dc\uc624.
67 | [error]_402 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud544\ub4dc \uc778\ub371\uc2a4\uc785\ub2c8\ub2e4.
68 | [warning]_404 = \ud544\ub4dc\uc5d0 \ub808\uc774\ube14\uc774 \uc5c6\uc2b5\ub2c8\ub2e4.
69 | [warning]_403 = \ud544\ub4dc \ub808\uc774\ube14\uacfc \uac12\uc774 \uc77c\uce58\ud558\uc9c0 \uc54a\uc2b5\ub2c8\ub2e4.
70 | [error]_999999997 = \uc54c \uc218 \uc5c6\ub294 \uc624\ub958.
71 | [error]_999999998 = \uc0ac\uc6a9\uc790\uac00 \ucc98\ub9ac\ub97c \uc911\ub2e8\ud588\uc2b5\ub2c8\ub2e4.
72 | [error]_999999999 = \uc54c \uc218 \uc5c6\ub294 \uc624\ub958.
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 R CF \uad6c\uc131\uc694\uc18c \ub370\uc774\ud130 \ubaa8\ub378 \ud615\uc2dd.
78 | [RError]_1002 = \ub370\uc774\ud130 \ubaa8\ub378\uc5d0 \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud544\ub4dc \uc774\ub984\uc774 \uc788\uc2b5\ub2c8\ub2e4. \uc911\ubcf5\ub41c \uac12\uc774 \uc788\uc2b5\ub2c8\ub2e4.
79 | [warning]_1003 = \uac12 \ub808\uc774\ube14\uc5d0 \ub300\ud574 \uc911\ubcf5\ub41c \uac12\uc774 \uc788\uc2b5\ub2c8\ub2e4.
80 | [RError]_1004 = SetDataModel\uc5d0 \ub300\ud574 \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud544\ub4dc \uc800\uc7a5 \uacf5\uac04\uc774 \uc788\uc2b5\ub2c8\ub2e4.
81 | [RError]_1005 = SetDataModel\uc5d0 \ub300\ud574 \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud544\ub4dc \uce21\ub3c4\uac00 \uc788\uc2b5\ub2c8\ub2e4.
82 | [RError]_1006 = SetDataModel\uc5d0 \ub300\ud574 \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud544\ub4dc \ud615\uc2dd\uc774 \uc788\uc2b5\ub2c8\ub2e4.
83 | [RError]_1007 = SetDataModel\uc5d0 \ub300\ud574 \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud544\ub4dc \uc5ed\ud560\uc774 \uc788\uc2b5\ub2c8\ub2e4.
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud544\ub4dc \uc774\ub984.
88 | [RError]_1021 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \uacb0\uce21\uac12 \ud615\uc2dd.
89 | [RError]_1022 = \ud50c\ub798\uadf8 \ud544\ub4dc\uc5d0 \uac12\uc774 \uc5c6\uc2b5\ub2c8\ub2e4.
90 |
91 | ## data
92 | [RError]_1008 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 factorMode \uc778\uc218 \uac12("none", "levels" \ub610\ub294 "labels"\uc5ec\uc57c \ud568)
93 | [RError]_1009 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 rDate \uc778\uc218 \uac12("none", "POSIXct" \ub610\ub294 "POSIXlt"\uc5ec\uc57c \ud568)
94 | [RError]_1010 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 missingValue \uc778\uc218 \uac12(NA, NaN \ub610\ub294 "asis"\uc5ec\uc57c \ud568)
95 | [RError]_1011 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \ud568\uc218 \ud638\ucd9c. \ud568\uc218\ub294 SetDataModel\uc744 \ud638\ucd9c\ud55c \ud6c4\uc5d0\ub9cc \ud638\ucd9c\ud560 \uc218 \uc788\uc2b5\ub2c8\ub2e4.
96 | [RError]_1012 = \ub370\uc774\ud130 \ubc0f \ub370\uc774\ud130 \ubaa8\ub378\uc774 \uc77c\uce58\ud558\uc9c0 \uc54a\uc2b5\ub2c8\ub2e4.
97 |
98 | [RError]_1013 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 GetOutputsNames \uc778\ub371\uc2a4
99 | [RError]_1014 = \uc720\ud6a8\ud558\uc9c0 \uc54a\uc740 \uadf8\ub798\ud53d \uc774\ub984 \ub610\ub294 \uacbd\ub85c.
100 | [RError]_1015 = \uc62c\ubc14\ub974\uc9c0 \uc54a\uc740 \uadf8\ub798\ud53d \ud615\uc2dd("JPG", "PNG" \ub610\ub294 "BMP"\uc5ec\uc57c \ud568).
101 | [RError]_1016 = \uc22b\uc790 \uc778\uc218\uac00 \ud544\uc694\ud569\ub2c8\ub2e4.
102 | [RError]_1017 = \uc815\uc218 \uc778\uc218\uac00 \ud544\uc694\ud569\ub2c8\ub2e4.
103 | [RError]_1018 = \ubd80\uc6b8 \uc778\uc218\uac00 \ud544\uc694\ud569\ub2c8\ub2e4.
104 | [RError]_1019 = \uc778\uc218 \ubcc0\uc218\ub294 \ubb38\uc790\uc5f4, \ubca1\ud130 \ub610\ub294 \ubaa9\ub85d\uc774\uc5b4\uc57c \ud569\ub2c8\ub2e4.
105 |
106 | # General errors
107 | SPSSError = IBM SPSS CF \uc624\ub958
108 | SPSSWarning = IBM SPSS CF \uacbd\uace0
109 | error_code = \uc624\ub958 \ucf54\ub4dc\ub294 \ub2e4\uc74c\uacfc \uac19\uc2b5\ub2c8\ub2e4.
110 | with_message = \uba54\uc2dc\uc9c0 \ud3ec\ud568
111 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_pl.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = Brak b\u0142\u0119du.
13 | [ok]_1 = Komentarz.
14 | [warning]_2 = Ostrze\u017cenie.
15 | [error]_3 = Powa\u017cny b\u0142\u0105d.
16 | [error]_4 = B\u0142\u0105d krytyczny.
17 | [error]_5 = Katastrofalny b\u0142\u0105d.
18 | [error]_6 = B\u0142\u0105d sk\u0142adni polecenia.
19 | [error]_401 = Nieprawid\u0142owy indeks.
20 | [error]_11 = Nie mo\u017cna doda\u0107 obiektu do obszaru roboczego XML.
21 | [error]_12 = Nieprawid\u0142owy obiekt uchwytu.
22 | [error]_13 = Nie mo\u017cna usun\u0105\u0107 obiektu obszaru roboczego XML.
23 | [error]_15 = Nie mo\u017cna uzyska\u0107 wyniku.
24 | [error]_16 = Nieprawid\u0142owa warto\u015b\u0107.
25 | [warning]_20 = Istniej\u0105cy uchwyt obszaru roboczego XML zosta\u0142 zast\u0105piony.
26 | [error]_21 = Nieprawid\u0142owe wyra\u017cenie XPath.
27 | [error]_22 = B\u0142\u0105d kodu XML.
28 | [warning]_23 = Nie mo\u017cna odczyta\u0107 dalszych danych.
29 | [error]_24 = Nieprawid\u0142owy typ danych
30 | [error]_25 = Zduplikowana nazwa zmiennej.
31 | [error]_26 = Nieprawid\u0142owy typ zmiennej.
32 | [error]_27 = Nieprawid\u0142owa nazwa zmiennej.
33 | [error]_30 = Nieprawid\u0142owa obserwacja.
34 | [error]_31 = Nie mo\u017cna uko\u0144czy\u0107 tej czynno\u015bci, gdy otwarte jest po\u0142\u0105czenie danych s\u0142u\u017c\u0105ce do przetwarzania plik\u00f3w podzielonych.
35 | [error]_32 = Trwa dzia\u0142anie procedury u\u017cytkownika.
36 | [error]_34 = Nieprawid\u0142owy poziom pomiaru.
37 | [error]_36 = Nieprawid\u0142owy format warto\u015bci brakuj\u0105cych.
38 | [error]_40 = Wymagane jest \u017ar\u00f3d\u0142o danych procedury.
39 | [error]_44 = Aktywny zbi\u00f3r danych jest pusty.
40 | [error]_47 = Nieprawid\u0142owy typ formatu.
41 | [error]_48 = Nieprawid\u0142owa szeroko\u015b\u0107 formatu.
42 | [error]_49 = Nieprawid\u0142owy punkt dziesi\u0119tny.
43 | [error]_54 = W aktywnym zbiorze danych nie ma wi\u0119cej dost\u0119pnych danych.
44 | [error]_56 = Dozwolone s\u0105 tylko zmienne \u0142a\u0144cuchowe.
45 | [error]_57 = Dozwolone s\u0105 tylko zmienne numeryczne.
46 | [error]_58 = Nieprawid\u0142owa nazwa atrybutu.
47 | [error]_59 = D\u0142ugo\u015b\u0107 brakuj\u0105cej warto\u015bci u\u017cytkownika w przypadku zmiennej \u0142a\u0144cuchowej musi wynosi\u0107 8 znak\u00f3w lub mniej.
48 | [error]_61 = Zbyt d\u0142uga warto\u015b\u0107 danych.
49 | [error]_62 = D\u0142ugo\u015b\u0107 zmiennej \u0142a\u0144cuchowej nie mo\u017ce przekracza\u0107 32767 bajt\u00f3w.
50 | [error]_64 = Nie mo\u017cna zmieni\u0107 warto\u015bci danych lub informacji o zmiennej w oryginalnym zbiorze danych.
51 | [warning]_67 = Osi\u0105gni\u0119to koniec aktualnego podzia\u0142u.
52 | [error]_70 = Etykieta jest zbyt d\u0142uga.
53 | [error]_71 = Warto\u015b\u0107 jest zbyt d\u0142uga.
54 | [error]_82 = Zmienna nie znajduje si\u0119 w aktywnym zbiorze danych.
55 | [error]_86 = W celu uko\u0144czenia tej czynno\u015bci wymagane jest aktywne \u017ar\u00f3d\u0142o danych.
56 | [error]_87 = Nieprawid\u0142owa nazwa zbioru danych.
57 | [error]_88 = T\u0119 metod\u0119 mo\u017cna wywo\u0142a\u0107 tylko mi\u0119dzy SetDictionaryToSPSS i EndDataStep.
58 | [error]_89 = Nieprawid\u0142owe wywo\u0142anie funkcji. Funkcj\u0119 mo\u017cna wywo\u0142a\u0107 tylko podczas tworzenia zbioru danych lub w obr\u0119bie procedury u\u017cytkownika.
59 | [error]_90 = Nie mo\u017cna utworzy\u0107 aktywnego zbioru danych w obr\u0119bie procedury u\u017cytkownika.
60 | [error]_91 = Zbi\u00f3r danych o tej samej nazwie ju\u017c istnieje.
61 | [error]_92 = Nie mo\u017cna uko\u0144czy\u0107 tej czynno\u015bci, gdy trwa tworzenie zbioru danych.
62 | [error]_94 = Nie mo\u017cna utworzy\u0107 zbioru danych, gdy trwaj\u0105 przekszta\u0142cenia.
63 | [error]_96 = Nie mo\u017cna znale\u017a\u0107 okre\u015blonej nazwy atrybutu.
64 | [error]_99 = Nie mo\u017cna utworzy\u0107 okre\u015blonego zbioru danych.
65 | [error]_100 = Nieprawid\u0142owa definicja zestawu wielokrotnych odpowiedzi.
66 | [error]_301 = Brak modelu w w\u0119\u017ale wprowadzaj\u0105cym CF. Upewnij si\u0119, \u017ce w w\u0119\u017ale kreatora okre\u015blono zmienn\u0105 SetModel.
67 | [error]_402 = Nieprawid\u0142owy indeks zmiennej.
68 | [warning]_404 = Zmienne nie maj\u0105 etykiet.
69 | [warning]_403 = Etykiety zmiennych i warto\u015bci nie s\u0105 zgodne.
70 | [error]_999999997 = Nieznany b\u0142\u0105d.
71 | [error]_999999998 = Przetwarzanie zosta\u0142o przerwane przez u\u017cytkownika.
72 | [error]_999999999 = Nieznany b\u0142\u0105d.
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = Nieprawid\u0142owy format modelu danych sk\u0142adnika CF pakietu R.
78 | [RError]_1002 = Nieprawid\u0142owa nazwa zmiennej w modelu danych. Wyst\u0119puj\u0105 powielone warto\u015bci.
79 | [warning]_1003 = W przypadku etykiet warto\u015bci wyst\u0119puj\u0105 powielone warto\u015bci.
80 | [RError]_1004 = Nieprawid\u0142owy spos\u00f3b zapisu w pami\u0119ci dla SetDataModel.
81 | [RError]_1005 = Nieprawid\u0142owa miara zmiennej dla SetDataModel.
82 | [RError]_1006 = Nieprawid\u0142owy format zmiennej dla SetDataModel.
83 | [RError]_1007 = Nieprawid\u0142owa rola zmiennej dla SetDataModel.
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = Nieprawid\u0142owa nazwa zmiennej w argumencie.
88 | [RError]_1021 = Nieprawid\u0142owa brakuj\u0105ca warto\u015b\u0107 zmiennej.
89 | [RError]_1022 = Zmienna typu flaga nie ma warto\u015bci.
90 |
91 | ## data
92 | [RError]_1008 = Nieprawid\u0142owa warto\u015b\u0107 argumentu factorMode (musi by\u0107 "none", "levels" lub "labels").
93 | [RError]_1009 = Nieprawid\u0142owa warto\u015b\u0107 argumentu rDate (musi by\u0107 "none", "POSIXct" lub "POSIXlt").
94 | [RError]_1010 = Nieprawid\u0142owa warto\u015b\u0107 argumentu missingValue (musi by\u0107 NA, NaN lub "asis").
95 | [RError]_1011 = Nieprawid\u0142owe wywo\u0142anie funkcji. Funkcj\u0119 mo\u017cna wywo\u0142a\u0107 tylko po wywo\u0142aniu SetDataModel.
96 | [RError]_1012 = Dane i model danych nie s\u0105 zgodne.
97 |
98 | [RError]_1013 = Nieprawid\u0142owy indeks GetOutputsNames.
99 | [RError]_1014 = Nieprawid\u0142owa \u015bcie\u017cka lub nazwa grafiki.
100 | [RError]_1015 = Nieprawid\u0142owy format grafiki (musi by\u0107 "JPG", "PNG" lub "BMP").
101 | [RError]_1016 = Oczekiwany argument numeryczny.
102 | [RError]_1017 = Oczekiwany argument - liczba ca\u0142kowita.
103 | [RError]_1018 = Oczekiwany argument - warto\u015b\u0107 logiczna.
104 | [RError]_1019 = Zmienne argument\u00f3w musz\u0105 stanowi\u0107 \u0142a\u0144cuch, wektor lub list\u0119.
105 |
106 | # General errors
107 | SPSSError = B\u0142\u0105d CF IBM SPSS
108 | SPSSWarning = Ostrze\u017cenie CF IBM SPSS
109 | error_code = Kod b\u0142\u0119du to
110 | with_message = Z komunikatem
111 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_pt_BR.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = Nenhum erro.
13 | [ok]_1 = Coment\u00e1rio.
14 | [warning]_2 = Alerta.
15 | [error]_3 = Erro grave.
16 | [error]_4 = Erro fatal.
17 | [error]_5 = Erro catastr\u00f3fico.
18 | [error]_6 = Erro de sintaxe de comando.
19 | [error]_401 = \u00cdndice inv\u00e1lido.
20 | [error]_11 = N\u00e3o \u00e9 poss\u00edvel incluir objeto na \u00e1rea de trabalho XML.
21 | [error]_12 = Objeto de manipula\u00e7\u00e3o inv\u00e1lido.
22 | [error]_13 = N\u00e3o \u00e9 poss\u00edvel remover objeto da \u00e1rea de trabalho XML.
23 | [error]_15 = N\u00e3o \u00e9 poss\u00edvel obter resultado.
24 | [error]_16 = Valor inv\u00e1lido.
25 | [warning]_20 = A manipula\u00e7\u00e3o de uma \u00e1rea de trabalho XML existente foi sobrescrita.
26 | [error]_21 = Express\u00e3o XPath inv\u00e1lida.
27 | [error]_22 = Erro de XML.
28 | [warning]_23 = N\u00e3o \u00e9 poss\u00edvel ler mais dados.
29 | [error]_24 = Tipo de dados inv\u00e1lido.
30 | [error]_25 = Nome de vari\u00e1vel duplicado.
31 | [error]_26 = Tipo de vari\u00e1vel inv\u00e1lido.
32 | [error]_27 = Nome de vari\u00e1vel inv\u00e1lido.
33 | [error]_30 = Caso inv\u00e1lido.
34 | [error]_31 = N\u00e3o \u00e9 poss\u00edvel concluir esta a\u00e7\u00e3o enquanto a conex\u00e3o de dados para processar arquivos divididos estiver aberta.
35 | [error]_32 = Um Procedimento do Usu\u00e1rio est\u00e1 em execu\u00e7\u00e3o.
36 | [error]_34 = N\u00edvel de medi\u00e7\u00e3o inv\u00e1lido.
37 | [error]_36 = Formato do valor omisso inv\u00e1lido.
38 | [error]_40 = Uma Origem de Dados de Procedimento \u00e9 necess\u00e1ria.
39 | [error]_44 = O conjunto de dados ativo est\u00e1 vazio.
40 | [error]_47 = Tipo de formato inv\u00e1lido.
41 | [error]_48 = Largura de formato inv\u00e1lida.
42 | [error]_49 = V\u00edrgula decimal inv\u00e1lido.
43 | [error]_54 = N\u00e3o h\u00e1 mais nenhum dado dispon\u00edvel no conjunto de dados ativo.
44 | [error]_56 = Apenas vari\u00e1veis de sequ\u00eancia de caracteres s\u00e3o permitidas.
45 | [error]_57 = Apenas vari\u00e1veis num\u00e9ricas s\u00e3o permitidas.
46 | [error]_58 = Nome do atributo inv\u00e1lido.
47 | [error]_59 = O comprimento do valor omisso para o usu\u00e1rio para uma vari\u00e1vel de sequ\u00eancia de caracteres deve ser de 8 caracteres ou menos.
48 | [error]_61 = O valor dos dados \u00e9 muito longo.
49 | [error]_62 = O comprimento de uma vari\u00e1vel de sequ\u00eancia de caracteres n\u00e3o pode exceder 32767 bytes.
50 | [error]_64 = N\u00e3o \u00e9 poss\u00edvel alterar valores de dados ou informa\u00e7\u00f5es de vari\u00e1vel no conjunto de dados original.
51 | [warning]_67 = O fim da divis\u00e3o atual foi atingido.
52 | [error]_70 = O comprimento do r\u00f3tulo \u00e9 muito longo.
53 | [error]_71 = O comprimento do valor \u00e9 muito longo.
54 | [error]_82 = A vari\u00e1vel n\u00e3o est\u00e1 no conjunto de dados ativo.
55 | [error]_86 = Uma origem de dados ativos \u00e9 necess\u00e1ria para a conclus\u00e3o desta a\u00e7\u00e3o.
56 | [error]_87 = Nome do conjunto de dados inv\u00e1lido.
57 | [error]_88 = Este m\u00e9todo s\u00f3 pode ser chamado entre SetDictionaryToSPSS e EndDataStep.
58 | [error]_89 = Chamada de fun\u00e7\u00e3o inv\u00e1lida. A fun\u00e7\u00e3o s\u00f3 pode ser chamada durante a cria\u00e7\u00e3o do conjunto de dados ou dentro de um Procedimento do Usu\u00e1rio.
59 | [error]_90 = N\u00e3o \u00e9 poss\u00edvel criar um conjunto de dados ativo dentro de um Procedimento do Usu\u00e1rio.
60 | [error]_91 = Um conjunto de dados com o mesmo nome j\u00e1 existe.
61 | [error]_92 = N\u00e3o \u00e9 poss\u00edvel concluir esta a\u00e7\u00e3o enquanto a cria\u00e7\u00e3o do conjunto de dados est\u00e1 em processo.
62 | [error]_94 = N\u00e3o \u00e9 poss\u00edvel criar um conjunto de dados enquanto h\u00e1 transforma\u00e7\u00f5es pendentes.
63 | [error]_96 = N\u00e3o \u00e9 poss\u00edvel localizar o nome do atributo especificado.
64 | [error]_99 = N\u00e3o \u00e9 poss\u00edvel criar um conjunto de dados especificado.
65 | [error]_100 = Defini\u00e7\u00e3o do conjunto de m\u00faltiplas respostas inv\u00e1lida.
66 | [error]_301 = Nenhum modelo no N\u00f3 do Aplicador CF, certifique-se do SetModel no N\u00f3 Builder.
67 | [error]_402 = \u00cdndice de campos inv\u00e1lido.
68 | [warning]_404 = O campo n\u00e3o tem r\u00f3tulos.
69 | [warning]_403 = Os valores e os r\u00f3tulos do campo n\u00e3o correspondem.
70 | [error]_999999997 = Erro desconhecido.
71 | [error]_999999998 = O processamento foi interrompido pelo usu\u00e1rio.
72 | [error]_999999999 = Erro desconhecido.
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = Formato do Modelo de Dados do Componente CF R inv\u00e1lido.
78 | [RError]_1002 = Nome de campo inv\u00e1lido no modelo de dados. H\u00e1 valores duplicados presentes.
79 | [warning]_1003 = H\u00e1 valores duplicados presentes para os r\u00f3tulos de valor.
80 | [RError]_1004 = Armazenamento de campo inv\u00e1lido para SetDataModel.
81 | [RError]_1005 = Medida de campo inv\u00e1lida para SetDataModel.
82 | [RError]_1006 = Formato de campo inv\u00e1lido para SetDataModel.
83 | [RError]_1007 = Papel de campo inv\u00e1lido para SetDataModel.
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = Nome do campo inv\u00e1lido no argumento.
88 | [RError]_1021 = Valor omisso do campo inv\u00e1lido.
89 | [RError]_1022 = O campo de flag n\u00e3o possui valores.
90 |
91 | ## data
92 | [RError]_1008 = Valor inv\u00e1lido para argumento factorMode (deve ser "none", "levels" ou "labels").
93 | [RError]_1009 = Valor inv\u00e1lido para argumento rDate (deve ser "none", "POSIXct" ou "POSIXlt").
94 | [RError]_1010 = Valor inv\u00e1lido para argumento missingValue (deve ser NA, NaN ou "asis").
95 | [RError]_1011 = Chamada de fun\u00e7\u00e3o inv\u00e1lida. A fun\u00e7\u00e3o s\u00f3 pode ser chamada ap\u00f3s a chamada de SetDataModel.
96 | [RError]_1012 = Dados e modelo de dados n\u00e3o correspondem.
97 |
98 | [RError]_1013 = \u00cdndice inv\u00e1lido para GetOutputsNames.
99 | [RError]_1014 = Caminho ou nome do gr\u00e1fico inv\u00e1lido.
100 | [RError]_1015 = Formato gr\u00e1fico inv\u00e1lido (deve ser "JPG", "PNG" ou "BMP").
101 | [RError]_1016 = Esperado um argumento num\u00e9rico.
102 | [RError]_1017 = Esperado um argumento de n\u00famero inteiro.
103 | [RError]_1018 = Esperado um argumento booleano.
104 | [RError]_1019 = As vari\u00e1veis de argumento devem ser sequ\u00eancia, vetor ou lista.
105 |
106 | # General errors
107 | SPSSError = Erro do IBM SPSS CF
108 | SPSSWarning = Aviso do IBM SPSS CF
109 | error_code = O c\u00f3digo de erro \u00e9
110 | with_message = Com mensagem
111 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_ru.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = \u041d\u0435\u0442 \u043e\u0448\u0438\u0431\u043a\u0438.
13 | [ok]_1 = \u041a\u043e\u043c\u043c\u0435\u043d\u0442\u0430\u0440\u0438\u0439.
14 | [warning]_2 = \u041f\u0440\u0435\u0434\u0443\u043f\u0440\u0435\u0436\u0434\u0435\u043d\u0438\u0435.
15 | [error]_3 = \u0421\u0435\u0440\u044c\u0435\u0437\u043d\u0430\u044f \u043e\u0448\u0438\u0431\u043a\u0430.
16 | [error]_4 = \u041d\u0435\u0438\u0441\u043f\u0440\u0430\u0432\u0438\u043c\u0430\u044f \u043e\u0448\u0438\u0431\u043a\u0430.
17 | [error]_5 = \u041a\u0430\u0442\u0430\u0441\u0442\u0440\u043e\u0444\u0438\u0447\u0435\u0441\u043a\u0430\u044f \u043e\u0448\u0438\u0431\u043a\u0430.
18 | [error]_6 = \u041e\u0448\u0438\u0431\u043a\u0430 \u0432 \u0441\u0438\u043d\u0442\u0430\u043a\u0441\u0438\u0441\u0435 \u043a\u043e\u043c\u0430\u043d\u0434\u044b.
19 | [error]_401 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0438\u043d\u0434\u0435\u043a\u0441.
20 | [error]_11 = \u041d\u0435 \u0443\u0434\u0430\u043b\u043e\u0441\u044c \u0434\u043e\u0431\u0430\u0432\u0438\u0442\u044c \u043e\u0431\u044a\u0435\u043a\u0442 \u0432 \u0440\u0430\u0431\u043e\u0447\u0435\u0435 \u043f\u0440\u043e\u0441\u0442\u0440\u0430\u043d\u0441\u0442\u0432\u043e XML.
21 | [error]_12 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u043e\u0431\u044a\u0435\u043a\u0442 \u0445\u044d\u043d\u0434\u043b\u0430.
22 | [error]_13 = \u041d\u0435 \u0443\u0434\u0430\u043b\u043e\u0441\u044c \u0443\u0434\u0430\u043b\u0438\u0442\u044c \u043e\u0431\u044a\u0435\u043a\u0442 \u0440\u0430\u0431\u043e\u0447\u0435\u0433\u043e \u043f\u0440\u043e\u0441\u0442\u0440\u0430\u043d\u0441\u0442\u0432\u0430 XML.
23 | [error]_15 = \u041d\u0435 \u0443\u0434\u0430\u043b\u043e\u0441\u044c \u043f\u043e\u043b\u0443\u0447\u0438\u0442\u044c \u0440\u0435\u0437\u0443\u043b\u044c\u0442\u0430\u0442.
24 | [error]_16 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0435.
25 | [warning]_20 = \u0421\u0443\u0449\u0435\u0441\u0442\u0432\u0443\u044e\u0449\u0438\u0439 \u0445\u044d\u043d\u0434\u043b \u0440\u0430\u0431\u043e\u0447\u0435\u0433\u043e \u043f\u0440\u043e\u0441\u0442\u0440\u0430\u043d\u0441\u0442\u0432\u0430 XML \u0431\u044b\u043b \u043f\u0435\u0440\u0435\u0437\u0430\u043f\u0438\u0441\u0430\u043d.
26 | [error]_21 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0432\u044b\u0440\u0430\u0436\u0435\u043d\u0438\u0435 XPath.
27 | [error]_22 = \u041e\u0448\u0438\u0431\u043a\u0430 XML.
28 | [warning]_23 = \u041d\u0435 \u0443\u0434\u0430\u043b\u043e\u0441\u044c \u043f\u0440\u043e\u0447\u0438\u0442\u0430\u0442\u044c \u0434\u043e\u043f\u043e\u043b\u043d\u0438\u0442\u0435\u043b\u044c\u043d\u044b\u0435 \u0434\u0430\u043d\u043d\u044b\u0435.
29 | [error]_24 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0442\u0438\u043f \u0434\u0430\u043d\u043d\u044b\u0445.
30 | [error]_25 = \u041f\u043e\u0432\u0442\u043e\u0440\u0435\u043d\u0438\u0435 \u0438\u043c\u0435\u043d\u0438 \u043f\u0435\u0440\u0435\u043c\u0435\u043d\u043d\u043e\u0439.
31 | [error]_26 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0442\u0438\u043f \u043f\u0435\u0440\u0435\u043c\u0435\u043d\u043d\u043e\u0439.
32 | [error]_27 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0438\u043c\u044f \u043f\u0435\u0440\u0435\u043c\u0435\u043d\u043d\u043e\u0439.
33 | [error]_30 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0440\u0435\u0433\u0438\u0441\u0442\u0440 \u0441\u0438\u043c\u0432\u043e\u043b\u043e\u0432.
34 | [error]_31 = \u041d\u0435\u0432\u043e\u0437\u043c\u043e\u0436\u043d\u043e \u0437\u0430\u0432\u0435\u0440\u0448\u0438\u0442\u044c \u044d\u0442\u043e \u0434\u0435\u0439\u0441\u0442\u0432\u0438\u0435, \u043f\u043e\u043a\u0430 \u043e\u0442\u043a\u0440\u044b\u0442\u043e \u0441\u043e\u0435\u0434\u0438\u043d\u0435\u043d\u0438\u0435 \u0434\u0430\u043d\u043d\u044b\u0445 \u0434\u043b\u044f \u043e\u0431\u0440\u0430\u0431\u043e\u0442\u043a\u0438 \u0444\u0430\u0439\u043b\u0430 \u0440\u0430\u0437\u0431\u0438\u0435\u043d\u0438\u044f.
35 | [error]_32 = \u041f\u043e\u043b\u044c\u0437\u043e\u0432\u0430\u0442\u0435\u043b\u044c\u0441\u043a\u0430\u044f \u043f\u0440\u043e\u0446\u0435\u0434\u0443\u0440\u0430 \u043d\u0430\u0445\u043e\u0434\u0438\u0442\u0441\u044f \u0432 \u043f\u0440\u043e\u0446\u0435\u0441\u0441\u0435 \u0432\u044b\u043f\u043e\u043b\u043d\u0435\u043d\u0438\u044f.
36 | [error]_34 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0442\u0438\u043f \u0438\u0437\u043c\u0435\u0440\u0435\u043d\u0438\u0439.
37 | [error]_36 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0444\u043e\u0440\u043c\u0430\u0442 \u043f\u0440\u043e\u043f\u0443\u0449\u0435\u043d\u043d\u043e\u0433\u043e \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u044f.
38 | [error]_40 = \u041d\u0443\u0436\u043d\u043e \u0437\u0430\u0434\u0430\u0442\u044c \u0438\u0441\u0442\u043e\u0447\u043d\u0438\u043a \u0434\u0430\u043d\u043d\u044b\u0445 \u043f\u0440\u043e\u0446\u0435\u0434\u0443\u0440\u044b.
39 | [error]_44 = \u0410\u043a\u0442\u0438\u0432\u043d\u044b\u0439 \u043d\u0430\u0431\u043e\u0440 \u0434\u0430\u043d\u043d\u044b\u0445 \u043f\u0443\u0441\u0442.
40 | [error]_47 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0442\u0438\u043f \u0444\u043e\u0440\u043c\u0430\u0442\u0430.
41 | [error]_48 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u0430\u044f \u0448\u0438\u0440\u0438\u043d\u0430 \u0444\u043e\u0440\u043c\u0430\u0442\u0430.
42 | [error]_49 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u0430\u044f \u0434\u0435\u0441\u044f\u0442\u0438\u0447\u043d\u0430\u044f \u0442\u043e\u0447\u043a\u0430.
43 | [error]_54 = \u0412 \u0430\u043a\u0442\u0438\u0432\u043d\u043e\u043c \u043d\u0430\u0431\u043e\u0440\u0435 \u0434\u0430\u043d\u043d\u044b\u0445 \u0431\u043e\u043b\u044c\u0448\u0435 \u043d\u0435\u0442 \u0434\u043e\u0441\u0442\u0443\u043f\u043d\u044b\u0445 \u0434\u0430\u043d\u043d\u044b\u0445.
44 | [error]_56 = \u0414\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b \u0442\u043e\u043b\u044c\u043a\u043e \u0441\u0442\u0440\u043e\u043a\u043e\u0432\u044b\u0435 \u043f\u0435\u0440\u0435\u043c\u0435\u043d\u043d\u044b\u0435.
45 | [error]_57 = \u0414\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b \u0442\u043e\u043b\u044c\u043a\u043e \u0447\u0438\u0441\u043b\u043e\u0432\u044b\u0435 \u043f\u0435\u0440\u0435\u043c\u0435\u043d\u043d\u044b\u0435.
46 | [error]_58 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0438\u043c\u044f \u0430\u0442\u0440\u0438\u0431\u0443\u0442\u0430.
47 | [error]_59 = \u041f\u043e\u043b\u044c\u0437\u043e\u0432\u0430\u0442\u0435\u043b\u044c\u0441\u043a\u043e\u0435 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0435 \u043e\u0442\u0441\u0443\u0442\u0441\u0442\u0432\u0438\u044f \u0434\u043b\u044f \u0441\u0442\u0440\u043e\u043a\u043e\u0432\u043e\u0439 \u043f\u0435\u0440\u0435\u043c\u0435\u043d\u043d\u043e\u0439 \u0434\u043e\u043b\u0436\u043d\u043e \u0441\u043e\u0434\u0435\u0440\u0436\u0430\u0442\u044c \u043d\u0435 \u0431\u043e\u043b\u0435\u0435 8 \u0441\u0438\u043c\u0432\u043e\u043b\u043e\u0432.
48 | [error]_61 = \u0421\u043b\u0438\u0448\u043a\u043e\u043c \u0434\u043b\u0438\u043d\u043d\u043e\u0435 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0435 \u0434\u0430\u043d\u043d\u044b\u0445.
49 | [error]_62 = \u0414\u043b\u0438\u043d\u0430 \u0441\u0442\u0440\u043e\u043a\u043e\u0432\u043e\u0439 \u043f\u0435\u0440\u0435\u043c\u0435\u043d\u043d\u043e\u0439 \u043d\u0435 \u043c\u043e\u0436\u0435\u0442 \u043f\u0440\u0435\u0432\u044b\u0448\u0430\u0442\u044c 32767 \u0431\u0430\u0439\u0442.
50 | [error]_64 = \u041d\u0435\u043b\u044c\u0437\u044f \u0438\u0437\u043c\u0435\u043d\u0438\u0442\u044c \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u044f \u0434\u0430\u043d\u043d\u044b\u0445 \u0438\u043b\u0438 \u0438\u043d\u0444\u043e\u0440\u043c\u0430\u0446\u0438\u044e \u043e \u043f\u0435\u0440\u0435\u043c\u0435\u043d\u043d\u044b\u0445 \u0432 \u0438\u0441\u0445\u043e\u0434\u043d\u043e\u043c \u043d\u0430\u0431\u043e\u0440\u0435 \u0434\u0430\u043d\u043d\u044b\u0445.
51 | [warning]_67 = \u0411\u044b\u043b \u0434\u043e\u0441\u0442\u0438\u0433\u043d\u0443\u0442 \u043a\u043e\u043d\u0435\u0446 \u0442\u0435\u043a\u0443\u0449\u0435\u0433\u043e \u0441\u043b\u043e\u044f \u0440\u0430\u0437\u0431\u0438\u0435\u043d\u0438\u044f.
52 | [error]_70 = \u0421\u043b\u0438\u0448\u043a\u043e\u043c \u0434\u043b\u0438\u043d\u043d\u0430\u044f \u043c\u0435\u0442\u043a\u0430.
53 | [error]_71 = \u0421\u043b\u0438\u0448\u043a\u043e\u043c \u0434\u043b\u0438\u043d\u043d\u043e\u0435 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0435.
54 | [error]_82 = \u042d\u0442\u0430 \u043f\u0435\u0440\u0435\u043c\u0435\u043d\u043d\u0430\u044f \u043e\u0442\u0441\u0443\u0442\u0441\u0442\u0432\u0443\u0435\u0442 \u0432 \u0430\u043a\u0442\u0438\u0432\u043d\u043e\u043c \u043d\u0430\u0431\u043e\u0440\u0435 \u0434\u0430\u043d\u043d\u044b\u0445.
55 | [error]_86 = \u0414\u043b\u044f \u0437\u0430\u0432\u0435\u0440\u0448\u0435\u043d\u0438\u044f \u044d\u0442\u043e\u0433\u043e \u0434\u0435\u0439\u0441\u0442\u0432\u0438\u044f \u0442\u0440\u0435\u0431\u0443\u0435\u0442\u0441\u044f \u0430\u043a\u0442\u0438\u0432\u043d\u044b\u0439 \u0438\u0441\u0442\u043e\u0447\u043d\u0438\u043a \u0434\u0430\u043d\u043d\u044b\u0445.
56 | [error]_87 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0438\u043c\u044f \u043d\u0430\u0431\u043e\u0440\u0430 \u0434\u0430\u043d\u043d\u044b\u0445.
57 | [error]_88 = \u042d\u0442\u043e\u0442 \u043c\u0435\u0442\u043e\u0434 \u043c\u043e\u0436\u043d\u043e \u0432\u044b\u0437\u0432\u0430\u0442\u044c \u0442\u043e\u043b\u044c\u043a\u043e SetDictionaryToSPSS \u0438 EndDataStep.
58 | [error]_89 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0432\u044b\u0437\u043e\u0432 \u0444\u0443\u043d\u043a\u0446\u0438\u0438. \u0424\u0443\u043d\u043a\u0446\u0438\u044e \u043c\u043e\u0436\u043d\u043e \u0432\u044b\u0437\u0432\u0430\u0442\u044c \u0442\u043e\u043b\u044c\u043a\u043e \u0432\u043e \u0432\u0440\u0435\u043c\u044f \u0441\u043e\u0437\u0434\u0430\u043d\u0438\u044f \u043d\u0430\u0431\u043e\u0440\u0430 \u0434\u0430\u043d\u043d\u044b\u0445 \u0438\u043b\u0438 \u0432\u043d\u0443\u0442\u0440\u0438 \u043f\u043e\u043b\u044c\u0437\u043e\u0432\u0430\u0442\u0435\u043b\u044c\u0441\u043a\u043e\u0439 \u043f\u0440\u043e\u0446\u0435\u0434\u0443\u0440\u044b.
59 | [error]_90 = \u041d\u0435\u0432\u043e\u0437\u043c\u043e\u0436\u043d\u043e \u0441\u043e\u0437\u0434\u0430\u0442\u044c \u0430\u043a\u0442\u0438\u0432\u043d\u044b\u0439 \u043d\u0430\u0431\u043e\u0440 \u0434\u0430\u043d\u043d\u044b\u0445 \u0432\u043d\u0443\u0442\u0440\u0438 \u043f\u043e\u043b\u044c\u0437\u043e\u0432\u0430\u0442\u0435\u043b\u044c\u0441\u043a\u043e\u0439 \u043f\u0440\u043e\u0446\u0435\u0434\u0443\u0440\u044b.
60 | [error]_91 = \u041d\u0430\u0431\u043e\u0440 \u0434\u0430\u043d\u043d\u044b\u0445 \u0441 \u0442\u0430\u043a\u0438\u043c \u0436\u0435 \u0438\u043c\u0435\u043d\u0435\u043c \u0443\u0436\u0435 \u0441\u0443\u0449\u0435\u0441\u0442\u0432\u0443\u0435\u0442.
61 | [error]_92 = \u041d\u0435\u0432\u043e\u0437\u043c\u043e\u0436\u043d\u043e \u0437\u0430\u0432\u0435\u0440\u0448\u0438\u0442\u044c \u044d\u0442\u043e \u0434\u0435\u0439\u0441\u0442\u0432\u0438\u0435, \u043f\u043e\u043a\u0430 \u043e\u0431\u0440\u0430\u0431\u0430\u0442\u044b\u0432\u0430\u0435\u0442\u0441\u044f \u0441\u043e\u0437\u0434\u0430\u043d\u0438\u0435 \u043d\u0430\u0431\u043e\u0440\u0430 \u0434\u0430\u043d\u043d\u044b\u0445.
62 | [error]_94 = \u041d\u0435\u0432\u043e\u0437\u043c\u043e\u0436\u043d\u043e \u0441\u043e\u0437\u0434\u0430\u0442\u044c \u043d\u0430\u0431\u043e\u0440 \u0434\u0430\u043d\u043d\u044b\u0445, \u043f\u043e\u043a\u0430 \u0435\u0441\u0442\u044c \u043e\u0442\u043b\u043e\u0436\u0435\u043d\u043d\u044b\u0435 \u043f\u0440\u0435\u043e\u0431\u0440\u0430\u0437\u043e\u0432\u0430\u043d\u0438\u044f.
63 | [error]_96 = \u041d\u0435 \u043d\u0430\u0439\u0434\u0435\u043d\u043e \u0443\u043a\u0430\u0437\u0430\u043d\u043d\u043e\u0435 \u0438\u043c\u044f \u0430\u0442\u0440\u0438\u0431\u0443\u0442\u0430.
64 | [error]_99 = \u041d\u0435 \u0443\u0434\u0430\u043b\u043e\u0441\u044c \u0441\u043e\u0437\u0434\u0430\u0442\u044c \u0443\u043a\u0430\u0437\u0430\u043d\u043d\u044b\u0439 \u043d\u0430\u0431\u043e\u0440 \u0434\u0430\u043d\u043d\u044b\u0445.
65 | [error]_100 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u043e\u043f\u0440\u0435\u0434\u0435\u043b\u0435\u043d\u0438\u0435 \u043d\u0430\u0431\u043e\u0440\u0430 \u043c\u043d\u043e\u0436\u0435\u0441\u0442\u0432\u0435\u043d\u043d\u044b\u0445 \u043e\u0442\u0432\u0435\u0442\u043e\u0432.
66 | [error]_301 = \u0412 \u0443\u0437\u043b\u0435 CF Applier \u043d\u0435\u0442 \u043c\u043e\u0434\u0435\u043b\u0438, \u0443\u0431\u0435\u0434\u0438\u0442\u0435\u0441\u044c, \u0447\u0442\u043e SetModel \u043f\u0440\u0438\u043c\u0435\u043d\u044f\u0435\u0442\u0441\u044f \u0432 \u0443\u0437\u043b\u0435 Builder.
67 | [error]_402 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0438\u043d\u0434\u0435\u043a\u0441 \u043f\u043e\u043b\u044f.
68 | [warning]_404 = \u0423 \u043f\u043e\u043b\u044f \u043d\u0435\u0442 \u043c\u0435\u0442\u043e\u043a.
69 | [warning]_403 = \u041c\u0435\u0442\u043a\u0438 \u043f\u043e\u043b\u044f \u043d\u0435 \u0441\u043e\u043e\u0442\u0432\u0435\u0442\u0441\u0442\u0432\u0443\u044e\u0442 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u044f\u043c.
70 | [error]_999999997 = \u041d\u0435\u0438\u0437\u0432\u0435\u0441\u0442\u043d\u0430\u044f \u043e\u0448\u0438\u0431\u043a\u0430.
71 | [error]_999999998 = \u041e\u0431\u0440\u0430\u0431\u043e\u0442\u043a\u0430 \u0431\u044b\u043b\u0430 \u043f\u0440\u0435\u0440\u0432\u0430\u043d\u0430 \u043f\u043e\u043b\u044c\u0437\u043e\u0432\u0430\u0442\u0435\u043b\u0435\u043c.
72 | [error]_999999999 = \u041d\u0435\u0438\u0437\u0432\u0435\u0441\u0442\u043d\u0430\u044f \u043e\u0448\u0438\u0431\u043a\u0430.
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0444\u043e\u0440\u043c\u0430\u0442 \u043c\u043e\u0434\u0435\u043b\u0438 \u0434\u0430\u043d\u043d\u044b\u0445 \u043a\u043e\u043c\u043f\u043e\u043d\u0435\u043d\u0442\u0430 CF R.
78 | [RError]_1002 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0438\u043c\u044f \u043f\u043e\u043b\u044f \u0432 \u043c\u043e\u0434\u0435\u043b\u0438 \u0434\u0430\u043d\u043d\u044b\u0445. \u041f\u043e\u0432\u0442\u043e\u0440\u0435\u043d\u0438\u0435 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0439.
79 | [warning]_1003 = \u041f\u043e\u0432\u0442\u043e\u0440\u0435\u043d\u0438\u0435 \u043c\u0435\u0442\u043e\u043a \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0439.
80 | [RError]_1004 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u0430\u044f \u0441\u0438\u0441\u0442\u0435\u043c\u0430 \u0445\u0440\u0430\u043d\u0435\u043d\u0438\u044f \u0434\u043b\u044f \u043f\u043e\u043b\u044f SetDataModel.
81 | [RError]_1005 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0438\u0437\u043c\u0435\u0440\u0435\u043d\u0438\u0435 \u0434\u043b\u044f \u043f\u043e\u043b\u044f SetDataModel.
82 | [RError]_1006 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0444\u043e\u0440\u043c\u0430\u0442 \u0434\u043b\u044f \u043f\u043e\u043b\u044f SetDataModel.
83 | [RError]_1007 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u0430\u044f \u0440\u043e\u043b\u044c \u0434\u043b\u044f \u043f\u043e\u043b\u044f SetDataModel.
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0438\u043c\u044f \u043f\u043e\u043b\u044f \u0432 \u0430\u0440\u0433\u0443\u043c\u0435\u043d\u0442\u0435.
88 | [RError]_1021 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u043e\u0442\u0441\u0443\u0442\u0441\u0442\u0432\u0443\u044e\u0449\u0435\u0435 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0435 \u043f\u043e\u043b\u044f.
89 | [RError]_1022 = \u0423 \u043f\u043e\u043b\u044f \u0444\u043b\u0430\u0433\u0430 \u043d\u0435\u0442 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0439.
90 |
91 | ## data
92 | [RError]_1008 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0435 \u0430\u0440\u0433\u0443\u043c\u0435\u043d\u0442\u0430 factorMode (\u0434\u043e\u043b\u0436\u043d\u043e \u0431\u044b\u0442\u044c "none", "levels" \u0438\u043b\u0438 "labels").
93 | [RError]_1009 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0435 \u0430\u0440\u0433\u0443\u043c\u0435\u043d\u0442\u0430 rDate (\u0434\u043e\u043b\u0436\u043d\u043e \u0431\u044b\u0442\u044c "none", "POSIXct" \u0438\u043b\u0438 "POSIXlt").
94 | [RError]_1010 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0437\u043d\u0430\u0447\u0435\u043d\u0438\u0435 \u0430\u0440\u0433\u0443\u043c\u0435\u043d\u0442\u0430 missingValue (\u0434\u043e\u043b\u0436\u043d\u043e \u0431\u044b\u0442\u044c NA, NaN \u0438\u043b\u0438 "asis").
95 | [RError]_1011 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0432\u044b\u0437\u043e\u0432 \u0444\u0443\u043d\u043a\u0446\u0438\u0438. \u0424\u0443\u043d\u043a\u0446\u0438\u044e \u043c\u043e\u0436\u043d\u043e \u0432\u044b\u0437\u0432\u0430\u0442\u044c \u0442\u043e\u043b\u044c\u043a\u043e \u043f\u043e\u0441\u043b\u0435 \u0432\u044b\u0437\u043e\u0432\u0430 SetDataModel.
96 | [RError]_1012 = \u0414\u0430\u043d\u043d\u044b\u0435 \u043d\u0435 \u0441\u043e\u043e\u0442\u0432\u0435\u0442\u0441\u0442\u0432\u0443\u044e\u0442 \u043c\u043e\u0434\u0435\u043b\u0438 \u0434\u0430\u043d\u043d\u044b\u0445.
97 |
98 | [RError]_1013 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0438\u043d\u0434\u0435\u043a\u0441 \u0434\u043b\u044f GetOutputsNames.
99 | [RError]_1014 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u043e\u0435 \u0438\u043c\u044f \u0438\u043b\u0438 \u043f\u0443\u0442\u044c \u0438\u0437\u043e\u0431\u0440\u0430\u0436\u0435\u043d\u0438\u044f.
100 | [RError]_1015 = \u041d\u0435\u0434\u043e\u043f\u0443\u0441\u0442\u0438\u043c\u044b\u0439 \u0444\u043e\u0440\u043c\u0430\u0442 \u0438\u0437\u043e\u0431\u0440\u0430\u0436\u0435\u043d\u0438\u044f (\u0434\u043e\u043b\u0436\u0435\u043d \u0431\u044b\u0442\u044c "JPG", "PNG" \u0438\u043b\u0438 "BMP").
101 | [RError]_1016 = \u041e\u0436\u0438\u0434\u0430\u0435\u0442\u0441\u044f \u0447\u0438\u0441\u043b\u043e\u0432\u043e\u0439 \u0430\u0440\u0433\u0443\u043c\u0435\u043d\u0442.
102 | [RError]_1017 = \u041e\u0436\u0438\u0434\u0430\u0435\u0442\u0441\u044f \u0430\u0440\u0433\u0443\u043c\u0435\u043d\u0442 - \u0446\u0435\u043b\u043e\u0435 \u0447\u0438\u0441\u043b\u043e.
103 | [RError]_1018 = \u041e\u0436\u0438\u0434\u0430\u0435\u0442\u0441\u044f \u043b\u043e\u0433\u0438\u0447\u0435\u0441\u043a\u0438\u0439 \u0430\u0440\u0433\u0443\u043c\u0435\u043d\u0442.
104 | [RError]_1019 = \u041f\u0435\u0440\u0435\u043c\u0435\u043d\u043d\u044b\u0435 \u0430\u0440\u0433\u0443\u043c\u0435\u043d\u0442\u0430 \u0434\u043e\u043b\u0436\u043d\u044b \u0431\u044b\u0442\u044c \u0441\u0442\u0440\u043e\u043a\u043e\u0432\u044b\u043c\u0438, \u0432\u0435\u043a\u0442\u043e\u0440\u043d\u044b\u043c\u0438 \u0438\u043b\u0438 \u0441\u043f\u0438\u0441\u043e\u0447\u043d\u044b\u043c\u0438.
105 |
106 | # General errors
107 | SPSSError = \u041e\u0448\u0438\u0431\u043a\u0430 CF IBM SPSS
108 | SPSSWarning = \u041f\u0440\u0435\u0434\u0443\u043f\u0440\u0435\u0436\u0434\u0435\u043d\u0438\u0435 CF IBM SPSS
109 | error_code = \u041a\u043e\u0434 \u043e\u0448\u0438\u0431\u043a\u0438 -
110 | with_message = \u0421 \u0441\u043e\u043e\u0431\u0449\u0435\u043d\u0438\u0435\u043c
111 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_zh_CN.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = \u65e0\u9519\u8bef\u3002
13 | [ok]_1 = \u6ce8\u91ca\u3002
14 | [warning]_2 = \u8b66\u544a\u3002
15 | [error]_3 = \u4e25\u91cd\u9519\u8bef\u3002
16 | [error]_4 = \u81f4\u547d\u9519\u8bef\u3002
17 | [error]_5 = \u707e\u96be\u6027\u9519\u8bef\u3002
18 | [error]_6 = \u547d\u4ee4\u8bed\u6cd5\u9519\u8bef\u3002
19 | [error]_401 = \u7d22\u5f15\u65e0\u6548\u3002
20 | [error]_11 = \u65e0\u6cd5\u5c06\u5bf9\u8c61\u6dfb\u52a0\u5230 XML \u5de5\u4f5c\u7a7a\u95f4\u3002
21 | [error]_12 = \u53e5\u67c4\u5bf9\u8c61\u65e0\u6548\u3002
22 | [error]_13 = \u65e0\u6cd5\u9664\u53bb XML \u5de5\u4f5c\u7a7a\u95f4\u5bf9\u8c61\u3002
23 | [error]_15 = \u65e0\u6cd5\u83b7\u53d6\u7ed3\u679c\u3002
24 | [error]_16 = \u503c\u65e0\u6548\u3002
25 | [warning]_20 = \u73b0\u6709\u7684 XML \u5de5\u4f5c\u7a7a\u95f4\u53e5\u67c4\u5df2\u88ab\u8986\u76d6\u3002
26 | [error]_21 = XPath \u8868\u8fbe\u5f0f\u65e0\u6548\u3002
27 | [error]_22 = XML \u9519\u8bef\u3002
28 | [warning]_23 = \u65e0\u6cd5\u8bfb\u53d6\u66f4\u591a\u6570\u636e\u3002
29 | [error]_24 = \u6570\u636e\u7c7b\u578b\u65e0\u6548\u3002
30 | [error]_25 = \u53d8\u91cf\u540d\u91cd\u590d\u3002
31 | [error]_26 = \u53d8\u91cf\u7c7b\u578b\u65e0\u6548\u3002
32 | [error]_27 = \u53d8\u91cf\u540d\u79f0\u65e0\u6548\u3002
33 | [error]_30 = \u5927\u5c0f\u5199\u65e0\u6548\u3002
34 | [error]_31 = \u5728\u7528\u4e8e\u5904\u7406\u62c6\u5206\u6587\u4ef6\u7684\u6570\u636e\u8fde\u63a5\u5904\u4e8e\u6253\u5f00\u72b6\u6001\u65f6\uff0c\u65e0\u6cd5\u5b8c\u6210\u6b64\u64cd\u4f5c\u3002
35 | [error]_32 = \u7528\u6237\u8fc7\u7a0b\u6b63\u5728\u8fd0\u884c\u4e2d\u3002
36 | [error]_34 = \u6d4b\u91cf\u7ea7\u522b\u65e0\u6548\u3002
37 | [error]_36 = \u7f3a\u5931\u503c\u683c\u5f0f\u65e0\u6548\u3002
38 | [error]_40 = \u9700\u8981\u8fc7\u7a0b\u6570\u636e\u6e90\u3002
39 | [error]_44 = \u6d3b\u52a8\u6570\u636e\u96c6\u4e3a\u7a7a\u3002
40 | [error]_47 = \u683c\u5f0f\u7c7b\u578b\u65e0\u6548\u3002
41 | [error]_48 = \u683c\u5f0f\u5bbd\u5ea6\u65e0\u6548\u3002
42 | [error]_49 = \u5c0f\u6570\u70b9\u65e0\u6548\u3002
43 | [error]_54 = \u6d3b\u52a8\u6570\u636e\u96c6\u4e2d\u6ca1\u6709\u66f4\u591a\u53ef\u7528\u6570\u636e\u3002
44 | [error]_56 = \u53ea\u5141\u8bb8\u4f7f\u7528\u5b57\u7b26\u4e32\u53d8\u91cf\u3002
45 | [error]_57 = \u53ea\u5141\u8bb8\u4f7f\u7528\u6570\u5b57\u53d8\u91cf\u3002
46 | [error]_58 = \u5c5e\u6027\u540d\u79f0\u65e0\u6548\u3002
47 | [error]_59 = \u5b57\u7b26\u4e32\u53d8\u91cf\u7684\u7528\u6237\u7f3a\u5931\u503c\u7684\u957f\u5ea6\u4e0d\u5f97\u8d85\u8fc7 8 \u4e2a\u5b57\u7b26\u3002
48 | [error]_61 = \u6570\u636e\u503c\u8fc7\u957f\u3002
49 | [error]_62 = \u5b57\u7b26\u4e32\u53d8\u91cf\u7684\u957f\u5ea6\u4e0d\u5f97\u8d85\u8fc7 32767 \u5b57\u8282\u3002
50 | [error]_64 = \u65e0\u6cd5\u66f4\u6539\u539f\u59cb\u6570\u636e\u96c6\u4e2d\u7684\u6570\u636e\u503c\u6216\u53d8\u91cf\u4fe1\u606f\u3002
51 | [warning]_67 = \u5df2\u5230\u8fbe\u5f53\u524d\u5206\u5272\u7684\u672b\u5c3e\u3002
52 | [error]_70 = \u6807\u7b7e\u957f\u5ea6\u8fc7\u957f\u3002
53 | [error]_71 = \u503c\u957f\u5ea6\u8fc7\u957f\u3002
54 | [error]_82 = \u53d8\u91cf\u4e0d\u5728\u6d3b\u52a8\u6570\u636e\u96c6\u4e2d\u3002
55 | [error]_86 = \u9700\u8981\u6d3b\u52a8\u6570\u636e\u6e90\u624d\u80fd\u5b8c\u6210\u6b64\u64cd\u4f5c\u3002
56 | [error]_87 = \u6570\u636e\u96c6\u540d\u79f0\u65e0\u6548\u3002
57 | [error]_88 = \u53ea\u80fd\u5728 SetDictionaryToSPSS \u4e0e EndDataStep \u4e4b\u95f4\u8c03\u7528\u6b64\u65b9\u6cd5\u3002
58 | [error]_89 = \u51fd\u6570\u8c03\u7528\u65e0\u6548\u3002 \u53ea\u80fd\u5728\u6570\u636e\u96c6\u521b\u5efa\u671f\u95f4\u6216\u8005\u5728\u7528\u6237\u8fc7\u7a0b\u4e2d\u8c03\u7528\u51fd\u6570\u3002
59 | [error]_90 = \u65e0\u6cd5\u5728\u7528\u6237\u8fc7\u7a0b\u4e2d\u521b\u5efa\u6d3b\u52a8\u6570\u636e\u96c6\u3002
60 | [error]_91 = \u5df2\u5b58\u5728\u540c\u540d\u7684\u6570\u636e\u96c6\u3002
61 | [error]_92 = \u5728\u6570\u636e\u96c6\u521b\u5efa\u8fc7\u7a0b\u4e2d\uff0c\u65e0\u6cd5\u5b8c\u6210\u6b64\u64cd\u4f5c\u3002
62 | [error]_94 = \u5b58\u5728\u6682\u6302\u53d8\u6362\u65f6\uff0c\u65e0\u6cd5\u521b\u5efa\u6570\u636e\u96c6\u3002
63 | [error]_96 = \u627e\u4e0d\u5230\u6307\u5b9a\u7684\u5c5e\u6027\u540d\u79f0\u3002
64 | [error]_99 = \u65e0\u6cd5\u521b\u5efa\u6307\u5b9a\u7684\u6570\u636e\u96c6\u3002
65 | [error]_100 = \u591a\u91cd\u54cd\u5e94\u96c6\u5b9a\u4e49\u65e0\u6548\u3002
66 | [error]_301 = CF \u5e94\u7528\u8005\u8282\u70b9\u4e2d\u6ca1\u6709\u6a21\u578b\uff0c\u8bf7\u786e\u4fdd\u5728\u6784\u5efa\u5668\u8282\u70b9\u4e2d\u6267\u884c SetModel\u3002
67 | [error]_402 = \u5b57\u6bb5\u7d22\u5f15\u65e0\u6548\u3002
68 | [warning]_404 = \u5b57\u6bb5\u6ca1\u6709\u6807\u7b7e\u3002
69 | [warning]_403 = \u5b57\u6bb5\u6807\u7b7e\u4e0e\u503c\u4e0d\u5339\u914d\u3002
70 | [error]_999999997 = \u53d1\u751f\u4e86\u672a\u77e5\u9519\u8bef\u3002
71 | [error]_999999998 = \u5904\u7406\u88ab\u7528\u6237\u4e2d\u65ad\u3002
72 | [error]_999999999 = \u53d1\u751f\u4e86\u672a\u77e5\u9519\u8bef\u3002
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = R CF \u7ec4\u4ef6\u6570\u636e\u6a21\u578b\u683c\u5f0f\u65e0\u6548\u3002
78 | [RError]_1002 = \u6570\u636e\u6a21\u578b\u4e2d\u7684\u5b57\u6bb5\u540d\u79f0\u65e0\u6548\u3002 \u5b58\u5728\u91cd\u590d\u7684\u503c\u3002
79 | [warning]_1003 = \u5b58\u5728\u503c\u6807\u7b7e\u7684\u91cd\u590d\u503c\u3002
80 | [RError]_1004 = \u5b57\u6bb5\u5b58\u50a8\u5bf9\u4e8e SetDataModel \u800c\u8a00\u65e0\u6548\u3002
81 | [RError]_1005 = \u5b57\u6bb5\u6d4b\u91cf\u5bf9\u4e8e SetDataModel \u800c\u8a00\u65e0\u6548\u3002
82 | [RError]_1006 = \u5b57\u6bb5\u683c\u5f0f\u5bf9\u4e8e SetDataModel \u800c\u8a00\u65e0\u6548\u3002
83 | [RError]_1007 = \u5b57\u6bb5\u89d2\u8272\u5bf9\u4e8e SetDataModel \u800c\u8a00\u65e0\u6548\u3002
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = \u81ea\u53d8\u91cf\u4e2d\u7684\u5b57\u6bb5\u540d\u79f0\u65e0\u6548\u3002
88 | [RError]_1021 = \u5b57\u6bb5\u7f3a\u5931\u503c\u65e0\u6548\u3002
89 | [RError]_1022 = \u6807\u5fd7\u5b57\u6bb5\u6ca1\u6709\u503c\u3002
90 |
91 | ## data
92 | [RError]_1008 = \u81ea\u53d8\u91cf factorMode \u7684\u503c\u65e0\u6548\uff08\u5fc5\u987b\u662f\u201cnone\u201d\u3001\u201clevels\u201d\u6216\u201clabels\u201d\uff09\u3002
93 | [RError]_1009 = \u81ea\u53d8\u91cf rDate \u7684\u503c\u65e0\u6548\uff08\u5fc5\u987b\u662f\u201cnone\u201d\u3001\u201cPOSIXct\u201d\u6216\u201cPOSIXlt\u201d\uff09\u3002
94 | [RError]_1010 = \u81ea\u53d8\u91cf missingValue \u7684\u503c\u65e0\u6548\uff08\u5fc5\u987b\u662f NA\u3001NaN \u6216\u201casis\u201d\uff09\u3002
95 | [RError]_1011 = \u51fd\u6570\u8c03\u7528\u65e0\u6548\u3002 \u53ea\u80fd\u5728\u8c03\u7528 SetDataModel \u4e4b\u540e\u8c03\u7528\u51fd\u6570\u3002
96 | [RError]_1012 = \u6570\u636e\u4e0e\u6570\u636e\u6a21\u578b\u4e0d\u5339\u914d\u3002
97 |
98 | [RError]_1013 = \u7d22\u5f15\u5bf9\u4e8e GetOutputsNames \u800c\u8a00\u65e0\u6548\u3002
99 | [RError]_1014 = \u56fe\u5f62\u540d\u79f0\u6216\u8def\u5f84\u65e0\u6548\u3002
100 | [RError]_1015 = \u56fe\u5f62\u683c\u5f0f\u65e0\u6548\uff08\u5fc5\u987b\u662f\u201cJPG\u201d\u3001\u201cPNG\u201d\u6216\u201cBMP\u201d\uff09\u3002
101 | [RError]_1016 = \u9700\u8981\u6570\u5b57\u81ea\u53d8\u91cf\u3002
102 | [RError]_1017 = \u9700\u8981\u6574\u6570\u81ea\u53d8\u91cf\u3002
103 | [RError]_1018 = \u9700\u8981\u5e03\u5c14\u81ea\u53d8\u91cf\u3002
104 | [RError]_1019 = \u81ea\u53d8\u91cf\u5fc5\u987b\u662f\u5b57\u7b26\u4e32\u3001\u5411\u91cf\u6216\u5217\u8868\u3002
105 |
106 | # General errors
107 | SPSSError = IBM SPSS CF \u9519\u8bef
108 | SPSSWarning = IBM SPSS CF \u8b66\u544a
109 | error_code = \u9519\u8bef\u7801\u4e3a
110 | with_message = \u6d88\u606f\u4e3a
111 |
--------------------------------------------------------------------------------
/src/inst/lang/ibmspsscfr_zh_TW.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # NLS_ENCODING=UNICODE
9 | # NLS_MESSAGEFORMAT_NONE
10 |
11 | # Errors come from IBM SPSS Statistics backend.
12 | [ok]_0 = \u7121\u932f\u8aa4\u3002
13 | [ok]_1 = \u8a3b\u89e3\u3002
14 | [warning]_2 = \u8b66\u544a\u3002
15 | [error]_3 = \u91cd\u5927\u932f\u8aa4\u3002
16 | [error]_4 = \u56b4\u91cd\u932f\u8aa4\u3002
17 | [error]_5 = \u707d\u96e3\u6027\u932f\u8aa4\u3002
18 | [error]_6 = \u6307\u4ee4\u8a9e\u6cd5\u932f\u8aa4\u3002
19 | [error]_401 = \u7d22\u5f15\u7121\u6548\u3002
20 | [error]_11 = \u7121\u6cd5\u5411 XML \u5de5\u4f5c\u5340\u65b0\u589e\u7269\u4ef6\u3002
21 | [error]_12 = \u63a7\u9ede\u7269\u4ef6\u7121\u6548\u3002
22 | [error]_13 = \u7121\u6cd5\u79fb\u9664 XML \u5de5\u4f5c\u5340\u7269\u4ef6\u3002
23 | [error]_15 = \u7121\u6cd5\u53d6\u5f97\u7d50\u679c\u3002
24 | [error]_16 = \u503c\u7121\u6548\u3002
25 | [warning]_20 = \u73fe\u6709\u7684 XML \u5de5\u4f5c\u5340\u63a7\u9ede\u5df2\u6539\u5beb\u3002
26 | [error]_21 = XPath \u8868\u793a\u5f0f\u7121\u6548\u3002
27 | [error]_22 = XML \u932f\u8aa4\u3002
28 | [warning]_23 = \u7121\u6cd5\u8b80\u53d6\u5176\u4ed6\u8cc7\u6599\u3002
29 | [error]_24 = \u8cc7\u6599\u985e\u578b\u7121\u6548\u3002
30 | [error]_25 = \u8b8a\u6578\u540d\u7a31\u91cd\u8907\u3002
31 | [error]_26 = \u8b8a\u6578\u985e\u578b\u7121\u6548\u3002
32 | [error]_27 = \u8b8a\u6578\u540d\u7a31\u7121\u6548\u3002
33 | [error]_30 = \u5927\u5c0f\u5beb\u7121\u6548\u3002
34 | [error]_31 = \u7576\u8655\u7406\u5206\u5272\u6a94\u6848\u7684\u8cc7\u6599\u9023\u7dda\u958b\u555f\u6642\uff0c\u7121\u6cd5\u5b8c\u6210\u6b64\u52d5\u4f5c\u3002
35 | [error]_32 = \u4f7f\u7528\u8005\u7a0b\u5e8f\u57f7\u884c\u4e2d\u3002
36 | [error]_34 = \u5ea6\u91cf\u5c64\u6b21\u7121\u6548\u3002
37 | [error]_36 = \u907a\u6f0f\u503c\u683c\u5f0f\u7121\u6548\u3002
38 | [error]_40 = \u9700\u8981\u7a0b\u5e8f\u8cc7\u6599\u4f86\u6e90\u3002
39 | [error]_44 = \u4f5c\u7528\u4e2d\u7684\u8cc7\u6599\u96c6\u7a7a\u767d\u3002
40 | [error]_47 = \u683c\u5f0f\u985e\u578b\u7121\u6548\u3002
41 | [error]_48 = \u683c\u5f0f\u5bec\u5ea6\u7121\u6548\u3002
42 | [error]_49 = \u5c0f\u6578\u9ede\u7121\u6548\u3002
43 | [error]_54 = \u4f5c\u7528\u4e2d\u7684\u8cc7\u6599\u96c6\u4e2d\u6c92\u6709\u5176\u4ed6\u53ef\u7528\u7684\u8cc7\u6599\u3002
44 | [error]_56 = \u53ea\u63a5\u53d7\u5b57\u4e32\u8b8a\u6578\u3002
45 | [error]_57 = \u53ea\u63a5\u53d7\u6578\u503c\u8b8a\u6578\u3002
46 | [error]_58 = \u5c6c\u6027\u540d\u7a31\u7121\u6548\u3002
47 | [error]_59 = \u5b57\u4e32\u8b8a\u6578\u7684\u4f7f\u7528\u8005\u907a\u6f0f\u503c\u9577\u5ea6\u5fc5\u9808\u5c0f\u8207\u6216\u7b49\u65bc 8 \u500b\u5b57\u5143\u3002
48 | [error]_61 = \u8cc7\u6599\u503c\u904e\u9577\u3002
49 | [error]_62 = \u5b57\u4e32\u8b8a\u6578\u7684\u9577\u5ea6\u4e0d\u5f97\u8d85\u51fa 32767 \u500b\u4f4d\u5143\u7d44\u3002
50 | [error]_64 = \u7121\u6cd5\u8b8a\u66f4\u539f\u59cb\u8cc7\u6599\u96c6\u4e2d\u7684\u8cc7\u6599\u503c\u6216\u8b8a\u6578\u8cc7\u8a0a\u3002
51 | [warning]_67 = \u5df2\u9054\u5230\u73fe\u884c\u5206\u5272\u7684\u7d50\u5c3e\u3002
52 | [error]_70 = \u6a19\u7c64\u9577\u5ea6\u904e\u9577\u3002
53 | [error]_71 = \u503c\u9577\u5ea6\u904e\u9577\u3002
54 | [error]_82 = \u8b8a\u6578\u4e0d\u5728\u4f5c\u7528\u4e2d\u7684\u8cc7\u6599\u96c6\u5167\u3002
55 | [error]_86 = \u9700\u8981\u4f5c\u7528\u4e2d\u7684\u8cc7\u6599\u4f86\u6e90\u624d\u80fd\u5b8c\u6210\u8a72\u52d5\u4f5c\u3002
56 | [error]_87 = \u8cc7\u6599\u96c6\u540d\u7a31\u7121\u6548\u3002
57 | [error]_88 = \u6b64\u65b9\u6cd5\u53ea\u80fd\u7528\u65bc SetDictionaryToSPSS \u53ca EndDataStep \u4e4b\u9593\u547c\u53eb\u3002
58 | [error]_89 = \u51fd\u6578\u547c\u53eb\u7121\u6548\u3002 \u53ea\u80fd\u5728\u5efa\u7acb\u8cc7\u6599\u96c6\u671f\u9593\u6216\u4f7f\u7528\u8005\u7a0b\u5e8f\u5167\u547c\u53eb\u6b64\u51fd\u6578\u3002
59 | [error]_90 = \u5728\u4f7f\u7528\u8005\u7a0b\u5e8f\u5167\u7121\u6cd5\u5efa\u7acb\u4f5c\u7528\u4e2d\u7684\u8cc7\u6599\u96c6\u3002
60 | [error]_91 = \u5df2\u6709\u76f8\u540c\u540d\u7a31\u7684\u8cc7\u6599\u96c6\u3002
61 | [error]_92 = \u7576\u6b63\u5728\u9032\u884c\u8cc7\u6599\u96c6\u5efa\u7acb\u6642\u7121\u6cd5\u5b8c\u6210\u6b64\u52d5\u4f5c\u3002
62 | [error]_94 = \u7576\u64f1\u7f6e\u8f49\u63db\u6642\u7121\u6cd5\u5efa\u7acb\u8cc7\u6599\u96c6\u3002
63 | [error]_96 = \u627e\u4e0d\u5230\u6307\u5b9a\u7684\u5c6c\u6027\u540d\u7a31\u3002
64 | [error]_99 = \u7121\u6cd5\u5efa\u7acb\u6307\u5b9a\u7684\u8cc7\u6599\u96c6\u3002
65 | [error]_100 = \u591a\u500b\u56de\u61c9\u96c6\u5b9a\u7fa9\u7121\u6548\u3002
66 | [error]_301 = \u300cCF Applier \u7bc0\u9ede\u300d\u4e2d\u6c92\u6709\u6a21\u578b\uff0c\u8acb\u78ba\u5b9a\u300c\u5efa\u7f6e\u5668\u7bc0\u9ede\u300d\u4e2d\u6709 SetModel\u3002
67 | [error]_402 = \u6b04\u4f4d\u7d22\u5f15\u7121\u6548\u3002
68 | [warning]_404 = \u6b04\u4f4d\u6c92\u6709\u6a19\u7c64\u3002
69 | [warning]_403 = \u6b04\u4f4d\u6a19\u7c64\u8207\u503c\u4e0d\u7b26\u3002
70 | [error]_999999997 = \u4e0d\u660e\u932f\u8aa4\u3002
71 | [error]_999999998 = \u8655\u7406\u5df2\u88ab\u4f7f\u7528\u8005\u5c94\u65b7\u3002
72 | [error]_999999999 = \u4e0d\u660e\u932f\u8aa4\u3002
73 |
74 | # Errors come from R plug-in.
75 | #[warning]_1000 = There are no more split groups.
76 | ## data model
77 | [RError]_1001 = R CF \u5143\u4ef6\u8cc7\u6599\u6a21\u578b\u683c\u5f0f\u7121\u6548\u3002
78 | [RError]_1002 = \u8cc7\u6599\u6a21\u578b\u4e2d\u7684\u6b04\u540d\u7121\u6548\u3002 \u5b58\u5728\u91cd\u8907\u7684\u503c\u3002
79 | [warning]_1003 = \u503c\u6a19\u7c64\u5b58\u5728\u91cd\u8907\u7684\u503c\u3002
80 | [RError]_1004 = SetDataModel \u7684\u6b04\u4f4d\u5132\u5b58\u9ad4\u7121\u6548\u3002
81 | [RError]_1005 = SetDataModel \u7684\u6b04\u4f4d\u6e2c\u91cf\u7121\u6548\u3002
82 | [RError]_1006 = SetDataModel \u7684\u6b04\u4f4d\u683c\u5f0f\u7121\u6548\u3002
83 | [RError]_1007 = SetDataModel \u7684\u6b04\u4f4d\u89d2\u8272\u7121\u6548\u3002
84 |
85 |
86 | ##this is for GetDataModel or GetData
87 | [RError]_1020 = \u5f15\u6578\u4e2d\u7684\u6b04\u4f4d\u540d\u7a31\u7121\u6548\u3002
88 | [RError]_1021 = \u907a\u6f0f\u503c\u7684\u6b04\u4f4d\u7121\u6548\u3002
89 | [RError]_1022 = \u65d7\u6a19\u6b04\u4f4d\u6c92\u6709\u503c\u3002
90 |
91 | ## data
92 | [RError]_1008 = \u5f15\u6578 factorMode \u7684\u503c\u7121\u6548\uff08\u5fc5\u9808\u662f\u300c\u7121\u300d\u3001\u300c\u5c64\u6b21\u300d\u6216\u300c\u6a19\u7c64\u300d\uff09\u3002
93 | [RError]_1009 = \u5f15\u6578 rDate \u7684\u503c\u7121\u6548\uff08\u5fc5\u9808\u662f\u300c\u7121\u300d\u3001\u300cPOSIXct\u300d\u6216\u300cPOSIXlt\u300d\uff09\u3002
94 | [RError]_1010 = \u5f15\u6578 missingValue \u7684\u503c\u7121\u6548\uff08\u5fc5\u9808\u662f NA\u3001NaN \u6216\u300c\u4f9d\u73fe\u72c0\u300d\uff09\u3002
95 | [RError]_1011 = \u51fd\u6578\u547c\u53eb\u7121\u6548\u3002 \u53ea\u80fd\u5728\u547c\u53eb SetDataModel \u4e4b\u5f8c\u547c\u53eb\u51fd\u6578\u3002
96 | [RError]_1012 = \u8cc7\u6599\u8207\u8cc7\u6599\u6a21\u578b\u4e0d\u7b26\u3002
97 |
98 | [RError]_1013 = GetOutputsNames \u7684\u7d22\u5f15\u7121\u6548\u3002
99 | [RError]_1014 = \u5716\u5f62\u540d\u7a31\u6216\u8def\u5f91\u7121\u6548\u3002
100 | [RError]_1015 = \u5716\u5f62\u683c\u5f0f\u7121\u6548\uff08\u5fc5\u9808\u662f "JPG"\u3001"PNG" \u6216 "BMP"\uff09\u3002
101 | [RError]_1016 = \u9810\u671f\u6578\u5b57\u5f15\u6578\u3002
102 | [RError]_1017 = \u9810\u671f\u6574\u6578\u5f15\u6578\u3002
103 | [RError]_1018 = \u9810\u671f\u5e03\u6797\u5f15\u6578\u3002
104 | [RError]_1019 = \u5f15\u6578\u8b8a\u6578\u5fc5\u9808\u70ba\u5b57\u4e32\u3001\u5411\u91cf\u6216\u6e05\u55ae\u3002
105 |
106 | # General errors
107 | SPSSError = IBM SPSS CF \u932f\u8aa4
108 | SPSSWarning = IBM SPSS CF \u8b66\u544a
109 | error_code = \u932f\u8aa4\u78bc\u70ba
110 | with_message = \u5305\u542b\u8a0a\u606f
111 |
--------------------------------------------------------------------------------
/src/inst/lang/it/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # Errors come from IBM SPSS Statistics backend.
9 | [ok]_0 = No error.
10 | [ok]_1 = Comment.
11 | [warning]_2 = Warning.
12 | [error]_3 = Serious error.
13 | [error]_4 = Fatal error.
14 | [error]_5 = Catastrophic error.
15 | [error]_6 = Command syntax error.
16 | [error]_401 = Invalid index.
17 | [error]_11 = Cannot add object to XML workspace.
18 | [error]_12 = Invalid handle object.
19 | [error]_13 = Cannot remove XML workspace object.
20 | [error]_15 = Cannot get the result.
21 | [error]_16 = Invalid value.
22 | [warning]_20 = An existing XML workspace handle has been overwritten.
23 | [error]_21 = Invalid XPath expression.
24 | [error]_22 = XML error.
25 | [warning]_23 = Cannot read more data.
26 | [error]_24 = Invalid data type.
27 | [error]_25 = Duplicate variable name.
28 | [error]_26 = Invalid variable type.
29 | [error]_27 = Invalid variable name.
30 | [error]_30 = Invalid case.
31 | [error]_31 = Cannot complete this action while a data connection for processing split files is open.
32 | [error]_32 = A User Procedure is running.
33 | [error]_34 = Invalid measurement level.
34 | [error]_36 = Invalid missing value format.
35 | [error]_40 = A Procedure Data Source is required.
36 | [error]_44 = The active dataset is empty.
37 | [error]_47 = Invalid format type.
38 | [error]_48 = Invalid format width.
39 | [error]_49 = Invalid decimal point.
40 | [error]_54 = No more data is available in the active dataset.
41 | [error]_56 = Only string variables are allowed.
42 | [error]_57 = Only numeric variables are allowed.
43 | [error]_58 = Invalid attribute name.
44 | [error]_59 = The length of user-missing value for a string variable must be 8 characters or less.
45 | [error]_61 = The data value is too long.
46 | [error]_62 = The length of a string variable cannot exceed 32767 bytes.
47 | [error]_64 = Cannot change data values or variable information in the original dataset.
48 | [warning]_67 = The end of the current split has been reached.
49 | [error]_70 = The label length is too long.
50 | [error]_71 = The value length is too long.
51 | [error]_82 = The variable is not in the active dataset.
52 | [error]_86 = An active data source is required to complete this action.
53 | [error]_87 = Invalid dataset name.
54 | [error]_88 = This method can only be called between SetDictionaryToSPSS and EndDataStep.
55 | [error]_89 = Invalid function call. Function can only be called during dataset creation or within a User Procedure.
56 | [error]_90 = Cannot create an active dataset within a User Procedure.
57 | [error]_91 = A dataset with the same name already exists.
58 | [error]_92 = Cannot complete this action while dataset creation is in process.
59 | [error]_94 = Cannot create a dataset while there are pending transformations.
60 | [error]_96 = Cannot find specified attribute name.
61 | [error]_99 = Cannot create specified dataset.
62 | [error]_100 = Invalid multiple response set definition.
63 | [error]_301 = No model in CF Applier Node,please make sure SetModel in Builder Node.
64 | [error]_402 = Invalid field index.
65 | [warning]_404 = Field does not have labels.
66 | [warning]_403 = Field labels and values do not match.
67 | [error]_999999997 = Unknown error.
68 | [error]_999999998 = Processing was interrupted by the user.
69 | [error]_999999999 = Unknown error.
70 |
71 | # Errors come from R plug-in.
72 | #[warning]_1000 = There are no more split groups.
73 | ## data model
74 | [RError]_1001 = Invalid R CF Component Data Model format.
75 | [RError]_1002 = Invalid field name in data model. Duplicate values are present.
76 | [warning]_1003 = Duplicate values are present for value labels.
77 | [RError]_1004 = Invalid field storage for SetDataModel.
78 | [RError]_1005 = Invalid field measure for SetDataModel.
79 | [RError]_1006 = Invalid field format for SetDataModel.
80 | [RError]_1007 = Invalid field role for SetDataModel.
81 |
82 | [RError]_1021 = Invalid field missing value.
83 | ##this is for GetDataModel or GetData
84 | [RError]_1020 = Invalid field name in argument.
85 |
86 | ## data
87 | [RError]_1008 = Invalid value for argument factorMode (must be "none", "levels" or "labels").
88 | [RError]_1009 = Invalid value for argument rDate (must be "none", "POSIXct" or "POSIXlt").
89 | [RError]_1010 = Invalid value for argument missingValue (must be NA, NaN or "asis").
90 | [RError]_1011 = Invalid function call. Function can only be called after calling SetDataModel.
91 | [RError]_1012 = Data and data model does not match.
92 |
93 | [RError]_1013 = Invalid index for GetOutputsNames.
94 | [RError]_1014 = Invalid graphic name or path.
95 | [RError]_1015 = Invalid graphic format (must be "JPG", "PNG" or "BMP").
96 | [RError]_1016 = Expects a numeric argument.
97 | [RError]_1017 = Expects an integer argument.
98 | [RError]_1018 = Expects a boolean argument.
99 | [RError]_1019 = Argument variables must be string, vector or list.
100 |
101 | # General errors
102 | SPSSError = IBM SPSS CF error
103 | SPSSWarning = IBM SPSS CF warning
104 | error_code = The error code is
105 | with_message = With message
106 |
--------------------------------------------------------------------------------
/src/inst/lang/ja/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # Errors come from IBM SPSS Statistics backend.
9 | [ok]_0 = No error.
10 | [ok]_1 = Comment.
11 | [warning]_2 = Warning.
12 | [error]_3 = Serious error.
13 | [error]_4 = Fatal error.
14 | [error]_5 = Catastrophic error.
15 | [error]_6 = Command syntax error.
16 | [error]_401 = Invalid index.
17 | [error]_11 = Cannot add object to XML workspace.
18 | [error]_12 = Invalid handle object.
19 | [error]_13 = Cannot remove XML workspace object.
20 | [error]_15 = Cannot get the result.
21 | [error]_16 = Invalid value.
22 | [warning]_20 = An existing XML workspace handle has been overwritten.
23 | [error]_21 = Invalid XPath expression.
24 | [error]_22 = XML error.
25 | [warning]_23 = Cannot read more data.
26 | [error]_24 = Invalid data type.
27 | [error]_25 = Duplicate variable name.
28 | [error]_26 = Invalid variable type.
29 | [error]_27 = Invalid variable name.
30 | [error]_30 = Invalid case.
31 | [error]_31 = Cannot complete this action while a data connection for processing split files is open.
32 | [error]_32 = A User Procedure is running.
33 | [error]_34 = Invalid measurement level.
34 | [error]_36 = Invalid missing value format.
35 | [error]_40 = A Procedure Data Source is required.
36 | [error]_44 = The active dataset is empty.
37 | [error]_47 = Invalid format type.
38 | [error]_48 = Invalid format width.
39 | [error]_49 = Invalid decimal point.
40 | [error]_54 = No more data is available in the active dataset.
41 | [error]_56 = Only string variables are allowed.
42 | [error]_57 = Only numeric variables are allowed.
43 | [error]_58 = Invalid attribute name.
44 | [error]_59 = The length of user-missing value for a string variable must be 8 characters or less.
45 | [error]_61 = The data value is too long.
46 | [error]_62 = The length of a string variable cannot exceed 32767 bytes.
47 | [error]_64 = Cannot change data values or variable information in the original dataset.
48 | [warning]_67 = The end of the current split has been reached.
49 | [error]_70 = The label length is too long.
50 | [error]_71 = The value length is too long.
51 | [error]_82 = The variable is not in the active dataset.
52 | [error]_86 = An active data source is required to complete this action.
53 | [error]_87 = Invalid dataset name.
54 | [error]_88 = This method can only be called between SetDictionaryToSPSS and EndDataStep.
55 | [error]_89 = Invalid function call. Function can only be called during dataset creation or within a User Procedure.
56 | [error]_90 = Cannot create an active dataset within a User Procedure.
57 | [error]_91 = A dataset with the same name already exists.
58 | [error]_92 = Cannot complete this action while dataset creation is in process.
59 | [error]_94 = Cannot create a dataset while there are pending transformations.
60 | [error]_96 = Cannot find specified attribute name.
61 | [error]_99 = Cannot create specified dataset.
62 | [error]_100 = Invalid multiple response set definition.
63 | [error]_301 = No model in CF Applier Node,please make sure SetModel in Builder Node.
64 | [error]_402 = Invalid field index.
65 | [warning]_404 = Field does not have labels.
66 | [warning]_403 = Field labels and values do not match.
67 | [error]_999999997 = Unknown error.
68 | [error]_999999998 = Processing was interrupted by the user.
69 | [error]_999999999 = Unknown error.
70 |
71 | # Errors come from R plug-in.
72 | #[warning]_1000 = There are no more split groups.
73 | ## data model
74 | [RError]_1001 = Invalid R CF Component Data Model format.
75 | [RError]_1002 = Invalid field name in data model. Duplicate values are present.
76 | [warning]_1003 = Duplicate values are present for value labels.
77 | [RError]_1004 = Invalid field storage for SetDataModel.
78 | [RError]_1005 = Invalid field measure for SetDataModel.
79 | [RError]_1006 = Invalid field format for SetDataModel.
80 | [RError]_1007 = Invalid field role for SetDataModel.
81 |
82 | [RError]_1021 = Invalid field missing value.
83 | ##this is for GetDataModel or GetData
84 | [RError]_1020 = Invalid field name in argument.
85 |
86 | ## data
87 | [RError]_1008 = Invalid value for argument factorMode (must be "none", "levels" or "labels").
88 | [RError]_1009 = Invalid value for argument rDate (must be "none", "POSIXct" or "POSIXlt").
89 | [RError]_1010 = Invalid value for argument missingValue (must be NA, NaN or "asis").
90 | [RError]_1011 = Invalid function call. Function can only be called after calling SetDataModel.
91 | [RError]_1012 = Data and data model does not match.
92 |
93 | [RError]_1013 = Invalid index for GetOutputsNames.
94 | [RError]_1014 = Invalid graphic name or path.
95 | [RError]_1015 = Invalid graphic format (must be "JPG", "PNG" or "BMP").
96 | [RError]_1016 = Expects a numeric argument.
97 | [RError]_1017 = Expects an integer argument.
98 | [RError]_1018 = Expects a boolean argument.
99 | [RError]_1019 = Argument variables must be string, vector or list.
100 |
101 | # General errors
102 | SPSSError = IBM SPSS CF error
103 | SPSSWarning = IBM SPSS CF warning
104 | error_code = The error code is
105 | with_message = With message
106 |
--------------------------------------------------------------------------------
/src/inst/lang/ko/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # Errors come from IBM SPSS Statistics backend.
9 | [ok]_0 = No error.
10 | [ok]_1 = Comment.
11 | [warning]_2 = Warning.
12 | [error]_3 = Serious error.
13 | [error]_4 = Fatal error.
14 | [error]_5 = Catastrophic error.
15 | [error]_6 = Command syntax error.
16 | [error]_401 = Invalid index.
17 | [error]_11 = Cannot add object to XML workspace.
18 | [error]_12 = Invalid handle object.
19 | [error]_13 = Cannot remove XML workspace object.
20 | [error]_15 = Cannot get the result.
21 | [error]_16 = Invalid value.
22 | [warning]_20 = An existing XML workspace handle has been overwritten.
23 | [error]_21 = Invalid XPath expression.
24 | [error]_22 = XML error.
25 | [warning]_23 = Cannot read more data.
26 | [error]_24 = Invalid data type.
27 | [error]_25 = Duplicate variable name.
28 | [error]_26 = Invalid variable type.
29 | [error]_27 = Invalid variable name.
30 | [error]_30 = Invalid case.
31 | [error]_31 = Cannot complete this action while a data connection for processing split files is open.
32 | [error]_32 = A User Procedure is running.
33 | [error]_34 = Invalid measurement level.
34 | [error]_36 = Invalid missing value format.
35 | [error]_40 = A Procedure Data Source is required.
36 | [error]_44 = The active dataset is empty.
37 | [error]_47 = Invalid format type.
38 | [error]_48 = Invalid format width.
39 | [error]_49 = Invalid decimal point.
40 | [error]_54 = No more data is available in the active dataset.
41 | [error]_56 = Only string variables are allowed.
42 | [error]_57 = Only numeric variables are allowed.
43 | [error]_58 = Invalid attribute name.
44 | [error]_59 = The length of user-missing value for a string variable must be 8 characters or less.
45 | [error]_61 = The data value is too long.
46 | [error]_62 = The length of a string variable cannot exceed 32767 bytes.
47 | [error]_64 = Cannot change data values or variable information in the original dataset.
48 | [warning]_67 = The end of the current split has been reached.
49 | [error]_70 = The label length is too long.
50 | [error]_71 = The value length is too long.
51 | [error]_82 = The variable is not in the active dataset.
52 | [error]_86 = An active data source is required to complete this action.
53 | [error]_87 = Invalid dataset name.
54 | [error]_88 = This method can only be called between SetDictionaryToSPSS and EndDataStep.
55 | [error]_89 = Invalid function call. Function can only be called during dataset creation or within a User Procedure.
56 | [error]_90 = Cannot create an active dataset within a User Procedure.
57 | [error]_91 = A dataset with the same name already exists.
58 | [error]_92 = Cannot complete this action while dataset creation is in process.
59 | [error]_94 = Cannot create a dataset while there are pending transformations.
60 | [error]_96 = Cannot find specified attribute name.
61 | [error]_99 = Cannot create specified dataset.
62 | [error]_100 = Invalid multiple response set definition.
63 | [error]_301 = No model in CF Applier Node,please make sure SetModel in Builder Node.
64 | [error]_402 = Invalid field index.
65 | [warning]_404 = Field does not have labels.
66 | [warning]_403 = Field labels and values do not match.
67 | [error]_999999997 = Unknown error.
68 | [error]_999999998 = Processing was interrupted by the user.
69 | [error]_999999999 = Unknown error.
70 |
71 | # Errors come from R plug-in.
72 | #[warning]_1000 = There are no more split groups.
73 | ## data model
74 | [RError]_1001 = Invalid R CF Component Data Model format.
75 | [RError]_1002 = Invalid field name in data model. Duplicate values are present.
76 | [warning]_1003 = Duplicate values are present for value labels.
77 | [RError]_1004 = Invalid field storage for SetDataModel.
78 | [RError]_1005 = Invalid field measure for SetDataModel.
79 | [RError]_1006 = Invalid field format for SetDataModel.
80 | [RError]_1007 = Invalid field role for SetDataModel.
81 |
82 | [RError]_1021 = Invalid field missing value.
83 | ##this is for GetDataModel or GetData
84 | [RError]_1020 = Invalid field name in argument.
85 |
86 | ## data
87 | [RError]_1008 = Invalid value for argument factorMode (must be "none", "levels" or "labels").
88 | [RError]_1009 = Invalid value for argument rDate (must be "none", "POSIXct" or "POSIXlt").
89 | [RError]_1010 = Invalid value for argument missingValue (must be NA, NaN or "asis").
90 | [RError]_1011 = Invalid function call. Function can only be called after calling SetDataModel.
91 | [RError]_1012 = Data and data model does not match.
92 |
93 | [RError]_1013 = Invalid index for GetOutputsNames.
94 | [RError]_1014 = Invalid graphic name or path.
95 | [RError]_1015 = Invalid graphic format (must be "JPG", "PNG" or "BMP").
96 | [RError]_1016 = Expects a numeric argument.
97 | [RError]_1017 = Expects an integer argument.
98 | [RError]_1018 = Expects a boolean argument.
99 | [RError]_1019 = Argument variables must be string, vector or list.
100 |
101 | # General errors
102 | SPSSError = IBM SPSS CF error
103 | SPSSWarning = IBM SPSS CF warning
104 | error_code = The error code is
105 | with_message = With message
106 |
--------------------------------------------------------------------------------
/src/inst/lang/pl/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # Errors come from IBM SPSS Statistics backend.
9 | [ok]_0 = No error.
10 | [ok]_1 = Comment.
11 | [warning]_2 = Warning.
12 | [error]_3 = Serious error.
13 | [error]_4 = Fatal error.
14 | [error]_5 = Catastrophic error.
15 | [error]_6 = Command syntax error.
16 | [error]_401 = Invalid index.
17 | [error]_11 = Cannot add object to XML workspace.
18 | [error]_12 = Invalid handle object.
19 | [error]_13 = Cannot remove XML workspace object.
20 | [error]_15 = Cannot get the result.
21 | [error]_16 = Invalid value.
22 | [warning]_20 = An existing XML workspace handle has been overwritten.
23 | [error]_21 = Invalid XPath expression.
24 | [error]_22 = XML error.
25 | [warning]_23 = Cannot read more data.
26 | [error]_24 = Invalid data type.
27 | [error]_25 = Duplicate variable name.
28 | [error]_26 = Invalid variable type.
29 | [error]_27 = Invalid variable name.
30 | [error]_30 = Invalid case.
31 | [error]_31 = Cannot complete this action while a data connection for processing split files is open.
32 | [error]_32 = A User Procedure is running.
33 | [error]_34 = Invalid measurement level.
34 | [error]_36 = Invalid missing value format.
35 | [error]_40 = A Procedure Data Source is required.
36 | [error]_44 = The active dataset is empty.
37 | [error]_47 = Invalid format type.
38 | [error]_48 = Invalid format width.
39 | [error]_49 = Invalid decimal point.
40 | [error]_54 = No more data is available in the active dataset.
41 | [error]_56 = Only string variables are allowed.
42 | [error]_57 = Only numeric variables are allowed.
43 | [error]_58 = Invalid attribute name.
44 | [error]_59 = The length of user-missing value for a string variable must be 8 characters or less.
45 | [error]_61 = The data value is too long.
46 | [error]_62 = The length of a string variable cannot exceed 32767 bytes.
47 | [error]_64 = Cannot change data values or variable information in the original dataset.
48 | [warning]_67 = The end of the current split has been reached.
49 | [error]_70 = The label length is too long.
50 | [error]_71 = The value length is too long.
51 | [error]_82 = The variable is not in the active dataset.
52 | [error]_86 = An active data source is required to complete this action.
53 | [error]_87 = Invalid dataset name.
54 | [error]_88 = This method can only be called between SetDictionaryToSPSS and EndDataStep.
55 | [error]_89 = Invalid function call. Function can only be called during dataset creation or within a User Procedure.
56 | [error]_90 = Cannot create an active dataset within a User Procedure.
57 | [error]_91 = A dataset with the same name already exists.
58 | [error]_92 = Cannot complete this action while dataset creation is in process.
59 | [error]_94 = Cannot create a dataset while there are pending transformations.
60 | [error]_96 = Cannot find specified attribute name.
61 | [error]_99 = Cannot create specified dataset.
62 | [error]_100 = Invalid multiple response set definition.
63 | [error]_301 = No model in CF Applier Node,please make sure SetModel in Builder Node.
64 | [error]_402 = Invalid field index.
65 | [warning]_404 = Field does not have labels.
66 | [warning]_403 = Field labels and values do not match.
67 | [error]_999999997 = Unknown error.
68 | [error]_999999998 = Processing was interrupted by the user.
69 | [error]_999999999 = Unknown error.
70 |
71 | # Errors come from R plug-in.
72 | #[warning]_1000 = There are no more split groups.
73 | ## data model
74 | [RError]_1001 = Invalid R CF Component Data Model format.
75 | [RError]_1002 = Invalid field name in data model. Duplicate values are present.
76 | [warning]_1003 = Duplicate values are present for value labels.
77 | [RError]_1004 = Invalid field storage for SetDataModel.
78 | [RError]_1005 = Invalid field measure for SetDataModel.
79 | [RError]_1006 = Invalid field format for SetDataModel.
80 | [RError]_1007 = Invalid field role for SetDataModel.
81 |
82 | [RError]_1021 = Invalid field missing value.
83 | ##this is for GetDataModel or GetData
84 | [RError]_1020 = Invalid field name in argument.
85 |
86 | ## data
87 | [RError]_1008 = Invalid value for argument factorMode (must be "none", "levels" or "labels").
88 | [RError]_1009 = Invalid value for argument rDate (must be "none", "POSIXct" or "POSIXlt").
89 | [RError]_1010 = Invalid value for argument missingValue (must be NA, NaN or "asis").
90 | [RError]_1011 = Invalid function call. Function can only be called after calling SetDataModel.
91 | [RError]_1012 = Data and data model does not match.
92 |
93 | [RError]_1013 = Invalid index for GetOutputsNames.
94 | [RError]_1014 = Invalid graphic name or path.
95 | [RError]_1015 = Invalid graphic format (must be "JPG", "PNG" or "BMP").
96 | [RError]_1016 = Expects a numeric argument.
97 | [RError]_1017 = Expects an integer argument.
98 | [RError]_1018 = Expects a boolean argument.
99 | [RError]_1019 = Argument variables must be string, vector or list.
100 |
101 | # General errors
102 | SPSSError = IBM SPSS CF error
103 | SPSSWarning = IBM SPSS CF warning
104 | error_code = The error code is
105 | with_message = With message
106 |
--------------------------------------------------------------------------------
/src/inst/lang/pt_BR/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # Errors come from IBM SPSS Statistics backend.
9 | [ok]_0 = No error.
10 | [ok]_1 = Comment.
11 | [warning]_2 = Warning.
12 | [error]_3 = Serious error.
13 | [error]_4 = Fatal error.
14 | [error]_5 = Catastrophic error.
15 | [error]_6 = Command syntax error.
16 | [error]_401 = Invalid index.
17 | [error]_11 = Cannot add object to XML workspace.
18 | [error]_12 = Invalid handle object.
19 | [error]_13 = Cannot remove XML workspace object.
20 | [error]_15 = Cannot get the result.
21 | [error]_16 = Invalid value.
22 | [warning]_20 = An existing XML workspace handle has been overwritten.
23 | [error]_21 = Invalid XPath expression.
24 | [error]_22 = XML error.
25 | [warning]_23 = Cannot read more data.
26 | [error]_24 = Invalid data type.
27 | [error]_25 = Duplicate variable name.
28 | [error]_26 = Invalid variable type.
29 | [error]_27 = Invalid variable name.
30 | [error]_30 = Invalid case.
31 | [error]_31 = Cannot complete this action while a data connection for processing split files is open.
32 | [error]_32 = A User Procedure is running.
33 | [error]_34 = Invalid measurement level.
34 | [error]_36 = Invalid missing value format.
35 | [error]_40 = A Procedure Data Source is required.
36 | [error]_44 = The active dataset is empty.
37 | [error]_47 = Invalid format type.
38 | [error]_48 = Invalid format width.
39 | [error]_49 = Invalid decimal point.
40 | [error]_54 = No more data is available in the active dataset.
41 | [error]_56 = Only string variables are allowed.
42 | [error]_57 = Only numeric variables are allowed.
43 | [error]_58 = Invalid attribute name.
44 | [error]_59 = The length of user-missing value for a string variable must be 8 characters or less.
45 | [error]_61 = The data value is too long.
46 | [error]_62 = The length of a string variable cannot exceed 32767 bytes.
47 | [error]_64 = Cannot change data values or variable information in the original dataset.
48 | [warning]_67 = The end of the current split has been reached.
49 | [error]_70 = The label length is too long.
50 | [error]_71 = The value length is too long.
51 | [error]_82 = The variable is not in the active dataset.
52 | [error]_86 = An active data source is required to complete this action.
53 | [error]_87 = Invalid dataset name.
54 | [error]_88 = This method can only be called between SetDictionaryToSPSS and EndDataStep.
55 | [error]_89 = Invalid function call. Function can only be called during dataset creation or within a User Procedure.
56 | [error]_90 = Cannot create an active dataset within a User Procedure.
57 | [error]_91 = A dataset with the same name already exists.
58 | [error]_92 = Cannot complete this action while dataset creation is in process.
59 | [error]_94 = Cannot create a dataset while there are pending transformations.
60 | [error]_96 = Cannot find specified attribute name.
61 | [error]_99 = Cannot create specified dataset.
62 | [error]_100 = Invalid multiple response set definition.
63 | [error]_301 = No model in CF Applier Node,please make sure SetModel in Builder Node.
64 | [error]_402 = Invalid field index.
65 | [warning]_404 = Field does not have labels.
66 | [warning]_403 = Field labels and values do not match.
67 | [error]_999999997 = Unknown error.
68 | [error]_999999998 = Processing was interrupted by the user.
69 | [error]_999999999 = Unknown error.
70 |
71 | # Errors come from R plug-in.
72 | #[warning]_1000 = There are no more split groups.
73 | ## data model
74 | [RError]_1001 = Invalid R CF Component Data Model format.
75 | [RError]_1002 = Invalid field name in data model. Duplicate values are present.
76 | [warning]_1003 = Duplicate values are present for value labels.
77 | [RError]_1004 = Invalid field storage for SetDataModel.
78 | [RError]_1005 = Invalid field measure for SetDataModel.
79 | [RError]_1006 = Invalid field format for SetDataModel.
80 | [RError]_1007 = Invalid field role for SetDataModel.
81 |
82 | [RError]_1021 = Invalid field missing value.
83 | ##this is for GetDataModel or GetData
84 | [RError]_1020 = Invalid field name in argument.
85 |
86 | ## data
87 | [RError]_1008 = Invalid value for argument factorMode (must be "none", "levels" or "labels").
88 | [RError]_1009 = Invalid value for argument rDate (must be "none", "POSIXct" or "POSIXlt").
89 | [RError]_1010 = Invalid value for argument missingValue (must be NA, NaN or "asis").
90 | [RError]_1011 = Invalid function call. Function can only be called after calling SetDataModel.
91 | [RError]_1012 = Data and data model does not match.
92 |
93 | [RError]_1013 = Invalid index for GetOutputsNames.
94 | [RError]_1014 = Invalid graphic name or path.
95 | [RError]_1015 = Invalid graphic format (must be "JPG", "PNG" or "BMP").
96 | [RError]_1016 = Expects a numeric argument.
97 | [RError]_1017 = Expects an integer argument.
98 | [RError]_1018 = Expects a boolean argument.
99 | [RError]_1019 = Argument variables must be string, vector or list.
100 |
101 | # General errors
102 | SPSSError = IBM SPSS CF error
103 | SPSSWarning = IBM SPSS CF warning
104 | error_code = The error code is
105 | with_message = With message
106 |
--------------------------------------------------------------------------------
/src/inst/lang/zh_CN/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # Errors come from IBM SPSS Statistics backend.
9 | [ok]_0 = No error.
10 | [ok]_1 = Comment.
11 | [warning]_2 = Warning.
12 | [error]_3 = Serious error.
13 | [error]_4 = Fatal error.
14 | [error]_5 = Catastrophic error.
15 | [error]_6 = Command syntax error.
16 | [error]_401 = Invalid index.
17 | [error]_11 = Cannot add object to XML workspace.
18 | [error]_12 = Invalid handle object.
19 | [error]_13 = Cannot remove XML workspace object.
20 | [error]_15 = Cannot get the result.
21 | [error]_16 = Invalid value.
22 | [warning]_20 = An existing XML workspace handle has been overwritten.
23 | [error]_21 = Invalid XPath expression.
24 | [error]_22 = XML error.
25 | [warning]_23 = Cannot read more data.
26 | [error]_24 = Invalid data type.
27 | [error]_25 = Duplicate variable name.
28 | [error]_26 = Invalid variable type.
29 | [error]_27 = Invalid variable name.
30 | [error]_30 = Invalid case.
31 | [error]_31 = Cannot complete this action while a data connection for processing split files is open.
32 | [error]_32 = A User Procedure is running.
33 | [error]_34 = Invalid measurement level.
34 | [error]_36 = Invalid missing value format.
35 | [error]_40 = A Procedure Data Source is required.
36 | [error]_44 = The active dataset is empty.
37 | [error]_47 = Invalid format type.
38 | [error]_48 = Invalid format width.
39 | [error]_49 = Invalid decimal point.
40 | [error]_54 = No more data is available in the active dataset.
41 | [error]_56 = Only string variables are allowed.
42 | [error]_57 = Only numeric variables are allowed.
43 | [error]_58 = Invalid attribute name.
44 | [error]_59 = The length of user-missing value for a string variable must be 8 characters or less.
45 | [error]_61 = The data value is too long.
46 | [error]_62 = The length of a string variable cannot exceed 32767 bytes.
47 | [error]_64 = Cannot change data values or variable information in the original dataset.
48 | [warning]_67 = The end of the current split has been reached.
49 | [error]_70 = The label length is too long.
50 | [error]_71 = The value length is too long.
51 | [error]_82 = The variable is not in the active dataset.
52 | [error]_86 = An active data source is required to complete this action.
53 | [error]_87 = Invalid dataset name.
54 | [error]_88 = This method can only be called between SetDictionaryToSPSS and EndDataStep.
55 | [error]_89 = Invalid function call. Function can only be called during dataset creation or within a User Procedure.
56 | [error]_90 = Cannot create an active dataset within a User Procedure.
57 | [error]_91 = A dataset with the same name already exists.
58 | [error]_92 = Cannot complete this action while dataset creation is in process.
59 | [error]_94 = Cannot create a dataset while there are pending transformations.
60 | [error]_96 = Cannot find specified attribute name.
61 | [error]_99 = Cannot create specified dataset.
62 | [error]_100 = Invalid multiple response set definition.
63 | [error]_301 = No model in CF Applier Node,please make sure SetModel in Builder Node.
64 | [error]_402 = Invalid field index.
65 | [warning]_404 = Field does not have labels.
66 | [warning]_403 = Field labels and values do not match.
67 | [error]_999999997 = Unknown error.
68 | [error]_999999998 = Processing was interrupted by the user.
69 | [error]_999999999 = Unknown error.
70 |
71 | # Errors come from R plug-in.
72 | #[warning]_1000 = There are no more split groups.
73 | ## data model
74 | [RError]_1001 = Invalid R CF Component Data Model format.
75 | [RError]_1002 = Invalid field name in data model. Duplicate values are present.
76 | [warning]_1003 = Duplicate values are present for value labels.
77 | [RError]_1004 = Invalid field storage for SetDataModel.
78 | [RError]_1005 = Invalid field measure for SetDataModel.
79 | [RError]_1006 = Invalid field format for SetDataModel.
80 | [RError]_1007 = Invalid field role for SetDataModel.
81 |
82 | [RError]_1021 = Invalid field missing value.
83 | ##this is for GetDataModel or GetData
84 | [RError]_1020 = Invalid field name in argument.
85 |
86 | ## data
87 | [RError]_1008 = Invalid value for argument factorMode (must be "none", "levels" or "labels").
88 | [RError]_1009 = Invalid value for argument rDate (must be "none", "POSIXct" or "POSIXlt").
89 | [RError]_1010 = Invalid value for argument missingValue (must be NA, NaN or "asis").
90 | [RError]_1011 = Invalid function call. Function can only be called after calling SetDataModel.
91 | [RError]_1012 = Data and data model does not match.
92 |
93 | [RError]_1013 = Invalid index for GetOutputsNames.
94 | [RError]_1014 = Invalid graphic name or path.
95 | [RError]_1015 = Invalid graphic format (must be "JPG", "PNG" or "BMP").
96 | [RError]_1016 = Expects a numeric argument.
97 | [RError]_1017 = Expects an integer argument.
98 | [RError]_1018 = Expects a boolean argument.
99 | [RError]_1019 = Argument variables must be string, vector or list.
100 |
101 | # General errors
102 | SPSSError = IBM SPSS CF error
103 | SPSSWarning = IBM SPSS CF warning
104 | error_code = The error code is
105 | with_message = With message
106 |
--------------------------------------------------------------------------------
/src/inst/lang/zh_TW/ibmspsscfr.properties:
--------------------------------------------------------------------------------
1 |
2 | # Error messages for IBM SPSS Statistics-R plug-in
3 | # The numbers indicate the error level
4 | # The strings after "=" indicate the error message
5 | # [okay]_, [warning]_, [error]_, [RError]_ are part of keys
6 | # Don't translate them.
7 |
8 | # Errors come from IBM SPSS Statistics backend.
9 | [ok]_0 = No error.
10 | [ok]_1 = Comment.
11 | [warning]_2 = Warning.
12 | [error]_3 = Serious error.
13 | [error]_4 = Fatal error.
14 | [error]_5 = Catastrophic error.
15 | [error]_6 = Command syntax error.
16 | [error]_401 = Invalid index.
17 | [error]_11 = Cannot add object to XML workspace.
18 | [error]_12 = Invalid handle object.
19 | [error]_13 = Cannot remove XML workspace object.
20 | [error]_15 = Cannot get the result.
21 | [error]_16 = Invalid value.
22 | [warning]_20 = An existing XML workspace handle has been overwritten.
23 | [error]_21 = Invalid XPath expression.
24 | [error]_22 = XML error.
25 | [warning]_23 = Cannot read more data.
26 | [error]_24 = Invalid data type.
27 | [error]_25 = Duplicate variable name.
28 | [error]_26 = Invalid variable type.
29 | [error]_27 = Invalid variable name.
30 | [error]_30 = Invalid case.
31 | [error]_31 = Cannot complete this action while a data connection for processing split files is open.
32 | [error]_32 = A User Procedure is running.
33 | [error]_34 = Invalid measurement level.
34 | [error]_36 = Invalid missing value format.
35 | [error]_40 = A Procedure Data Source is required.
36 | [error]_44 = The active dataset is empty.
37 | [error]_47 = Invalid format type.
38 | [error]_48 = Invalid format width.
39 | [error]_49 = Invalid decimal point.
40 | [error]_54 = No more data is available in the active dataset.
41 | [error]_56 = Only string variables are allowed.
42 | [error]_57 = Only numeric variables are allowed.
43 | [error]_58 = Invalid attribute name.
44 | [error]_59 = The length of user-missing value for a string variable must be 8 characters or less.
45 | [error]_61 = The data value is too long.
46 | [error]_62 = The length of a string variable cannot exceed 32767 bytes.
47 | [error]_64 = Cannot change data values or variable information in the original dataset.
48 | [warning]_67 = The end of the current split has been reached.
49 | [error]_70 = The label length is too long.
50 | [error]_71 = The value length is too long.
51 | [error]_82 = The variable is not in the active dataset.
52 | [error]_86 = An active data source is required to complete this action.
53 | [error]_87 = Invalid dataset name.
54 | [error]_88 = This method can only be called between SetDictionaryToSPSS and EndDataStep.
55 | [error]_89 = Invalid function call. Function can only be called during dataset creation or within a User Procedure.
56 | [error]_90 = Cannot create an active dataset within a User Procedure.
57 | [error]_91 = A dataset with the same name already exists.
58 | [error]_92 = Cannot complete this action while dataset creation is in process.
59 | [error]_94 = Cannot create a dataset while there are pending transformations.
60 | [error]_96 = Cannot find specified attribute name.
61 | [error]_99 = Cannot create specified dataset.
62 | [error]_100 = Invalid multiple response set definition.
63 | [error]_301 = No model in CF Applier Node,please make sure SetModel in Builder Node.
64 | [error]_402 = Invalid field index.
65 | [warning]_404 = Field does not have labels.
66 | [warning]_403 = Field labels and values do not match.
67 | [error]_999999997 = Unknown error.
68 | [error]_999999998 = Processing was interrupted by the user.
69 | [error]_999999999 = Unknown error.
70 |
71 | # Errors come from R plug-in.
72 | #[warning]_1000 = There are no more split groups.
73 | ## data model
74 | [RError]_1001 = Invalid R CF Component Data Model format.
75 | [RError]_1002 = Invalid field name in data model. Duplicate values are present.
76 | [warning]_1003 = Duplicate values are present for value labels.
77 | [RError]_1004 = Invalid field storage for SetDataModel.
78 | [RError]_1005 = Invalid field measure for SetDataModel.
79 | [RError]_1006 = Invalid field format for SetDataModel.
80 | [RError]_1007 = Invalid field role for SetDataModel.
81 |
82 | [RError]_1021 = Invalid field missing value.
83 | ##this is for GetDataModel or GetData
84 | [RError]_1020 = Invalid field name in argument.
85 |
86 | ## data
87 | [RError]_1008 = Invalid value for argument factorMode (must be "none", "levels" or "labels").
88 | [RError]_1009 = Invalid value for argument rDate (must be "none", "POSIXct" or "POSIXlt").
89 | [RError]_1010 = Invalid value for argument missingValue (must be NA, NaN or "asis").
90 | [RError]_1011 = Invalid function call. Function can only be called after calling SetDataModel.
91 | [RError]_1012 = Data and data model does not match.
92 |
93 | [RError]_1013 = Invalid index for GetOutputsNames.
94 | [RError]_1014 = Invalid graphic name or path.
95 | [RError]_1015 = Invalid graphic format (must be "JPG", "PNG" or "BMP").
96 | [RError]_1016 = Expects a numeric argument.
97 | [RError]_1017 = Expects an integer argument.
98 | [RError]_1018 = Expects a boolean argument.
99 | [RError]_1019 = Argument variables must be string, vector or list.
100 |
101 | # General errors
102 | SPSSError = IBM SPSS CF error
103 | SPSSWarning = IBM SPSS CF warning
104 | error_code = The error code is
105 | with_message = With message
106 |
--------------------------------------------------------------------------------
/src/src/Makevars.aix64:
--------------------------------------------------------------------------------
1 | PKG_CPPFLAGS = -DAIX
--------------------------------------------------------------------------------
/src/src/Makevars.mac:
--------------------------------------------------------------------------------
1 | PKG_CPPFLAGS = -DDARWIN -isysroot /Applications/Xcode.app/Contents/Developer/Platforms/MacOSX.platform/Developer/SDKs/MacOSX10.8.sdk -mmacosx-version-min=10.8
2 | PKG_LIBS = -Wl,-syslibroot,/Applications/Xcode.app/Contents/Developer/Platforms/MacOSX.platform/Developer/SDKs/MacOSX10.8.sdk -mmacosx-version-min=10.8
--------------------------------------------------------------------------------
/src/src/Makevars.plnx64:
--------------------------------------------------------------------------------
1 | PKG_LIBS=-G -qpic=large
2 |
--------------------------------------------------------------------------------
/src/src/Makevars.win:
--------------------------------------------------------------------------------
1 | PKG_CPPFLAGS = -DRINVOKEMODELER_EXPORTS -D_WINDOWS
2 |
--------------------------------------------------------------------------------
/src/src/r_plugin_ibm_spss.h:
--------------------------------------------------------------------------------
1 | /************************************************************************
2 | ** IBM?? SPSS?? Modeler - Essentials for R
3 | ** (c) Copyright IBM Corp. 1989, 2012
4 | **
5 | ** This program is free software; you can redistribute it and/or modify
6 | ** it under the terms of the GNU General Public License version 2 as published by
7 | ** the Free Software Foundation.
8 | **
9 | ** This program is distributed in the hope that it will be useful,
10 | ** but WITHOUT ANY WARRANTY; without even the implied warranty of
11 | ** MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 | ** GNU General Public License for more details.
13 | **
14 | ** You should have received a copy of the GNU General Public License version 2
15 | ** along with this program; if not, write to the Free Software
16 | ** Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
17 | ************************************************************************/
18 |
19 | #ifndef __R_PLUGIN_IBM_SPSS_H__
20 | #define __R_PLUGIN_IBM_SPSS_H__
21 |
22 | #ifdef _WINDOWS
23 | #ifdef RINVOKEMODELER_EXPORTS
24 | #define RINVOKEMODELER_API __declspec(dllexport)
25 | #else
26 | #define RINVOKEMODELER_API __declspec(dllimport)
27 | #endif
28 | #else
29 | #define RINVOKEMODELER_API
30 | #endif
31 |
32 | #include
33 | #include
34 |
35 | extern "C" {
36 | #include
37 | RINVOKEMODELER_API void ext_PostOutput(const char **text, int *length, int *errLevel);
38 | RINVOKEMODELER_API void ext_StartProcedure(int* errLevel);
39 | RINVOKEMODELER_API void ext_StopProcedure(int* errLevel);
40 | RINVOKEMODELER_API void ext_GetOutputDir(const char **dirPath, int* errLevel);
41 | RINVOKEMODELER_API void ext_GetTempDataFile(const char **filePath, int *miss, int* errLevel);
42 | RINVOKEMODELER_API void ext_SetDataToTemp(const char **filePath, int* errLevel);
43 | RINVOKEMODELER_API void ext_GetModel(const char** modelName, int* errLevel);
44 | RINVOKEMODELER_API void ext_IsDisplayTextOutput(int* isDisplayTextOutput, int* errLevel);
45 | RINVOKEMODELER_API void ext_GetSystemLocale(const char** locale, int* errLevel);
46 | RINVOKEMODELER_API void ext_SendErrorCode(SEXP errCode, SEXP msgType, SEXP para, SEXP errLevel);
47 |
48 | RINVOKEMODELER_API void ext_GetFieldName(const char **fieldName, int* index, int* errLevel);
49 | RINVOKEMODELER_API void ext_GetFieldStorage(const char **fieldStorage, int* index, int* errLevel);
50 | RINVOKEMODELER_API void ext_GetFieldCount(int* count, int* errLevel);
51 |
52 | RINVOKEMODELER_API SEXP ext_GetFieldNames(SEXP fields, SEXP errLevel);
53 | RINVOKEMODELER_API SEXP ext_GetFieldStorages(SEXP fields, SEXP errLevel);
54 | RINVOKEMODELER_API SEXP ext_GetFieldMeasures(SEXP fields, SEXP errLevel);
55 | RINVOKEMODELER_API SEXP ext_GetFieldLabels(SEXP fields, SEXP errLevel);
56 | RINVOKEMODELER_API SEXP ext_GetFieldFormats(SEXP fields, SEXP errLevel);
57 | RINVOKEMODELER_API SEXP ext_GetFieldRoles(SEXP fields, SEXP errLevel);
58 |
59 | RINVOKEMODELER_API SEXP ext_GetMissingValues(SEXP field, SEXP errLevel);
60 | RINVOKEMODELER_API SEXP ext_GetFlagValues(SEXP field, SEXP errLevel);
61 | RINVOKEMODELER_API SEXP ext_GetValueLabels(SEXP field, SEXP errLevel);
62 |
63 | // data functions
64 | RINVOKEMODELER_API bool ext_NextRecord(int* errLevel);
65 | RINVOKEMODELER_API void ext_HasMoreData(bool* hasMoreData, int* errLevel);
66 | RINVOKEMODELER_API void ext_GetRecordCount(int* count, int* errLevel);
67 | RINVOKEMODELER_API SEXP ext_GetData(SEXP fieldIndexs, SEXP recordCount, SEXP missing, SEXP errLevel);
68 | RINVOKEMODELER_API SEXP ext_SetData(SEXP data, SEXP fieldStorages, SEXP errLevel);
69 | RINVOKEMODELER_API SEXP ext_SetDataModel(SEXP dataModel, SEXP errLevel);
70 |
71 | //===================R initialize=========================
72 | RINVOKEMODELER_API void R_init_RInvokeModeler(DllInfo *info);
73 | RINVOKEMODELER_API void R_unload_RInvokeModeler(DllInfo *info);
74 | }
75 |
76 | #endif //__R_PLUGIN_IBM_SPSS_H__
77 |
--------------------------------------------------------------------------------