From 7f72e40263afd8d3e651a1a4ec3d5da9bc8eedd7 Mon Sep 17 00:00:00 2001 From: Jerry DeLisle <jvdelisle@gcc.gnu.org> Date: Wed, 17 May 2017 20:33:20 +0000 Subject: [PATCH] re PR fortran/80741 ([Regression 7/8] DTIO wrong code causes incorrect behaviour of namelist READ) 2017-05-17 Jerry DeLisle <jvdelisle@gcc.gnu.org> PR libgfortran/80741 * transfer.c (finalize_transfer): Reset last_char to 'empty'. * file_pos.c (formatted_backspace): Likewise. (st_endfile): Likewise. (st_rewind): Likewise. (st_flush): Likewise. PR fortran/80741 * trans-io.c (transfer_namelist_element): Change check from NULL_TREE to null_pointer_node. From-SVN: r248170 --- gcc/fortran/ChangeLog | 6 +++++ gcc/fortran/trans-io.c | 2 +- gcc/testsuite/gfortran.dg/read_4.f90 | 35 ++++++++++++++++++++++++++++ libgfortran/ChangeLog | 9 +++++++ libgfortran/io/file_pos.c | 6 ++++- libgfortran/io/transfer.c | 2 +- 6 files changed, 57 insertions(+), 3 deletions(-) create mode 100644 gcc/testsuite/gfortran.dg/read_4.f90 diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog index e978f32b8be7..703060d32ab7 100644 --- a/gcc/fortran/ChangeLog +++ b/gcc/fortran/ChangeLog @@ -1,3 +1,9 @@ +2017-05-17 Jerry DeLisle <jvdelisle@gcc.gnu.org> + + PR fortran/80741 + * trans-io.c (transfer_namelist_element): Change check from + NULL_TREE to null_pointer_node. + 2017-05-17 Fritz Reese <fritzoreese@gmail.com> PR fortran/80668 diff --git a/gcc/fortran/trans-io.c b/gcc/fortran/trans-io.c index 1b70136f4935..c557c1140d82 100644 --- a/gcc/fortran/trans-io.c +++ b/gcc/fortran/trans-io.c @@ -1756,7 +1756,7 @@ transfer_namelist_element (stmtblock_t * block, const char * var_name, else tmp = build_int_cst (gfc_charlen_type_node, 0); - if (dtio_proc == NULL_TREE) + if (dtio_proc == null_pointer_node) tmp = build_call_expr_loc (input_location, iocall[IOCALL_SET_NML_VAL], 6, dt_parm_addr, addr_expr, string, diff --git a/gcc/testsuite/gfortran.dg/read_4.f90 b/gcc/testsuite/gfortran.dg/read_4.f90 new file mode 100644 index 000000000000..7a835b124af4 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/read_4.f90 @@ -0,0 +1,35 @@ +! { dg-do run } +! PR80741 wrong code causes incorrect behaviour of namelist READ +program p + use, intrinsic :: iso_fortran_env, only: iostat_end + implicit none + integer :: x, y, ios, io + character(10) :: line + namelist /test/ x, y + + x = 10 + y = 10 + ios = 0 + io = 10 + open(unit=io, status='scratch') + write(io, test) + write(io, *) 'done' + rewind(io) + x = 0 + y = 0 + read(io, test) + if (x.ne.10 .or. y.ne.10) call abort + ! + read(io, *) line + if (line.ne.'done') call abort + ! + read(io, *, iostat=ios) line + if (ios/=iostat_end) call abort + rewind(io) + x = 0 + y = 0 + read(io, test) + if (x.ne.10 .or. y.ne.10) call abort + read(io, *, iostat=ios) line + if (line.ne.'done') call abort +end diff --git a/libgfortran/ChangeLog b/libgfortran/ChangeLog index b604147ffee2..7fe527dda3e3 100644 --- a/libgfortran/ChangeLog +++ b/libgfortran/ChangeLog @@ -1,3 +1,12 @@ +2017-05-17 Jerry DeLisle <jvdelisle@gcc.gnu.org> + + PR libgfortran/80741 + * transfer.c (finalize_transfer): Reset last_char to 'empty'. + * file_pos.c (formatted_backspace): Likewise. + (st_endfile): Likewise. + (st_rewind): Likewise. + (st_flush): Likewise. + 2017-05-15 Jerry DeLisle <jvdelisle@gcc.gnu.org> PR libgfortran/80727 diff --git a/libgfortran/io/file_pos.c b/libgfortran/io/file_pos.c index 5af9619bf465..771d548ea1d9 100644 --- a/libgfortran/io/file_pos.c +++ b/libgfortran/io/file_pos.c @@ -82,7 +82,7 @@ formatted_backspace (st_parameter_filepos *fpp, gfc_unit *u) goto io_error; u->last_record--; u->endfile = NO_ENDFILE; - + u->last_char = EOF - 1; return; io_error: @@ -322,6 +322,7 @@ st_endfile (st_parameter_filepos *fpp) unit_truncate (u, stell (u->s), &fpp->common); u->endfile = AFTER_ENDFILE; + u->last_char = EOF - 1; if (0 == stell (u->s)) u->flags.position = POSITION_REWIND; } @@ -371,6 +372,7 @@ st_endfile (st_parameter_filepos *fpp) if (u == NULL) return; u->endfile = AFTER_ENDFILE; + u->last_char = EOF - 1; } } @@ -430,6 +432,7 @@ st_rewind (st_parameter_filepos *fpp) u->current_record = 0; u->strm_pos = 1; u->read_bad = 0; + u->last_char = EOF - 1; } /* Update position for INQUIRE. */ u->flags.position = POSITION_REWIND; @@ -458,6 +461,7 @@ st_flush (st_parameter_filepos *fpp) fbuf_flush (u, u->mode); sflush (u->s); + u->last_char = EOF - 1; unlock_unit (u); } else diff --git a/libgfortran/io/transfer.c b/libgfortran/io/transfer.c index 928a448f74cf..298b29e8d3ef 100644 --- a/libgfortran/io/transfer.c +++ b/libgfortran/io/transfer.c @@ -3977,7 +3977,7 @@ finalize_transfer (st_parameter_dt *dtp) fbuf_seek (dtp->u.p.current_unit, 0, SEEK_END); dtp->u.p.current_unit->saved_pos = 0; - + dtp->u.p.current_unit->last_char = EOF - 1; next_record (dtp, 1); done: -- GitLab