Hi all,
The attached patch fixes this issue by moving the DTIO namelist checks from
namelist resolution to READ/WRITE statement resolution. This allows the checks
to be specific to the io_kind. The dtio_procs_present function is moved and
modified to accept the io_kind as an argument and check for the specific DTIO
procedure.
The original dtio_procs_present function also had a segfault for one of the test
cases because in the particular case the accessed structures do not exist. This
is prevented by adding the appropriate guarding to avoid memory accesses to
never never land.
Several new test cases added. Regression tested on x86-64.
OK for trunk. I would like to recommend back porting to 7 after allowing some
time for testing.
Regards,
Jerry
2017-05-11 Jerry DeLisle <jvdeli...@gcc.gnu.org>
PR fortran/78659
* io.c (dtio_procs_present): Add new function to check for DTIO
procedures relative to I/O statement READ or WRITE.
(gfc_resolve_dt): Add namelist checks using the new function.
* resolve.c (dtio_procs_present): Remove function and related
namelist checks. (resolve_fl_namelist): Add check specific to
Fortran 95 restriction on namelist objects.
! { dg-do compile }
! PR78659 Spurious "requires DTIO" reported against namelist statement
program p
type t
integer :: k
end type
class(t), allocatable :: x
namelist /nml/ x
end
! { dg-do compile }
! PR78659 Spurious "requires DTIO" reported against namelist statement
MODULE ma
IMPLICIT NONE
TYPE :: ta
INTEGER, allocatable :: array(:)
END TYPE ta
END MODULE ma
PROGRAM p
USE ma
type(ta):: x
NAMELIST /nml/ x
WRITE (*, nml) ! { dg-error "has ALLOCATABLE or POINTER components and thus requires a defined input/output" }
READ (*, nml) ! { dg-error "has ALLOCATABLE or POINTER components and thus requires a defined input/output" }
END PROGRAM p
! { dg-do compile }
! PR78659 Spurious "requires DTIO" reported against namelist statement
MODULE ma
IMPLICIT NONE
TYPE :: ta
INTEGER, allocatable :: array(:)
END TYPE ta
END MODULE ma
PROGRAM p
USE ma
class(ta), allocatable :: x
NAMELIST /nml/ x
WRITE (*, nml)! { dg-error "is polymorphic and requires a defined input/output procedure" }
READ (*, nml) ! { dg-error "is polymorphic and requires a defined input/output procedure" }
END PROGRAM p
! { dg-do compile }
! PR78659 Spurious "requires DTIO" reported against namelist statement
MODULE m
IMPLICIT NONE
TYPE :: t
CHARACTER :: c
CONTAINS
PROCEDURE :: write_formatted
GENERIC :: WRITE(FORMATTED) => write_formatted
END TYPE
CONTAINS
SUBROUTINE write_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
CLASS(t), INTENT(IN) :: dtv
INTEGER, INTENT(IN) :: unit
CHARACTER(*), INTENT(IN) :: iotype
INTEGER, INTENT(IN) :: v_list(:)
INTEGER, INTENT(OUT) :: iostat
CHARACTER(*), INTENT(INOUT) :: iomsg
WRITE (unit, "(A)", IOSTAT=iostat, IOMSG=iomsg) dtv%c
print *, "what"
END SUBROUTINE
END MODULE
PROGRAM p
USE m
IMPLICIT NONE
class(t), allocatable :: x
NAMELIST /nml/ x
x = t('a')
WRITE (*, nml)
READ (*, nml) ! { dg-error "is polymorphic and requires a defined input/output procedure" }
END