diff gcc/testsuite/gfortran.dg/pointer_function_result_1.f90 @ 111:04ced10e8804

gcc 7
author kono
date Fri, 27 Oct 2017 22:46:09 +0900
parents
children 84e7813d76e9
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/gcc/testsuite/gfortran.dg/pointer_function_result_1.f90	Fri Oct 27 22:46:09 2017 +0900
@@ -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