From e01473e5f6ba4686b32fc8b3a8ae2ad66e791d59 Mon Sep 17 00:00:00 2001
From: Bob Dubner <rdubner@symas.com>
Date: Mon, 6 Jan 2025 14:32:48 -0500
Subject: [PATCH] Update some UAT error messages to diagnostic format

---
 gcc/cobol/ChangeLog                           |  4 +-
 gcc/cobol/UAT/testsuite.src/fundamental.at    |  8 +++-
 gcc/cobol/UAT/testsuite.src/run_regression.at | 39 +++++++++++++------
 gcc/cobol/UAT/testsuite.src/syn_refmod.at     | 36 ++++++++++++-----
 gcc/cobol/UAT/testsuite.src/syn_subscripts.at |  8 +++-
 5 files changed, 70 insertions(+), 25 deletions(-)

diff --git a/gcc/cobol/ChangeLog b/gcc/cobol/ChangeLog
index 273924ff3608..10c33869cc49 100644
--- a/gcc/cobol/ChangeLog
+++ b/gcc/cobol/ChangeLog
@@ -65,5 +65,7 @@
 	wrapped those necessary macros into functions.
 	* Normalize #includes in symbols.h.cc
 
-
+2025-01-06  Robert Dubner <rdubner@symas.com>
+	* Updated warning in tests/check_88 and etests/check_88
+	* Updated some UAT error messages.
 
diff --git a/gcc/cobol/UAT/testsuite.src/fundamental.at b/gcc/cobol/UAT/testsuite.src/fundamental.at
index 3289798557d8..ecec28587357 100644
--- a/gcc/cobol/UAT/testsuite.src/fundamental.at
+++ b/gcc/cobol/UAT/testsuite.src/fundamental.at
@@ -63,8 +63,12 @@ AT_DATA([prog.cob], [
            DISPLAY "Gratuitous procedure division statement.".
        END PROGRAM prog.
 ])
-AT_CHECK([$COMPILE prog.cob], [1], [], [prog.cob:9: syntax error: name truncated to 'this-should-fail_xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx6' (max 63 characters) at 'this-should-fail_xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx64'
-prog.cob:11: 1 errors in DATA DIVISION, compilation ceases at 'PROCEDURE DIVISION'
+AT_CHECK([$COMPILE prog.cob], [1], [], [prog.cob:9:9: error: syntax error: name truncated to 'this-should-fail_xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx6' (max 63 characters)
+    9 |        77 this-should-fail_xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx64
+      |         ^
+prog.cob:11:2: error: 1 errors in DATA DIVISION, compilation ceases
+   11 |        PROCEDURE DIVISION.
+      |  ^
 cobol1: error: failed compiling prog.cob
 ])
 AT_CLEANUP
diff --git a/gcc/cobol/UAT/testsuite.src/run_regression.at b/gcc/cobol/UAT/testsuite.src/run_regression.at
index 259893f60b4d..57ed5af89bf3 100644
--- a/gcc/cobol/UAT/testsuite.src/run_regression.at
+++ b/gcc/cobol/UAT/testsuite.src/run_regression.at
@@ -101,8 +101,9 @@ AT_DATA([prog.cob], [
        PROCEDURE DIVISION.
           DISPLAY "OK".
 ])
-AT_CHECK([$COMPILE prog.cob], [1], [], [prog.cob:6: syntax error at 'a'
-cobol1: error: failed compiling prog.cob
+AT_CHECK([$COMPILE prog.cob], [1], [], [prog.cob:4:57: error: syntax error
+    4 |        ENVIRONMENT DIVISION.
+      |        Bob sez:  This error seems odd                 ^
 ])
 AT_CLEANUP
 
@@ -293,7 +294,9 @@ AT_DATA([prog.cob], [       IDENTIFICATION   DIVISION.
            END-DISPLAY.
            STOP RUN.
 ])
-AT_CHECK([$COMPILE prog.cob], [1], [], [prog.cob:10: syntax error at ':'
+AT_CHECK([$COMPILE prog.cob], [1], [], [prog.cob:10:23: error: syntax error
+   10 |            DISPLAY X(:) NO ADVANCING
+      |                       ^
 cobol1: error: failed compiling prog.cob
 ])
 AT_CLEANUP
@@ -314,9 +317,13 @@ AT_DATA([prog.cob], [      *> This program aborts during compilation because the
        GOBACK.
 ])
 AT_CHECK([$COMPILE prog.cob], [1], [],
-[prog.cob:10: error: VAR1 limited to capacity of 37 (would need 339)
-prog.cob:10: 1 errors in DATA DIVISION, compilation ceases at 'PROCEDURE DIVISION'
-cobol1: error: failed compiling prog.cob
+[prog.cob:9:18: error: VAR1 limited to capacity of 37 (would need 339)
+    9 |        01 VAR1  PIC 9(3)V9(336).
+      |                  ^
+prog.cob:10:2: error: 1 errors in DATA DIVISION, compilation ceases
+   10 |        PROCEDURE DIVISION.
+      |  ^
+
 ])
 AT_CLEANUP
 
@@ -338,11 +345,21 @@ AT_DATA([prog.cob], [       IDENTIFICATION DIVISION.
        GOBACK.
 ])
 AT_CHECK([$COMPILE prog.cob], [1], [],
-[prog.cob:6: error: '(0)' invalid in PICTURE (ISO 2023 13.18.40.3)
-prog.cob:7: error: '(0)' invalid in PICTURE (ISO 2023 13.18.40.3)
-prog.cob:8: error: '(0)' invalid in PICTURE (ISO 2023 13.18.40.3)
-prog.cob:9: error: '(0)' invalid in PICTURE (ISO 2023 13.18.40.3)
-prog.cob:9: 4 errors in DATA DIVISION, compilation ceases at 'PROCEDURE DIVISION'
+[prog.cob:5:31: error: '(0)' invalid in PICTURE (ISO 2023 13.18.40.3)
+    5 |        01 VAR1  PICTURE 9(7)V9(0).
+      |                               ^
+prog.cob:6:31: error: '(0)' invalid in PICTURE (ISO 2023 13.18.40.3)
+    6 |        01 VAR2  PICTURE 9(7)V9(0).
+      |                               ^
+prog.cob:7:31: error: '(0)' invalid in PICTURE (ISO 2023 13.18.40.3)
+    7 |        01 VAR3  PICTURE 9(7)V9(0).
+      |                               ^
+prog.cob:8:31: error: '(0)' invalid in PICTURE (ISO 2023 13.18.40.3)
+    8 |        01 VAR4  PICTURE 9(7)V9(0).
+      |                               ^
+prog.cob:9:2: error: 4 errors in DATA DIVISION, compilation ceases
+    9 |        PROCEDURE DIVISION.
+      |  ^
 cobol1: error: failed compiling prog.cob
 ])
 AT_CLEANUP
diff --git a/gcc/cobol/UAT/testsuite.src/syn_refmod.at b/gcc/cobol/UAT/testsuite.src/syn_refmod.at
index 8d99272298e3..6ead81c3edc9 100644
--- a/gcc/cobol/UAT/testsuite.src/syn_refmod.at
+++ b/gcc/cobol/UAT/testsuite.src/syn_refmod.at
@@ -81,15 +81,33 @@ AT_DATA([prog.cob], [
            STOP RUN.
 ])
 AT_CHECK([$COMPILE_ONLY prog.cob], [1], [],
-[prog.cob:9: error: X(0) out of bounds, size is 4 at ')'
-prog.cob:11: error: X(0) out of bounds, size is 4 at ')'
-prog.cob:13: error: X(5) out of bounds, size is 4 at ')'
-prog.cob:15: error: X(5) out of bounds, size is 4 at ')'
-prog.cob:17: error: X(1:0) out of bounds, size is 4 at ')'
-prog.cob:19: error: X(Y:0) out of bounds, size is 4 at ')'
-prog.cob:21: error: X(1:5) out of bounds, size is 4 at ')'
-prog.cob:23: error: X(Y:5) out of bounds, size is 4 at ')'
-prog.cob:25: error: X(3:3) out of bounds, size is 4 at ')'
+[prog.cob:9:21: error: X(0) out of bounds, size is 4
+    9 |            DISPLAY X(0:1)
+      |                     ^
+prog.cob:11:21: error: X(0) out of bounds, size is 4
+   11 |            DISPLAY X(0:Y)
+      |                     ^
+prog.cob:12:21: error: X(5) out of bounds, size is 4
+   12 |            END-DISPLAY.
+      |                     ^
+prog.cob:15:21: error: X(5) out of bounds, size is 4
+   15 |            DISPLAY X(5:Y)
+      |                     ^
+prog.cob:17:21: error: X(1:0) out of bounds, size is 4
+   17 |            DISPLAY X(1:0)
+      |                     ^
+prog.cob:19:21: error: X(Y:0) out of bounds, size is 4
+   19 |            DISPLAY X(Y:0)
+      |                     ^
+prog.cob:21:21: error: X(1:5) out of bounds, size is 4
+   21 |            DISPLAY X(1:5)
+      |                     ^
+prog.cob:23:21: error: X(Y:5) out of bounds, size is 4
+   23 |            DISPLAY X(Y:5)
+      |                     ^
+prog.cob:24:21: error: X(3:3) out of bounds, size is 4
+   24 |            END-DISPLAY.
+      |                     ^
 cobol1: error: failed compiling prog.cob
 ])
 AT_CLEANUP
diff --git a/gcc/cobol/UAT/testsuite.src/syn_subscripts.at b/gcc/cobol/UAT/testsuite.src/syn_subscripts.at
index 52644fd8931b..d4e33bf025f5 100644
--- a/gcc/cobol/UAT/testsuite.src/syn_subscripts.at
+++ b/gcc/cobol/UAT/testsuite.src/syn_subscripts.at
@@ -62,8 +62,12 @@ AT_DATA([prog.cob], [
            STOP RUN.
 ])
 AT_CHECK([$COMPILE_ONLY prog.cob], [1], [],
-[prog.cob:10: error: 1 subscripts provided for G, which has no dimensions at 'END-DISPLAY'
-prog.cob:12: error: 1 subscripts provided for X, which has no dimensions at 'END-DISPLAY'
+[prog.cob:9:21: error: 1 subscripts provided for G, which has no dimensions
+    9 |            DISPLAY G(1)
+      |                     ^
+prog.cob:11:21: error: 1 subscripts provided for X, which has no dimensions
+   11 |            DISPLAY X(1)
+      |                     ^
 cobol1: error: failed compiling prog.cob
 ])
 AT_CLEANUP
-- 
GitLab