PR tree-optimization/86415 - strlen() not folded for substrings within constant arrays
[official-gcc.git] / gcc / testsuite / gfortran.dg / simplify_argN_1.f90
blob58fef33c444ed7a59d417b9f9d8135db4bd4aefa
1 ! { dg-do run }
2 ! Tests the fix for PR35780, in which the assignment for C was not
3 ! scalarized in expr.c.
5 ! Contributed by Dick Hendrickson <dick.hendrickson@gmail.com>
7 MODULE MODS
8 integer, parameter :: N = 10
9 INTEGER, PARAMETER, DIMENSION(N) :: A = [(i, i = 1, N)]
10 INTEGER, PARAMETER, DIMENSION(N) :: B = [(i - 5, i = 1, N)]
11 INTEGER, PARAMETER, DIMENSION(N) :: C = ISHFTC(3, B, 5) !ICE
12 INTEGER, PARAMETER, DIMENSION(N) :: D = ISHFTC(A, 3, 5) ! OK
13 INTEGER, PARAMETER, DIMENSION(N) :: E = ISHFTC(A, B, 5) ! OK
15 END MODULE MODS
17 use mods
18 integer, dimension(N) :: X = A
19 integer, dimension(N) :: Y = B
21 ! Check the simplifed expressions against the library
22 if (any (ISHFTC(3, Y, 5) /= C)) STOP 1
23 if (any (ISHFTC(X, 3, 5) /= D)) STOP 2
24 if (any (ISHFTC(X, Y, 5) /= E)) STOP 3
25 end