diff --git a/gcc/cobol/ChangeLog b/gcc/cobol/ChangeLog
index ac41c8e25ec4a96b50077496bea6d3a9f0ed29ef..27fc6c20c746e25d16d52f1a21676a5891da27cd 100644
--- a/gcc/cobol/ChangeLog
+++ b/gcc/cobol/ChangeLog
@@ -20,6 +20,7 @@
 	trimmed .h files in structs.cc
 
 	* Eliminate vestigial unused code from the PERFORM-PROC-AS_CALL experiment
+	* Fix TRACE1 problems with FldConditionals and parser_leave_file
 	* Introduce cbl_message, cbl_warning, cbl_error, cbl_internal_error
 	convert genapi.cc to cbl_warning and cbl_internal_error
 	convert cdf-copy.cc to cbl_warning
@@ -40,10 +41,7 @@
 	convert show-parse.h to cbl_warning
 	convert symbols.h to cbl_warning
 	convert symbols.cc to cbl_warning
-    
-    
-    
-    
-
-
+	fixed UAT for recursive copybook file warnings
+	convert scan_ante.h to cbl_warning
+	convert scan_post.h to cbl_warning
 
diff --git a/gcc/cobol/UAT/testsuite.src/syn_copy.at b/gcc/cobol/UAT/testsuite.src/syn_copy.at
index d5a6b2a2e3e2cd14ac130f0ef65059583030385e..9965d5ba49c9f92d918c1625b22e492223169953 100644
--- a/gcc/cobol/UAT/testsuite.src/syn_copy.at
+++ b/gcc/cobol/UAT/testsuite.src/syn_copy.at
@@ -279,12 +279,12 @@ AT_DATA([copy3.CPY],
        01 TEST-VAR3 PIC X(2) VALUE "V3".
 ])
 AT_CHECK([$COMPILE_ONLY prog.cob], [1], [],
-[cobol1: depth line copybook filename
-        ----- ---- ------------------------------------------------
-cobol1:     1    1 prog.cob
-cobol1:     2    1 copy1.CPY
-cobol1:     3    1 copy2.CPY
-cobol1:     4    1 copy3.CPY
+[cobol1: warning: depth line copybook filename
+                 ----- ---- ------------------------------------------------
+cobol1: warning:     1    1 prog.cob
+cobol1: warning:     2    1 copy1.CPY
+cobol1: warning:     3    1 copy2.CPY
+cobol1: warning:     4    1 copy3.CPY
 copy3.CPY:1: recursive copybook: 'copy1.CPY' includes itself
 cobol1: error: failed compiling prog.cob
 ])
diff --git a/gcc/cobol/failures/playpen/playpen.cbl b/gcc/cobol/failures/playpen/playpen.cbl
index 8e17a1593460188fd5ebbbd258297773c101014b..a32a01a357e29f321ddca5bfedd7ba55449ffe2b 100644
--- a/gcc/cobol/failures/playpen/playpen.cbl
+++ b/gcc/cobol/failures/playpen/playpen.cbl
@@ -1,12 +1,9 @@
-        identification      division.
-        program-id.         prog.
-        procedure division.
-        DECLARATIVES.
-        declaratives-ec-all section.
-            use after exception condition ec-all.
-                display "      declarative for ec-all".
-           end declaratives.
-        main section.
-        display "hello".
-        end program         prog.
 
+       IDENTIFICATION   DIVISION.
+       PROGRAM-ID.      prog.
+       DATA             DIVISION.
+       WORKING-STORAGE  SECTION.
+       COPY copy1.
+       PROCEDURE        DIVISION.
+           DISPLAY TEST-VAR.
+           STOP RUN.
diff --git a/gcc/cobol/scan_ante.h b/gcc/cobol/scan_ante.h
index 07fe05731b2b8e36139ed6a68a66069ac5dea345..8166ec1802583899a1de58a25bb8a48a843c2b39 100644
--- a/gcc/cobol/scan_ante.h
+++ b/gcc/cobol/scan_ante.h
@@ -315,7 +315,7 @@ static class parsing_status_t : public std::stack<cdf_status_t> {
   void splat() const {
     int i=0;
     for( const auto& status : c ) {
-      warnx( "%4d\t%s", ++i, status.str() );
+      cbl_warning( "%4d\t%s", ++i, status.str() );
     }
   }
 } parsing;
@@ -379,7 +379,7 @@ static void level_found() {
 
 #define YY_USER_ACTION                                          \
   yylloc.first_line = yylloc.last_line = yylineno;              \
-  if( yy_flex_debug ) warnx("SC: %s", start_condition_is() );
+  if( yy_flex_debug ) cbl_warning("SC: %s", start_condition_is() );
                           
 # define YY_INPUT(buf, result, max_size)                        \
 {                                                               \
@@ -407,7 +407,7 @@ level_of( const char input[] ) {
   if( input[0] == '0' ) input++;
 
   if( 1 != sscanf(input, "%u", &output) ) {
-    warnx( "%s:%d: invalid level '%s'", __func__, __LINE__, input );
+    cbl_warning( "%s:%d: invalid level '%s'", __func__, __LINE__, input );
   }
 
   return output;
@@ -442,7 +442,7 @@ is_integer_token( int *pvalue = NULL ) {
 
 static bool need_nume = false;
 bool need_nume_set( bool tf ) {
-  if( yydebug ) warnx( "need_nume now %s", tf? "true" : "false" );
+  if( yydebug ) cbl_warning( "need_nume now %s", tf? "true" : "false" );
   return need_nume = tf;
 }
 
@@ -570,7 +570,7 @@ typed_name( const char name[] ) {
     return cbl_field_of(e)->level == 88? NAME88 : CLASS_NAME;
     break;
   default:
-    warnx("%s:%d: invalid symbol type %s for symbol \"%s\"",
+    cbl_warning("%s:%d: invalid symbol type %s for symbol \"%s\"",
           __func__, __LINE__, cbl_field_type_str(type), name);
     return NAME;
   }
@@ -587,7 +587,7 @@ tmpstring_append( int len ) {
   }
   free(tmpstring);
   if( getenv(__func__) ) {
-    warnx("%s: value is now '%s'", __func__, s);
+    cbl_warning("%s: value is now '%s'", __func__, s);
   }
   return tmpstring = s;
 }
@@ -605,17 +605,17 @@ wait_for_the_child(void) {
   }
 
   if( WIFSIGNALED(status) ) {
-    warnx( "process %d terminated by %s", pid, strsignal(WTERMSIG(status)) );
+    cbl_warning( "process %d terminated by %s", pid, strsignal(WTERMSIG(status)) );
     return false;
   }
   if( WIFEXITED(status) ) {
     if( WEXITSTATUS(status) != 0 ) {
-      warnx("process %d exited with status %d", pid, status);
+      cbl_warning("process %d exited with status %d", pid, status);
       return false;
     }
   }
   if( yy_flex_debug ) {
-    warnx("process %d exited with status %d", pid, status);
+    cbl_warning("process %d exited with status %d", pid, status);
   }
   return true;
 }
@@ -630,7 +630,7 @@ integer_of( const char input[], bool is_hex = false) {
   if( input[0] == '0' ) input++;
 
   if( 1 != sscanf(input, fmt, &output) ) {
-    warnx( "%s:%d: invalid integer '%s'", __func__, __LINE__, input );
+    cbl_warning( "%s:%d: invalid integer '%s'", __func__, __LINE__, input );
   }
 
   return output;
@@ -649,7 +649,7 @@ radix_10( const char input[] ) {
   uint64_t value = integer_of(input2);
 
   if( -1 == asprintf( &p, "%ld", value) ) {
-    warnx("%s:%d: failed to make a string of %ld", __func__, __LINE__, value);
+    cbl_warning("%s:%d: failed to make a string of %ld", __func__, __LINE__, value);
   }
   free(input2);
   return p;
diff --git a/gcc/cobol/scan_post.h b/gcc/cobol/scan_post.h
index a6f9cbd82648bfa7bbd47e17e346a4fa93cbf2f7..ad46a0c4e56c298e57ffbaa1b167291fd26b35b1 100644
--- a/gcc/cobol/scan_post.h
+++ b/gcc/cobol/scan_post.h
@@ -119,7 +119,7 @@ datetime_format_of( const char input[] ) {
 
       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);
+        cbl_warning("%s:%d: %s: %s", __func__, __LINE__, keyword_str(p->token), msg);
       }
     }
   }
@@ -207,7 +207,7 @@ run_cdf( int token ) {
 
   parsing.inject_token(token); // because it will be needed by CDF parser
 
-  if( yy_flex_debug ) warnx("CDF parser start with '%s'", keyword_str(token));
+  if( yy_flex_debug ) cbl_warning("CDF parser start with '%s'", keyword_str(token));
   
   parsing.parser_save(ydfparse);
 
@@ -281,12 +281,12 @@ prelex() {
   if( YY_START == field_state && level_needed() ) { 
     switch( token ) {
     case NUMSTR:
-      if( yy_flex_debug ) warnx("final token is NUMSTR");
+      if( yy_flex_debug ) cbl_warning("final token is NUMSTR");
       yylval.number = level_of(yylval.numstr.string);
       token = LEVEL;
       break;
     case YDF_NUMBER:
-      if( yy_flex_debug ) warnx("final token is YDF_NUMBER");
+      if( yy_flex_debug ) cbl_warning("final token is YDF_NUMBER");
       yylval.number = ydflval.number;
       token = LEVEL;
       break;
@@ -306,7 +306,7 @@ prelex() {
     }
   }
   
-  if( yydebug ) warnx( ">>CDF parser done, returning "
+  if( yydebug ) cbl_warning( ">>CDF parser done, returning "
                        "%s (because final_token %s, lookhead %d) on line %d",
                        keyword_str(token), keyword_str(final_token),
                        ydfchar, yylineno );
@@ -363,7 +363,7 @@ yylex(void) {
     token = prelex();
     if( yy_flex_debug ) {
       if( parsing.in_cdf() ) {
-        warnx( "%s:%d: %s routing %s to CDF parser", __func__, __LINE__,
+        cbl_warning( "%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",
@@ -382,7 +382,7 @@ yylex(void) {
   }
   
   if( token == YYEOF && parsing.in_cdf() ) {
-    if( yy_flex_debug) warnx("deflecting EOF");
+    if( yy_flex_debug) cbl_warning("deflecting EOF");
     parsing.at_eof(true);
     return NO_CONDITION;
   }
diff --git a/gcc/cobol/util.cc b/gcc/cobol/util.cc
index d2890456efb295857c43989ee12b35cf5583013f..18900afddc8755c9c51d25e8f44487be1463a3e9 100644
--- a/gcc/cobol/util.cc
+++ b/gcc/cobol/util.cc
@@ -1987,8 +1987,8 @@ class unique_stack : public std::stack<input_file_t>
     if( n > 1 || yydebug ) {
       static char wd[PATH_MAX];
       getcwd(wd, sizeof(wd));
-      cbl_warning( "depth line copybook filename\n"
-             "        "
+      cbl_warning("depth line copybook filename\n"
+             "                 "
              "----- ---- --------"
              "----------------------------------------");
       for( const auto& v : c ) {