aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/class_to_type_1.f03
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/class_to_type_1.f03
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/class_to_type_1.f03')
-rw-r--r--gcc-4.9/gcc/testsuite/gfortran.dg/class_to_type_1.f0397
1 files changed, 97 insertions, 0 deletions
diff --git a/gcc-4.9/gcc/testsuite/gfortran.dg/class_to_type_1.f03 b/gcc-4.9/gcc/testsuite/gfortran.dg/class_to_type_1.f03
new file mode 100644
index 000000000..0243343d6
--- /dev/null
+++ b/gcc-4.9/gcc/testsuite/gfortran.dg/class_to_type_1.f03
@@ -0,0 +1,97 @@
+! { dg-do run }
+!
+! Passing CLASS to TYPE
+!
+implicit none
+type t
+ integer :: A
+ real, allocatable :: B(:)
+end type t
+
+type, extends(t) :: t2
+ complex :: z = cmplx(3.3, 4.4)
+end type t2
+integer :: i
+class(t), allocatable :: x(:)
+
+allocate(t2 :: x(10))
+select type(x)
+ type is(t2)
+ if (size (x) /= 10) call abort ()
+ x = [(t2(a=-i, B=[1*i,2*i,3*i,4*i]), i = 1, 10)]
+ do i = 1, 10
+ if (x(i)%a /= -i .or. size (x(i)%b) /= 4 &
+ .or. any (x(i)%b /= [1*i,2*i,3*i,4*i])) then
+ call abort()
+ end if
+ if (x(i)%z /= cmplx(3.3, 4.4)) call abort()
+ end do
+ class default
+ call abort()
+end select
+
+call base(x)
+call baseExplicit(x, size(x))
+call class(x)
+call classExplicit(x, size(x))
+contains
+ subroutine base(y)
+ type(t) :: y(:)
+ if (size (y) /= 10) call abort ()
+ do i = 1, 10
+ if (y(i)%a /= -i .or. size (y(i)%b) /= 4 &
+ .or. any (y(i)%b /= [1*i,2*i,3*i,4*i])) then
+ call abort()
+ end if
+ end do
+ end subroutine base
+ subroutine baseExplicit(v, n)
+ integer, intent(in) :: n
+ type(t) :: v(n)
+ if (size (v) /= 10) call abort ()
+ do i = 1, 10
+ if (v(i)%a /= -i .or. size (v(i)%b) /= 4 &
+ .or. any (v(i)%b /= [1*i,2*i,3*i,4*i])) then
+ call abort()
+ end if
+ end do
+ end subroutine baseExplicit
+ subroutine class(z)
+ class(t), intent(in) :: z(:)
+ select type(z)
+ type is(t2)
+ if (size (z) /= 10) call abort ()
+ do i = 1, 10
+ if (z(i)%a /= -i .or. size (z(i)%b) /= 4 &
+ .or. any (z(i)%b /= [1*i,2*i,3*i,4*i])) then
+ call abort()
+ end if
+ if (z(i)%z /= cmplx(3.3, 4.4)) call abort()
+ end do
+ class default
+ call abort()
+ end select
+ call base(z)
+ call baseExplicit(z, size(z))
+ end subroutine class
+ subroutine classExplicit(u, n)
+ integer, intent(in) :: n
+ class(t), intent(in) :: u(n)
+ select type(u)
+ type is(t2)
+ if (size (u) /= 10) call abort ()
+ do i = 1, 10
+ if (u(i)%a /= -i .or. size (u(i)%b) /= 4 &
+ .or. any (u(i)%b /= [1*i,2*i,3*i,4*i])) then
+ call abort()
+ end if
+ if (u(i)%z /= cmplx(3.3, 4.4)) call abort()
+ end do
+ class default
+ call abort()
+ end select
+ call base(u)
+ call baseExplicit(u, n)
+ end subroutine classExplicit
+end
+