File tree Expand file tree Collapse file tree 2 files changed +48
-3
lines changed Expand file tree Collapse file tree 2 files changed +48
-3
lines changed Original file line number Diff line number Diff line change @@ -484,9 +484,15 @@ INT_CONSTANT {digit}+
484484 }
485485}
486486
487- "EXEC"[ ]+"SQL"[ ]+"INCLUDE" {
488- period = 0;
489- startlineno = yylineno;
487+ "EXEC"[ ]+"SQL"[ \r\n ]+"INCLUDE" {
488+ period = 0;
489+ int newlines = 0;
490+ for (char *p = yytext; *p != ' \0' ; p++) {
491+ if (*p == ' \n ' ) {
492+ newlines++;
493+ }
494+ }
495+ startlineno = yylineno - newlines;
490496 host_reference_list = NULL ;
491497 res_host_reference_list = NULL ;
492498 memset (dbname,0 ,sizeof (dbname));
Original file line number Diff line number Diff line change @@ -195,3 +195,42 @@ AT_CHECK([ocesql --inc=. prog.cbl prog.cob > /dev/null],[0])
195195AT_CHECK([diff prog.cob prog.txt], [0])
196196
197197AT_CLEANUP
198+
199+
200+ AT_SETUP([use include with newline])
201+
202+ AT_DATA([prog.cbl], [
203+ IDENTIFICATION DIVISION.
204+ ******************************************************************
205+ PROGRAM-ID. prog.
206+ ******************************************************************
207+ DATA DIVISION.
208+ ******************************************************************
209+ WORKING-STORAGE SECTION.
210+ EXEC SQL
211+ INCLUDE SQLCA
212+ END-EXEC.
213+ PROCEDURE DIVISION.
214+ STOP RUN.
215+ ])
216+
217+ AT_DATA([prog.txt], [
218+ IDENTIFICATION DIVISION.
219+ ******************************************************************
220+ PROGRAM-ID. prog.
221+ ******************************************************************
222+ DATA DIVISION.
223+ ******************************************************************
224+ WORKING-STORAGE SECTION.
225+ OCESQL*EXEC SQL
226+ OCESQL* INCLUDE SQLCA
227+ OCESQL*END-EXEC.
228+ OCESQL copy "sqlca.cbl".
229+ PROCEDURE DIVISION.
230+ STOP RUN.
231+ ])
232+
233+ AT_CHECK([ocesql prog.cbl prog.cob > /dev/null],[0])
234+ AT_CHECK([diff prog.cob prog.txt], [0])
235+
236+ AT_CLEANUP
You can’t perform that action at this time.
0 commit comments