From 0b1ebb1ee1acbdd3bd229bf8de387529651b1094 Mon Sep 17 00:00:00 2001
From: Bob Dubner <rdubner@symas.com>
Date: Wed, 3 Jan 2024 23:01:14 -0500
Subject: [PATCH] Repair failsuite "FUNCTION BIGGER-POINTER" test

---
 gcc/cobol/UAT/failsuite.src/run_functions.at | 40 +++++++++++---------
 1 file changed, 23 insertions(+), 17 deletions(-)

diff --git a/gcc/cobol/UAT/failsuite.src/run_functions.at b/gcc/cobol/UAT/failsuite.src/run_functions.at
index 5de7d653daf4..25417135f008 100644
--- a/gcc/cobol/UAT/failsuite.src/run_functions.at
+++ b/gcc/cobol/UAT/failsuite.src/run_functions.at
@@ -842,36 +842,42 @@ AT_DATA([prog.cob], [
        PROGRAM-ID.      prog.
        DATA             DIVISION.
        WORKING-STORAGE  SECTION.
-       77  N   PICTURE  S9(8) COMP.
-       77  P   REDEFINES N    USAGE POINTER.
-       01  X   PIC      A(4) VALUE Z"ABC".
-           05  E PIC    A    OCCURS 4.
-       77  B   PICTURE  A BASED.
+       01  N                PIC     S9(8) COMP-5 value 0.
+       01  P   REDEFINES N  POINTER.
+       01  FILLER.
+        05 X                PIC      A(4) VALUE "ABC".
+        05 E REDEFINES X    PIC      A(1)  OCCURS 4.
+       LINKAGE SECTION.
+       77  B                PIC      A BASED.
 
        PROCEDURE        DIVISION.
            set P to address of E(1).
 
            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
-             set p up by 1.
-           end-perform.
-           display '.'.
-
-           set P to address of E(1).
+             set p up by 1
+             set address of B to p
+           end-perform
+           display '.'
 
+           set P to address of E(1)
+           set address of B to p
            perform until B = SPACES
-             set address of B to p.
              display B no advancing
-             add 8 to N.
-           end-perform.
-           display '.'.
+             add 1 to N
+             set address of B to p
+           end-perform
+           display '.'
 
            STOP RUN.
 ])
 
 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
-- 
GitLab