aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/coarray_poly_3.f90
diff options
context:
space:
mode:
authorBen Cheng <bccheng@google.com>2014-03-25 22:37:19 -0700
committerBen Cheng <bccheng@google.com>2014-03-25 22:37:19 -0700
commit1bc5aee63eb72b341f506ad058502cd0361f0d10 (patch)
treec607e8252f3405424ff15bc2d00aa38dadbb2518 /gcc-4.9/gcc/testsuite/gfortran.dg/coarray_poly_3.f90
parent283a0bf58fcf333c58a2a92c3ebbc41fb9eb1fdb (diff)
downloadtoolchain_gcc-1bc5aee63eb72b341f506ad058502cd0361f0d10.tar.gz
toolchain_gcc-1bc5aee63eb72b341f506ad058502cd0361f0d10.tar.bz2
toolchain_gcc-1bc5aee63eb72b341f506ad058502cd0361f0d10.zip
Initial checkin of GCC 4.9.0 from trunk (r208799).
Change-Id: I48a3c08bb98542aa215912a75f03c0890e497dba
Diffstat (limited to 'gcc-4.9/gcc/testsuite/gfortran.dg/coarray_poly_3.f90')
-rw-r--r--gcc-4.9/gcc/testsuite/gfortran.dg/coarray_poly_3.f90165
1 files changed, 165 insertions, 0 deletions
diff --git a/gcc-4.9/gcc/testsuite/gfortran.dg/coarray_poly_3.f90 b/gcc-4.9/gcc/testsuite/gfortran.dg/coarray_poly_3.f90
new file mode 100644
index 000000000..fd46206ea
--- /dev/null
+++ b/gcc-4.9/gcc/testsuite/gfortran.dg/coarray_poly_3.f90
@@ -0,0 +1,165 @@
+! { dg-do compile }
+! { dg-options "-fcoarray=single" }
+!
+
+
+subroutine cont1(x) ! { dg-error "has the CONTIGUOUS attribute but is not an array pointer or an assumed-shape or assumed-rank array" }
+ type t
+ end type t
+ class(t), contiguous, allocatable :: x(:)
+end
+
+subroutine cont2(x) ! { dg-error "has the CONTIGUOUS attribute but is not an array pointer or an assumed-shape or assumed-rank array" }
+ type t
+ end type t
+ class(t), contiguous, allocatable :: x(:)[:]
+end
+
+subroutine cont3(x, y)
+ type t
+ end type t
+ class(t), contiguous, pointer :: x(:)
+ class(t), contiguous :: y(:)
+end
+
+function func() ! { dg-error "shall not be a coarray or have a coarray component" }
+ type t
+ end type t
+ class(t), allocatable :: func[*]
+end
+
+function func2() ! { dg-error "must be dummy, allocatable or pointer" }
+ type t
+ integer, allocatable :: caf[:]
+ end type t
+ class(t) :: func2a ! { dg-error "CLASS variable 'func2a' at .1. must be dummy, allocatable or pointer" }
+ class(t) :: func2
+end
+
+subroutine foo1(x1) ! { dg-error "Coarray variable 'x1' at .1. shall not have codimensions with deferred shape" }
+ type t
+ end type t
+ type(t) :: x1(:)[:]
+end
+
+subroutine foo2(x2) ! { dg-error "Coarray variable 'x2' at .1. shall not have codimensions with deferred shape" }
+ type t
+ end type t
+ type(t) :: x2[:]
+end
+
+
+! DITTO FOR CLASS
+
+subroutine foo3(x1) ! { dg-error "Coarray variable 'x1' at .1. shall not have codimensions with deferred shape" }
+ type t
+ end type t
+ class(t) :: x1(:)[:]
+end
+
+subroutine foo4(x2) ! { dg-error "Coarray variable 'x2' at .1. shall not have codimensions with deferred shape" }
+ type t
+ end type t
+ class(t) :: x2[:]
+end
+
+
+
+
+subroutine bar1(y1) ! { dg-error "Allocatable coarray variable 'y1' at .1. must have deferred shape" }
+ type t
+ end type t
+ type(t), allocatable :: y1(:)[5:*]
+end
+
+subroutine bar2(y2) ! { dg-error "Allocatable coarray variable 'y2' at .1. must have deferred shape" }
+ type t
+ end type t
+ type(t), allocatable :: y2[5:*]
+end
+
+subroutine bar3(z1) ! { dg-error "Allocatable coarray variable 'z1' at .1. must have deferred shape" }
+ type t
+ end type t
+ type(t), allocatable :: z1(5)[:]
+end
+
+subroutine bar4(z2) ! { dg-error "Allocatable array 'z2' at .1. must have a deferred shape" }
+ type t
+ end type t
+ type(t), allocatable :: z2(5)
+end subroutine bar4
+
+subroutine bar5(z3) ! { dg-error "Array pointer 'z3' at .1. must have a deferred shape" }
+ type t
+ end type t
+ type(t), pointer :: z3(5)
+end subroutine bar5
+
+
+
+
+! DITTO FOR CLASS
+
+subroutine bar1c(y1) ! { dg-error "Allocatable coarray variable 'y1' at .1. must have deferred shape" }
+ type t
+ end type t
+ class(t), allocatable :: y1(:)[5:*]
+end
+
+subroutine bar2c(y2) ! { dg-error "Allocatable coarray variable 'y2' at .1. must have deferred shape" }
+ type t
+ end type t
+ class(t), allocatable :: y2[5:*]
+end
+
+subroutine bar3c(z1) ! { dg-error "Allocatable coarray variable 'z1' at .1. must have deferred shape" }
+ type t
+ end type t
+ class(t), allocatable :: z1(5)[:]
+end
+
+subroutine bar4c(z2) ! { dg-error "Allocatable array 'z2' at .1. must have a deferred shape" }
+ type t
+ end type t
+ class(t), allocatable :: z2(5)
+end subroutine bar4c
+
+subroutine bar5c(z3) ! { dg-error "Array pointer 'z3' at .1. must have a deferred shape" }
+ type t
+ end type t
+ class(t), pointer :: z3(5)
+end subroutine bar5c
+
+
+subroutine sub()
+ type t
+ end type
+ type(t) :: a(5)
+ class(t), allocatable :: b(:)
+ call inter(a)
+ call inter(b)
+contains
+ subroutine inter(x)
+ class(t) :: x(5)
+ end subroutine inter
+end subroutine sub
+
+subroutine sub2()
+ type t
+ end type
+ type(t) :: a(5)
+contains
+ subroutine inter(x)
+ class(t) :: x(5)
+ end subroutine inter
+end subroutine sub2
+
+subroutine sub3()
+ type t
+ end type
+contains
+ subroutine inter2(x) ! { dg-error "must have a deferred shape" }
+ class(t), pointer :: x(5)
+ end subroutine inter2
+end subroutine sub3