Skip to content
Snippets Groups Projects
Commit 0b1ebb1e authored by rdubner's avatar rdubner
Browse files

Repair failsuite "FUNCTION BIGGER-POINTER" test

parent dc7f1977
No related branches found
No related tags found
No related merge requests found
Pipeline #1305 passed
...@@ -842,36 +842,42 @@ AT_DATA([prog.cob], [ ...@@ -842,36 +842,42 @@ AT_DATA([prog.cob], [
PROGRAM-ID. prog. PROGRAM-ID. prog.
DATA DIVISION. DATA DIVISION.
WORKING-STORAGE SECTION. WORKING-STORAGE SECTION.
77 N PICTURE S9(8) COMP. 01 N PIC S9(8) COMP-5 value 0.
77 P REDEFINES N USAGE POINTER. 01 P REDEFINES N POINTER.
01 X PIC A(4) VALUE Z"ABC". 01 FILLER.
05 E PIC A OCCURS 4. 05 X PIC A(4) VALUE "ABC".
77 B PICTURE A BASED. 05 E REDEFINES X PIC A(1) OCCURS 4.
LINKAGE SECTION.
77 B PIC A BASED.
PROCEDURE DIVISION. PROCEDURE DIVISION.
set P to address of E(1). set P to address of E(1).
display FUNCTION trim(x) '.' display FUNCTION trim(x) '.'
perform until B = SPACES set address of B to p.
set address of B to p. perform test after until B = SPACE
display B no advancing display B no advancing
set p up by 1. set p up by 1
end-perform. set address of B to p
display '.'. end-perform
display '.'
set P to address of E(1).
set P to address of E(1)
set address of B to p
perform until B = SPACES perform until B = SPACES
set address of B to p.
display B no advancing display B no advancing
add 8 to N. add 1 to N
end-perform. set address of B to p
display '.'. end-perform
display '.'
STOP RUN. STOP RUN.
]) ])
AT_CHECK([$COMPILE -dialect ibm prog.cob], [0], [], []) AT_CHECK([$COMPILE -dialect ibm prog.cob], [0], [], [])
AT_CHECK([$COBCRUN_DIRECT ./a.out], [0], [], []) AT_CHECK([$COBCRUN_DIRECT ./a.out], [0], [ABC.
ABC.
ABC.
], [])
AT_CLEANUP AT_CLEANUP
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment