Plugins: Add label-text.h to CPPLIB_H so it will be installed [PR115288]
[official-gcc.git] / gcc / testsuite / gfortran.dg / elemental_dependency_1.f90
blobdbf05d4bc0ea6140830b3f63b420e347eb997082
1 ! { dg-do run }
2 ! { dg-options "-fdump-tree-original" }
4 ! PR fortran/35681
5 ! Test the use of temporaries in case of elemental subroutines.
7 PROGRAM main
8 IMPLICIT NONE
9 INTEGER, PARAMETER :: sz = 5
10 INTEGER :: i
11 INTEGER :: a(sz) = (/ (i, i=1,sz) /)
12 INTEGER :: b(sz)
14 b = a
15 CALL double(a(sz-b+1), a) ! { dg-warning "might interfere with actual" }
16 ! Don't check the result, as the above is invalid
17 ! and might produce unexpected results (overlapping vector subscripts).
20 b = a
21 CALL double (a, a) ! same range, no temporary
22 IF (ANY(a /= 2*b)) STOP 1
25 b = a
26 CALL double (a+1, a) ! same range, no temporary
27 IF (ANY(a /= 2*b+2)) STOP 2
30 b = a
31 CALL double ((a(1:sz)), a(1:sz)) ! same range, no temporary
32 IF (ANY(a /= 2*b)) STOP 3
35 b = a
36 CALL double(a(1:sz-1), a(2:sz)) ! { dg-warning "might interfere with actual" }
37 ! Don't check the result, as the above is invalid,
38 ! and might produce unexpected results (arguments overlap).
41 b = a
42 CALL double((a(1:sz-1)), a(2:sz)) ! paren expression, temporary created
43 ! { dg-final { scan-tree-dump-times "A\.16\\\[4\\\]" 1 "original" } }
45 IF (ANY(a /= (/ b(1), (2*b(i), i=1,sz-1) /))) STOP 4
48 b = a
49 CALL double(a(1:sz-1)+1, a(2:sz)) ! op expression, temporary created
50 ! { dg-final { scan-tree-dump-times "A\.25\\\[4\\\]" 1 "original" } }
52 IF (ANY(a /= (/ b(1), (2*b(i)+2, i=1,sz-1) /))) STOP 5
55 b = a
56 CALL double(self(a), a) ! same range, no temporary
57 IF (ANY(a /= 2*b)) STOP 6
60 b = a
61 CALL double(self(a(1:sz-1)), a(2:sz)) ! function expr, temporary created
62 ! { dg-final { scan-tree-dump-times "A\.37\\\[4\\\]" 1 "original" } }
64 IF (ANY(a /= (/ b(1), (2*b(i), i=1,sz-1) /))) STOP 7
67 CONTAINS
68 ELEMENTAL SUBROUTINE double(a, b)
69 IMPLICIT NONE
70 INTEGER, INTENT(IN) :: a
71 INTEGER, INTENT(OUT) :: b
72 b = 2 * a
73 END SUBROUTINE double
74 ELEMENTAL FUNCTION self(a)
75 IMPLICIT NONE
76 INTEGER, INTENT(IN) :: a
77 INTEGER :: self
78 self = a
79 END FUNCTION self
80 END PROGRAM main
82 ! { dg-final { scan-tree-dump-times "_gfortran_internal_unpack" 3 "original" } }