diff --git a/gcc/cobol/cdf_text.h b/gcc/cobol/cdf_text.h
index 5eeb25b6d795c4bebee6964b537d308beb7be650..1d784c57129da54f96d9a3354b72242253e26d01 100644
--- a/gcc/cobol/cdf_text.h
+++ b/gcc/cobol/cdf_text.h
@@ -243,7 +243,7 @@ cdftext::open_output() {
     sprintf(stem, "%sXXXXXX", name);
     if( -1 == (fd = mkstemp(stem)) ) {
       err(EXIT_FAILURE,
-	  "error: could not open temporary file '%s' (%s)", name, realpath(name, stem));
+          "error: could not open temporary file '%s' (%s)", name, realpath(name, stem));
     }
     return fd;
   }
@@ -275,12 +275,12 @@ cdftext::map_file( int fd ) {
       static char block[4096 * 4];
       ssize_t n;
       while( (n = read(input, block, sizeof(block))) != 0 ) {
-	ssize_t nout = write(fd, block, n);
-	if( nout != n ) {
-	  err(EXIT_FAILURE, "%s: could not prepare map file from FIFO %d",
-	      __func__, input);
-	}
-	if( false ) warnx("%s: copied %ld bytes from FIFO", __func__, nout);
+        ssize_t nout = write(fd, block, n);
+        if( nout != n ) {
+          err(EXIT_FAILURE, "%s: could not prepare map file from FIFO %d",
+              __func__, input);
+        }
+        if( false ) warnx("%s: copied %ld bytes from FIFO", __func__, nout);
       }
     }
   } while( S_ISFIFO(sb.st_mode) );
diff --git a/gcc/cobol/dts.h b/gcc/cobol/dts.h
index 893ef87502b08a29b70d09bf914c0e288bfe4bea..794f0b15a14c76d65c0343adbca0350c1ff8d35c 100644
--- a/gcc/cobol/dts.h
+++ b/gcc/cobol/dts.h
@@ -71,8 +71,8 @@ namespace dts {
 #if __cpp_exceptions
         throw std::logic_error(msg);
 #else
-	pattern = NULL;
-	yyerrorv("error: %s", msg);
+        pattern = NULL;
+        yyerrorv("error: %s", msg);
 #endif
       }
     }
diff --git a/gcc/cobol/ec.h b/gcc/cobol/ec.h
index fa8397b19b6a92551b17471a6a60e719cd5d461d..e32df71a87baf4153a1eac9d81c2bd05693daf08 100644
--- a/gcc/cobol/ec.h
+++ b/gcc/cobol/ec.h
@@ -329,8 +329,8 @@ struct cbl_declarative_t {
   }
 
   cbl_declarative_t( size_t section, ec_type_t type,
-		     const std::list<size_t>& files,
-		     cbl_file_mode_t mode, bool global = false )
+                     const std::list<size_t>& files,
+                     cbl_file_mode_t mode, bool global = false )
     : section(section), global(global), type(type)
     , nfile(files.size())
     , mode(mode)
diff --git a/gcc/cobol/gcobolspec.cc b/gcc/cobol/gcobolspec.cc
index e342a5383548a7a877e334a76dda57fbc514d381..d1f2f7b85cc85831e74be9d43ab3a4a34c51ca12 100644
--- a/gcc/cobol/gcobolspec.cc
+++ b/gcc/cobol/gcobolspec.cc
@@ -465,41 +465,32 @@ lang_specific_driver (struct cl_decoded_option **in_decoded_options,
 
       case OPT__version:
         no_files_error = false;
-#if 0
-        printf ("GNU Fortran %s%s\n", pkgversion_string, version_string);
-        printf ("Copyright %s 2022 Free Software Foundation, Inc.\n",
-          _("(C)"));
-        fputs (_("This is free software; see the source for copying conditions.  There is NO\n\
-                 warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.\n\n"),
-        stdout);
-        exit (0);
-#endif
         break;
 
       case OPT__help:
-	/*
-	 * $ man ./gcobol.1 | ./help.gen
-	 */
-	puts( "Options specific to gcobol: " );
-	puts(
-	"  -main   option uses the first PROGRAM of filename as the entry point for\n"
-	"          the main() procedure.  \n"
-	"  -no_main    \n"
-	"          means that there is no -main, and the main() entry point is\n"
-	"          provided by some other compilation or .o file\n"
-	"  -findicator-column\n"
-	"          describes the location of the Indicator Area in a COBOL file with\n"
-	"          standard 80-column lines.  \n"
-	"  -ffixed-form\n"
-	"          Use strict Reference Format in reading the COBOL input: 72-char‐\n"
-	"          acter lines, with a 6-character sequence area, and an indicator\n"
-	"          column.  \n"
-	"  -ffree-form\n"
-	"          Force the COBOL input to be interpreted as free format.  \n"
-	"  -fmax-errors nerror\n"
-	"          nerror represents the number of error messages produced.  \n"
-	"  -fflex-debug, -fyacc-debug\n"
-	"          produce messages useful for compiler development.  \n" );
+        /*
+         * $ man ./gcobol.1 | ./help.gen
+         */
+        puts( "Options specific to gcobol: " );
+        puts(
+        "  -main   option uses the first PROGRAM of filename as the entry point for\n"
+        "          the main() procedure.  \n"
+        "  -no_main    \n"
+        "          means that there is no -main, and the main() entry point is\n"
+        "          provided by some other compilation or .o file\n"
+        "  -findicator-column\n"
+        "          describes the location of the Indicator Area in a COBOL file with\n"
+        "          standard 80-column lines.  \n"
+        "  -ffixed-form\n"
+        "          Use strict Reference Format in reading the COBOL input: 72-char‐\n"
+        "          acter lines, with a 6-character sequence area, and an indicator\n"
+        "          column.  \n"
+        "  -ffree-form\n"
+        "          Force the COBOL input to be interpreted as free format.  \n"
+        "  -fmax-errors nerror\n"
+        "          nerror represents the number of error messages produced.  \n"
+        "  -fflex-debug, -fyacc-debug\n"
+        "          produce messages useful for compiler development.  \n" );
 
 
         /* Let gcc.cc handle this, as it has a really
diff --git a/gcc/cobol/genapi.h b/gcc/cobol/genapi.h
index 78360d800fcbeba8dfd0596d50d8814f33419470..f91b890ddf144a975b85a77503862cdcf087af1d 100644
--- a/gcc/cobol/genapi.h
+++ b/gcc/cobol/genapi.h
@@ -52,7 +52,7 @@ void parser_enter_file(const char *filename);
 void parser_leave_file();
 void parser_next_is_main(bool is_main);
 void parser_division( cbl_division_t division,
-		      cbl_field_t *ret, size_t narg, cbl_ffi_arg_t args[] );
+                      cbl_field_t *ret, size_t narg, cbl_ffi_arg_t args[] );
 void parser_enter_program(const char *funcname, bool is_function);
 void parser_leave_program();
 
@@ -61,11 +61,11 @@ void parser_accept_exception( cbl_label_t *name );
 void parser_accept_exception_end( cbl_label_t *name );
 
 void parser_accept_envar( cbl_refer_t refer, cbl_refer_t envar,
-			  cbl_label_t *error, cbl_label_t *not_error );
+                          cbl_label_t *error, cbl_label_t *not_error );
 void parser_set_envar( cbl_refer_t envar, cbl_refer_t refer );
 
 void parser_accept_command_line( cbl_refer_t tgt, cbl_refer_t src,
-			  cbl_label_t *error, cbl_label_t *not_error );
+                          cbl_label_t *error, cbl_label_t *not_error );
 void parser_accept_command_line_count( cbl_refer_t tgt );
 
 void parser_accept_date_yymmdd( cbl_field_t *tgt );
@@ -277,23 +277,23 @@ void parser_display_literal(const char *literal,
 
 void
 parser_assign( size_t nC, cbl_num_result_t *C,
-	       struct cbl_refer_t from,
-	       cbl_label_t *on_error,
-	       cbl_label_t *not_error,
-	       cbl_label_t *compute_error );
+               struct cbl_refer_t from,
+               cbl_label_t *on_error,
+               cbl_label_t *not_error,
+               cbl_label_t *compute_error );
 
 void parser_move(struct cbl_refer_t to,
-		 struct cbl_refer_t from,
-		 cbl_round_t rounded=truncation_e,
+                 struct cbl_refer_t from,
+                 cbl_round_t rounded=truncation_e,
      bool skip_fill_from = false);
 
 void parser_move( size_t ntgt, cbl_refer_t *tgts,
-		  cbl_refer_t src, cbl_round_t rounded=truncation_e );
+                  cbl_refer_t src, cbl_round_t rounded=truncation_e );
 
 void parser_initialize_table( size_t ntgt, cbl_refer_t src, 
-			      size_t nspan, const cbl_bytespan_t spans[],
-			      size_t table, // symbol table index
-			      size_t ntbl, const cbl_subtable_t tbls[] ); 
+                              size_t nspan, const cbl_bytespan_t spans[],
+                              size_t table, // symbol table index
+                              size_t ntbl, const cbl_subtable_t tbls[] ); 
 
 void parser_set_pointers( size_t ntgt, cbl_refer_t *tgts, cbl_refer_t src );
 
@@ -339,12 +339,12 @@ parser_file_close( struct cbl_file_t *file, file_close_how_t how = file_close_no
 
 void
 parser_file_read( struct cbl_file_t *file,
-		  struct cbl_refer_t buffer,
-		  int where );
+                  struct cbl_refer_t buffer,
+                  int where );
 
 void
 parser_file_start( struct cbl_file_t *file, relop_t op, int flk,
-		   cbl_refer_t = cbl_refer_t() );
+                   cbl_refer_t = cbl_refer_t() );
 
 /*
  * Write *field* to *file*.  *after* is a bool where false
@@ -370,7 +370,7 @@ parser_file_write(  cbl_file_t *file,
 
 void
 parser_file_rewrite( cbl_file_t *file, cbl_field_t *field,
-		     bool sequentially );
+                     bool sequentially );
 
 void
 parser_file_delete( cbl_file_t *file, bool sequentially );
@@ -494,9 +494,9 @@ parser_intrinsic_call_4( cbl_field_t *tgt,
                        cbl_refer_t& ref4 );
 
 // void parser_declarative_except( bool global, bool standard, bool error,
-				// declarative_culprit_t culprit,
-				// size_t nproc,
-				// cbl_file_t *files[] );
+                                // declarative_culprit_t culprit,
+                                // size_t nproc,
+                                // cbl_file_t *files[] );
 
 
 void
@@ -514,17 +514,17 @@ parser_string(  cbl_refer_t tgt,
 
 void
 parser_unstring( cbl_refer_t src,
-		 size_t ndelimited,
-		 cbl_refer_t *delimiteds,
-		 // into
-		 size_t noutput,
-		 cbl_refer_t *outputs,
-		 cbl_refer_t *delimiters,
-		 cbl_refer_t *counts,
-		 cbl_refer_t pointer,
-		 cbl_refer_t tally,
-		 cbl_label_t *overflow,
-		 cbl_label_t *not_overflow );
+                 size_t ndelimited,
+                 cbl_refer_t *delimiteds,
+                 // into
+                 size_t noutput,
+                 cbl_refer_t *outputs,
+                 cbl_refer_t *delimiters,
+                 cbl_refer_t *counts,
+                 cbl_refer_t pointer,
+                 cbl_refer_t tally,
+                 cbl_label_t *overflow,
+                 cbl_label_t *not_overflow );
 
 void parser_return_start( cbl_file_t *file, cbl_refer_t into );
 void parser_return_atend( cbl_file_t *file );
@@ -532,7 +532,7 @@ void parser_return_notatend( cbl_file_t *file );
 void parser_return_finish( cbl_file_t *file );
 
 void parser_exception_prepare( const cbl_name_t statement_name,
-			       const cbl_enabled_exceptions_array_t *enabled );
+                               const cbl_enabled_exceptions_array_t *enabled );
 
 //void parser_exception_condition( cbl_field_t *ec );
 
@@ -547,14 +547,14 @@ void parser_call_exception_end( cbl_label_t *name );
 //void parser_stash_exceptions(const cbl_enabled_exceptions_array_t *enabled);
 
 void parser_match_exception(cbl_field_t *index,
-			    cbl_field_t *blob);
+                            cbl_field_t *blob);
 void parser_check_fatal_exception();
 void parser_clear_exception();
 
 void parser_call_targets_dump();
 size_t parser_call_target_update( size_t caller,
-				  const char extant[],
-				  const char mangled_tgt[] );
+                                  const char extant[],
+                                  const char mangled_tgt[] );
 
 void parser_file_stash( struct cbl_file_t *file );
 
@@ -568,7 +568,7 @@ void parser_call( cbl_refer_t name,
 void parser_entry_activate( size_t iprog, const cbl_label_t *declarative );
 
 void parser_entry( cbl_field_t *name,
-		   size_t narg = 0, cbl_ffi_arg_t args[] = NULL);
+                   size_t narg = 0, cbl_ffi_arg_t args[] = NULL);
 
 bool is_ascending_key(cbl_refer_t key);
 
diff --git a/gcc/cobol/inspect.h b/gcc/cobol/inspect.h
index 81a873830a69c95d817c3ed19f2b762ec766a0ae..3b8414d9a7294b92a512234e0cf79edcebe38666 100644
--- a/gcc/cobol/inspect.h
+++ b/gcc/cobol/inspect.h
@@ -127,14 +127,14 @@ struct cbx_inspect_replace_t : public cbx_inspect_match_t<DATA> {
   DATA replacement;
 
   cbx_inspect_replace_t( const DATA& matching = DATA(),
-			 const DATA& replacement = DATA() )
+                         const DATA& replacement = DATA() )
     : cbx_inspect_match_t<DATA>(matching)
     , replacement(replacement)
   {}
   cbx_inspect_replace_t( const DATA& matching,
-			 const DATA& replacement,
-			 const cbx_inspect_qual_t<DATA>& before,
-			 const cbx_inspect_qual_t<DATA>& after )
+                         const DATA& replacement,
+                         const cbx_inspect_qual_t<DATA>& before,
+                         const cbx_inspect_qual_t<DATA>& after )
     : cbx_inspect_match_t<DATA>(matching, before, after)
     , replacement(replacement)
   {}
@@ -143,11 +143,11 @@ struct cbx_inspect_replace_t : public cbx_inspect_match_t<DATA> {
 typedef cbx_inspect_replace_t<cbl_refer_t> cbl_inspect_replace_t;
 
 enum cbl_inspect_bound_t {
-		bound_characters_e,
-		bound_all_e,
-		bound_first_e,
-		bound_leading_e,
-		bound_trailing_e,
+                bound_characters_e,
+                bound_all_e,
+                bound_first_e,
+                bound_leading_e,
+                bound_trailing_e,
 };
 
 // One partial tally or substitution.
@@ -160,7 +160,7 @@ struct cbx_inspect_oper_t {
   cbx_inspect_replace_t<DATA> *replaces;
 
   cbx_inspect_oper_t( cbl_inspect_bound_t bound,
-		      std::list<cbx_inspect_match_t<DATA>> matches )
+                      std::list<cbx_inspect_match_t<DATA>> matches )
     : bound(bound)
     , n_identifier_3( matches.size())
     , matches(NULL)
@@ -171,7 +171,7 @@ struct cbx_inspect_oper_t {
     }
 
   cbx_inspect_oper_t( cbl_inspect_bound_t bound,
-		      std::list<cbx_inspect_replace_t<DATA>> replaces )
+                      std::list<cbx_inspect_replace_t<DATA>> replaces )
     : bound(bound)
     , n_identifier_3( replaces.size() )
     , matches(NULL)
@@ -220,7 +220,7 @@ struct cbx_inspect_t {
       this->opers[0] = oper;
     }
   cbx_inspect_t( const DATA& tally,
-		 const std::list<cbx_inspect_oper_t<DATA>>& opers )
+                 const std::list<cbx_inspect_oper_t<DATA>>& opers )
     : tally(tally)
     , nbound( opers.size() )
     , opers(NULL)
@@ -238,7 +238,7 @@ typedef cbx_inspect_t<cbl_refer_t> cbl_inspect_t;
  */
 
 void parser_inspect( cbl_refer_t input, bool backward,
-		     size_t ninspect, cbl_inspect_t *inspects );
+                     size_t ninspect, cbl_inspect_t *inspects );
 void parser_inspect_conv( cbl_refer_t input, bool backward,
                           cbl_refer_t original,
                           cbl_refer_t replacement,
diff --git a/gcc/cobol/io.h b/gcc/cobol/io.h
index e0b9c129625d122148d90f2f9e8d5bc5877d0a5c..9b08c62081f7331627dc2768b2b68cd3d5474540 100644
--- a/gcc/cobol/io.h
+++ b/gcc/cobol/io.h
@@ -85,48 +85,48 @@ enum file_high_t {
 };
 
 enum file_status_t {
-		    FsSuccess     = FhSuccess,
-		    FsDupRead     = (FhSuccess * 10) + 2,   // First digit is 0
-		    FsRecordLength= (FhSuccess * 10) + 4,
-		    FsUnavail     = (FhSuccess * 10) + 5,
-		    FsNotaTape    = (FhSuccess * 10) + 7,
+                    FsSuccess     = FhSuccess,
+                    FsDupRead     = (FhSuccess * 10) + 2,   // First digit is 0
+                    FsRecordLength= (FhSuccess * 10) + 4,
+                    FsUnavail     = (FhSuccess * 10) + 5,
+                    FsNotaTape    = (FhSuccess * 10) + 7,
 
-		    FsEofSeq      = (FhAtEnd * 10) + 0,     // First digit is 1
-		    FsEofRel      = (FhAtEnd * 10) + 4,
+                    FsEofSeq      = (FhAtEnd * 10) + 0,     // First digit is 1
+                    FsEofRel      = (FhAtEnd * 10) + 4,
 
-		    FsKeySeq      = (FhInvKey * 10) + 1,    // First digit is 2
-		    FsDupWrite    = (FhInvKey * 10) + 2,
-		    FsNotFound    = (FhInvKey * 10) + 3,
-		    FsEofWrite    = (FhInvKey * 10) + 4,
+                    FsKeySeq      = (FhInvKey * 10) + 1,    // First digit is 2
+                    FsDupWrite    = (FhInvKey * 10) + 2,
+                    FsNotFound    = (FhInvKey * 10) + 3,
+                    FsEofWrite    = (FhInvKey * 10) + 4,
 
-		    FsOsError     = (FhOsError * 10) + 0,   // First digit is 3
-		    FsNameError   = (FhOsError * 10) + 1,
-		    FsBoundary    = (FhOsError * 10) + 4,
-		    FsNoFile      = (FhOsError * 10) + 5,
-		    FsNoAccess    = (FhOsError * 10) + 7,
-		    FsCloseLock   = (FhOsError * 10) + 8,
-		    FsWrongType   = (FhOsError * 10) + 9,
+                    FsOsError     = (FhOsError * 10) + 0,   // First digit is 3
+                    FsNameError   = (FhOsError * 10) + 1,
+                    FsBoundary    = (FhOsError * 10) + 4,
+                    FsNoFile      = (FhOsError * 10) + 5,
+                    FsNoAccess    = (FhOsError * 10) + 7,
+                    FsCloseLock   = (FhOsError * 10) + 8,
+                    FsWrongType   = (FhOsError * 10) + 9,
 
-		    FsLogicErr    = (FhLogicError * 10) + 0,    // First digit is 4
-		    FsIsOpen      = (FhLogicError * 10) + 1,
-		    FsCloseNotOpen= (FhLogicError * 10) + 2,
-		    FsNoRead      = (FhLogicError * 10) + 3,
-		    FsBoundWrite  = (FhLogicError * 10) + 4,
-		    FsReadError   = (FhLogicError * 10) + 6,
-		    FsReadNotOpen = (FhLogicError * 10) + 7,
-		    FsNoWrite     = (FhLogicError * 10) + 8,
-		    FsNoDelete    = (FhLogicError * 10) + 9,
+                    FsLogicErr    = (FhLogicError * 10) + 0,    // First digit is 4
+                    FsIsOpen      = (FhLogicError * 10) + 1,
+                    FsCloseNotOpen= (FhLogicError * 10) + 2,
+                    FsNoRead      = (FhLogicError * 10) + 3,
+                    FsBoundWrite  = (FhLogicError * 10) + 4,
+                    FsReadError   = (FhLogicError * 10) + 6,
+                    FsReadNotOpen = (FhLogicError * 10) + 7,
+                    FsNoWrite     = (FhLogicError * 10) + 8,
+                    FsNoDelete    = (FhLogicError * 10) + 9,
 
-		    FsWrongThread = (FhImplementor * 10) + 0,   // First digit is 9
-		    FsPassword    = (FhImplementor * 10) + 1,
-		    FsLogicOther  = (FhImplementor * 10) + 2,
-		    FsNoResource  = (FhImplementor * 10) + 3,
-		    FsIncomplete  = (FhImplementor * 10) + 5,
-		    FsNoDD        = (FhImplementor * 10) + 6,
-		    FsVsamOK      = (FhImplementor * 10) + 7,
-		    FsBadEnvVar   = (FhImplementor * 10) + 8,
+                    FsWrongThread = (FhImplementor * 10) + 0,   // First digit is 9
+                    FsPassword    = (FhImplementor * 10) + 1,
+                    FsLogicOther  = (FhImplementor * 10) + 2,
+                    FsNoResource  = (FhImplementor * 10) + 3,
+                    FsIncomplete  = (FhImplementor * 10) + 5,
+                    FsNoDD        = (FhImplementor * 10) + 6,
+                    FsVsamOK      = (FhImplementor * 10) + 7,
+                    FsBadEnvVar   = (FhImplementor * 10) + 8,
 
-		    FsErrno       = (1000000)                   // This means "map errno to one of the above errors"
+                    FsErrno       = (1000000)                   // This means "map errno to one of the above errors"
 };
 
 #define FhNotOkay FsEofSeq  // Values less than 10 mean the data are valid
diff --git a/gcc/cobol/lang-specs.h b/gcc/cobol/lang-specs.h
index e4043b3ccf41aad2bdb147618dc34fb32760c30f..6184cdd98d1a5d59309fa87a8c6e29253bc1139c 100644
--- a/gcc/cobol/lang-specs.h
+++ b/gcc/cobol/lang-specs.h
@@ -33,15 +33,15 @@
     {".cbl", "@cobol", 0, 0, 0},
     {".CBL", "@cobol", 0, 0, 0},
     {"@cobol",
-	"cobol1 %i %(cc1_options) "
-	"%{D*} %{E} %{I*} %{fmax-errors*} %{fsyntax-only*} "
-	"%{fcobol-exceptions*} "
-	"%{copyext} "
-	"%{fstatic-call} %{fdefaultbyte} "
-	"%{ffixed-form} %{ffree-form} %{indicator-column*} "
-	"%{preprocess} "
-	"%{dialect} "
-	"%{include} "
-	"%{nomain} "
-	"%{!fsyntax-only:%(invoke_as)} "
-	, 0, 0, 0},
+        "cobol1 %i %(cc1_options) "
+        "%{D*} %{E} %{I*} %{fmax-errors*} %{fsyntax-only*} "
+        "%{fcobol-exceptions*} "
+        "%{copyext} "
+        "%{fstatic-call} %{fdefaultbyte} "
+        "%{ffixed-form} %{ffree-form} %{indicator-column*} "
+        "%{preprocess} "
+        "%{dialect} "
+        "%{include} "
+        "%{nomain} "
+        "%{!fsyntax-only:%(invoke_as)} "
+        , 0, 0, 0},
diff --git a/gcc/cobol/lexio.h b/gcc/cobol/lexio.h
index 680e2b9b273e780031ebb50e7931477ff588ac8f..232550123e8ccf1d9066a7d23aedc7279b1eba78 100644
--- a/gcc/cobol/lexio.h
+++ b/gcc/cobol/lexio.h
@@ -87,12 +87,12 @@ struct bytespan_t {
 
     for( char *q = data; (q = std::find_if(q, eodata, isquote)) != eodata; q++) {
       if( !open ) {
-	open = *q; // first quote opens
-	continue;
+        open = *q; // first quote opens
+        continue;
       }
       if( open == *q && q + 1 < eodata && q[0] == q[1] ) { // doubled
-	q++;
-	continue;
+        q++;
+        continue;
       }
       if( open == *q ) open = '\0'; // closing quote must match
     }
@@ -231,12 +231,12 @@ struct span_t {
 struct replace_t {
   struct span_t before, after;
   replace_t( span_t before = span_t(),
-	     span_t after  = span_t() )
+             span_t after  = span_t() )
     : before(before), after(after)
   {
     if( false )
       warnx( "%s:%d: replace\n'%.*s' with\n'%.*s'", __func__, __LINE__,
-	     before.size(), before.p, after.size(), after.p );
+             before.size(), before.p, after.size(), after.p );
   }
   replace_t& reset() {
     before = after = span_t();
diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h
index 00b687a22dca0b88eb474274e3dbf55b248c05c6..422567fa252352ebc36c79387b4404daad85156e 100644
--- a/gcc/cobol/parse_ante.h
+++ b/gcc/cobol/parse_ante.h
@@ -274,7 +274,7 @@ namcpy( cbl_name_t tgt, const char *src ) {
   snprintf(tgt, sizeof(cbl_name_t), "%s", src);
   if( sizeof(cbl_name_t) - 1 < strlen(src) ) {
     yyerrorv("syntax error: name truncated to '%s' (max %zu characters)",
-	     tgt, sizeof(cbl_name_t)-1);
+             tgt, sizeof(cbl_name_t)-1);
     return false;
   }
   return true;
@@ -736,7 +736,7 @@ class eval_subject_t {
   bool decide( relop_t op, const cbl_refer_t& object, bool invert ) {
     if( pcol == columns.end() ) return false;
     if( yydebug ) warnx("%s() if not %s goto %s", __func__,
-			result->name, when()->name);
+                        result->name, when()->name);
     if( compare(op, object, true) ) {
       if( invert ) {
         parser_logop( result, NULL, not_op, result );
@@ -779,8 +779,8 @@ public:
     if( yydebug ) {
       auto& ev( top() );
       yywarnv("eval_subject: res: %s, When %s, Yeah %s, Done %s",
-	      ev.result->name,
-	      ev.when()->name, ev.yeah()->name, ev.done()->name);
+              ev.result->name,
+              ev.when()->name, ev.yeah()->name, ev.done()->name);
     }
     return top();
   }
@@ -966,7 +966,7 @@ class tokenset_t {
   
  public:
   tokenset_t( const char * const *first,
-	      const char * const *last );
+              const char * const *last );
   int find( const cbl_name_t name, bool include_intrinsics );
   
   bool equate( int token, const cbl_name_t name ) {
@@ -1817,15 +1817,15 @@ static class current_t {
       switch( section ) {
       case file_sect_e:
       case linkage_sect_e:
-	break;
+        break;
       case working_sect_e:
-	options_paragraph.initial_value.working = value;
-	return true;
-	break;
+        options_paragraph.initial_value.working = value;
+        return true;
+        break;
       case local_sect_e:
-	options_paragraph.initial_value.local = value;
-	return true;
-	break;
+        options_paragraph.initial_value.local = value;
+        return true;
+        break;
       }
     }
     return false;
@@ -1911,8 +1911,8 @@ static class current_t {
   }
   void udf_update( const ffi_args_t *ffi_args );
   bool udf_args_valid( const cbl_label_t *func,
-		       const std::list<cbl_refer_t>& args,
-		       std::vector<function_descr_arg_t>& params /*out*/ );
+                       const std::list<cbl_refer_t>& args,
+                       std::vector<function_descr_arg_t>& params /*out*/ );
 
   void udf_dump() const {
     if( yydebug ) {
@@ -2035,7 +2035,7 @@ static class current_t {
 
     if( (L = symbol_program_local(name)) != NULL ) {
       yyerrorv("error: program '%s' already defined on line %d",
-	       L->name, L->line);
+               L->name, L->line);
       return false;
     }
 
@@ -2103,8 +2103,8 @@ static class current_t {
             parser_call_target_update(caller, called->name, mangled_name);
           // Zero is not an error
           if( yydebug ) {
-	    warnx("updated %zu calls from #%-3zu (%s) s/%s/%s/",
-		  n, caller, caller_name, called->name, mangled_name);
+            warnx("updated %zu calls from #%-3zu (%s) s/%s/%s/",
+                  n, caller, caller_name, called->name, mangled_name);
           }
         }
       }
@@ -2626,7 +2626,7 @@ symbol_find( const std::list<const char *>& names ) {
   if( found.first && !found.second ) {
     auto field = cbl_field_of(found.first);
     yyerrorv( "syntax error: '%s' is not unique, first defined on line %d",
-  	    field->name, field->line );
+            field->name, field->line );
     return NULL;
   }
   return found.first;
@@ -2639,10 +2639,10 @@ field_find( const std::list<const char *>& names ) {
     if( value ) {
       cbl_field_t * field;
       if( value->is_numeric() ) {
-	field = new_tempnumeric();
-	parser_set_numeric(field, value->as_number());
+        field = new_tempnumeric();
+        parser_set_numeric(field, value->as_number());
       } else {
-	field = new_literal(value->string);
+        field = new_literal(value->string);
       }
       return field;
     }
@@ -2662,7 +2662,7 @@ symbol_find( const char *name ) {
   if( found.first && !found.second ) {
     auto field = cbl_field_of(found.first);
     yyerrorv( "syntax error: '%s' is not unique, first defined on line %d",
-  	    field->name, field->line );
+            field->name, field->line );
     return NULL;
   }
   return found.first;
@@ -2966,7 +2966,7 @@ field_capacity_error( const cbl_field_t *field ) {
   if( parent_capacity < field->data.capacity && !symbol_redefines(field) ) {
     if( yydebug ) warnx( "%s: %s", __func__, field_str(field) );
     yyerrorv( "syntax error: %s has USAGE incompatible with PICTURE",
-	      field->name );
+              field->name );
     return true;
   }
   return false;
@@ -3149,8 +3149,8 @@ parser_move_carefully( const char */*F*/, int /*L*/,
             }
 
           yyerrorv( "cannot MOVE '%s' (%s) to '%s' (%s)",
-		    name_of(src.field), stype,
-		    name_of(tgt.field), dtype);
+                    name_of(src.field), stype,
+                    name_of(tgt.field), dtype);
           delete tgt_list;
           return false;
         }
@@ -3571,7 +3571,7 @@ goodnight_gracie() {
   if( !externals.empty() ) {
     for( const auto& name : externals ) {
       warnx("%s calls external symbol '%s'",
-	    prog->name, name.c_str());
+            prog->name, name.c_str());
     }
     return false;
   }
diff --git a/gcc/cobol/parse_util.h b/gcc/cobol/parse_util.h
index 96e3f26cfd4dde0284b50ae36bdfa70a122005ee..b273da9ed249054063a665cc5e87e3e413730be9 100644
--- a/gcc/cobol/parse_util.h
+++ b/gcc/cobol/parse_util.h
@@ -347,7 +347,7 @@ intrinsic_invalid_parameter( int token, size_t n, cbl_field_t **fields ) {
                          } );
   if( p == function_descrs_end ) {
     warnx( "%s: internal error: intrinsic function  %s not found",
-	   __func__, keyword_str(token) );
+           __func__, keyword_str(token) );
     return n? fields[0] : NULL;
   }
 
@@ -375,16 +375,16 @@ intrinsic_invalid_parameter( int token, size_t n, cbl_field_t **fields ) {
     case '8' : //UTF-8
     default:
       errx(EXIT_FAILURE, "%s: invalid function descr type '%c'",
-	   __func__, descr.types[i]);
+           __func__, descr.types[i]);
     }
 
     static std::map<char, const char*> typenames;
 
     if( typenames.empty() ) {
       const char *names[] = { "AAlphabetic", "IInteger",
-			      "NNumeric", "XAlphanumeric" };
+                              "NNumeric", "XAlphanumeric" };
       for( size_t i=0; i < COUNT_OF(names); i++ ) {
-	typenames[names[i][0]] = names[i] + 1;
+        typenames[names[i][0]] = names[i] + 1;
       }
     }
 
@@ -395,9 +395,9 @@ intrinsic_invalid_parameter( int token, size_t n, cbl_field_t **fields ) {
     case FldForward:
     case FldIndex:
       yyerrorv("%s: field '%s' (%s) invalid for %s parameter",
-	       descr.name,
-	       fields[i]->name, cbl_field_type_str(fields[i]->type),
-	       typenames[descr.types[i]]);
+               descr.name,
+               fields[i]->name, cbl_field_type_str(fields[i]->type),
+               typenames[descr.types[i]]);
       return fields[i];
       break;
     case FldGroup:
@@ -407,21 +407,21 @@ intrinsic_invalid_parameter( int token, size_t n, cbl_field_t **fields ) {
 
     if( is_numeric(fields[i]) || is_integer_literal(fields[i])) {
       if( strchr("A", descr.types[i]) != NULL ) {
-	yyerrorv("%s: numeric field '%s' (%s) invalid for %s parameter",
-		 descr.name,
-		 fields[i]->name, cbl_field_type_str(fields[i]->type),
-		 typenames[descr.types[i]]);
-	return fields[i];
+        yyerrorv("%s: numeric field '%s' (%s) invalid for %s parameter",
+                 descr.name,
+                 fields[i]->name, cbl_field_type_str(fields[i]->type),
+                 typenames[descr.types[i]]);
+        return fields[i];
       }
     } else { // string field
       if( strchr("IN", descr.types[i]) != NULL ) {
-	if( data_category_of(fields[i]) == data_alphabetic_e ) {
-	  yyerrorv("%s: non-numeric field '%s' (%s) invalid for %s parameter",
-		   descr.name,
-		   fields[i]->name, cbl_field_type_str(fields[i]->type),
-		   typenames[descr.types[i]]);
-	  return fields[i];
-	}
+        if( data_category_of(fields[i]) == data_alphabetic_e ) {
+          yyerrorv("%s: non-numeric field '%s' (%s) invalid for %s parameter",
+                   descr.name,
+                   fields[i]->name, cbl_field_type_str(fields[i]->type),
+                   typenames[descr.types[i]]);
+          return fields[i];
+        }
       }
     }
   } // end loop
diff --git a/gcc/cobol/scan_ante.h b/gcc/cobol/scan_ante.h
index 923d93153010a95f5ef2d95ad2038f39b120ba41..30351e403215f2534cbe1be7e3aac38cebc32c20 100644
--- a/gcc/cobol/scan_ante.h
+++ b/gcc/cobol/scan_ante.h
@@ -106,7 +106,7 @@ lexer_echo() {
 static void
 dialect_error( const char term[], const char dialect[] ) {
   yyerrorv("error: %s is not ISO syntax, requires -dialect %s",
-	   term, dialect);
+           term, dialect);
 }
 
 // IBM says a picture can be up to 50 bytes, not 1000 words.
@@ -155,7 +155,7 @@ numstr_of( const char string[], radix_t radix = decimal_e ) {
   const char *input = yylval.numstr.string;
   auto eoinput = input + strlen(input);
   auto p = std::find_if( input, eoinput,
-			 []( char ch ) { return ch == 'e' || ch == 'E';} );
+                         []( char ch ) { return ch == 'e' || ch == 'E';} );
 
   if( p < eoinput ) {
     if( eoinput == std::find(input, eoinput, symbol_decimal_point()) ) {
@@ -194,18 +194,18 @@ numstr_of( const char string[], radix_t radix = decimal_e ) {
     //  the exponent shall also be zero and neither significand nor exponent
     //  shall have a negative sign."
     bool zero_signficand = std::all_of( input, p,
-					[]( char ch ) {
-					  return !isdigit(ch) || ch == '0'; } );
+                                        []( char ch ) {
+                                          return !isdigit(ch) || ch == '0'; } );
     if( zero_signficand ) {
       if( p != std::find(input, p, '-') ) {
-	yyerrorv("error: zero significand of %s "
-		 "cannot be negative", input);
-	return NO_CONDITION;
+        yyerrorv("error: zero significand of %s "
+                 "cannot be negative", input);
+        return NO_CONDITION;
       }
       if( eoinput != std::find(p, eoinput, '-') ) {
-	yyerrorv("error: exponent of zero significand of %s "
-		 "cannot be negative", input);
-	return NO_CONDITION;
+        yyerrorv("error: exponent of zero significand of %s "
+                 "cannot be negative", input);
+        return NO_CONDITION;
       }
     }
   }
@@ -246,7 +246,7 @@ struct cdf_status_t {
   const char * str() const {
     static char line[132];
     snprintf(line, sizeof(line), "%s:%d: %s, parsing %s",
-	     filename, lineno, keyword_str(token), boolalpha(parsing));
+             filename, lineno, keyword_str(token), boolalpha(parsing));
     return line;
   }
   static const char * as_string( const cdf_status_t& status ) {
@@ -279,7 +279,7 @@ static class parsing_status_t : public std::stack<cdf_status_t> {
  public:
   bool on() const { // true only if all true
     bool parsing = std::all_of( c.begin(), c.end(),
-			       []( const auto& status ) { return status.parsing; } );
+                               []( const auto& status ) { return status.parsing; } );
     return parsing;
   }
 
@@ -337,7 +337,7 @@ void scanner_parsing( int token, bool tf ) {
   parsing.push( cdf_status_t(token, tf) );
   if( yydebug ) {
     yywarnv("%10s: parsing now %5s, depth %zu", 
-	    keyword_str(token), boolalpha(parsing.on()), parsing.size());
+            keyword_str(token), boolalpha(parsing.on()), parsing.size());
     parsing.splat();
   }
 }
@@ -349,7 +349,7 @@ void scanner_parsing_toggle() {
   parsing.top().toggle();
   if( yydebug ) {
     yywarnv("%10s: parsing now %5s",
-	    keyword_str(CDF_ELSE), boolalpha(parsing.on()));
+            keyword_str(CDF_ELSE), boolalpha(parsing.on()));
   }
 }
 void scanner_parsing_pop() {
@@ -360,7 +360,7 @@ void scanner_parsing_pop() {
   parsing.pop();
   if( yydebug ) {
     yywarnv("%10s: parsing now %5s, depth %zu", 
-	    keyword_str(CDF_END_IF), boolalpha(parsing.on()), parsing.size());
+            keyword_str(CDF_END_IF), boolalpha(parsing.on()), parsing.size());
     parsing.splat();
   }
 }
@@ -376,23 +376,23 @@ static void level_found() {
 
 #define YY_DECL int lexer(void)
 
-#define YY_USER_ACTION						\
-  yylloc.first_line = yylloc.last_line = yylineno;		\
+#define YY_USER_ACTION                                          \
+  yylloc.first_line = yylloc.last_line = yylineno;              \
   if( yy_flex_debug ) warnx("SC: %s", start_condition_is() );
-			  
-# define YY_INPUT(buf, result, max_size)			\
-{								\
-  if( 0 == (result = lexer_input(buf, max_size, yyin)) )	\
-    result = YY_NULL;						\
+                          
+# define YY_INPUT(buf, result, max_size)                        \
+{                                                               \
+  if( 0 == (result = lexer_input(buf, max_size, yyin)) )        \
+    result = YY_NULL;                                           \
 }
 
-#define scomputable(T, C)				\
-    yylval.computational.type=T,			\
-    yylval.computational.capacity=C,			\
+#define scomputable(T, C)                               \
+    yylval.computational.type=T,                        \
+    yylval.computational.capacity=C,                    \
     yylval.computational.signable=true, COMPUTATIONAL
-#define ucomputable(T, C)				\
-    yylval.computational.type=T,			\
-    yylval.computational.capacity=C,			\
+#define ucomputable(T, C)                               \
+    yylval.computational.type=T,                        \
+    yylval.computational.capacity=C,                    \
     yylval.computational.signable=false, COMPUTATIONAL
 
 static char *tmpstring = NULL;
@@ -426,7 +426,7 @@ picset( int token ) {
 
   if( eop < p + yyleng ) {
     yyerrorv("PICTURE exceeds maximum size of %zu bytes",
-	     sizeof(orig_picture) - 1);
+             sizeof(orig_picture) - 1);
   }
   snprintf( p, eop - p, "%s", yytext );
   return token;
@@ -465,19 +465,19 @@ symbol_exists( const char name[] ) {
 
   if( in_procedure_division() && cache.empty() ) {
     for( auto e = symbols_begin(PROGRAM) + 1;
-	 PROGRAM == e->program && e < symbols_end(); e++ ) {
+         PROGRAM == e->program && e < symbols_end(); e++ ) {
       if( e->type == SymFile ) {
-	cbl_file_t *f(cbl_file_of(e));
-	cbl_name_t lname;
-	std::transform( f->name, f->name + strlen(f->name) + 1, lname, tolower );
-	cache[lname] = symbol_index(e);
-	continue;
+        cbl_file_t *f(cbl_file_of(e));
+        cbl_name_t lname;
+        std::transform( f->name, f->name + strlen(f->name) + 1, lname, tolower );
+        cache[lname] = symbol_index(e);
+        continue;
       }
       if( e->type == SymField ) {
-	auto f(cbl_field_of(e));
-	cbl_name_t lname;
-	std::transform( f->name, f->name + strlen(f->name) + 1, lname, tolower );
-	cache[lname] = symbol_index(e);
+        auto f(cbl_field_of(e));
+        cbl_name_t lname;
+        std::transform( f->name, f->name + strlen(f->name) + 1, lname, tolower );
+        cache[lname] = symbol_index(e);
       }
     }
     cache.erase("");
@@ -522,11 +522,11 @@ typed_name( const char name[] ) {
     {
       auto f = cbl_field_of(e);
       if( is_constant(f) ) {
-	int token = datetime_format_of(f->data.initial);
-	if( token ) {
-	  yylval.string = strdup(f->data.initial);
-	  return token;
-	}
+        int token = datetime_format_of(f->data.initial);
+        if( token ) {
+          yylval.string = strdup(f->data.initial);
+          return token;
+        }
       }
     }
     __attribute__((fallthrough));
@@ -534,18 +534,18 @@ typed_name( const char name[] ) {
     {
       auto f = cbl_field_of(e);
       if( false && 0 == (f->attr & constant_e) ) {
-	yyerrorv("%s: logic error: %s is not constant", __func__, name);
+        yyerrorv("%s: logic error: %s is not constant", __func__, name);
       }
       if( type == FldLiteralN ) {
-	yylval.numstr.radix =
-	  f->has_attr(hex_encoded_e)? hexadecimal_e : decimal_e;
-	yylval.numstr.string = strdup(f->data.initial);
-	return NUMSTR;
+        yylval.numstr.radix =
+          f->has_attr(hex_encoded_e)? hexadecimal_e : decimal_e;
+        yylval.numstr.string = strdup(f->data.initial);
+        return NUMSTR;
       }
       if( !f->has_attr(record_key_e) ) { // not a key-name literal
-	yylval.literal.set(f);
-	ydflval.string = yylval.literal.data;
-	return LITERAL;
+        yylval.literal.set(f);
+        ydflval.string = yylval.literal.data;
+        return LITERAL;
       }
     }
     __attribute__((fallthrough));
@@ -570,7 +570,7 @@ typed_name( const char name[] ) {
     break;
   default:
     warnx("%s:%d: invalid symbol type %s for symbol \"%s\"",
-	  __func__, __LINE__, cbl_field_type_str(type), name);
+          __func__, __LINE__, cbl_field_type_str(type), name);
     return NAME;
   }
   return cbl_field_of(e)->level == 88? NAME88 : NAME;
@@ -659,10 +659,10 @@ might_be(void) {
   assert(yyleng > 0);
   for( char *name = yytext + yyleng  - 1; name > yytext; name-- ) {
     if( isspace(*name) ) {
-	symbol_elem_t *e =  symbol_exists(++name);
+        symbol_elem_t *e =  symbol_exists(++name);
       // TRUE if the input names a field that isn't a level 88 or switch
       return e && e->type == SymField &&
-	cbl_field_of(e)->type != FldSwitch && cbl_field_of(e)->level != 88;
+        cbl_field_of(e)->type != FldSwitch && cbl_field_of(e)->level != 88;
     }
   }
   return false;
diff --git a/gcc/cobol/scan_post.h b/gcc/cobol/scan_post.h
index 3363bdb332360abeae28a2ba7ce027aa732d36db..a6f9cbd82648bfa7bbd47e17e346a4fa93cbf2f7 100644
--- a/gcc/cobol/scan_post.h
+++ b/gcc/cobol/scan_post.h
@@ -109,8 +109,8 @@ datetime_format_of( const char input[] ) {
     sprintf(time_pattern, "%s|%s", time_fmt_b, time_fmt_e);
 
     sprintf(datetime_pattern, "(%sT%s)|(%sT%s)",
-	    date_fmt_b, time_fmt_b,
-	    date_fmt_e, time_fmt_e);
+            date_fmt_b, time_fmt_b,
+            date_fmt_e, time_fmt_e);
 
     for( auto p = patterns; p < eopatterns; p++ ) {
       static const int cflags = REG_EXTENDED | REG_ICASE;
@@ -118,8 +118,8 @@ datetime_format_of( const char input[] ) {
       int erc;
 
       if( 0 != (erc = regcomp(&p->re, p->regex, cflags)) ) {
-	regerror(erc, &p->re, msg, sizeof(msg));
-	warnx("%s:%d: %s: %s", __func__, __LINE__, keyword_str(p->token), msg);
+        regerror(erc, &p->re, msg, sizeof(msg));
+        warnx("%s:%d: %s: %s", __func__, __LINE__, keyword_str(p->token), msg);
       }
     }
   }
@@ -134,11 +134,11 @@ datetime_format_of( const char input[] ) {
     regmatch_t matches[nmatch];
 
     auto p = std::find_if( patterns, eopatterns,
-			   [input, &matches]( auto& pattern ) {
-			     auto erc = regexec( &pattern.re, input,
-						 COUNT_OF(matches), matches, 0 );
-			     return erc == 0;
-			   } );
+                           [input, &matches]( auto& pattern ) {
+                             auto erc = regexec( &pattern.re, input,
+                                                 COUNT_OF(matches), matches, 0 );
+                             return erc == 0;
+                           } );
 
     return p != eopatterns? p->token : 0;
   }
@@ -294,22 +294,22 @@ prelex() {
     if( token == LEVEL ) {
       switch(yylval.number) {
       case 66:
-	token = LEVEL66;
-	break;
+        token = LEVEL66;
+        break;
       case 78:
-	token = LEVEL78;
-	break;
+        token = LEVEL78;
+        break;
       case 88:
-	token = LEVEL78;
-	break;
+        token = LEVEL78;
+        break;
       }
     }
   }
   
   if( yydebug ) warnx( ">>CDF parser done, returning "
-		       "%s (because final_token %s, lookhead %d) on line %d",
-		       keyword_str(token), keyword_str(final_token),
-		       ydfchar, yylineno );
+                       "%s (because final_token %s, lookhead %d) on line %d",
+                       keyword_str(token), keyword_str(final_token),
+                       ydfchar, yylineno );
   in_cdf = false;
   return token;
 }
@@ -363,11 +363,11 @@ yylex(void) {
     token = prelex();
     if( yy_flex_debug ) {
       if( parsing.in_cdf() ) {
-	warnx( "%s:%d: %s routing %s to CDF parser", __func__, __LINE__,
-	       start_condition_is(), keyword_str(token) );
+        warnx( "%s:%d: %s routing %s to CDF parser", __func__, __LINE__,
+               start_condition_is(), keyword_str(token) );
       } else if( !parsing.on() ) {
-	yywarnv( "eating %s because conditional compilation is FALSE",
-		 keyword_str(token) );
+        yywarnv( "eating %s because conditional compilation is FALSE",
+                 keyword_str(token) );
       }
     }
 
diff --git a/gcc/cobol/show_parse.h b/gcc/cobol/show_parse.h
index 095a24a5d963f8487187d86d6d5fa887911ff3e6..ef6c15a1e8b325eee96a42bcdd8bf7674147afa3 100644
--- a/gcc/cobol/show_parse.h
+++ b/gcc/cobol/show_parse.h
@@ -335,12 +335,12 @@ extern bool cursor_at_sol;
           gg_fprintf(trace_handle, 0, "("); \
           if( b.refmod.from ) \
             { \
-	      gg_fprintf(trace_handle, 1, "%s", gg_string_literal(   b.refmod.from->name() ? b.refmod.from->name() : "" )); \
+              gg_fprintf(trace_handle, 1, "%s", gg_string_literal(   b.refmod.from->name() ? b.refmod.from->name() : "" )); \
             } \
           gg_fprintf(trace_handle, 0, ":"); \
           if( b.refmod.len ) \
             { \
-	      gg_fprintf(trace_handle, 1, "%s", gg_string_literal(    b.refmod.len->name()   ? b.refmod.len->name() : "" )); \
+              gg_fprintf(trace_handle, 1, "%s", gg_string_literal(    b.refmod.len->name()   ? b.refmod.len->name() : "" )); \
             } \
           gg_fprintf(trace_handle, 0, "("); \
           } \
diff --git a/gcc/cobol/symbols.cc b/gcc/cobol/symbols.cc
index 31aa91df3c18723cbe4201cd0864f78021d175ef..f8c99455834a8c7ef3cb70f4f5c1e0204b2f31fa 100644
--- a/gcc/cobol/symbols.cc
+++ b/gcc/cobol/symbols.cc
@@ -176,7 +176,7 @@ symbol_at_impl( size_t index, bool internal = true ) {
 
   if( e->type == SymField && cbl_field_of(e)->type == FldForward ) {
     return symbol_field(e->program,
-			cbl_field_of(e)->parent, cbl_field_of(e)->name);
+                        cbl_field_of(e)->parent, cbl_field_of(e)->name);
   }
   return e;
 }
@@ -234,13 +234,13 @@ symbol_valid_udf_args( size_t function, std::list<cbl_refer_t> args ) {
     return NULL;
   }
   auto e = std::find_if( symbol_at(function), symbols_end(),
-			 []( auto symbol ) {
-			   if( symbol.type == SymDataSection ) {
-			     auto section(symbol.elem.section);
-			     return section.type == linkage_sect_e;
-			   }
-			   return false;
-			 } );
+                         []( auto symbol ) {
+                           if( symbol.type == SymDataSection ) {
+                             auto section(symbol.elem.section);
+                             return section.type == linkage_sect_e;
+                           }
+                           return false;
+                         } );
   for( auto arg : args ) {
     size_t iarg(1);
     e++; // skip over linkage_sect_e, which appears after the function
@@ -265,18 +265,18 @@ symbol_valid_udf_args( size_t function, std::list<cbl_refer_t> args ) {
 static const struct cbl_occurs_t nonarray = cbl_occurs_t();
 
 static const struct cbl_field_t empty_float = {
-				0, FldFloat, FldInvalid,
-				intermediate_e,
-				0, 0, 0, nonarray, 0, "",
-				0, cbl_field_t::linkage_t(), 
-				{16, 16, 32, 0, NULL, NULL, {NULL}, {NULL}}, NULL };
+                                0, FldFloat, FldInvalid,
+                                intermediate_e,
+                                0, 0, 0, nonarray, 0, "",
+                                0, cbl_field_t::linkage_t(), 
+                                {16, 16, 32, 0, NULL, NULL, {NULL}, {NULL}}, NULL };
 
 static const struct cbl_field_t empty_comp5 = {
-				0, FldNumericBin5, FldInvalid,
-				signable_e | intermediate_e,
-				0, 0, 0, nonarray, 0, "",
-				0, cbl_field_t::linkage_t(),
-				{16, 16, MAX_FIXED_POINT_DIGITS, 0, NULL, NULL, {NULL}, {NULL}}, NULL };
+                                0, FldNumericBin5, FldInvalid,
+                                signable_e | intermediate_e,
+                                0, 0, 0, nonarray, 0, "",
+                                0, cbl_field_t::linkage_t(),
+                                {16, 16, MAX_FIXED_POINT_DIGITS, 0, NULL, NULL, {NULL}, {NULL}}, NULL };
 
 #if 0
 # define CONSTANT_E constant_e
@@ -285,16 +285,16 @@ static const struct cbl_field_t empty_comp5 = {
 #endif
    
 static struct cbl_field_t empty_literal = {
-				0, FldInvalid, FldInvalid, CONSTANT_E,
-				0, 0, 0, nonarray, 0, "",
-				0, cbl_field_t::linkage_t(),
-				{0,0,0,0, NULL, NULL, {NULL}, {NULL}}, NULL };
+                                0, FldInvalid, FldInvalid, CONSTANT_E,
+                                0, 0, 0, nonarray, 0, "",
+                                0, cbl_field_t::linkage_t(),
+                                {0,0,0,0, NULL, NULL, {NULL}, {NULL}}, NULL };
 
 static const struct cbl_field_t empty_conditional = {
-				0, FldConditional, FldInvalid, intermediate_e,
-				0, 0, 0, nonarray, 0, "",
-				0, cbl_field_t::linkage_t(),
-				{0,0,0,0, NULL, NULL, {NULL}, {NULL}}, NULL };
+                                0, FldConditional, FldInvalid, intermediate_e,
+                                0, 0, 0, nonarray, 0, "",
+                                0, cbl_field_t::linkage_t(),
+                                {0,0,0,0, NULL, NULL, {NULL}, {NULL}}, NULL };
 
 
 /**
@@ -412,8 +412,8 @@ is_global( const cbl_field_t * field ) {
     if( field->parent > 0 ) {
       symbol_elem_t *e = symbol_at(field->parent);
       if( SymField == e->type ) {
-	field = cbl_field_of(e);
-	continue;
+        field = cbl_field_of(e);
+        continue;
       }
     }
     break;
@@ -980,7 +980,7 @@ update_block_offsets( struct symbol_elem_t *block)
   if( getenv(__func__) ) {
     cbl_field_t *field = cbl_field_of(block);
     warnx( "%s: offset is %3zu for %2u %-30s #%3zu P%zu",
-	   __func__, field->offset, field->level, field->name,
+           __func__, field->offset, field->level, field->name,
            symbol_index(block), field->parent );
   }
 
@@ -1152,7 +1152,7 @@ symbols_dump( size_t first, bool header ) {
 
   if( header ) {
     fprintf(stderr, "Symbol Table has %zu elements\n",
-	    symbols_end() - symbols_begin());
+            symbols_end() - symbols_begin());
   }
 
   for( struct symbol_elem_t *e = symbols_begin(first); e < symbols_end(); e++ ) {
@@ -1161,33 +1161,33 @@ symbols_dump( size_t first, bool header ) {
     switch(e->type) {
     case SymFilename:
       asprintf(&s, "%4zu %-18s %s", e->program,
-	       "Filename", e->elem.filename);
+               "Filename", e->elem.filename);
       break;
     case SymDataSection:
       asprintf(&s, "%4zu %-18s line %d", e->program,
-	       cbl_section_of(e)->name(), cbl_section_of(e)->line);
+               cbl_section_of(e)->name(), cbl_section_of(e)->line);
       break;
     case SymFunction:
       asprintf(&s, "%4zu %-15s %s", e->program,
-	       "Function", e->elem.function.name);
+               "Function", e->elem.function.name);
       break;
     case SymField: {
       auto field = cbl_field_of(e);
       char *odo_str = NULL;
       if( field->occurs.depending_on != 0 ) {
-	asprintf( &odo_str, "odo %zu", field->occurs.depending_on );
+        asprintf( &odo_str, "odo %zu", field->occurs.depending_on );
       }
       ninvalid += cbl_field_of(e)->type == FldInvalid? 1 : 0;
       asprintf(&s, "%4zu %-18s %s (%s)", e->program,
-	       cbl_field_type_str(cbl_field_of(e)->type) + 3,
-	       field_str(cbl_field_of(e)),
-	       odo_str? odo_str : 
-	       cbl_field_type_str(cbl_field_of(e)->usage) + 3);
+               cbl_field_type_str(cbl_field_of(e)->type) + 3,
+               field_str(cbl_field_of(e)),
+               odo_str? odo_str : 
+               cbl_field_type_str(cbl_field_of(e)->usage) + 3);
       }
       break;
     case SymLabel:
       asprintf(&s, "%4zu %-18s %s", e->program,
-	       "Label", e->elem.label.str());
+               "Label", e->elem.label.str());
       if( LblProgram == cbl_label_of(e)->type ) {
         const auto& L = *cbl_label_of(e);
         if( L.os_name ) {
@@ -1199,21 +1199,21 @@ symbols_dump( size_t first, bool header ) {
       break;
     case SymSpecial:
       asprintf(&s, "%4zu %-18s id=%2d, %s", e->program,
-	       "Special", e->elem.special.id, e->elem.special.name);
+               "Special", e->elem.special.id, e->elem.special.name);
       break;
     case SymAlphabet:
       asprintf(&s, "%4zu %-18s encoding=%2d, '%s'", e->program, "Alphabet",
-	       int(e->elem.alphabet.encoding), e->elem.alphabet.name);
+               int(e->elem.alphabet.encoding), e->elem.alphabet.name);
       break;
     case SymFile:
       asprintf(&s, "%4zu %-18s    %-20s", e->program,
-	       "File", e->elem.file.name);
+               "File", e->elem.file.name);
       {
         char same_as[26] = "";
         if( cbl_file_of(e)->same_record_as > 0 ) {
           sprintf(same_as, "s%3zu", cbl_file_of(e)->same_record_as);
         }
-	const char *type = file_org_str(e->elem.file.org);
+        const char *type = file_org_str(e->elem.file.org);
         char *part = s;
 
         asprintf(&s, "%s %-4s %s %s %s{%zu-%zu} status=#%zu",
@@ -1596,7 +1596,7 @@ cbl_field_t::attr_str( const std::vector<cbl_field_attr_t>& attrs ) const
     char *part = out;
     if( has_attr(attr) ) {
       int erc = asprintf(&out, "%s%s%s",
-			 part? part : "", sep, cbl_field_attr_str(attr));
+                         part? part : "", sep, cbl_field_attr_str(attr));
       if( -1 == erc ) return part;
       free(part);
       sep = ", ";
@@ -1625,7 +1625,7 @@ field_str( const cbl_field_t *field ) {
   }
 
   pend += snprintf(pend, string + sizeof(string) - pend,
-		   "%02d %-20s ", field->level, name);
+                   "%02d %-20s ", field->level, name);
 
   char offset[32] = "";
   if( field->level > 1 ) {
@@ -1700,14 +1700,14 @@ field_str( const cbl_field_t *field ) {
   };
 
   pend += snprintf(pend, string + sizeof(string) - pend,
-		   "%c%3zu %-6s %c%c%c %2u{%3u,%u,%d = %s} (%s), line %d",
-		   parredef, field->parent, offset,
-		   (field->attr & global_e)? 'G' : 0x20,
-		   (field->attr & external_e)? 'E' : 0x20,
-		   storage_type,
+                   "%c%3zu %-6s %c%c%c %2u{%3u,%u,%d = %s} (%s), line %d",
+                   parredef, field->parent, offset,
+                   (field->attr & global_e)? 'G' : 0x20,
+                   (field->attr & external_e)? 'E' : 0x20,
+                   storage_type,
                    field->data.memsize,
-		   field->data.capacity, field->data.digits, field->data.rdigits,
-		   data, field->attr_str(attrs), field->line );
+                   field->data.capacity, field->data.digits, field->data.rdigits,
+                   data, field->attr_str(attrs), field->line );
   return string;
 }
 
@@ -1853,10 +1853,10 @@ symbols_update( size_t first, bool parsed_ok ) {
     case 1:
       pend = calculate_capacity(p);
       if( dialect_mf() && is_table(field) ) {
-	cbl_field_t *field = cbl_field_of(p);
-	if( field->data.memsize < field->size() ) {
-	  field->data.memsize = field->size();
-	}
+        cbl_field_t *field = cbl_field_of(p);
+        if( field->data.memsize < field->size() ) {
+          field->data.memsize = field->size();
+        }
       }
       update_block_offsets(p);
       verify_block(p, pend);
@@ -1883,14 +1883,14 @@ symbols_update( size_t first, bool parsed_ok ) {
     if( is_table(field) ) {
       size_t& odo = field->occurs.depending_on;
       if( odo != 0 ) {
-	auto odo_field = cbl_field_of(symbol_at(odo)); // get not-FldForward if exists
-	if( is_forward(odo_field) ) {
-	  yyerrorv("error: table %s (line %d) DEPENDS ON %s, which is not defined",
-		   field->name, field->line, odo_field->name);
-	} else {
-	  // set odo to found field
-	  odo = field_index(odo_field);
-	}
+        auto odo_field = cbl_field_of(symbol_at(odo)); // get not-FldForward if exists
+        if( is_forward(odo_field) ) {
+          yyerrorv("error: table %s (line %d) DEPENDS ON %s, which is not defined",
+                   field->name, field->line, odo_field->name);
+        } else {
+          // set odo to found field
+          odo = field_index(odo_field);
+        }
       }
     }
     
@@ -2101,8 +2101,8 @@ symbol_find_forward_field( size_t program, const char name[] ) {
     size_t nelem = symbols_end() - start;
 
     e = static_cast<struct symbol_elem_t *>(lfind( &key, start,
-						   &nelem, sizeof(key),
-						   symbol_elem_cmp ) );
+                                                   &nelem, sizeof(key),
+                                                   symbol_elem_cmp ) );
     if( !e && yydebug ) warnx("%s:%d: no forward reference for program %zu '%s'",
                               __func__, __LINE__, program, name);
 
@@ -2235,7 +2235,7 @@ symbol_field_parent_set( struct cbl_field_t *field )
                     "error: group %s cannot have PICTURE clause", prior->name);
           return NULL;
         }
-	prior->type = FldGroup;
+        prior->type = FldGroup;
         field->attr |= numeric_group_attrs(prior);
       }
       // verify level 88 domain value
@@ -2395,13 +2395,13 @@ symbol_table_init(void) {
 
   group_size_t group_size =
     std::accumulate(debug_registers,
-		    debug_registers + COUNT_OF(debug_registers), group_size_t());
+                    debug_registers + COUNT_OF(debug_registers), group_size_t());
   debug_registers[0].data.memsize =
   debug_registers[0].data.capacity = group_size.capacity();
 
   auto debug_start = p = table.elems + table.nelem;
   p = std::transform(debug_registers,
-		     debug_registers + COUNT_OF(debug_registers), p, elementize);
+                     debug_registers + COUNT_OF(debug_registers), p, elementize);
   table.nelem = p - table.elems;
   assert(table.nelem < table.capacity);
   std::for_each(debug_start+1, p, parent_elem_set(debug_start - table.elems));
@@ -2411,8 +2411,8 @@ symbol_table_init(void) {
 
   p = table.elems + table.nelem;
   p = std::transform(special_registers,
-		     special_registers + COUNT_OF(special_registers),
-		     p, elementize);
+                     special_registers + COUNT_OF(special_registers),
+                     p, elementize);
   table.nelem = p - table.elems;
   assert(table.nelem < table.capacity);
 
@@ -2458,8 +2458,8 @@ symbol_add( struct symbol_elem_t *elem )
 
   struct symbol_elem_t *p =
     static_cast<struct symbol_elem_t *>(lsearch( elem, symbols.elems,
-						 &symbols.nelem, sizeof(*elem),
-						 symbol_elem_cmp ) );
+                                                 &symbols.nelem, sizeof(*elem),
+                                                 symbol_elem_cmp ) );
   assert(symbols.nelem > 1);
 
   if( is_program(*p) ) {
@@ -2689,20 +2689,20 @@ symbol_field_add( size_t program, struct cbl_field_t *field )
   if( (s = getenv(__func__)) != NULL ) {
     if( s[0] == 'D' ) {
       for( struct symbol_elem_t *e = symbols_begin(); e < symbols_end(); e++ ) {
-	fprintf(stderr, "%zu: %s ", e - symbols.elems, symbol_type_str(e->type));
-	if( e->type == SymField ) {
-	  fprintf(stderr, "%s = %s",
-		  cbl_field_of(e)->name, cbl_field_of(e)->data.initial);
-	}
-	fprintf(stderr, "\n");
+        fprintf(stderr, "%zu: %s ", e - symbols.elems, symbol_type_str(e->type));
+        if( e->type == SymField ) {
+          fprintf(stderr, "%s = %s",
+                  cbl_field_of(e)->name, cbl_field_of(e)->data.initial);
+        }
+        fprintf(stderr, "\n");
       }
     }
 
     warnx( "%s:%d: %3zu %-18s %02d %-16s %u/%u/%d = '%s'", __func__, __LINE__,
-	   field->offset,
-	   cbl_field_type_str(field->type), field->level, field->name,
-	   field->data.capacity, field->data.digits, field->data.rdigits,
-	   field->data.initial? field->data.initial : "(none)" );
+           field->offset,
+           cbl_field_type_str(field->type), field->level, field->name,
+           field->data.capacity, field->data.digits, field->data.rdigits,
+           field->data.initial? field->data.initial : "(none)" );
   }
 
   if( is_forward(field) ) {
@@ -2825,14 +2825,14 @@ symbol_elem_t *
 symbol_register( const char name[] )
 {
   auto p = std::find_if(symbols_begin(), symbol_at(symbols.first_program), 
-			[len = strlen(name), name]( auto e ) {
-			  if( e.type == SymField ) {
-			    if( strlen(cbl_field_of(&e)->name) == len ) {
-			      return 0 == strcasecmp(cbl_field_of(&e)->name, name);
-			    }
-			  }
-			  return false;
-			} );
+                        [len = strlen(name), name]( auto e ) {
+                          if( e.type == SymField ) {
+                            if( strlen(cbl_field_of(&e)->name) == len ) {
+                              return 0 == strcasecmp(cbl_field_of(&e)->name, name);
+                            }
+                          }
+                          return false;
+                        } );
   
   return p;
 }
@@ -2867,7 +2867,7 @@ symbol_field_forward_add( size_t program, size_t parent,
                                FldForward, FldInvalid, 0, parent, 0, 0,
                                nonarray, line, "",
                                0, cbl_field_t::linkage_t(),
-			       {0,0,0,0, " ", NULL, {NULL}, {NULL}}, NULL };
+                               {0,0,0,0, " ", NULL, {NULL}, {NULL}}, NULL };
   if( sizeof(field.name) < strlen(name) ) {
     warnx("%s:%d: logic error: name %s too long", __func__, __LINE__, name);
     return NULL;
@@ -2924,12 +2924,12 @@ symbol_file( size_t program, const char name[] ) {
     }
     if( e->type != SymField ) {
       warnx("%s:%d: '%s' is not a file and has parent of type %s",
-	    __func__, __LINE__, name, symbol_type_str(e->type));
+            __func__, __LINE__, name, symbol_type_str(e->type));
       return NULL;
     }
     if( symbol_index(e) == 0 ) {
       warnx("%s:%d: '%s' is not a file and has no parent",
-	    __func__, __LINE__, name);
+            __func__, __LINE__, name);
       return NULL;
     }
   }
@@ -2959,7 +2959,7 @@ symbol_field_alias( struct symbol_elem_t *e, const char name[] )
 
 struct symbol_elem_t *
 symbol_field_alias2( struct symbol_elem_t *e, struct symbol_elem_t *e2,
-		     const char name[] )
+                     const char name[] )
 {
   assert(cbl_field_of(e)->data.picture == NULL);
   e = symbol_field_alias(e, name);
@@ -3360,9 +3360,9 @@ new_temporary_impl( enum cbl_field_type_t type )
   static int nstack, nliteral; 
   static const struct cbl_field_t empty_alpha = {
                                 0, FldAlphanumeric, FldInvalid,
-				intermediate_e, 0, 0, 0, nonarray, 0, "",
-				0, cbl_field_t::linkage_t(),
-				{0,0,0,0, NULL, NULL, {NULL}, {NULL}}, NULL };
+                                intermediate_e, 0, 0, 0, nonarray, 0, "",
+                                0, cbl_field_t::linkage_t(),
+                                {0,0,0,0, NULL, NULL, {NULL}, {NULL}}, NULL };
   struct cbl_field_t *f = new cbl_field_t;
   f->type = type;
 
@@ -4036,7 +4036,7 @@ struct cbl_special_name_t *
 symbol_special( special_name_t id ) {
   cbl_special_name_t special = { .id = id };
   struct symbol_elem_t key = { SymSpecial, 0,
-			       { .special = special } }, *e;
+                               { .special = special } }, *e;
 
   e = static_cast<struct symbol_elem_t *>(lfind( &key, symbols.elems,
                                                  &symbols.nelem, sizeof(key),
@@ -4070,7 +4070,7 @@ symbol_special_add( size_t program, struct cbl_special_name_t *special )
 
   if( getenv(__func__) ) {
     warnx( "%s:%d: added special '%s'", __func__, __LINE__,
-	   e->elem.special.name);
+           e->elem.special.name);
   }
 
   elem_key_t key(program, cbl_special_name_of(e)->name);
@@ -4082,7 +4082,7 @@ symbol_special_add( size_t program, struct cbl_special_name_t *special )
 struct cbl_section_t *
 symbol_section( size_t program, struct cbl_section_t *section ) {
   struct symbol_elem_t key = { SymDataSection, program,
-			       { .section = *section } }, *e;
+                               { .section = *section } }, *e;
 
   e = static_cast<struct symbol_elem_t *>(lfind( &key, symbols.elems,
                                                  &symbols.nelem, sizeof(key),
@@ -4099,7 +4099,7 @@ symbol_section_add( size_t program, struct cbl_section_t *section )
   }
 
   struct symbol_elem_t *e, elem = { SymDataSection,
-				    program, { .section = *section } };
+                                    program, { .section = *section } };
 
   if( (e = symbol_add(&elem)) == NULL ) {
     errx(EXIT_FAILURE,
@@ -4566,7 +4566,7 @@ cbl_occurs_t::field_add( cbl_field_list_t& field_list, cbl_field_t *field ) {
 
   list.fields =
     static_cast<size_t*>(realloc(list.fields,
-				 sizeof(list.fields[0]) * (list.nfield +1)));
+                                 sizeof(list.fields[0]) * (list.nfield +1)));
   if( list.fields ) {
     list.fields[list.nfield++] = ifield;
     field_list = list;
@@ -4928,7 +4928,7 @@ file_status_status_of( file_status_t status ) {
   file_status_field_t *fs, key = { .status = status };
 
   fs = (file_status_field_t*)lfind( &key, file_status_fields,
-				    &n, sizeof(*fs), cbl_file_status_cmp );
+                                    &n, sizeof(*fs), cbl_file_status_cmp );
 
   return fs? (long)fs->status : -1;
 }
@@ -4936,8 +4936,8 @@ file_status_status_of( file_status_t status ) {
 cbl_field_t *
 ast_file_status_between( file_status_t lower, file_status_t upper ) {
   struct { cbl_field_t *lb, *ub, *both; } cond = { new_temporary(FldConditional),
-						   new_temporary(FldConditional),
-						   new_temporary(FldConditional) };
+                                                   new_temporary(FldConditional),
+                                                   new_temporary(FldConditional) };
 
   cbl_field_t *file_status = cbl_field_of(symbol_field(0, 0, "_FILE_STATUS"));
 
diff --git a/gcc/cobol/symbols.h b/gcc/cobol/symbols.h
index 8cb5c6d4ce19a97437847fa7852d9ac015beb9f8..e6c06498b2fa40ab57a1afb7f25da5681b1c0fd9 100644
--- a/gcc/cobol/symbols.h
+++ b/gcc/cobol/symbols.h
@@ -1035,7 +1035,7 @@ struct cbl_string_src_t {
   cbl_refer_t *inputs;      // identifier-1
 
   cbl_string_src_t( const cbl_refer_t& delimited_by,
-		    size_t ninput, cbl_refer_t *inputs )
+                    size_t ninput, cbl_refer_t *inputs )
     : delimited_by(delimited_by)
     , ninput(ninput)
     , inputs(inputs)
@@ -2321,7 +2321,7 @@ size_t end_of_group( size_t igroup );
 struct symbol_elem_t * symbol_typedef( size_t program, std::list<const char *> names );
 struct symbol_elem_t * symbol_typedef( size_t program, const char name[] );
 struct symbol_elem_t * symbol_field( size_t program,
-				     size_t parent, const char name[] );
+                                     size_t parent, const char name[] );
 struct cbl_label_t *   symbol_program( size_t parent, const char name[] );
 struct cbl_label_t *   symbol_label( size_t program, cbl_label_type_t type,
                                      size_t section, const char name[],