diff --git a/gcc/cobol/UAT/testsuite.src/syn_copy.at b/gcc/cobol/UAT/testsuite.src/syn_copy.at index 6c8d97a91be48db6a6d0e0c5c9376b3d2ee7b644..d5a6b2a2e3e2cd14ac130f0ef65059583030385e 100644 --- a/gcc/cobol/UAT/testsuite.src/syn_copy.at +++ b/gcc/cobol/UAT/testsuite.src/syn_copy.at @@ -281,12 +281,11 @@ AT_DATA([copy3.CPY], AT_CHECK([$COMPILE_ONLY prog.cob], [1], [], [cobol1: depth line copybook filename ----- ---- ------------------------------------------------ -cobol1: 5 1 prog.cob -cobol1: 4 1 copy1.CPY +cobol1: 1 1 prog.cob +cobol1: 2 1 copy1.CPY cobol1: 3 1 copy2.CPY -cobol1: 2 1 copy3.CPY -cobol1: 1 1 ./copy1.CPY -copy1.CPY:1: recursive copybook: 'copy2.CPY' includes itself detected at end of file +cobol1: 4 1 copy3.CPY +copy3.CPY:1: recursive copybook: 'copy1.CPY' includes itself cobol1: error: failed compiling prog.cob ]) AT_CLEANUP diff --git a/gcc/cobol/UAT/testsuite.src/syn_definition.at b/gcc/cobol/UAT/testsuite.src/syn_definition.at index 3000c2a64850000267bcb62fdbb6ffa4e4aeec29..02946974bd7ea1e85be845720513600bb366632a 100644 --- a/gcc/cobol/UAT/testsuite.src/syn_definition.at +++ b/gcc/cobol/UAT/testsuite.src/syn_definition.at @@ -490,7 +490,7 @@ prog.cob:93: error: unimplemented USAGE type: BIT at 'BIT' prog.cob:93: syntax error at 'BIT' prog.cob:96: error: unimplemented USAGE type: BIT at 'BIT' prog.cob:96: syntax error at 'BIT' -.:97: 44 errors in DATA DIVISION, compilation ceases detected at end of file +:97: 44 errors in DATA DIVISION, compilation ceases detected at end of file cobol1: error: failed compiling prog.cob ]) AT_CLEANUP @@ -528,7 +528,7 @@ AT_DATA([prog.cob], [ AT_CHECK([$COMPILE_ONLY prog.cob], [1], [], [prog.cob:7: x has 'S' in PICTURE, cannot be BLANK WHEN ZERO -.:12: 1 errors in DATA DIVISION, compilation ceases detected at end of file +:12: 1 errors in DATA DIVISION, compilation ceases detected at end of file cobol1: error: failed compiling prog.cob ]) AT_CLEANUP @@ -549,7 +549,7 @@ AT_DATA([prog.cob], [ AT_CHECK([$COMPILE_ONLY prog.cob], [1], [], [prog.cob:7: syntax error at 'COMP-6' -.:9: 1 errors in DATA DIVISION, compilation ceases detected at end of file +:9: 1 errors in DATA DIVISION, compilation ceases detected at end of file cobol1: error: failed compiling prog.cob ]) AT_CLEANUP @@ -683,7 +683,7 @@ badprog.cob:10: error: F1 created with SAME AS or TYPE TO, cannot have new membe badprog.cob:10: error: 05 FILLER is not part of an 01 record at 'FILLER' badprog.cob:12: error: 01 MT3 SAME AS precludes other DATA DIVISION clauses badprog.cob:12: error: 77 OUTPUT-NAME SAME AS MESSAGE-TEXT-2: must be elementary -.:13: 5 errors in DATA DIVISION, compilation ceases detected at end of file +:13: 5 errors in DATA DIVISION, compilation ceases detected at end of file cobol1: error: failed compiling badprog.cob ]) AT_CLEANUP diff --git a/gcc/cobol/UAT/testsuite.src/syn_file.at b/gcc/cobol/UAT/testsuite.src/syn_file.at index 14128127e26764aad85f12db082ddc4f47890cc5..0f850cf8f5fc9c4ac1366b73bc7d20edc3e109b3 100644 --- a/gcc/cobol/UAT/testsuite.src/syn_file.at +++ b/gcc/cobol/UAT/testsuite.src/syn_file.at @@ -117,8 +117,8 @@ AT_DATA([prog.cob], [ AT_CHECK([$COMPILE_ONLY prog.cob], [1], [], [prog.cob:10: error: file name not found at 'file1' -.:16: error: line 7: file2 lacks a file description detected at end of file -.:16: 2 errors in DATA DIVISION, compilation ceases detected at end of file +:16: error: line 7: file2 lacks a file description detected at end of file +:16: 2 errors in DATA DIVISION, compilation ceases detected at end of file cobol1: error: failed compiling prog.cob ]) AT_CLEANUP @@ -367,8 +367,8 @@ AT_DATA([prog.cob], [ # cobc says: prog.cob:11: error: syntax error, unexpected Identifier, expecting DYNAMIC or RANDOM or SEQUENTIAL # but why? AT_CHECK([$COMPILE_ONLY prog.cob], [1], [], -[.:13: error: line 12: testfile lacks a file description detected at end of file -.:13: 1 errors in DATA DIVISION, compilation ceases detected at end of file +[:13: error: line 12: testfile lacks a file description detected at end of file +:13: 1 errors in DATA DIVISION, compilation ceases detected at end of file cobol1: error: failed compiling prog.cob ]) AT_CLEANUP @@ -454,8 +454,8 @@ AT_DATA([prog.cob], [ AT_CHECK([$COMPILE_ONLY prog.cob], [1], [], [prog.cob:8: error: INDEXED file file-1 cannot have RELATIVE key file-1-key prog.cob:10: error: RELATIVE file file-2 cannot have RECORD key file-2-key -.:11: error: line 8: file-1 lacks a file description detected at end of file -.:11: 3 errors in DATA DIVISION, compilation ceases detected at end of file +:11: error: line 8: file-1 lacks a file description detected at end of file +:11: 3 errors in DATA DIVISION, compilation ceases detected at end of file cobol1: error: failed compiling prog.cob ]) diff --git a/gcc/cobol/UAT/testsuite.src/syn_misc.at b/gcc/cobol/UAT/testsuite.src/syn_misc.at index 7a8956d18495e1c46bbfaa2eebba67c04c0f2fe6..422b12ecfbf736d9b2f2026c8ecceda00e67538e 100644 --- a/gcc/cobol/UAT/testsuite.src/syn_misc.at +++ b/gcc/cobol/UAT/testsuite.src/syn_misc.at @@ -724,7 +724,7 @@ AT_DATA([prog.cob], [ AT_CHECK([$COMPILE_ONLY prog.cob], [1], [], [prog.cob:12: error: invalid-1 must be signed for SIGN IS prog.cob:13: error: invalid-2 is binary NUMERIC type, incompatible with SIGN IS -.:14: 2 errors in DATA DIVISION, compilation ceases detected at end of file +:14: 2 errors in DATA DIVISION, compilation ceases detected at end of file cobol1: error: failed compiling prog.cob ]) AT_CLEANUP diff --git a/gcc/cobol/UAT/testsuite.src/syn_redefines.at b/gcc/cobol/UAT/testsuite.src/syn_redefines.at index 2c9b67d3e9100f6af3742e71592f4b63d5735b74..f9d3e8f5f83f4e53fc7ffa53da6789c6ffa4c7ea 100644 --- a/gcc/cobol/UAT/testsuite.src/syn_redefines.at +++ b/gcc/cobol/UAT/testsuite.src/syn_redefines.at @@ -39,7 +39,7 @@ AT_DATA([prog.cob], [ AT_CHECK([$COMPILE_ONLY prog.cob], [1], [], [prog.cob:7: REDEFINES must appear immediately after LEVEL and NAME at 'X' -.:8: 1 errors in DATA DIVISION, compilation ceases detected at end of file +:8: 1 errors in DATA DIVISION, compilation ceases detected at end of file cobol1: error: failed compiling prog.cob ]) diff --git a/gcc/cobol/cdf-copy.cc b/gcc/cobol/cdf-copy.cc index e32e57d4e4b0569bb821d46872d1e07fc448cffe..3002394c0ed8d401d3ded565d7efac3eb08964a5 100644 --- a/gcc/cobol/cdf-copy.cc +++ b/gcc/cobol/cdf-copy.cc @@ -185,7 +185,7 @@ copybook_directory_add( const char gcob_copybook[] ) { if( !gcob_copybook ) return; char *directories = strdup(gcob_copybook), *p = directories; if( !directories ) { - warnx( "OS error: %s", strerror(errno) ); + warn( "OS error: %s", gcob_copybook ); return; } char *eodirs = strchr(directories, '\0'); @@ -247,42 +247,64 @@ copybook_t::extensions_add( const char ext[], const char alt[] ) { } } +static inline ino_t +inode_of( int fd ) { + struct stat sb; + if( -1 == fstat(fd, &sb) ) { + err(EXIT_FAILURE, "could not stat fd %d", fd); + } + return sb.st_ino; +} + int copybook_elem_t::open_file( const char directory[], bool literally ) { int erc; char *pattern, *copier = strdup(cobol_filename()); - if( ! directory ) directory = dirname(copier); - const char *library = this->library? this->library : "."; + if( ! directory ) { + directory = dirname(copier); + if( 0 == strcmp(".", directory) ) directory = NULL; + } - if( literally ) { - static char path[PATH_MAX]; - snprintf(path, sizeof(path), "%s/%s/%s", directory, library, source); + static char path[PATH_MAX]; + if( directory || library ) { + if( directory && library ) { + snprintf( path, sizeof(path), "%s/%s/%s", directory, library, source ); + } else { + const char *dir = directory? directory : library; + snprintf( path, sizeof(path), "%s/%s", dir, source ); + } + } else { + snprintf( path, sizeof(path), "%s", source ); + } + + if( literally ) { if( yydebug ) { warnx("copybook_elem_t::open_file: trying %s", path); } - if( (this->fd = open(path, O_RDONLY)) != -1 ) { - this->source = strdup(path); - if( ! cobol_filename(this->source) ) { - yyerrorv("recursive copybook: '%s' includes itself", path); - (void)! close(fd); - fd = -1; - } + if( (this->fd = open(path, O_RDONLY)) == -1 ) { + if( yydebug ) warn("error: could not open %s", path); return fd; + } + this->source = strdup(path); + if( ! cobol_filename(this->source, inode_of(fd)) ) { + yyerrorv("recursive copybook: '%s' includes itself", path); + (void)! close(fd); + fd = -1; } + return fd; } - - if( literally ) return -1; - + assert( ! literally ); + if( extensions ) { - if( -1 == asprintf(&pattern, "%s/%s/%s{,.cpy,.CPY,.cbl,.CBL,.cob,.COB,%s}", - directory, library, this->source, this->extensions) ) { + if( -1 == asprintf(&pattern, "%s{,.cpy,.CPY,.cbl,.CBL,.cob,.COB,%s}", + path, this->extensions) ) { err(EXIT_FAILURE, "could not create glob pattern"); } } else { - if( -1 == asprintf(&pattern, "%s/%s/%s{,.cpy,.CPY,.cbl,.CBL,.cob,.COB}", - directory, library, this->source) ) { + if( -1 == asprintf(&pattern, "%s{,.cpy,.CPY,.cbl,.CBL,.cob,.COB}", + path) ) { err(EXIT_FAILURE, "could not create glob pattern"); } } @@ -313,12 +335,18 @@ copybook_elem_t::open_file( const char directory[], bool literally ) { for( size_t i=0; i < globber.gl_pathc; i++ ) { auto filename = globber.gl_pathv[i]; if( (this->fd = open(filename, O_RDONLY)) != -1 ) { - this->source = realpath(filename, NULL); if( yydebug ) { warnx("found copybook file %s", filename); } - if( ! cobol_filename(this->source) ) { - yyerrorv("recursive copybook: '%s' includes itself", basename(strdup(filename))); + this->source = strdup(filename); + if( ! this->source ) { + yyerrorv("could not allocate memory for copybook name %s: %s", + filename, strerror(errno)); + (void)! close(fd); + fd = -1; + } + if( ! cobol_filename(this->source, inode_of(fd)) ) { + yyerrorv("recursive copybook: '%s' includes itself", this->source); (void)! close(fd); fd = -1; } diff --git a/gcc/cobol/cdf_text.h b/gcc/cobol/cdf_text.h index f6f8f739d23f0d9f0375e95cf2267f1a038d40ba..aae8c138f7fe81fb133ab2b624338da401c75cf9 100644 --- a/gcc/cobol/cdf_text.h +++ b/gcc/cobol/cdf_text.h @@ -110,6 +110,15 @@ cdftext::echo_input( int input, const char filename[] ) { } } +static inline ino_t +inode_of( int fd ) { + struct stat sb; + if( -1 == fstat(fd, &sb) ) { + err(EXIT_FAILURE, "could not stat fd %d", fd); + } + return sb.st_ino; +} + FILE * cdftext::lex_open( const char filename[] ) { int input = open_input( filename ); @@ -117,7 +126,7 @@ cdftext::lex_open( const char filename[] ) { int output = open_output(); filespan_t mfile( free_form_reference_format( input ) ); - cobol_filename(filename); + cobol_filename(filename, inode_of(input)); process_file( mfile, output ); if( lexer_echo() ) { @@ -405,6 +414,7 @@ const char * cobol_filename_restore(); */ void cdftext::process_file( filespan_t mfile, int output, bool second_pass ) { + static size_t nfiles = 0; std::list<replace_t> replacements; __gnu_cxx::stdio_filebuf<char> outbuf(fdopen(output, "w"), std::ios::out); @@ -414,7 +424,7 @@ cdftext::process_file( filespan_t mfile, int output, bool second_pass ) { // indicate current file static const char file_push[] = "\f#FILE PUSH ", file_pop[] = "\f#FILE POP\f"; - if( !second_pass ) { + if( !second_pass && nfiles++ ) { static const char delimiter[] = "\f"; const char *filename = cobol_filename(); std::copy(file_push, file_push + strlen(file_push), ofs); diff --git a/gcc/cobol/copybook.h b/gcc/cobol/copybook.h index e33e3edef379df134377a98fc4f9b2929ccdcdb4..7e3d071f15820e7caa5b2825f2603e5555e4a229 100644 --- a/gcc/cobol/copybook.h +++ b/gcc/cobol/copybook.h @@ -47,7 +47,7 @@ FILE * copy_mode_start(); const char * cobol_filename(); -bool cobol_filename( const char *name ); +bool cobol_filename( const char *name, ino_t inode ); void scanner_lexing( int token, bool tf ); void scanner_lexing_toggle(); diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h index ecbf2525242311cdf79fd685abb12ac6a10255fd..69df1b259e776edeb34ac0882e8236eed43d065f 100644 --- a/gcc/cobol/parse_ante.h +++ b/gcc/cobol/parse_ante.h @@ -58,8 +58,9 @@ yyerror( char const *s, int error_level = LOG_ERR) { fflush(stdout); if( yychar == 0 ) { // strictly YYEOF, but not defined here - fprintf( stderr, "%s:%d: %s detected at end of file\n", - cobol_filename(), yylineno, s); + const char *where = yylineno == 1? "" : " detected at end of file"; + fprintf( stderr, "%s:%d: %s%s\n", + cobol_filename(), yylineno, s, where); return; } diff --git a/gcc/cobol/scan.l b/gcc/cobol/scan.l index 4cee696d4eff1fb8c4557efcf859cf2bd0ec891f..8670e6ca907d388656626cc3344d00482fde31b4 100644 --- a/gcc/cobol/scan.l +++ b/gcc/cobol/scan.l @@ -1888,7 +1888,7 @@ COPY { assert(name != NULL); name[yyleng - 1] = '\0'; // kill the trailing formfeed name = name + 12; - cobol_filename(name); + cobol_filename(name, 0); if( yy_flex_debug ) warnx(" starting line %4d of %s", yylineno, name); } {POP_FILE} { diff --git a/gcc/cobol/util.cc b/gcc/cobol/util.cc index 02da3160d9593b37b5f13c842c6c4350af621f00..6ec4ee5afc8a5d36c121c658befb84c9df2533b1 100644 --- a/gcc/cobol/util.cc +++ b/gcc/cobol/util.cc @@ -1909,18 +1909,24 @@ date_time_fmt( const char input[] ) { #include <stack> struct input_file_t { + ino_t inode; int lineno; const char *name; - input_file_t( const char *name, int lineno=1 ) : lineno(lineno), name(name) {} + input_file_t( const char *name, ino_t inode, int lineno=1 ) + : inode(inode), lineno(lineno), name(name) + {} bool operator==( const input_file_t& that ) const { - return 0 == strcmp(name, that.name); + return inode == that.inode; } }; class unique_stack : public std::stack<input_file_t> { public: bool push( const value_type& value ) { - auto p = std::find( c.cbegin(), c.cend(), value ); - if( p == c.cend() ) { + auto ok = std::none_of( c.cbegin(), c.cend(), + [value]( auto& that ) { + return value == that; + } ); + if( ok ) { std::stack<input_file_t>::push(value); return true; } @@ -1933,7 +1939,7 @@ class unique_stack : public std::stack<input_file_t> "----- ---- --------" "----------------------------------------"); for( const auto& v : c ) { - warnx( " %4zu %4d %s", n--, v.lineno, no_wd(wd, v.name) ); + warnx( " %4zu %4d %s", c.size() - --n, v.lineno, no_wd(wd, v.name) ); } } return false; @@ -1948,9 +1954,21 @@ class unique_stack : public std::stack<input_file_t> }; static unique_stack input_filenames; - -bool cobol_filename( const char *name ) { - bool pushed = input_filenames.push(name); +static std::map<std::string, ino_t> old_filenames; + +bool cobol_filename( const char *name, ino_t inode ) { + if( inode == 0 ) { + auto p = old_filenames.find(name); + if( p == old_filenames.end() ) { + for( auto& elem : old_filenames ) { + warnx("%6zu %-30s", elem.second, elem.first.c_str()); + } + errx(EXIT_FAILURE, "logic error: missing inode for %s", name); + } + inode = p->second; + assert(inode != 0); + } + bool pushed = input_filenames.push( input_file_t(name, inode) ); input_filenames.top().lineno = yylineno = 1; if( getenv(__func__) ) { warnx(" saving %s with lineno as %d", @@ -1978,6 +1996,9 @@ cobol_filename() { const char * cobol_filename_restore() { assert(!input_filenames.empty()); + const input_file_t& top( input_filenames.top() ); + old_filenames[top.name] = top.inode; + input_filenames.pop(); if( input_filenames.empty() ) return NULL;