diff --git a/gcc/cobol/etests/check_88/known-good.txt b/gcc/cobol/etests/check_88/known-good.txt
index eec5f567d02f03eee027dad6e4685c8fc231e747..a4ef952620a848bd6b1761715d83cec07829e3ab 100644
--- a/gcc/cobol/etests/check_88/known-good.txt
+++ b/gcc/cobol/etests/check_88/known-good.txt
@@ -1,6 +1,6 @@
-check_88.cbl:13:37: warning: '' has embedded NUL
+check_88.cbl:13:33: warning: '' has embedded NUL
    13 |            88  CheckBinary VALUE X"000102".
-      |                                     ^
+      |                                 ^
 -><-
 ->   <-
 ->"""<-
diff --git a/gcc/cobol/failures/playpen/playpen.cbl b/gcc/cobol/failures/playpen/playpen.cbl
index 0670d3bcba5c91b90acc4a87f35d72d63e267365..9b58f25cac57b3cb8b072065a29f5d101039d40c 100644
--- a/gcc/cobol/failures/playpen/playpen.cbl
+++ b/gcc/cobol/failures/playpen/playpen.cbl
@@ -1,10 +1,15 @@
-1        identification division.
-2        program-id. prog.
-3        procedure division.
-4
-5
-6        display "Hello"
-7
-8
-9        goback.
-10       end program prog.
+
+
+
+
+
+
+
+
+
+
+       IDENTIFICATION   DIVISION.
+       PROGRAM-ID.      prog.
+       PROCEDURE        DIVISION RETURNING OMITTED.
+           MOVE 42 TO RETURN-CODE
+           GOBACK.
diff --git a/gcc/cobol/genapi.cc b/gcc/cobol/genapi.cc
index 1eefb7094ce76016f38a37bf26d91bdcdfd5e98c..552c0d5110f3d56328748765f0b0b42016483799 100644
--- a/gcc/cobol/genapi.cc
+++ b/gcc/cobol/genapi.cc
@@ -3602,6 +3602,8 @@ parser_enter_program( const char *funcname_,
       }
     }
 
+  gg_set_current_line_number(CURRENT_LINE_NUMBER);
+
   if( strcmp(funcname, "dubner") == 0)
     {
     // This should be enabled by an environment variable.
@@ -6397,6 +6399,8 @@ parser_division(cbl_division_t division,
     SHOW_PARSE_END
     }
 
+  gg_set_current_line_number(CURRENT_LINE_NUMBER);
+
   if( division == data_div_e )
     {
     Analyze();
diff --git a/gcc/cobol/tests/check_88/known-good.txt b/gcc/cobol/tests/check_88/known-good.txt
index 71d227a35307ca1a222e16aaea3d09de08fde2d0..a4ef952620a848bd6b1761715d83cec07829e3ab 100644
--- a/gcc/cobol/tests/check_88/known-good.txt
+++ b/gcc/cobol/tests/check_88/known-good.txt
@@ -1,6 +1,6 @@
-check_88.cbl:13:36: warning: '' has embedded NUL
+check_88.cbl:13:33: warning: '' has embedded NUL
    13 |            88  CheckBinary VALUE X"000102".
-      |                                    ^
+      |                                 ^
 -><-
 ->   <-
 ->"""<-
diff --git a/gcc/cobol/util.cc b/gcc/cobol/util.cc
index a8bb7d692a8fe43abd944ac96dda8c7b7260ddf6..984f74e9e235377767829d1b3753dc83e7bdaaf7 100644
--- a/gcc/cobol/util.cc
+++ b/gcc/cobol/util.cc
@@ -2075,14 +2075,8 @@ static location_t token_location;
 
 void
 gcc_location_set( const YYLTYPE& loc ) {
-  static int current_line = 0;
-  
-  if( current_line != loc.last_line ) {
-    current_line = loc.last_line;
-    token_location = linemap_line_start( line_table, current_line, 80 );
-  }
+  token_location = linemap_line_start( line_table, loc.last_line, 80 );
   token_location = linemap_position_for_column( line_table, loc.first_column);
-  
   if( getenv(__func__) ) {
     location_dump(__func__, __LINE__, "parser", loc);
   }