URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [subref_array_pointer_1.f90] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do run }! Test the fix for PRs29396, 29606, 30625 and 30871, in which pointers! to arrays with subreferences did not work.!call pr29396call pr29606call pr30625call pr30871containssubroutine pr29396! Contributed by Francois-Xavier Coudert <fxcoudert@gcc.gnu.org>CHARACTER(LEN=2), DIMENSION(:), POINTER :: aCHARACTER(LEN=4), DIMENSION(3), TARGET :: bb=(/"bbbb","bbbb","bbbb"/)a=>b(:)(2:3)a="aa"IF (ANY(b.NE.(/"baab","baab","baab"/))) CALL ABORT()END subroutinesubroutine pr29606! Contributed by Daniel Franke <franke.daniel@gmail.com>TYPE fooINTEGER :: valueEND TYPETYPE foo_arrayTYPE(foo), DIMENSION(:), POINTER :: arrayEND TYPETYPE(foo_array) :: array_holderINTEGER, DIMENSION(:), POINTER :: array_ptrALLOCATE( array_holder%array(3) )array_holder%array = (/ foo(1), foo(2), foo(3) /)array_ptr => array_holder%array%valueif (any (array_ptr .ne. (/1,2,3/))) call abort ()END subroutinesubroutine pr30625! Contributed by Paul Thomas <pault@gcc.gnu.org>type :: areal :: r = 3.14159integer :: i = 42end type atype(a), target :: dt(2)integer, pointer :: ip(:)ip => dt%iif (any (ip .ne. 42)) call abort ()end subroutinesubroutine pr30871! Contributed by Joost VandeVondele <jv244@cam.ac.uk>TYPE dataCHARACTER(LEN=3) :: AEND TYPETYPE(data), DIMENSION(10), TARGET :: ZCHARACTER(LEN=1), DIMENSION(:), POINTER :: ptrZ(:)%A="123"ptr=>Z(:)%A(2:2)if (any (ptr .ne. "2")) call abort ()END subroutineend
