URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [class_array_1.f03] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do run }!! Test functionality of allocatable class arrays:! ALLOCATE with source, ALLOCATED, DEALLOCATE, passing as arguments for! ELEMENTAL and non-ELEMENTAL procedures, SELECT TYPE and LOWER/UPPER.!type :: type1integer :: iend typetype, extends(type1) :: type2real :: rend typeclass(type1), allocatable, dimension (:) :: xallocate(x(2), source = type2(42,42.0))call display(x, [1], [2], t2 = [type2(42,42.0),type2(42,42.0)])call display(x, [1], [2], t2 = [type2(111,99.0),type2(111,99.0)])if (allocated (x)) deallocate (x)allocate(x(1:4), source = [(type2(i,42.0 + float (i)), i = 1, 4)])call display(x, [1], [4], t2 = [(type2(i,42.0 + float (i)), i = 1, 4)])call display(x, [1], [4], t2 = [(type2(111,99.0), i = 1, 4)])if (any (disp (x) .ne. [99.0,99.0,99.0,99.0])) call abortif (allocated (x)) deallocate (x)allocate(x(1:4), source = type1(42))call display(x, [1], [4], t1 = [(type1(42), i = 1, 4)])call display(x, [1], [4], t1 = [type1(42),type1(99),type1(42),type1(42)])if (any (disp (x) .ne. [0.0,0.0,0.0,0.0])) call abortcontainssubroutine display(x, lower, upper, t1, t2)class(type1), allocatable, dimension (:) :: xinteger, dimension (:) :: lower, uppertype(type1), optional, dimension(:) :: t1type(type2), optional, dimension(:) :: t2select type (x)type is (type1)if (present (t1)) thenif (any (x%i .ne. t1%i)) call abortelsecall abortend ifx(2)%i = 99type is (type2)if (present (t2)) thenif (any (x%i .ne. t2%i)) call abortif (any (x%r .ne. t2%r)) call abortelsecall abortend ifx%i = 111x%r = 99.0end selectcall bounds (x, lower, upper)end subroutinesubroutine bounds (x, lower, upper)class(type1), allocatable, dimension (:) :: xinteger, dimension (:) :: lower, upperif (any (lower .ne. lbound (x))) call abortif (any (upper .ne. ubound (x))) call abortend subroutineelemental function disp(y) result(ans)class(type1), intent(in) :: yreal :: ansselect type (y)type is (type1)ans = 0.0type is (type2)ans = y%rend selectend functionend
