mirror of
https://github.com/intel/llvm.git
synced 2026-01-26 03:56:16 +08:00
12.6.3p5 requires an I/O data list item to have a defined I/O procedure if it is polymorphic. (We could defer this checking to the runtime, but no other Fortran compiler does so, and we would also have to be able to catch the case of an allocatable or pointer direct component in the absence of a defined I/O subroutine.) Also includes a patch to name resolution that ensures that a SELECT TYPE construct entity is polymorphic in the domain of a CLASS IS guard. Also ensures that non-defined I/O of types with PRIVATE components is caught. Differential Revision: https://reviews.llvm.org/D139050
77 lines
2.0 KiB
Fortran
77 lines
2.0 KiB
Fortran
! RUN: %python %S/test_errors.py %s %flang_fc1
|
|
! Tests for I/O of derived types without defined I/O procedures
|
|
! but with exposed allocatable/pointer components that would fail
|
|
! at run time.
|
|
|
|
module m1
|
|
type :: poison
|
|
real, allocatable :: allocatableComponent(:)
|
|
end type
|
|
type :: ok
|
|
integer :: x
|
|
type(poison) :: pill
|
|
contains
|
|
procedure :: wuf1
|
|
generic :: write(unformatted) => wuf1
|
|
end type
|
|
type :: maybeBad
|
|
integer :: x
|
|
type(poison) :: pill
|
|
end type
|
|
contains
|
|
subroutine wuf1(dtv, unit, iostat, iomsg)
|
|
class(ok), intent(in) :: dtv
|
|
integer, intent(in) :: unit
|
|
integer, intent(out) :: iostat
|
|
character(*), intent(in out) :: iomsg
|
|
write(unit) dtv%x
|
|
end subroutine
|
|
end module
|
|
|
|
module m2
|
|
use m1
|
|
interface write(unformatted)
|
|
module procedure wuf2
|
|
end interface
|
|
contains
|
|
subroutine wuf2(dtv, unit, iostat, iomsg)
|
|
class(maybeBad), intent(in) :: dtv
|
|
integer, intent(in) :: unit
|
|
integer, intent(out) :: iostat
|
|
character(*), intent(in out) :: iomsg
|
|
write(unit) dtv%x
|
|
end subroutine
|
|
end module
|
|
|
|
module m3
|
|
use m1
|
|
contains
|
|
subroutine test3(u)
|
|
integer, intent(in) :: u
|
|
type(ok) :: x
|
|
type(maybeBad) :: y
|
|
type(poison) :: z
|
|
write(u) x ! always ok
|
|
!ERROR: Derived type 'maybebad' in I/O cannot have an allocatable or pointer direct component 'allocatablecomponent' unless using defined I/O
|
|
write(u) y ! bad here
|
|
!ERROR: Derived type 'poison' in I/O cannot have an allocatable or pointer direct component 'allocatablecomponent' unless using defined I/O
|
|
write(u) z ! bad
|
|
end subroutine
|
|
end module
|
|
|
|
module m4
|
|
use m2
|
|
contains
|
|
subroutine test4(u)
|
|
integer, intent(in) :: u
|
|
type(ok) :: x
|
|
type(maybeBad) :: y
|
|
type(poison) :: z
|
|
write(u) x ! always ok
|
|
write(u) y ! ok here
|
|
!ERROR: Derived type 'poison' in I/O cannot have an allocatable or pointer direct component 'allocatablecomponent' unless using defined I/O
|
|
write(u) z ! bad
|
|
end subroutine
|
|
end module
|
|
|