c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_stopped_images_1.f08
blob681e2a5f0aa7349bb5245445587e7366b16ef0f1
1 ! { dg-do run }
2 ! { dg-options "-fdump-tree-original -fcoarray=lib -lcaf_single" }
3 ! { dg-additional-options "-latomic" { target libatomic_available } }
5 program test_stopped_images_1
6   implicit none
8   integer :: me,np,stat
9   character(len=1) :: c
10   integer, allocatable :: si(:)
11   integer(kind=1), allocatable :: ssi(:)
13   si = stopped_images()
14   if (size(si) > 0) error stop "stopped_images result shall be empty array at 1"
15   if (allocated(si)) error stop "stopped_images result shall not be allocated at 1"
17   ssi = stopped_images(KIND=1)
18   if (size(ssi) > 0) error stop "stopped_images result shall be empty array at 2"
19   if (allocated(ssi)) error stop "stopped_images result shall not be allocated at 2"
21   ssi = stopped_images(KIND=8)
22   if (size(ssi) > 0) error stop "stopped_images result shall be empty array at 3"
23 ! The implicit type conversion in the assignment above allocates an array. 
24 !  if (allocated(ssi)) error stop "stopped_images result shall not be allocated at 3"
25   
26 end program test_stopped_images_1
28 ! { dg-final { scan-tree-dump-times "_gfortran_caf_stopped_images \\\(&D\\\.\[0-9\]+, 0B, 0B\\\);" 1 "original" } }
29 ! { dg-final { scan-tree-dump-times "_gfortran_caf_stopped_images \\\(&D\\\.\[0-9\]+, 0B, D\\\.\[0-9\]+\\\);" 1 "original" } }
30 ! { dg-final { scan-tree-dump-times "_gfortran_caf_stopped_images \\\(&D\\\.\[0-9\]+, 0B, D\\\.\[0-9\]+\\\);" 1 "original" } }