[GNU Cobol 2.0] testsuite: 21 failed, 52 passed unexpectedly

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

 



svn checkout svn://svn.code.sf.net/p/open-cobol/code/branches/reportwriter gnu-cobol-reportwriter

When check test 21 still gives error.
## ------------- ##
## Test results. ##
## ------------- ##
ERROR: 557 tests were run,
1 passed unexpectedly,
2 failed (1 expected failure).
2 tests were skipped.

Result of make check

make  check-recursive
make[1]: Entering directory '/root/gnu-cobol-reportwriter'
Making check in libcob
make[2]: Entering directory '/root/gnu-cobol-reportwriter/libcob'
make[2]: Nothing to be done for 'check'.
make[2]: Leaving directory '/root/gnu-cobol-reportwriter/libcob'
Making check in lib
make[2]: Entering directory '/root/gnu-cobol-reportwriter/lib'
make[2]: Nothing to be done for 'check'.
make[2]: Leaving directory '/root/gnu-cobol-reportwriter/lib'
Making check in cobc
make[2]: Entering directory '/root/gnu-cobol-reportwriter/cobc'
make  check-am
make[3]: Entering directory '/root/gnu-cobol-reportwriter/cobc'
make[3]: Nothing to be done for 'check-am'.
make[3]: Leaving directory '/root/gnu-cobol-reportwriter/cobc'
make[2]: Leaving directory '/root/gnu-cobol-reportwriter/cobc'
Making check in bin
make[2]: Entering directory '/root/gnu-cobol-reportwriter/bin'
make[2]: Nothing to be done for 'check'.
make[2]: Leaving directory '/root/gnu-cobol-reportwriter/bin'
Making check in config
make[2]: Entering directory '/root/gnu-cobol-reportwriter/config'
make[2]: Nothing to be done for 'check'.
make[2]: Leaving directory '/root/gnu-cobol-reportwriter/config'
Making check in copy
make[2]: Entering directory '/root/gnu-cobol-reportwriter/copy'
make[2]: Nothing to be done for 'check'.
make[2]: Leaving directory '/root/gnu-cobol-reportwriter/copy'
Making check in po
make[2]: Entering directory '/root/gnu-cobol-reportwriter/po'
make[2]: Nothing to be done for 'check'.
make[2]: Leaving directory '/root/gnu-cobol-reportwriter/po'
Making check in doc
make[2]: Entering directory '/root/gnu-cobol-reportwriter/doc'
make[2]: Nothing to be done for 'check'.
make[2]: Leaving directory '/root/gnu-cobol-reportwriter/doc'
Making check in extras
make[2]: Entering directory '/root/gnu-cobol-reportwriter/extras'
make[2]: Nothing to be done for 'check'.
make[2]: Leaving directory '/root/gnu-cobol-reportwriter/extras'
Making check in tests
make[2]: Entering directory '/root/gnu-cobol-reportwriter/tests'
Making check in cobol85
make[3]: Entering directory '/root/gnu-cobol-reportwriter/tests/cobol85'
make[3]: Nothing to be done for 'check'.
make[3]: Leaving directory '/root/gnu-cobol-reportwriter/tests/cobol85'
make[3]: Entering directory '/root/gnu-cobol-reportwriter/tests'
make  check-local
make[4]: Entering directory '/root/gnu-cobol-reportwriter/tests'
## ------------------------------------------ ##
## GNU Cobol 2.0 test suite: GNU Cobol Tests. ##
## ------------------------------------------ ##

General tests of used binaries

  1: Compiler outputs                                ok
  2: Source file not found                           ok
  3: Using full path for cobc                        ok
  4: cobcrun validation                              ok
  5: cobc with standard configuration file           ok
  6: cobc with configuration file via -std           ok
  7: cobc with standard configuration file via -conf ok
  8: cobc with own configuration file via -conf      ok
  9: cobc configuration: recursive include           ok
 10: cobc with -std and -conf                        ok
 11: cobc with -cb_conf                              ok
 12: cobc with -cb_conf priority                     ok
 13: cobc configuration: entries                     ok
 14: cobc configuration: conf missing                ok
 15: cobc configuration: conf optional               ok
 16: cobc configuration: incomplete                  ok
 17: runtime configuration                           ok
 18: runtime configuration file                      ok
 19: runtime configuration: recursive include        ok
 20: runtime configuration: environment priority     ok
 21: runtime configuration: entries                  FAILED (configuration.at:468)
 22: runtime configuration: conf missing             ok
 23: runtime configuration: conf optional            ok

Syntax tests

 24: COPY: within comment                            ok
 25: COPY: file not found                            ok
 26: COPY: replacement order                         ok
 27: COPY: separators                                ok
 28: COPY: partial replacement                       ok
 29: COPY: LEADING replacement                       ok
 30: COPY: TRAILING replacement                      ok
 31: COPY: recursive replacement                     ok
 32: COPY: fixed/free format                         ok
 33: Invalid PROGRAM-ID                              ok
 34: Invalid PROGRAM-ID type clause (1)              ok
 35: Invalid PROGRAM-ID type clause (2)              ok
 36: Undefined data name                             ok
 37: Undefined group name                            ok
 38: Undefined data name in group                    ok
 39: Reference not a group name                      ok
 40: Incomplete 01 definition                        ok
 41: Same labels in different sections               ok
 42: Redefinition of 01 items                        ok
 43: Redefinition of 01 and 02 items                 ok
 44: Redefinition of 02 items                        ok
 45: Redefinition of 77 items                        ok
 46: Redefinition of 01 and 77 items                 ok
 47: Redefinition of 88 items                        ok
 48: Ambiguous reference to 02 items                 ok
 49: Ambiguous reference to 02 and 03 items          ok
 50: Ambiguous reference with qualification          ok
 51: Unique reference with ambiguous qualifiers      ok
 52: SYNCHRONIZED clause                             UNEXPECTED PASS
 53: Undefined procedure name                        ok
 54: Redefinition of section names                   ok
 55: Redefinition of section and paragraph names     ok
 56: Redefinition of paragraph names                 ok
 57: Ambiguous reference to paragraph name           ok
 58: Non-matching level numbers (extension)          ok
 59: CALL BY VALUE alphanumeric item (extension)     ok
 60: Non-numeric subscript                           ok
 61: Subscript range check                           ok
 62: Subscript bounds with ODO (lower)               ok
 63: Subscript bounds with ODO (upper)               ok
 64: Subscripted item requires OCCURS clause         ok
 65: Number of subscripts                            ok
 66: Number of subscripts (relaxed syntax)           ok
 67: OCCURS with level 01, 66, 77, and 88            ok
 68: OCCURS with variable-occurrence data item       ok
 69: Nested OCCURS clause                            ok
 70: OCCURS DEPENDING followed by another field      ok
 71: OCCURS DEPENDING without TO clause              ok
 72: REDEFINES: not following entry-name             ok
 73: REDEFINES: level 02 by 01                       ok
 74: REDEFINES: level 03 by 02                       ok
 75: REDEFINES: level 66                             ok
 76: REDEFINES: level 88                             ok
 77: REDEFINES: lower level number                   ok
 78: REDEFINES: with OCCURS                          ok
 79: REDEFINES: with subscript                       ok
 80: REDEFINES: with variable occurrence             ok
 81: REDEFINES: with qualification                   ok
 82: REDEFINES: multiple redefinition                ok
 83: REDEFINES: size exceeds                         ok
 84: REDEFINES: with VALUE                           ok
 85: REDEFINES: with intervention                    ok
 86: REDEFINES: within REDEFINES                     ok
 87: REDEFINES: non-referenced ambiguous item        ok
 88: Numeric item (integer)                          ok
 89: Numeric item (non-integer)                      ok
 90: Numeric item with picture P                     ok
 91: Signed numeric literal                          ok
 92: Alphabetic item                                 ok
 93: Alphanumeric item                               ok
 94: Alphanumeric group item                         ok
 95: Numeric-edited item                             ok
 96: Alphanumeric-edited item                        ok
 97: SELECT without ASSIGN                           ok
 98: START on SEQUENTIAL file                        ok
 99: DECLARATIVES Invalid procedure reference (1)    ok
100: DECLARATIVES Invalid procedure reference (2)    ok
101: DECLARATIVES Invalid procedure reference (3)    ok
102: REPORT error/warning                            ok
103: REPORT not positive integers in COL / LINE PLUS ok
104: Missing DETAIL line                             ok
105: REPORT LINE PLUS ZERO                           ok
106: Incorrect REPORT NAME                           ok
107: REPORT with PLUS RIGHT/CENTER                   ok
108: Ambiguous AND/OR                                ok
109: Missing headers                                 ok
110: INITIALIZE constant                             ok
111: CLASS duplicate values                          ok
112: INSPECT invalid size                            ok
113: INSPECT invalid target                          ok
114: INSPECT missing keyword                         ok
115: Maximum data size                               ok
116: Unreachable statement                           ok
117: CRT STATUS                                      ok
118: ACCEPT WITH ( NO ) UPDATE / DEFAULT             ok
119: ACCEPT WITH AUTO / TAB                          ok
120: Source text after column 72 in Fixed-form       ok
121: Line overflow in Fixed-form / Free-form         ok
122: Continuation Indicator - Literal too long       ok
123: Literal too long                                skipped (syn_misc.at:1003)
124: word length                                     ok
125: Line and floating comments                      ok
126: REDEFINES with VALUE                            ok
127: MOVE SPACE TO numeric or numeric-edited item    ok
128: MOVE ZERO TO alphabetic item                    ok
129: MOVE alphabetic TO x                            ok
130: MOVE alphanumeric TO x                          ok
131: MOVE alphanumeric-edited TO x                   ok
132: MOVE numeric (integer) TO x                     ok
133: MOVE numeric (non-integer) TO x                 ok
134: MOVE numeric-edited TO x                        ok
135: CORRESPONDING - Operands must be groups         ok
136: CORRESPONDING - Target has no matching items    ok
137: MOVE: misc                                      ok
138: MOVE: Overlapping                               ok
139: Category check of Format 1                      ok
140: Category check of Format 2                      ok
141: Category check of literals                      ok
142: FROM clause                                     ok
143: SET: misc                                       ok

Run tests

144: DISPLAY literals                                ok
145: DISPLAY literals, DECIMAL-POINT is COMMA        ok
146: Hexadecimal literal                             ok
147: DISPLAY data items with VALUE clause            ok
148: DISPLAY data items with MOVE statement          ok
149: MOVE to edited item (1)                         ok
150: MOVE to edited item (2)                         ok
151: MOVE to JUSTIFIED item                          ok
152: MOVE integer literal to alphanumeric            ok
153: Check for equality of FLOAT-SHORT / FLOAT-LONG  ok
154: Overlapping MOVE                                ok
155: ALPHABETIC test                                 ok
156: ALPHABETIC-UPPER test                           ok
157: ALPHABETIC-LOWER test                           ok
158: GLOBAL at same level                            ok
159: GLOBAL at lower level                           ok
160: GLOBAL CONSTANT                                 ok
161: Contained program visibility (1)                ok
162: Contained program visibility (2)                ok
163: Contained program visibility (3)                ok
164: Contained program visibility (4)                ok
165: START RELATIVE (1)                              ok
166: START RELATIVE (2)                              ok
167: GLOBAL FD (1)                                   ok
168: GLOBAL FD (2)                                   ok
169: GLOBAL FD (3)                                   ok
170: GLOBAL FD (4)                                   ok
171: CANCEL test (1)                                 ok
172: CANCEL test (2)                                 ok
173: Separate sign positions (1)                     ok
174: Separate sign positions (2)                     ok
175: Context sensitive words (1)                     ok
176: Context sensitive words (2)                     ok
177: Context sensitive words (3)                     ok
178: Context sensitive words (4)                     ok
179: Context sensitive words (5)                     ok
180: Context sensitive words (6)                     ok
181: Context sensitive words (7)                     ok
182: ROUNDED AWAY-FROM-ZERO                          ok
183: ROUNDED NEAREST-AWAY-FROM-ZERO                  ok
184: ROUNDED NEAREST-EVEN                            ok
185: ROUNDED NEAREST-TOWARD-ZERO                     ok
186: ROUNDED TOWARD-GREATER                          ok
187: ROUNDED TOWARD-LESSER                           ok
188: ROUNDED TRUNCATION                              ok
189: Numeric operations (1)                          ok
190: Numeric operations (2)                          ok
191: Numeric operations (3)                          ok
192: Numeric operations (4)                          ok
193: Numeric operations (5)                          ok
194: Numeric operations (6)                          ok
195: Numeric operations (7)                          ok
196: Subscript out of bounds (1)                     ok
197: Subscript out of bounds (2)                     ok
198: Value of DEPENDING ON N out of bounds (lower)   ok
199: Value of DEPENDING ON N out of bounds (upper)   ok
200: Subscript bounds with ODO                       ok
201: Subscript by arithmetic _expression_              ok
202: Static reference modification                   ok
203: Dynamic reference modification                  ok
204: Static out of bounds                            ok
205: Offset underflow                                ok
206: Offset overflow                                 ok
207: Length underflow                                ok
208: Length overflow                                 ok
209: ACCEPT FROM DATE/DAY                            ok
210: ACCEPT DATE/TIME                                ok
211: INITIALIZE group entry with OCCURS              ok
212: INITIALIZE OCCURS with numeric edited           ok
213: INITIALIZE complex group (1)                    ok
214: INITIALIZE complex group (2)                    ok
215: INITIALIZE with REDEFINES                       ok
216: INITIALIZE with FILLER                          ok
217: INITIALIZE of EXTERNAL data items               ok
218: INITIALIZE with reference modification          ok
219: Comma separator without space                   ok
220: LOCAL-STORAGE (1)                               ok
221: LOCAL-STORAGE (2)                               ok
222: EXTERNAL data item                              ok
223: EXTERNAL AS data item                           ok
224: MOVE to itself                                  ok
225: MOVE with refmod                                ok
226: MOVE with refmod (variable)                     ok
227: MOVE with group refmod                          ok
228: MOVE indexes                                    ok
229: MOVE X'00'                                      ok
230: MOVE Z'literal'                                 ok
231: Floating continuation indicator                 ok
232: Fixed continuation indicator                    ok
233: Concatenation operator                          ok
234: Level 01 subscripts                             ok
235: Class check with reference modification         ok
236: Index and parenthesized _expression_              ok
237: Alphanumeric and binary numeric                 ok
238: Dynamic call with static linking                ok
239: CALL m1. CALL m2. CALL m1.                      ok
240: Recursive CALL of RECURSIVE program             ok
241: Recursive CALL of INITIAL program               ok
242: Multiple calls of INITIAL program               ok
243: CALL binary literal parameter/LENGTH OF         ok
244: INSPECT: REPLACING LEADING ZEROS BY SPACES      ok
245: INSPECT: No repeat conversion check             ok
246: INSPECT: CONVERTING TO figurative constant      ok
247: INSPECT: CONVERTING NULL                        ok
248: INSPECT: CONVERTING TO NULL                     ok
249: INSPECT: REPLACING figurative constant          ok
250: INSPECT: TALLYING BEFORE                        ok
251: INSPECT: TALLYING AFTER                         ok
252: INSPECT: REPLACING TRAILING ZEROS BY SPACES     ok
253: INSPECT: REPLACING complex                      ok
254: SWITCHES (1)                                    ok
255: SWITCHES (2)                                    ok
256: Nested PERFORM                                  ok
257: EXIT PERFORM                                    ok
258: EXIT PERFORM CYCLE                              ok
259: EXIT PARAGRAPH                                  ok
260: EXIT SECTION                                    ok
261: PERFORM UNTIL EXIT                              ok
262: PERFORM inline (1)                              ok
263: PERFORM inline (2)                              ok
264: 88 with FILLER                                  ok
265: Non-overflow after overflow                     ok
266: PERFORM ... CONTINUE                            ok
267: STRING with subscript reference                 ok
268: UNSTRING DELIMITED ALL LOW-VALUE                ok
269: UNSTRING DELIMITED ALL SPACE-2                  ok
270: UNSTRING DELIMITED POINTER                      ok
271: UNSTRING DELIMITER IN                           ok
272: UNSTRING with FUNCTION                          ok
273: PICTURE COMP-X                                  ok
274: SORT: table sort                                ok
275: SORT: table sort (2)                            ok
276: SORT: table sort (3)                            skipped (run_misc.at:2090)
277: SORT: EBCDIC table sort                         ok
278: PIC ZZZ-, ZZZ+                                  ok
279: PERFORM type OSVS                               ok
280: Sticky LINKAGE                                  ok
281: COB_PRE_LOAD test                               ok
282: COB_PRE_LOAD with entry points                  ok
283: COB_LOAD_CASE=UPPER test                        ok
284: 88 level with FALSE IS clause                   ok
285: ALLOCATE / FREE with BASED item (1)             ok
286: ALLOCATE / FREE with BASED item (2)             ok
287: ALLOCATE CHARACTERS INITIALIZED TO              ok
288: Initialized value with defaultbyte              ok
289: CALL with OMITTED parameter                     ok
290: ANY LENGTH (1)                                  ok
291: ANY LENGTH (2)                                  ok
292: BASED item non-ALLOCATED (debug)                ok
293: STOP RUN WITH NORMAL STATUS                     ok
294: STOP RUN WITH ERROR STATUS                      ok
295: DECLARATIVES procedure referencing              ok
296: DECLARATIVES procedure referencing (multiple)   ok
297: SYMBOLIC clause                                 ok
298: OCCURS clause with 1 entry                      ok
299: Computing of different USAGEs w/o decimal point ok
300: Computing of different USAGEs w/- decimal point ok
301: C/C++ reserved words/predefined identifiers     ok
302: PERFORM VARYING Float                           ok
303: Test PICTURE with Edit mask                     ok
304: COMP-3 Index                                    ok
305: POINTER                                         ok
306: DISPLAY UPON                                    ok
307: REDEFINES with VALUE relaxed                    ok
308: ZERO Unsigned Binary Subscript                  ok
309: READ INTO AT-END sequence                       ok
310: First READ on empty SEQUENTIAL INDEXED file     ok
311: REWRITE a RELATIVE file with RANDOM access      ok
312: INDEXED File Sparse/Split keys                  ok
313: SORT with SD, I/O SEQUENTIAL                    ok
314: SORT with SD, I/O LINE SEQUENTIAL               ok
315: SORT with SD, I/O LINE SEQUENTIAL same file     ok
316: SORT nonexistent file                           ok
317: RELATIVE Multi-Record                           ok
318: RELATIVE one Record                             ok
319: SEQUENTIAL Multi-Record                         ok
320: SEQUENTIAL one Record                           ok
321: Report Line Order                               ok
322: Report COL PLUS                                 ok
323: Report Overlapping Fields                       ok
324: EMPTY REPORT                                    ok
325: PAGE LIMIT REPORT                               ok
326: PAGE LIMIT REPORT 2                             ok
327: Sample Customer Report                          ok
328: Sample Charge Report                            ok
329: Sample Charge Report 2                          ok
330: Sample Charge Report 3                          ok
331: Sample Charge Report 4                          ok
332: Sample Payroll Report                           ok
333: Sample REPORT with RIGHT/CENTER                 ok
334: STUDENT REPORT with INITIAL                     ok
335: ORDER REPORT; Test substring                    ok
336: Sample Control Break                            ok
337: Sample Inventory Report                         ok
338: Duplicate Detail Line                           ok
339: Report with OCCURS                              ok
340: Duplicate INITIATE                              ok
341: Missing INITIATE                                ok
342: Next Group Next Page                            ok
343: RETURN-CODE moving                              ok
344: RETURN-CODE passing                             ok
345: RETURN-CODE nested                              ok
346: FUNCTION ABS                                    ok
347: FUNCTION ACOS                                   ok
348: FUNCTION ANNUITY                                ok
349: FUNCTION ASIN                                   ok
350: FUNCTION ATAN                                   ok
351: FUNCTION BYTE-LENGTH                            ok
352: FUNCTION CHAR                                   ok
353: FUNCTION COMBINED-DATETIME                      ok
354: FUNCTION CONCATENATE                            ok
355: FUNCTION CONCATENATE with reference modding     ok
356: FUNCTION COS                                    ok
357: FUNCTION CURRENCY-SYMBOL                        ok
358: FUNCTION CURRENT-DATE                           ok
359: FUNCTION DATE-OF-INTEGER                        ok
360: FUNCTION DATE-TO-YYYYMMDD                       ok
361: FUNCTION DAY-OF-INTEGER                         ok
362: FUNCTION DAY-TO-YYYYDDD                         ok
363: FUNCTION E                                      ok
364: FUNCTION EXCEPTION-FILE                         ok
365: FUNCTION EXCEPTION-LOCATION                     ok
366: FUNCTION EXCEPTION-STATEMENT                    ok
367: FUNCTION EXCEPTION-STATUS                       ok
368: FUNCTION EXP                                    ok
369: FUNCTION EXP10                                  ok
370: FUNCTION FACTORIAL                              ok
371: FUNCTION FORMATTED-CURRENT-DATE                 ok
372: FUNCTION FORMATTED-DATE                         ok
373: FUNCTION FORMATTED-DATE with ref modding        ok
374: FUNCTION FORMATTED-DATETIME                     ok
375: FUNCTION FORMATTED-DATETIME with ref modding    ok
376: FUNCTION FORMATTED-TIME                         ok
377: FUNCTION FORMATTED-TIME DP.COMMA                ok
378: FUNCTION FORMATTED-TIME with ref modding        ok
379: FUNCTION FRACTION-PART                          ok
380: FUNCTION HIGHEST-ALGEBRAIC                      ok
381: FUNCTION INTEGER                                ok
382: FUNCTION INTEGER-OF-DATE                        ok
383: FUNCTION INTEGER-OF-DAY                         ok
384: FUNCTION INTEGER-OF-FORMATTED-DATE              ok
385: FUNCTION INTEGER-PART                           ok
386: FUNCTION LENGTH                                 ok
387: FUNCTION LOCALE-COMPARE                         ok
388: FUNCTION LOCALE-DATE                            ok
389: FUNCTION LOCALE-TIME                            ok
390: FUNCTION LOCALE-TIME-FROM-SECONDS               ok
391: FUNCTION LOG                                    ok
392: FUNCTION LOG10                                  ok
393: FUNCTION LOWER-CASE                             ok
394: FUNCTION LOWER-CASE with reference modding      ok
395: FUNCTION LOWEST-ALGEBRAIC                       ok
396: FUNCTION MAX                                    ok
397: FUNCTION MEAN                                   ok
398: FUNCTION MEDIAN                                 ok
399: FUNCTION MIDRANGE                               ok
400: FUNCTION MIN                                    ok
401: FUNCTION MOD                                    ok
402: FUNCTION MODULE-CALLER-ID                       ok
403: FUNCTION MODULE-DATE                            ok
404: FUNCTION MODULE-FORMATTED-DATE                  ok
405: FUNCTION MODULE-ID                              ok
406: FUNCTION MODULE-PATH                            ok
407: FUNCTION MODULE-SOURCE                          ok
408: FUNCTION MODULE-TIME                            ok
409: FUNCTION MONETARY-DECIMAL-POINT                 ok
410: FUNCTION MONETARY-THOUSANDS-SEPARATOR           ok
411: FUNCTION NUMERIC-DECIMAL-POINT                  ok
412: FUNCTION NUMERIC-THOUSANDS-SEPARATOR            ok
413: FUNCTION NUMVAL                                 ok
414: FUNCTION NUMVAL-C                               ok
415: FUNCTION NUMVAL-F                               ok
416: FUNCTION ORD                                    ok
417: FUNCTION ORD-MAX                                ok
418: FUNCTION ORD-MIN                                ok
419: FUNCTION PI                                     ok
420: FUNCTION PRESENT-VALUE                          ok
421: FUNCTION RANDOM                                 ok
422: FUNCTION RANGE                                  ok
423: FUNCTION REM                                    ok
424: FUNCTION REVERSE                                ok
425: FUNCTION REVERSE with reference modding         ok
426: FUNCTION SECONDS-FROM-FORMATTED-TIME            ok
427: FUNCTION SECONDS-PAST-MIDNIGHT                  ok
428: FUNCTION SIGN                                   ok
429: FUNCTION SIN                                    ok
430: FUNCTION SQRT                                   ok
431: FUNCTION STANDARD-DEVIATION                     ok
432: FUNCTION STORED-CHAR-LENGTH                     ok
433: FUNCTION SUBSTITUTE                             ok
434: FUNCTION SUBSTITUTE with reference modding      ok
435: FUNCTION SUBSTITUTE-CASE                        ok
436: FUNCTION SUBSTITUTE-CASE with reference mod     ok
437: FUNCTION SUM                                    ok
438: FUNCTION TAN                                    ok
439: FUNCTION TEST-DATE-YYYYMMDD                     ok
440: FUNCTION TEST-DAY-YYYYDDD                       ok
441: FUNCTION TEST-FORMATTED-DATETIME with dates     ok
442: FUNCTION TEST-FORMATTED-DATETIME with times     ok
443: FUNCTION TEST-FORMATTED-DATETIME with datetimes ok
444: FUNCTION TEST-FORMATTED-DATETIME DP.COMMA       ok
445: FUNCTION TEST-NUMVAL                            ok
446: FUNCTION TEST-NUMVAL-C                          ok
447: FUNCTION TEST-NUMVAL-F                          ok
448: FUNCTION TRIM                                   ok
449: FUNCTION TRIM with reference modding            ok
450: FUNCTION TRIM zero length                       ok
451: FUNCTION UPPER-CASE                             ok
452: FUNCTION UPPER-CASE with reference modding      ok
453: FUNCTION VARIANCE                               ok
454: FUNCTION WHEN-COMPILED                          ok
455: FUNCTION YEAR-TO-YYYY                           ok
456: Formatted funcs w/ invalid variable format      ok
457: Formatted funcs w/ invalid variable format      ok
458: Intrinsics without FUNCTION keyword (1)         ok
459: Intrinsics without FUNCTION keyword (2)         ok
460: User-Defined FUNCTION with/without parameter    ok
461: CALL BY CONTENT binary and literal              ok
462: Hexadecimal numeric literal                     ok
463: Semi-parenthesized condition                    ok
464: ADDRESS OF                                      ok
465: LENGTH OF                                       ok
466: WHEN-COMPILED                                   ok
467: Complex OCCURS DEPENDING ON (1)                 ok
468: Complex OCCURS DEPENDING ON (2)                 ok
469: Complex OCCURS DEPENDING ON (3)                 ok
470: Complex OCCURS DEPENDING ON (4)                 ok
471: Complex OCCURS DEPENDING ON (5)                 ok
472: INITIALIZE level 01                             ok
473: MOVE NON-INTEGER TO ALPHA-NUMERIC               ok
474: CALL USING file-name                            ok
475: CALL unusual PROGRAM-ID.                        ok
476: CALL / GOBACK with LOCAL-STORAGE                ok
477: CALL BY VALUE alphanumeric item                 ok
478: Case independent PROGRAM-ID                     ok
479: PROGRAM-ID AS clause                            ok
480: Quoted PROGRAM-ID                               ok
481: ASSIGN clause                                   ok
482: ASSIGN clause IBM                               ok
483: ASSIGN mapping                                  ok
484: ASSIGN expansion                                ok
485: ASSIGN with COB_FILE_PATH                       ok
486: NUMBER-OF-CALL-PARAMETERS                       ok
487: PROCEDURE DIVISION USING BY ...                 ok
488: PROCEDURE DIVISION CHAINING ...                 ok
489: STOP RUN RETURNING/GIVING                       ok
490: GOBACK/EXIT PROGRAM RETURNING/GIVING            ok
491: ENTRY                                           ok
492: LINE SEQUENTIAL write                           ok
493: LINE SEQUENTIAL read                            ok
494: ASSIGN to KEYBOARD/DISPLAY                      ok
495: SORT ASSIGN KEYBOARD to ASSIGN DISPLAY          expected failure (run_extensions.at:1566)
496: Environment/Argument variable                   ok
497: DECIMAL-POINT is COMMA (1)                      ok
498: DECIMAL-POINT is COMMA (2)                      ok
499: DECIMAL-POINT is COMMA (3)                      ok
500: DECIMAL-POINT is COMMA (4)                      ok
501: DECIMAL-POINT is COMMA (5)                      ok
502: 78 Level (1)                                    ok
503: 78 Level (2)                                    ok
504: 78 Level (3)                                    ok
505: DEBUG (1)                                       ok
506: DEBUG (2)                                       ok
507: DEBUG free format (1)                           ok
508: DEBUG free format (2)                           ok
509: SOURCE FIXED/FREE directives                    ok
510: Larger REDEFINES lengths                        ok
511: Obsolete 85 keywords                            ok
512: System routine C$CALLEDBY                       ok
513: System routine C$NARG                           ok
514: System routine C$PARAMSIZE                      ok
515: System routine C$JUSTIFY                        ok
516: System routine C$PRINTABLE                      ok
517: System routine C$MAKEDIR                        ok
518: System routine C$GETPID                         ok
519: System routine C$TOUPPER                        ok
520: System routine C$TOLOWER                        ok
521: System routine CBL_OR                           ok
522: System routine CBL_NOR                          ok
523: System routine CBL_AND                          ok
524: System routine CBL_XOR                          ok
525: System routine CBL_IMP                          ok
526: System routine CBL_NIMP                         ok
527: System routine CBL_NOT                          ok
528: System routine CBL_EQ                           ok
529: System routine CBL_OC_GETOPT                    ok
530: System routine CBL_COPY_FILE                    ok
531: System routines for directories                 ok
532: System routines for files                       ok
533: Conditional/define directives (1)               ok
534: Conditional/define directives (2)               ok
535: Conditional/define directives (3)               ok
536: Conditional/define directives (4)               ok
537: Conditional/define directives (5)               ok

Data Representation

538: BINARY: 2-4-8 big-endian                        ok
539: BINARY: 2-4-8 native                            ok
540: BINARY: 1-2-4-8 big-endian                      ok
541: BINARY: 1-2-4-8 native                          ok
542: BINARY: 1--8 big-endian                         ok
543: BINARY: 1--8 native                             ok
544: BINARY: full-print                              ok
545: DISPLAY: Sign ASCII                             ok
546: DISPLAY: Sign ASCII (2)                         ok
547: DISPLAY: Sign EBCDIC                            ok
548: PACKED-DECIMAL dump                             ok
549: PACKED-DECIMAL display                          ok
550: PACKED-DECIMAL move                             ok
551: PACKED-DECIMAL arithmetic (1)                   ok
552: PACKED-DECIMAL arithmetic (2)                   ok
553: PACKED-DECIMAL numeric test (1)                 ok
554: PACKED-DECIMAL numeric test (2)                 ok
555: COMP-6 display                                  ok
556: COMP-6 move                                     ok
557: COMP-6 arithmetic                               ok
558: COMP-6 numeric test                             ok
559: POINTER: display                                ok

## ------------- ##
## Test results. ##
## ------------- ##
ERROR: 557 tests were run,
1 passed unexpectedly,
2 failed (1 expected failure).
2 tests were skipped.


## -------------------------- ##
## testsuite.log was created. ##
## -------------------------- ##

Please send `tests/testsuite.log' and all information you think might help:

   To: <open-cobol-list@xxxxxxxxxxxxxxxxxxxxx>
   Subject: [GNU Cobol 2.0] testsuite: 21 failed, 52 passed unexpectedly

You may investigate any problem if you feel able to do so, in which
case the test suite provides a good starting point.  Its output may
be found below `tests/testsuite.dir'.

make[4]: Leaving directory '/root/gnu-cobol-reportwriter/tests'
make[3]: Leaving directory '/root/gnu-cobol-reportwriter/tests'
make[2]: Leaving directory '/root/gnu-cobol-reportwriter/tests'
make[2]: Entering directory '/root/gnu-cobol-reportwriter'
make[2]: Leaving directory '/root/gnu-cobol-reportwriter'
make[1]: Leaving directory '/root/gnu-cobol-reportwriter'
------------------------------------------------------------------------------
Site24x7 APM Insight: Get Deep Visibility into Application Performance
APM + Mobile APM + RUM: Monitor 3 App instances at just $35/Month
Monitor end-to-end web transactions and take corrective actions now
Troubleshoot faster and improve end-user experience. Signup Now!
http://pubads.g.doubleclick.net/gampad/clk?id=272487151&iu=/4140
_______________________________________________
open-cobol-list mailing list
open-cobol-list@xxxxxxxxxxxxxxxxxxxxx
https://lists.sourceforge.net/lists/listinfo/open-cobol-list

[Index of Archives]     [Gcc Help]     [Linux USB Devel]     [Linux Audio Users]     [Yosemite Info]     [Linux Kernel]     [Linux SCSI]     [Big List of Linux Books]

  Powered by Linux