From f066ca25152c47bda834ddc538dd3cd5bc939bae Mon Sep 17 00:00:00 2001
From: Bob Dubner <rdubner@symas.com>
Date: Tue, 7 May 2024 17:20:28 -0400
Subject: [PATCH] Surgical removal of to_default and apply_default_byte()

---
 gcc/cobol/parse.y      | 70 ++++++++++--------------------------------
 gcc/cobol/parse_ante.h |  3 --
 2 files changed, 16 insertions(+), 57 deletions(-)

diff --git a/gcc/cobol/parse.y b/gcc/cobol/parse.y
index ae7ca7c6067d..a6f7966e517b 100644
--- a/gcc/cobol/parse.y
+++ b/gcc/cobol/parse.y
@@ -160,22 +160,18 @@
 
   struct init_statement_t {
     bool to_value;
-    bool to_default;
     data_category_t category;
     category_map_t replacement;
 
-    init_statement_t( category_map_t replacement,
-                      bool to_default = false )
+    init_statement_t( category_map_t replacement )
       : to_value(false)
-      , to_default(to_default)
       , category(data_category_none)
       , replacement(replacement)
 
     {}
 
-    init_statement_t( bool to_value = false, bool to_default = false )
+    init_statement_t( bool to_value = false )
       : to_value(to_value)
-      , to_default(to_default)
       , category(data_category_none)
       , replacement(category_map_t())
     {}
@@ -858,8 +854,7 @@
   initialize_statement( std::list<cbl_refer_t> tgts,
                         bool with_filler,
                         data_category_t category,
-                        const category_map_t& replacement = category_map_t(),
-                        bool to_default = false );
+                        const category_map_t& replacement = category_map_t());
 
 
   unsigned char cbl_alphabet_t::nul_string[2] = ""; // 2 NULs lets us use one
@@ -7982,21 +7977,21 @@ initialize:     INITIALIZE vargs
                 {
                   statement_begin(@1, INITIALIZE);
                     initialize_statement( $vargs->args, false, $ini->category,
-                                          $ini->replacement, $ini->to_default );
+                                          $ini->replacement);
                   delete $vargs;
                 }
         |       INITIALIZE vargs init_clause[ini] with FILLER_kw
                 {
                   statement_begin(@1, INITIALIZE);
                     initialize_statement( $vargs->args, true, $ini->category,
-                                          $ini->replacement, $ini->to_default );
+                                          $ini->replacement);
                   delete $vargs;
                 }
         |       INITIALIZE vargs with FILLER_kw init_clause[ini]
                 {
                   statement_begin(@1, INITIALIZE);
                   initialize_statement( $vargs->args, true, $ini->category,
-                                        $ini->replacement, $ini->to_default );
+                                        $ini->replacement );
                   delete $vargs;
                 }
                ;
@@ -8021,15 +8016,15 @@ init_clause:    init_value
 
 init_value:     init_replace then to DEFAULT
                 {
-                  $$ = new init_statement_t( *$init_replace, true );
+                  $$ = new init_statement_t( *$init_replace);
                 }
         |       init_replace
                 {
-                  $$ = new init_statement_t( *$init_replace, false );
+                  $$ = new init_statement_t( *$init_replace);
                 }
         |       then to DEFAULT
                 {
-                  $$ = new init_statement_t( false, true );
+                  $$ = new init_statement_t( false );
                 }
                 ;
 
@@ -10997,10 +10992,8 @@ static bool
 initialize_statement( cbl_refer_t tgt, bool with_filler,
                      data_category_t value_category,
                       const category_map_t& replacements,
-                      bool to_default, bool explicitly = true )
+                      bool explicitly = true )
 {
-// DUBNER HACK
-to_default = false;
   if( dimensions(tgt.field) < tgt.nsubscript ) {
     yyerrorv( "syntax error: %s has %zu subscripts, but takes only %zu",
               tgt.field->name, tgt.nsubscript, dimensions(tgt.field) );
@@ -11034,7 +11027,7 @@ to_default = false;
     do {
       // recurse on each table element, which might itself be a table or group
       fOK = fOK && initialize_statement( tgt, with_filler, value_category,
-                                         replacements, to_default, false);
+                                         replacements, false);
       parser_add(*p, *p, literally_one);
     } while( ++i < tgt.field->occurs.ntimes() );
     return fOK;
@@ -11059,7 +11052,7 @@ to_default = false;
           tgt.field = f;
           // recurse on each member, which might be a table or group
           fOK = fOK && initialize_statement( tgt, with_filler, value_category,
-                                             replacements, to_default, false );
+                                             replacements, false );
         }
         if( f->type == FldGroup ) {
           imember = end_of_group(imember) - 1;
@@ -11104,7 +11097,6 @@ to_default = false;
       assert( with_filler || !tgt.field->has_attr(filler_e) );
       if( tgt.field->data.initial ) {
         parser_initialize(tgt);
-	to_default = false;
       }
     }
 
@@ -11134,37 +11126,9 @@ to_default = false;
     return true;
   }
 
-  // If THEN TO DEFAULT and nothing else worked, set to blank/zero.
-  if( to_default ) {
-    auto token = is_numeric(tgt.field->type)? ZERO : SPACES;
-    static cbl_field_t *value;
-    if( ! value ) {
-      cbl_field_t *default_value = constant_of(constant_index(token));
-      value = wsclear()? new_literal(1, wsclear(), quoted_e) : default_value;
-    }
-    cbl_refer_t src( value, true );
-    if( false && wsclear() ) warn("%s:%d: set all of %s to %02x",
-			 __func__, __LINE__,
-			 tgt.field->name, src.field->data.initial[0]);
-    parser_move(tgt, src, current_rounded_mode());
-
-    if( splat && *splat == '1' ) {
-      warnx("%s:to def: %s (0x%02x)", __func__, field_str(tgt.field),
-	    src.field->data.initial[0]);
-    }
-  }
   return true;
 }
 
-static void
-apply_default_byte( cbl_field_t *tgt ) {
-  static const bool with_filler = true, to_default = true, explicitly = true;
-  category_map_t replacements;
-  
-  initialize_statement( tgt, with_filler, data_category_all, replacements,
-			to_default, explicitly );
-}
-
 const char *
 data_category_str( data_category_t category ) {
   switch(category) {
@@ -11186,12 +11150,10 @@ data_category_str( data_category_t category ) {
 static void
 initialize_statement( std::list<cbl_refer_t> tgts, bool with_filler,
                      data_category_t value_category,
-                      const category_map_t& replacements,
-                      bool to_default ) {
+                      const category_map_t& replacements) {
   if( yydebug && getenv(__func__) ) {
-    warnx( "%s: %zu targets, %s filler, %s, to_default=%s",
-           __func__, tgts.size(), with_filler? "with" : "no",
-           data_category_str(value_category), to_default? "yes" : "no" );
+    warnx( "%s: %zu targets, %s filler",
+           __func__, tgts.size(), with_filler? "with" : "no");
     for( auto tgt : tgts ) {
       fprintf( stderr, "%28s: %s\n", __func__, name_of(tgt.field) );
     }
@@ -11204,7 +11166,7 @@ initialize_statement( std::list<cbl_refer_t> tgts, bool with_filler,
 
   for( auto tgt : tgts ) {
     initialize_statement( tgt, with_filler, value_category,
-                         replacements, to_default );
+                         replacements );
   }
 }
 
diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h
index cf4e596a1e1f..ac559e29468e 100644
--- a/gcc/cobol/parse_ante.h
+++ b/gcc/cobol/parse_ante.h
@@ -2776,8 +2776,6 @@ data_division_ready() {
   return true;
 }
 
-static void apply_default_byte( cbl_field_t *field );
-
 static bool
 procedure_division_ready( cbl_field_t *returning, ffi_args_t *ffi_args ) {
   auto prog = cbl_label_of(symbols_begin(current.program_index()));
@@ -2878,7 +2876,6 @@ procedure_division_ready( cbl_field_t *returning, ffi_args_t *ffi_args ) {
     if( wsclear() ) {
       switch(f->level) {
       case 1: case 77:
-        apply_default_byte(f);
         break;
       default:
         break;
-- 
GitLab