view gcc/testsuite/gfortran.dg/gomp/pr52531.f90 @ 152:2b5abeee2509

update gcc11
author anatofuz
date Mon, 25 May 2020 07:50:57 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
! PR fortran/52531
module test_mod
  type, public :: test_type
  end type
contains
  subroutine foo(bar)
    type(test_type) :: bar
!$omp parallel default(none) shared(bar) ! Compiles if one removes default(none)
    call question(bar)
!$omp end parallel
  end subroutine
  subroutine question(var)
    class(test_type), intent(in) :: var ! Compiles if one replaces class by type
  end subroutine
end module