aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/class_array_4.f03
diff options
context:
space:
mode:
Diffstat (limited to 'gcc-4.9/gcc/testsuite/gfortran.dg/class_array_4.f03')
-rw-r--r--gcc-4.9/gcc/testsuite/gfortran.dg/class_array_4.f0325
1 files changed, 25 insertions, 0 deletions
diff --git a/gcc-4.9/gcc/testsuite/gfortran.dg/class_array_4.f03 b/gcc-4.9/gcc/testsuite/gfortran.dg/class_array_4.f03
new file mode 100644
index 000000000..46b254db6
--- /dev/null
+++ b/gcc-4.9/gcc/testsuite/gfortran.dg/class_array_4.f03
@@ -0,0 +1,25 @@
+! { dg-do run }
+! PR43214 - implementation of class arrays
+!
+! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
+!
+module m
+ type t
+ real :: r = 99
+ contains
+ procedure, pass :: foo => foo
+ end type t
+contains
+ elemental subroutine foo(x, i)
+ class(t),intent(in) :: x
+ integer,intent(inout) :: i
+ i = x%r + i
+ end subroutine foo
+end module m
+
+ use m
+ type(t) :: x(3)
+ integer :: n(3) = [0,100,200]
+ call x(:)%foo(n)
+ if (any(n .ne. [99,199,299])) call abort
+end