From 1e3f0ccba17e2dd5d7945adb51cbd1e66ab5d8b5 Mon Sep 17 00:00:00 2001
From: "James K. Lowden" <jklowden@symas.com>
Date: Fri, 12 Apr 2024 13:42:36 -0400
Subject: [PATCH] rationalize new_temporary/new_reference

---
 gcc/cobol/parse.y      | 27 ---------------------------
 gcc/cobol/parse_ante.h | 12 ------------
 gcc/cobol/symbols.cc   | 21 ++++++++++++++-------
 gcc/cobol/symbols.h    |  4 ++--
 4 files changed, 16 insertions(+), 48 deletions(-)

diff --git a/gcc/cobol/parse.y b/gcc/cobol/parse.y
index 6a0d845aec35..ae009b75e990 100644
--- a/gcc/cobol/parse.y
+++ b/gcc/cobol/parse.y
@@ -11100,33 +11100,6 @@ new_literal( const literal_t& lit, enum cbl_field_attr_t attr ) {
   attrs |= literal_attr(lit.prefix);
 
   return new_literal(lit.len, lit.data, cbl_field_attr_t(attrs));
-#if 0  
-  cbl_field_t *field = new_temporary_imply(FldLiteralA);
-
-  field->attr |= (attr | constant_e);
-  field->attr |= literal_attr(lit.prefix);
-
-  field->data.initial = lit.data;
-  field->data.capacity = lit.len;
-  if( ! field->internalize() )
-    {
-      yyerrorv("inconsistent string literal encoding for '%.*s'",
-	       field->data.capacity, field->data.initial);
-    }
-  
-  if( !(attr & quoted_e) )
-    {
-    field->type = FldLiteralN;
-    field->data.valify();
-    }
-  else if( !(attr & FIGCONST_MASK) )
-    {
-    field->type = FldLiteralA;
-    }
-
-  parser_symbol_add(field);
-  return field;
-#endif
 }
 
 bool
diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h
index fec11a5ea11f..f0652c07b48d 100644
--- a/gcc/cobol/parse_ante.h
+++ b/gcc/cobol/parse_ante.h
@@ -1921,18 +1921,6 @@ new_tempnumeric(void) { return new_temporary(FldNumericBin5); }
 static inline cbl_field_t *
 new_tempnumeric_float(void) { return new_temporary(FldFloat); }
 
-static inline cbl_field_t *
-new_temporary_clone( const cbl_field_t *orig) {
-  cbl_field_type_t type = is_literal(orig)? FldAlphanumeric : orig->type;
-  auto f = new_temporary_imply(type);
-  f->data = orig->data;
-  if( f->type == FldNumericBin5 ) f->type = orig->type;
-  f->attr = temporary_e;
-
-  parser_symbol_add(f);
-  return f;
-}
-
 uint32_t
 type_capacity( enum cbl_field_type_t type, uint32_t digits );
 
diff --git a/gcc/cobol/symbols.cc b/gcc/cobol/symbols.cc
index 4115151c4ad3..bce1e7255322 100644
--- a/gcc/cobol/symbols.cc
+++ b/gcc/cobol/symbols.cc
@@ -2988,12 +2988,6 @@ new_temporary_impl( enum cbl_field_type_t type )
   return f;
 }
 
-// for use only by parse.y
-cbl_field_t *
-new_temporary_imply( enum cbl_field_type_t type ) {
-  return new_temporary_impl( type );
-}
-
 cbl_field_t *
 new_temporary_decl() {
   auto field = new_temporary_impl(FldAlphanumeric);
@@ -3177,7 +3171,7 @@ new_temporary( enum cbl_field_type_t type, const char *initial ) {
 
 cbl_field_t *
 new_temporary_like( cbl_field_t skel ) {
-  auto field = new_temporary_imply(skel.type);
+  auto field = new_temporary_impl(skel.type);
   memcpy(skel.name, field->name, sizeof(field->name));
   *field = skel;
 
@@ -3185,6 +3179,19 @@ new_temporary_like( cbl_field_t skel ) {
   return parser_symbol_add2(field);
 }
 
+cbl_field_t *
+new_temporary_clone( const cbl_field_t *orig) {
+  cbl_field_type_t type = is_literal(orig)? FldAlphanumeric : orig->type;
+  auto field = new_temporary_impl(type);
+  field->data = orig->data;
+  if( field->type == FldNumericBin5 ) field->type = orig->type;
+  field->attr = temporary_e;
+
+  temporaries.add(field);
+  parser_symbol_add(field);
+  return field;
+}
+
 bool
 cbl_field_t::is_ascii() const {
   return std::all_of( data.initial,
diff --git a/gcc/cobol/symbols.h b/gcc/cobol/symbols.h
index 11612c9302cc..1e3bebffa176 100644
--- a/gcc/cobol/symbols.h
+++ b/gcc/cobol/symbols.h
@@ -1188,10 +1188,10 @@ struct label_cmp_lessthan {
 
 size_t field_index( const cbl_field_t *f );
 
-cbl_field_t * new_temporary_imply( enum cbl_field_type_t type ); // for parser
-
 cbl_field_t * new_temporary( enum cbl_field_type_t type, const char initial[] = NULL );
 cbl_field_t * new_temporary_like( cbl_field_t skel );
+cbl_field_t * new_temporary_clone( const cbl_field_t *orig);
+
 cbl_field_t * new_literal( uint32_t len, const char initial[], 
                            enum cbl_field_attr_t attr = none_e );
 
-- 
GitLab