diff --git a/gcc/cobol/cbldiag.h b/gcc/cobol/cbldiag.h
index 901669a2150909527a4d1b476b4906e8759916c2..6ad2955d488c4e55cc67e1fc339c966cec5d9553 100644
--- a/gcc/cobol/cbldiag.h
+++ b/gcc/cobol/cbldiag.h
@@ -32,11 +32,10 @@
 
 const char * cobol_filename();
 
-void yyerror( char const *s, int error_level = LOG_ERR);
+void yyerror( char const *s );
 void yyerrorv( const char fmt[], ... );
 void yyerrorvl( int line, const char *filename, const char fmt[], ... );
 
-static inline void yywarn( char const *msg ) { yyerror( msg, LOG_WARNING ); }
-
-void yywarnv( const char fmt[], ... );
+bool yywarnv( const char fmt[], ... );
 
+static inline void yywarn( char const *msg ) { yywarnv( msg ); }
diff --git a/gcc/cobol/cdf.y b/gcc/cobol/cdf.y
index e59c6b10dd7796d9f6f009a6f609fc6c57b82d6f..b5e6d78060a1eebbf70baaf2bffd53cc4f683bec 100644
--- a/gcc/cobol/cdf.y
+++ b/gcc/cobol/cdf.y
@@ -34,7 +34,6 @@
 #include "symbols.h"
 #include "exceptl.h"
 #include "exceptg.h"
-#include "cbldiag.h"
 
 #define COUNT_OF(X) (sizeof(X) / sizeof(X[0]))
 
@@ -1005,10 +1004,10 @@ static int ydflex(void) {
 }
 
 #undef yyerror
-void yyerror( char const *s, int error_level = LOG_ERR );
+void yyerror( char const *s );
 
-void ydferror( char const *s, int error_level ) {
-  return yyerror(s, error_level);
+void ydferror( char const *s ) {
+  return yyerror(s);
 }
 
 bool
diff --git a/gcc/cobol/genapi.cc b/gcc/cobol/genapi.cc
index 51b8c305016537a66e2b2875a2579789f947f78d..dee2fd479ee359d678c8dc9fa5640f8f779837bb 100644
--- a/gcc/cobol/genapi.cc
+++ b/gcc/cobol/genapi.cc
@@ -37,6 +37,7 @@
 #include "diagnostic-core.h"
 
 #define HOWEVER_GCC_DEFINES_TREE 1
+
 #include "symbols.h"
 #include "gengen.h"
 #include "genutil.h"
diff --git a/gcc/cobol/lexio.cc b/gcc/cobol/lexio.cc
index 66197c76629685a0ea101165b869d293f3b60d98..d3dd172bc1fc5fb714e8c7b6fdeb52d3eb503e9f 100644
--- a/gcc/cobol/lexio.cc
+++ b/gcc/cobol/lexio.cc
@@ -1650,8 +1650,6 @@ cdftext::free_form_reference_format( int input ) {
   return source_buffer;
 }
 
-const char * cobol_filename_restore();
-
 /*
  * process_file is a recursive routine that opens and processes
  * included files.  It uses the input file stack in two ways: to check
@@ -1704,7 +1702,7 @@ cdftext::process_file( filespan_t mfile, int output, bool second_pass ) {
     out.flush();
   }
 
-  // pa§rse CDF directives
+  // parse CDF directives
   while( mfile.next_line() ) {
     auto copied = parse_copy_directive(mfile);
     if( copied.parsed && copied.fd != -1 ) {
diff --git a/gcc/cobol/parse.y b/gcc/cobol/parse.y
index c165159f36c059a9958d5c0f68ef3d99d8412d14..41be63e972d6e0a107d93d98e6dd99b62d750c48 100644
--- a/gcc/cobol/parse.y
+++ b/gcc/cobol/parse.y
@@ -2284,6 +2284,7 @@ domains:        domain
 domain:         all LITERAL[a]
                 {
                   if( ! string_of($a) ) {
+		    gcc_location_set(@a);
                     yywarnv("warning: '%s' has embedded NUL", $a.data);
                   }
                   $$ = NULL;
diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h
index 40d9648f618546820a8812dc4ce6633095e0a7c2..93f4e36fda7b76d6772a77d236002aad34af294c 100644
--- a/gcc/cobol/parse_ante.h
+++ b/gcc/cobol/parse_ante.h
@@ -31,7 +31,6 @@
 #include "genapi.h"
 #include "io.h"
 #include "ec.h"
-#include "cbldiag.h"
 
 #include <assert.h>
 #include <string.h>
@@ -81,8 +80,27 @@ size_t cbl_gcobol_features;
 
 static size_t nparse_error = 0;
 
+size_t parse_error_inc() { return ++nparse_error; }
 size_t parse_error_count() { return nparse_error; }
 
+#define YYLLOC_DEFAULT(Current, Rhs, N) 				\
+  do {									\
+      if (N)                                                            \
+        {                                                               \
+          (Current).first_line   = YYRHSLOC (Rhs, 1).first_line;        \
+          (Current).first_column = YYRHSLOC (Rhs, 1).first_column;      \
+          (Current).last_line    = YYRHSLOC (Rhs, N).last_line;         \
+          (Current).last_column  = YYRHSLOC (Rhs, N).last_column;       \
+        }                                                               \
+      else                                                              \
+        {                                                               \
+          (Current).first_line   = (Current).last_line   =              \
+            YYRHSLOC (Rhs, 0).last_line;                                \
+          (Current).first_column = (Current).last_column =              \
+            YYRHSLOC (Rhs, 0).last_column;                              \
+        }                                                               \
+      gcc_location_set( location_set(Current) );					\
+    } while (0)
 
 #include <syslog.h>
 
@@ -119,7 +137,7 @@ extern int yydebug;
 #include <stdarg.h>
 
 void
-yyerrorv( const char fmt[], ... ) {
+dnu_yyerrorv( const char fmt[], ... ) {
   char *msg;
   va_list ap;
 
@@ -132,7 +150,7 @@ yyerrorv( const char fmt[], ... ) {
 }
 
 void
-yywarnv( const char fmt[], ... ) {
+dnu_yywarnv( const char fmt[], ... ) {
   char *msg;
   va_list ap;
 
@@ -3609,9 +3627,9 @@ static YYLTYPE current_location;
 
 const YYLTYPE& cobol_location() { return current_location; }
 
-static void
+static inline YYLTYPE
 location_set( const YYLTYPE& loc ) {
-  current_location = loc;
+  return current_location = loc;
 }
 
 static int prior_statement;
diff --git a/gcc/cobol/scan.l b/gcc/cobol/scan.l
index 0eeb24d71488806e41a9a158536fbc569543839c..65e79504987a31fcde0713b6a777dd6fb5eb6c4d 100644
--- a/gcc/cobol/scan.l
+++ b/gcc/cobol/scan.l
@@ -2099,11 +2099,12 @@ BASIS		{ yy_push_state(basis); return BASIS; }
 			  yywarnv("logic warning: name adjusted to %s", --name);
 			}
 			cobol_filename(name, 0);
+
 			if( yy_flex_debug ) cbl_warnx("starting line %4d of %s",
 						  yylineno, name); }
   {POP_FILE} {
 			yy_set_bol(true);
-			auto name = cobol_filename_restore();
+			auto name = cobol_filename_restore(true);
 	   		if( yy_flex_debug ) cbl_warnx("resuming line %4d of %s",
 						  yylineno, name? name : "<none>"); }
 
diff --git a/gcc/cobol/scan_ante.h b/gcc/cobol/scan_ante.h
index 09c89162253f76faabbf8b3e566a55f2b6d15e27..4b41910af924334d9b0b5c0c8a31119bb9c2bb02 100644
--- a/gcc/cobol/scan_ante.h
+++ b/gcc/cobol/scan_ante.h
@@ -32,7 +32,6 @@
 #include "cdf.h"
 #include "symbols.h"
 #include "copybook.h"
-#include "cbldiag.h"
 
 /*
  * Flex override
diff --git a/gcc/cobol/symbols.h b/gcc/cobol/symbols.h
index 1b5500a56d252b7fd948055db0cc1a7720a97522..4b5eecc842b34f4a94ec97cee137d177b3e6a798 100644
--- a/gcc/cobol/symbols.h
+++ b/gcc/cobol/symbols.h
@@ -47,6 +47,7 @@
 
 #include "common-defs.h"
 #include "util.h"
+#include "cbldiag.h"
 
 #define PICTURE_MAX 64
 
@@ -224,10 +225,6 @@ const char * date4_is_now(void);
 const char * day4_is_now(void);
 const char * time_is_now(void);
 
-void yyerrorv( const char fmt[], ... );
-void yyerrorvl( int line, const char *filename, const char fmt[], ... );
-void yywarnv( const char fmt[], ... );
-
 struct cbl_upsi_mask_t {
   bool on_off;
   uint32_t value;
@@ -1931,8 +1928,6 @@ is_numeric( const cbl_field_t *field ) {
 bool cobol_filename( const char *name );
 const char * cobol_filename();
 
-const char * cobol_filename_restore();
-const char * cobol_lineno_save();
 const char * cobol_fileline_set( const char line[] );
 
 char *cobol_name_mangler(const char *cobol_name);
@@ -2195,8 +2190,9 @@ struct YYLTYPE
 # define YYLTYPE_IS_TRIVIAL 1
 
 const YYLTYPE& cobol_location();
-#endif
+void gcc_location_set( const YYLTYPE& loc );
 
+#endif
 
 // This is slightly oddball.  This is an entry point in the charutf8.cc module.
 // It's the only entry point in the module, and so it seemed to me wasteful to
diff --git a/gcc/cobol/util.cc b/gcc/cobol/util.cc
index db1c5fd0c96e850180da8b75baefaf58210ed38f..16dd82f03cffc1b7adf1d0ece6781d7f0b23e5d4 100644
--- a/gcc/cobol/util.cc
+++ b/gcc/cobol/util.cc
@@ -1937,14 +1937,29 @@ date_time_fmt( const char input[] ) {
 
 struct input_file_t {
   ino_t inode;
-  int lineno; const char *name;
-  input_file_t( const char *name, ino_t inode, int lineno=1 )
-    : inode(inode), lineno(lineno), name(name)
-  {}
+  int lineno;
+  const char *name;
+  const line_map *lines;
+  
+  input_file_t( const char *name, ino_t inode,
+		int lineno=1, const line_map *lines = NULL )
+    : inode(inode), lineno(lineno), name(name), lines(lines)
+  {
+    if( inode == 0 ) inode_set();
+  }
   bool operator==( const input_file_t& that ) const {
     return inode == that.inode;
   }
+ protected:
+  void inode_set()  {
+    struct stat sb;
+    if( -1 == stat(name, &sb) ) {
+      cbl_err(EXIT_FAILURE, "could not stat '%s'", name);
+    }
+    inode = sb.st_ino;
+  }
 };
+
 class unique_stack : public std::stack<input_file_t>
 {
  public:
@@ -1986,8 +2001,19 @@ class unique_stack : public std::stack<input_file_t>
 
 static unique_stack input_filenames;
 static std::map<std::string, ino_t> old_filenames;
+static const unsigned int sysp = 0;  // not a C header file, cf. line-map.h
 
+/*
+ * Maintain a stack of input filenames.  Ensure the files are unique (by
+ * inode), to prevent copybook cycles. Before pushing a new name, Record the
+ * line number that was is current for the current name, so that it can be
+ * restored when the usurper is popped.  
+ *
+ * Both the file-reader (lexio) and the scanner use this stack.  Lexio uses it
+ * to enforce uniqueness, and the scanner to maintain line numbers.
+ */
 bool cobol_filename( const char *name, ino_t inode ) {
+  line_map *lines = NULL;
   if( inode == 0 ) {
     auto p = old_filenames.find(name);
     if( p == old_filenames.end() ) {
@@ -1998,8 +2024,9 @@ bool cobol_filename( const char *name, ino_t inode ) {
     }
     inode = p->second;
     assert(inode != 0);
+    linemap_add(line_table, LC_ENTER, sysp, name, 1);
   }
-  bool pushed = input_filenames.push( input_file_t(name, inode) );
+  bool pushed = input_filenames.push( input_file_t(name, inode, 1, lines) );
   input_filenames.top().lineno = yylineno = 1;
   if( getenv(__func__) ) {
     cbl_warnx("   saving %s with lineno as %d",
@@ -2026,7 +2053,7 @@ cobol_filename() {
 }
 
 const char *
-cobol_filename_restore() {
+cobol_filename_restore( bool scanning ) {
   assert(!input_filenames.empty());
   const input_file_t& top( input_filenames.top() );
   old_filenames[top.name] = top.inode;
@@ -2034,7 +2061,11 @@ cobol_filename_restore() {
   input_filenames.pop();
   if( input_filenames.empty() ) return NULL;
 
-  auto input = input_filenames.top();
+  auto& input = input_filenames.top();
+  if( scanning ) {
+    input.lines = linemap_add(line_table, LC_LEAVE, sysp, NULL, 0);
+  }
+
   yylineno = input.lineno;
   if( getenv("cobol_filename") ) {
     cbl_warnx("restoring %s with lineno to %d",
@@ -2044,6 +2075,61 @@ cobol_filename_restore() {
   return input.name;
 }
 
+static location_t token_location;
+
+location_t
+gcc_location() { return token_location; }
+
+void
+gcc_location_set( const YYLTYPE& loc ) {
+  static int current_line = 0;
+  
+  if( current_line != loc.first_line ) {
+    current_line = loc.first_line;
+    token_location = linemap_line_start( line_table, current_line, 80 );
+  }
+  token_location = linemap_position_for_column( line_table, loc.first_column);
+  
+  if( getenv(__func__) ) {
+      fprintf(stderr, "%s:%d: location line %d column %d\n", __func__, __LINE__,
+	      loc.first_line, loc.first_column);
+  }
+}
+
+static const diagnostic_option_id option_id;
+size_t parse_error_inc();
+
+void
+yyerror( char const *msg ) { yyerrorv( msg ); }
+
+void
+yyerrorv( const char gmsgid[], ... ) {
+  parse_error_inc();
+  global_dc->begin_group();
+  va_list ap;
+  va_start (ap, gmsgid);
+  rich_location richloc (line_table, token_location);
+  bool ret = global_dc->diagnostic_impl (&richloc, nullptr, option_id,
+					 gmsgid, &ap, DK_WARNING);
+  va_end (ap);
+  global_dc->end_group();
+}
+
+bool
+yywarnv( const char gmsgid[], ... ) {
+  global_dc->begin_group();
+  va_list ap;
+  va_start (ap, gmsgid);
+  rich_location richloc (line_table, token_location);
+  bool ret = global_dc->diagnostic_impl (&richloc, nullptr, option_id,
+					 gmsgid, &ap, DK_WARNING);
+  va_end (ap);
+  global_dc->end_group();
+  return ret;
+}
+
+
+
 static inline size_t
 matched_length( const regmatch_t& rm ) { return rm.rm_eo - rm.rm_so; }
 
@@ -2082,11 +2168,12 @@ cobol_fileline_set( const char line[] ) {
   if( 1 != sscanf(line_str, "%d", &fileline) )
     cbl_warn("%s:%d: line number %s", __func__, __LINE__, line_str);
     
-  input_file_t input_file( filename, fileline );
+  input_file_t input_file( filename, ino_t(0), fileline ); // constructor sets inode
 
   if( getenv(__func__) ) return filename; // ignore #line directive 
   
   if( input_filenames.empty() ) {
+    input_file.lines = linemap_add(line_table, LC_ENTER, sysp, filename, 1);
     input_filenames.push(input_file);
   }
 
@@ -2212,7 +2299,7 @@ cbl_warning(const char *format_string, ...)
   char *ostring = xvasprintf(format_string, ap);
   va_end(ap);
   // We call warnging() with a code of zero, which is just a generic warning
-  warning(0, "%s", ostring);
+  warning_at(gcc_location(), 0, "%s", ostring);
   free(ostring);
   }
 
diff --git a/gcc/cobol/util.h b/gcc/cobol/util.h
index 791f409f1094a65ba804696e91c32562adc1c65f..d3a1449cd25a2a74c44f99e2e1ee0ab48e7aec98 100644
--- a/gcc/cobol/util.h
+++ b/gcc/cobol/util.h
@@ -46,4 +46,7 @@ bool fisspace(int c);
 int  ftolower(int c);
 bool fisprint(int c);
 
-#endif
\ No newline at end of file
+const char * cobol_filename_restore( bool scanning = false );
+const char * cobol_lineno_save();
+
+#endif