diff --git a/gcc/cobol/UAT/failsuite.src/run_functions.at b/gcc/cobol/UAT/failsuite.src/run_functions.at index 25417135f0088bb86baea63b6d527e31f12e5efb..62dd92a1832d0c9ee128c50cc6a48aeba43b7638 100644 --- a/gcc/cobol/UAT/failsuite.src/run_functions.at +++ b/gcc/cobol/UAT/failsuite.src/run_functions.at @@ -848,7 +848,7 @@ AT_DATA([prog.cob], [ 05 X PIC A(4) VALUE "ABC". 05 E REDEFINES X PIC A(1) OCCURS 4. LINKAGE SECTION. - 77 B PIC A BASED. + 77 B PIC A. PROCEDURE DIVISION. set P to address of E(1). @@ -856,7 +856,7 @@ AT_DATA([prog.cob], [ display FUNCTION trim(x) '.' set address of B to p. - perform test after until B = SPACE + perform until B = SPACE display B no advancing set p up by 1 set address of B to p