URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [pointer_function_result_1.f90] - Rev 801
Go to most recent revision | Compare with Previous | Blame | View Log
! { dg-do run }! Test the fix for PR47844, in which the stride in the function result! was ignored. Previously, the result was [1,3] at lines 15 and 16.!! Contributed by KePu <Kdx1999@gmail.com>!PROGRAM test_pointer_valueIMPLICIT NONEINTEGER, DIMENSION(10), TARGET :: array= [1,3,5,7,9,11,13,15,17,19]INTEGER, dimension(2) :: array_fifthINTEGER, POINTER, DIMENSION(:) :: ptr_array => NULL()INTEGER, POINTER, DIMENSION(:) :: ptr_array_fifth => NULL()ptr_array => arrayarray_fifth = every_fifth (ptr_array)if (any (array_fifth .ne. [1,11])) call abortif (any (every_fifth(ptr_array) .ne. [1,11])) call abortCONTAINSFUNCTION every_fifth (ptr_array) RESULT (ptr_fifth)IMPLICIT NONEINTEGER, POINTER, DIMENSION(:) :: ptr_fifthINTEGER, POINTER, DIMENSION(:), INTENT(in) :: ptr_arrayINTEGER :: lowINTEGER :: highlow = LBOUND (ptr_array, 1)high = UBOUND (ptr_array, 1)ptr_fifth => ptr_array (low: high: 5)END FUNCTION every_fifthEND PROGRAM test_pointer_value
Go to most recent revision | Compare with Previous | Blame | View Log
