summaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran/pr66680.f90
diff options
context:
space:
mode:
authorbstarynk <bstarynk@138bc75d-0d04-0410-961f-82ee72b054a4>2016-04-16 17:02:56 +0000
committerbstarynk <bstarynk@138bc75d-0d04-0410-961f-82ee72b054a4>2016-04-16 17:02:56 +0000
commitc8aed844acdc89884d630c7e3266ecd8d4101847 (patch)
tree0d046a9255339220c1bbd6ba14e84e5304acbe10 /libgomp/testsuite/libgomp.fortran/pr66680.f90
parent74f8420a5b204c5e021ce05b3d0d79ba9718360a (diff)
downloadgcc-c8aed844acdc89884d630c7e3266ecd8d4101847.tar.gz
2016-04-16 Basile Starynkevitch <basile@starynkevitch.net>
{{merging with even more of GCC 6, using subversion 1.9 svn merge -r231651:232605 ^/trunk }} [gcc/] 2016-04-16 Basile Starynkevitch <basile@starynkevitch.net> * melt/libmelt-ana-gimple.melt: (melt_build_transaction_with_label_norm): New inlined function, for gimple_transaction operator implementation... git-svn-id: svn+ssh://gcc.gnu.org/svn/gcc/branches/melt-branch@235064 138bc75d-0d04-0410-961f-82ee72b054a4
Diffstat (limited to 'libgomp/testsuite/libgomp.fortran/pr66680.f90')
-rw-r--r--libgomp/testsuite/libgomp.fortran/pr66680.f9046
1 files changed, 46 insertions, 0 deletions
diff --git a/libgomp/testsuite/libgomp.fortran/pr66680.f90 b/libgomp/testsuite/libgomp.fortran/pr66680.f90
new file mode 100644
index 00000000000..b068cb3e890
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/pr66680.f90
@@ -0,0 +1,46 @@
+! { dg-do run }
+! PR 66680: ICE with openmp, a loop and a type bound procedure
+! Contributed by Miha Polajnar <polajnar.miha@gmail.com>
+!
+module m1
+ implicit none
+ integer :: n = 5
+ type :: t1
+ contains
+ procedure :: s => s1
+ end type t1
+contains
+ pure subroutine s1(self,p,esta)
+ class(t1), intent(in) :: self
+ integer, optional, intent(in) :: p
+ integer, intent(out) :: esta
+ end subroutine s1
+end module m1
+module m2
+ use m1, only: t1, n
+ implicit none
+ type(t1), allocatable :: test(:)
+contains
+ pure subroutine s2(test1,esta)
+ type(t1), intent(in) :: test1
+ integer, intent(out) :: esta
+ integer :: p, i
+ do p = 1, n
+ i = p ! using i instead of p works
+ call test1%s(p=p,esta=esta)
+ if ( esta /= 0 ) return
+ end do
+ end subroutine s2
+ subroutine s3()
+ integer :: i, esta
+ !$omp parallel do &
+ !$omp private(i)
+ do i = 1, n
+ call s2(test(i),esta)
+ end do
+ !$omp end parallel do
+ end subroutine s3
+end module m2
+program main
+ implicit none
+end program main