aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/pointer_function_result_1.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc-4.9/gcc/testsuite/gfortran.dg/pointer_function_result_1.f90')
-rw-r--r--gcc-4.9/gcc/testsuite/gfortran.dg/pointer_function_result_1.f9028
1 files changed, 28 insertions, 0 deletions
diff --git a/gcc-4.9/gcc/testsuite/gfortran.dg/pointer_function_result_1.f90 b/gcc-4.9/gcc/testsuite/gfortran.dg/pointer_function_result_1.f90
new file mode 100644
index 000000000..764a666be
--- /dev/null
+++ b/gcc-4.9/gcc/testsuite/gfortran.dg/pointer_function_result_1.f90
@@ -0,0 +1,28 @@
+! { 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_value
+ IMPLICIT NONE
+ INTEGER, DIMENSION(10), TARGET :: array= [1,3,5,7,9,11,13,15,17,19]
+ INTEGER, dimension(2) :: array_fifth
+ INTEGER, POINTER, DIMENSION(:) :: ptr_array => NULL()
+ INTEGER, POINTER, DIMENSION(:) :: ptr_array_fifth => NULL()
+ ptr_array => array
+ array_fifth = every_fifth (ptr_array)
+ if (any (array_fifth .ne. [1,11])) call abort
+ if (any (every_fifth(ptr_array) .ne. [1,11])) call abort
+CONTAINS
+ FUNCTION every_fifth (ptr_array) RESULT (ptr_fifth)
+ IMPLICIT NONE
+ INTEGER, POINTER, DIMENSION(:) :: ptr_fifth
+ INTEGER, POINTER, DIMENSION(:), INTENT(in) :: ptr_array
+ INTEGER :: low
+ INTEGER :: high
+ low = LBOUND (ptr_array, 1)
+ high = UBOUND (ptr_array, 1)
+ ptr_fifth => ptr_array (low: high: 5)
+ END FUNCTION every_fifth
+END PROGRAM test_pointer_value