OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [coarray_12.f90] - Blame information for rev 715

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do compile }
2
! { dg-options "-fcoarray=single -fdump-tree-original" }
3
!
4
! Coarray support -- allocatable array coarrays
5
! PR fortran/18918
6
!
7
integer,allocatable :: a(:)[:,:]
8
nn = 5
9
mm = 7
10
allocate(a(nn)[mm,*])
11
end
12
 
13
subroutine testAlloc3
14
  implicit none
15
  integer, allocatable :: ab(:,:,:)[:,:]
16
  integer, allocatable, dimension(:),codimension[:] :: b(:,:,:)[:,:]
17
  integer, allocatable, dimension(:,:),codimension[:,:,:] :: c
18
  integer, allocatable, dimension(:,:),codimension[:,:,:] :: d[:,:]
19
  integer, allocatable, dimension(:,:,:),codimension[:,:,:] :: e(:,:)
20
  integer, allocatable, dimension(:,:,:),codimension[:,:,:] :: f(:,:)[:,:]
21
 
22
  allocate(ab(1,2,3)[4,*])
23
  allocate(b(1,2,3)[4,*])
24
  allocate(c(1,2)[3,4,*])
25
  allocate(d(1,2)[3,*])
26
  allocate(e(1,2)[3,4,*])
27
  allocate(f(1,2)[3,*])
28
end subroutine testAlloc3
29
 
30
subroutine testAlloc4()
31
  implicit none
32
  integer, allocatable :: xxx(:)[:,:,:,:]
33
  integer :: mmm
34
  mmm=88
35
  allocate(xxx(1)[7,-5:8,mmm:2,*])
36
end subroutine testAlloc4
37
 
38
subroutine testAlloc5()
39
  implicit none
40
  integer, allocatable :: yyy(:)[:,:,:,:]
41
  integer :: ooo, ppp
42
  ooo=88
43
  ppp=42
44
  allocate(yyy(1)[7,-5:ppp,1,ooo:*])
45
end subroutine testAlloc5
46
 
47
 
48
! { dg-final { scan-tree-dump-times "a.dim.0..lbound = 1;"     1 "original" } }
49
! { dg-final { scan-tree-dump-times "a.dim.0..ubound = .*nn;" 1 "original" } }
50
! { dg-final { scan-tree-dump-times "a.dim.1..lbound = 1;"     1 "original" } }
51
! { dg-final { scan-tree-dump-times "a.dim.1..ubound = .*mm;" 1 "original" } }
52
! { dg-final { scan-tree-dump-times "a.dim.2..lbound = 1;"     1 "original" } }
53
! { dg-final { scan-tree-dump-times "a.dim.2..ubound"          0 "original" } }
54
 
55
! { dg-final { scan-tree-dump-times "xxx.dim.0..lbound = 1;"     1 "original" } }
56
! { dg-final { scan-tree-dump-times "xxx.dim.0..ubound = 1;"     1 "original" } }
57
! { dg-final { scan-tree-dump-times "xxx.dim.1..lbound = 1;"     1 "original" } }
58
! { dg-final { scan-tree-dump-times "xxx.dim.1..ubound = 7;"     1 "original" } }
59
! { dg-final { scan-tree-dump-times "xxx.dim.2..lbound = -5;"    1 "original" } }
60
! { dg-final { scan-tree-dump-times "xxx.dim.2..ubound = 8;"     1 "original" } }
61
! { dg-final { scan-tree-dump-times "xxx.dim.3..lbound = .*mmm;" 1 "original" } }
62
! { dg-final { scan-tree-dump-times "xxx.dim.3..ubound = 2;"     1 "original" } }
63
! { dg-final { scan-tree-dump-times "xxx.dim.4..lbound = 1;"     1 "original" } }
64
! { dg-final { scan-tree-dump-times "xxx.dim.4..ubound"          0 "original" } }
65
 
66
! { dg-final { scan-tree-dump-times "yyy.dim.0..lbound = 1;"     1 "original" } }
67
! { dg-final { scan-tree-dump-times "yyy.dim.0..ubound = 1;"     1 "original" } }
68
! { dg-final { scan-tree-dump-times "yyy.dim.1..lbound = 1;"     1 "original" } }
69
! { dg-final { scan-tree-dump-times "yyy.dim.1..ubound = 7;"     1 "original" } }
70
! { dg-final { scan-tree-dump-times "yyy.dim.2..lbound = -5;"    1 "original" } }
71
! { dg-final { scan-tree-dump-times "yyy.dim.2..ubound = .*ppp;" 1 "original" } }
72
! { dg-final { scan-tree-dump-times "yyy.dim.3..lbound = 1;"     1 "original" } }
73
! { dg-final { scan-tree-dump-times "yyy.dim.3..ubound = 1;"     1 "original" } }
74
! { dg-final { scan-tree-dump-times "yyy.dim.4..lbound = .*ooo;" 1 "original" } }
75
! { dg-final { scan-tree-dump-times "yyy.dim.4..ubound"          0 "original" } }
76
 
77
! { dg-final { cleanup-tree-dump "original" } }

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.