RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_collectives_18.f90
blobc83899de0e5bf3dc7577032ebc64796f70e099a6
1 ! { dg-do compile }
2 ! { dg-additional-options "-fdump-tree-original -fcoarray=lib" }
4 ! PR 103970
5 ! Test case inspired by code submitted by Damian Rousson
7 program main
9 implicit none
11 type foo_t
12 integer i
13 integer, allocatable :: j
14 end type
16 type(foo_t) foo
17 integer, parameter :: source_image = 1
19 if (this_image() == source_image) then
20 foo = foo_t(2,3)
21 else
22 allocate(foo%j)
23 end if
24 call co_broadcast(foo, source_image)
26 if ((foo%i /= 2) .or. (foo%j /= 3)) error stop 1
27 sync all
29 end program
31 ! Wrong code generation produced too many temp descriptors
32 ! leading to stacked descriptors handed to the co_broadcast.
33 ! This lead to access to non exsitant memory in opencoarrays.
34 ! In single image mode just checking for reduced number of
35 ! descriptors is possible, i.e., execute always works.
36 ! { dg-final { scan-tree-dump-times "desc\\.\[0-9\]+" 12 "original" } }