https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88899

            Bug ID: 88899
           Summary: Derived type IO in conjunction with openmp fails with
                    invalid memory read
           Product: gcc
           Version: 9.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: mscfd at gmx dot net
  Target Milestone: ---

The code below fails with an invalid memory read. The derivated type IO
write(formatted) is declared but not used. Without this line the code runs
fine. Without the openmp loop it also runs fine.
Unfortunately, this bug makes derived type IO in parallelised code unusable.

module mod

implicit none
private

public work

type, public :: t
   real, dimension(:), allocatable :: r
contains
   procedure :: set
   generic :: assignment(=) => set

   ! comment out this write(formatted) declaration, and it runs fine
   generic :: write(formatted) => write_formatted
   procedure :: write_formatted
end type t

contains

subroutine work(a)
   class(t), intent(out) :: a
   a = [0.1, -0.3]
end subroutine work

subroutine set(self, r)
   class(t), intent(out) :: self
   real, dimension(:), intent(in) :: r
   self%r = r
end subroutine set

subroutine write_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
   class(t),              intent(in)    :: dtv
   integer,               intent(in)    :: unit
   character(len=*),      intent(in)    :: iotype
   integer, dimension(:), intent(in)    :: v_list
   integer,               intent(out)   :: iostat
   character(len=*),      intent(inout) :: iomsg
   write(unit, '(a)', iostat=iostat, iomsg=iomsg) 'formatted'
end subroutine write_formatted

end module mod


program dt_io

use mod
implicit none

type(t) :: x
integer :: i

!$omp parallel do default(shared) private(i, x)
do i = 1,1000000
   call work(x)
end do
!$omp end parallel do

end program dt_io

Reply via email to