summaryrefslogtreecommitdiffstats
path: root/gcc/testsuite/gfortran.dg/coarray/poly_run_2.f90
blob: 02704dd7796069c1e03450e0842e726d6d6690cf (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
! { dg-do run }
!
! Test for polymorphic coarrays
!
type t
end type t
class(t), allocatable :: A[:,:]
allocate (A[1:4,-5:*])
if (allocated(A)) stop
if (any (lcobound(A) /= [1, -5])) call abort ()
if (num_images() == 1) then
  if (any (ucobound(A) /= [4, -5])) call abort ()
else
  if (ucobound(A,dim=1) /= 4) call abort ()
end if
if (allocated(A)) i = 5
call s(A)
call st(A)
contains
subroutine s(x)
  class(t) :: x[4,2:*]
  if (any (lcobound(x) /= [1, 2])) call abort ()
  if (num_images() == 1) then
    if (any (ucobound(x) /= [4, 2])) call abort ()
  else
    if (ucobound(x,dim=1) /= 4) call abort ()
  end if
end subroutine s
subroutine st(x)
  class(t) :: x[:,:]
  if (any (lcobound(x) /= [1, -5])) call abort ()
  if (num_images() == 1) then
    if (any (ucobound(x) /= [4, -5])) call abort ()
  else
    if (ucobound(x,dim=1) /= 4) call abort ()
  end if
end subroutine st
end

OpenPOWER on IntegriCloud