Skip to content

Commit

Permalink
Merge SVN 3945
Browse files Browse the repository at this point in the history
  • Loading branch information
ddeclerck committed May 31, 2024
1 parent ea4e36a commit b3f799b
Show file tree
Hide file tree
Showing 2 changed files with 70 additions and 2 deletions.
4 changes: 2 additions & 2 deletions NEWS
Original file line number Diff line number Diff line change
Expand Up @@ -469,7 +469,7 @@ Open Plans:
still applied;
File name mapping now applies both to COBOL statements and CALLable
CBL_ and C$ file routines.

** Screen I/O: initial mouse support (for details see runtime.cfg),
use of CURSOR clause in SPECIAL-NAMES for positioning on ACCEPT

Expand Down Expand Up @@ -522,7 +522,7 @@ Open Plans:
not included in -Wall any more
-Wno-ignored-error allows to suppress messages that normally would be an
error and are only allowed because they are never executed
-Wcorresponding is now enabled by default
-Wimplicit-define and -Wcorresponding are now enabled by default

-f[no]-diagnostics-show-option, enabled by default, shows the
command line option responsible for the diagnostic message
Expand Down
68 changes: 68 additions & 0 deletions tests/testsuite.src/run_extensions.at
Original file line number Diff line number Diff line change
Expand Up @@ -1274,6 +1274,74 @@ GRP-5:***Mon49eyMon49eyMon49eyMon49eyMon49eyMon49eyMon49eyMon
AT_CLEANUP


AT_SETUP([INITIALIZE OCCURS UNBOUNDED])
AT_KEYWORDS([extensions runsubscripts subscripts refmod INITIALIZE])

AT_DATA([prog.cob], [
IDENTIFICATION DIVISION.
PROGRAM-ID. prog.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 p USAGE POINTER.
01 p2 USAGE POINTER.

LINKAGE SECTION.
01 a-table.
03 prefix.
05 n PIC 9(03) VALUE 123.
03 table-data value all "ABCDE".
04 rows OCCURS 0 TO UNBOUNDED TIMES
DEPENDING ON n.
05 col1 PIC X.
05 col2 PIC X(02).

PROCEDURE DIVISION.
ALLOCATE LENGTH OF prefix CHARACTERS
RETURNING p
SET ADDRESS OF a-table TO p
INITIALIZE prefix ALL TO VALUE
IF FUNCTION LENGTH (a-table) NOT = 372
DISPLAY 'WRONG LENGTH table: ' FUNCTION LENGTH (a-table)
END-DISPLAY
END-IF
ALLOCATE FUNCTION LENGTH (a-table) CHARACTERS
RETURNING p2
SET ADDRESS OF a-table TO p2
FREE p
INITIALIZE prefix ALL TO VALUE
*> FIXME: broken - initializes up to max but only should initialize
*> up to current size INITIALIZE table-data ALL TO VALUE
*> INITIALIZE table-data ALL TO VALUE
*> FIXME: broken - FUNCTION LENGTH(table-data) must be resolved
*> at run-time but is currently set to max at compile-time
*> INITIALIZE table-data (1:FUNCTION LENGTH(table-data))
*> ALL TO VALUE
INITIALIZE table-data (1:FUNCTION LENGTH(rows(1)) * n)
ALL TO VALUE
IF col2(1) NOT = "BC"
DISPLAY "col2(1) wrong: " col2(1)
END-DISPLAY
END-IF
IF rows(2) NOT = "DEA"
DISPLAY "rows(2) wrong: " rows(2)
END-DISPLAY
END-IF
DISPLAY LENGTH OF a-table
*> check if ref-mod also works as expected
MOVE ALL ZEROES TO a-table (1: (LENGTH OF a-table))
.
])

AT_CHECK([$COMPILE prog.cob], [0], [], [])

# multiple issues, see comments above
AT_XFAIL_IF(true)

AT_CHECK([$COBCRUN_DIRECT ./prog], [0], [], [])

AT_CLEANUP


AT_SETUP([DEPENDING ON with ODOSLIDE])
AT_KEYWORDS([nested ODO])

Expand Down

0 comments on commit b3f799b

Please sign in to comment.