From 27d6e2ac6d87d9bd49d69a07c1ffdca30e82203a Mon Sep 17 00:00:00 2001
From: "James K. Lowden" <jklowden@symas.com>
Date: Fri, 24 Jan 2025 19:25:47 -0500
Subject: [PATCH] introduce location when constructing field domains

---
 gcc/cobol/parse.y      | 35 ++++++++++++++++++-----------------
 gcc/cobol/parse_ante.h |  4 ++--
 gcc/cobol/symbols.h    | 24 +++++++++++++-----------
 3 files changed, 33 insertions(+), 30 deletions(-)

diff --git a/gcc/cobol/parse.y b/gcc/cobol/parse.y
index d47c7e5cb9ba..b3734e2cc68d 100644
--- a/gcc/cobol/parse.y
+++ b/gcc/cobol/parse.y
@@ -2337,7 +2337,7 @@ domain:         all LITERAL[a]
                     yywarn("'%s' has embedded NUL", $a.data);
                   }
                   $$ = NULL;
-                  cbl_domain_t domain($all, $a.len, $a.data);
+                  cbl_domain_t domain(@a, $all, $a.len, $a.data);
                   domains.push_back(domain);
                 }
         |       all[a_all] LITERAL[a] THRU all[z_all] LITERAL[z]
@@ -2349,27 +2349,28 @@ domain:         all LITERAL[a]
                     yywarn("'%s' has embedded NUL", $z.data);
                   }
                   $$ = NULL;
-                  cbl_domain_elem_t first($a_all, $a.len, $a.data),
-                                     last($z_all, $z.len, $z.data);
+                  cbl_domain_elem_t first(@a, $a_all, $a.len, $a.data),
+                                     last(@z, $z_all, $z.len, $z.data);
                   domains.push_back(cbl_domain_t(first, last));
                 }
         |       all NUMSTR[n]
                 {
                   $$ = NULL;
-                  domains.push_back(cbl_domain_t($all, $n.string, true));
+                  cbl_domain_t dom(@n, $all, strlen($n.string), $n.string, true);
+                  domains.push_back(dom);
                 }
         |       all[n_all] NUMSTR[n] THRU all[m_all] NUMSTR[m]
                 {
                   $$ = NULL;
-                  cbl_domain_elem_t first($n_all, strlen($n.string), $n.string, true),
-                                     last($m_all, strlen($m.string), $m.string, true);
+                  cbl_domain_elem_t first(@n, $n_all, strlen($n.string), $n.string, true),
+		                     last(@m, $m_all, strlen($m.string), $m.string, true);
                   domains.push_back(cbl_domain_t(first, last));
                 }
         |       all reserved_value {
                   $$ = NULL;
                   if( $2 == NULLS ) YYERROR;
                   auto value = constant_of(constant_index($2))->data.initial;
-                  struct cbl_domain_t domain( $all, value );
+                  struct cbl_domain_t domain( @2, $all, strlen(value), value );
                   domains.push_back(domain);
                 }
         |       all[a_all] reserved_value[a] THRU all[z_all] LITERAL[z] {
@@ -2379,16 +2380,16 @@ domain:         all LITERAL[a]
                   $$ = NULL;
                   if( $a == NULLS ) YYERROR;
                   auto value = constant_of(constant_index($a))->data.initial;
-                  cbl_domain_elem_t first($a_all, strlen(value), value),
-                                     last($z_all, $z.len, $z.data);
+                  cbl_domain_elem_t first(@a, $a_all, strlen(value), value),
+                                     last(@z, $z_all, $z.len, $z.data);
                   domains.push_back(cbl_domain_t(first, last));
                 }
         |       all[a_all] reserved_value[a] THRU all[z_all] NUMSTR[z] {
                   $$ = NULL;
                   if( $a == NULLS ) YYERROR;
                   auto value = constant_of(constant_index($a))->data.initial;
-                  cbl_domain_elem_t first($a_all, strlen(value), value, true),
-                                     last($z_all, strlen($z.string), $z.string, true);
+                  cbl_domain_elem_t first(@a, $a_all, strlen(value), value, true),
+                                     last(@z, $z_all, strlen($z.string), $z.string, true);
                   domains.push_back(cbl_domain_t(first, last));
                 }
         |       when_set_to FALSE_kw is LITERAL[value]
@@ -2397,17 +2398,17 @@ domain:         all LITERAL[a]
                     yywarn("'%s' has embedded NUL", $value.data);
                   }
                   char *dom = $value.data;
-                  $$ = new cbl_domain_t(false, $value.len, dom);
+                  $$ = new cbl_domain_t(@value, false, $value.len, dom);
                 }
         |       when_set_to FALSE_kw is reserved_value
                 {
                   if( $4 == NULLS ) YYERROR;
                   auto value = constant_of(constant_index($4))->data.initial;
-                  $$ = new cbl_domain_t( false, value );
+                  $$ = new cbl_domain_t(@4, false, strlen(value), value );
                 }
         |       when_set_to FALSE_kw is NUMSTR[n]
                 {
-		  $$ = new cbl_domain_t(false, $n.string, true);
+		  $$ = new cbl_domain_t(@n, false, strlen($n.string), $n.string, true);
                 }
                 ;
 when_set_to:    %empty
@@ -3065,10 +3066,10 @@ data_descr1:    level_name
 		    { 0,0,0,0, NULL, NULL, { NULL }, { NULL } }, NULL };
                   if( !namcpy(@NAME, field.name, $2) ) YYERROR;
 
-                  auto fig = constant_of(constant_index(NULLS));
+                  auto fig = constant_of(constant_index(NULLS))->data.initial;
                   struct cbl_domain_t *domain = new cbl_domain_t[2];
 
-                  domain[0] = fig;
+                  domain[0] = cbl_domain_t(@NAME, false, strlen(fig), fig);
 
                   field.data.domain = domain;
 
@@ -11592,7 +11593,7 @@ current_data_section_set(const YYLTYPE& loc,  data_section_t data_section ) {
   cbl_section_t section = { type, yylineno, NULL };
 
   if( ! symbol_section_add(PROGRAM, &section) ) {
-    yyerror( "could not add section %s to program %s, exists line %d",
+    error_msg(loc, "could not add section %s to program %s, exists line %d",
               section.name(), current.program()->name,
               symbol_section(PROGRAM, &section)->line );
     return false;
diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h
index 73efc8367208..8e5248db3816 100644
--- a/gcc/cobol/parse_ante.h
+++ b/gcc/cobol/parse_ante.h
@@ -106,7 +106,7 @@ extern int yydebug;
 #include <stdarg.h>
 
 const char *
-consistent_encoding_check( const char input[] ) {
+consistent_encoding_check( const YYLTYPE& loc, const char input[] ) {
   cbl_field_t faux = {
     .type = FldAlphanumeric, 
     .data = { .capacity = capacity_cast(strlen(input)), .initial = input }
@@ -114,7 +114,7 @@ consistent_encoding_check( const char input[] ) {
 
   auto s = faux.internalize();
   if( !s ) {
-    yyerror("inconsistent string literal encoding for '%s'", input);
+    error_msg(loc, "inconsistent string literal encoding for '%s'", input);
   } else {
     if( s != input ) return s;
   }
diff --git a/gcc/cobol/symbols.h b/gcc/cobol/symbols.h
index 8a099569e5e3..231d1a47d08b 100644
--- a/gcc/cobol/symbols.h
+++ b/gcc/cobol/symbols.h
@@ -171,7 +171,7 @@ is_working_storage(uint32_t attr) {
 enum cbl_figconst_t cbl_figconst_of( const char *value );
 const char * cbl_figconst_str( cbl_figconst_t fig );
 
-const char * consistent_encoding_check( const char input[] );
+const char * consistent_encoding_check( const YYLTYPE& loc, const char input[] );
 
 class cbl_domain_elem_t {
   uint32_t length;
@@ -179,14 +179,18 @@ class cbl_domain_elem_t {
  public:
   bool is_numeric,  all;
 
-  cbl_domain_elem_t( bool all = false,
-                     uint32_t length = 0, 
-                     const char *value = NULL,
+  cbl_domain_elem_t()
+    : length(0), value(NULL), is_numeric(false), all(false)
+  {}
+  cbl_domain_elem_t( const YYLTYPE& loc, 
+                     bool all,
+                     uint32_t length, 
+                     const char *value,
                      bool is_numeric = false )
     : length(length), value(value), is_numeric(is_numeric), all(all)
   {
     if( value && ! is_numeric ) {
-      auto s = consistent_encoding_check(value);
+      auto s = consistent_encoding_check(loc, value);
       if( s ) value = s;
     }
   }
@@ -196,16 +200,14 @@ class cbl_domain_elem_t {
 
 struct cbl_domain_t {
   cbl_domain_elem_t first, last;
-  cbl_domain_t( bool all = false,
-                const char * value = NULL,
-                bool is_numeric = false )
-    : first(all, 0, value, is_numeric), last(first)
+  cbl_domain_t() : first(), last(first)
   {}
-  cbl_domain_t( bool all,
+  cbl_domain_t( const YYLTYPE& loc,
+		bool all,
                 uint32_t length, 
                 const char * value,
                 bool is_numeric = false )
-    : first(all, length, value, is_numeric), last(first)
+    : first(loc, all, length, value, is_numeric), last(first)
   {}
   cbl_domain_t( const cbl_domain_elem_t& a, const cbl_domain_elem_t& z )
     : first(a)
-- 
GitLab