arm: Add .type and .size to __gnu_cmse_nonsecure_call [PR115360]
[official-gcc.git] / gcc / testsuite / gfortran.dg / internal_pack_7.f90
blob1241510b814855ac7c75166465ea13c80aec139d
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
3 ! { dg-require-visibility "" }
5 ! Test the fix for PR43072, in which unnecessary calls to
6 ! internal PACK/UNPACK were being generated.
8 ! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
10 MODULE M1
11 PRIVATE
12 REAL, PARAMETER :: c(2)=(/(i,i=1,2)/)
13 CONTAINS
14 ! WAS OK
15 SUBROUTINE S0
16 real :: r
17 r=0
18 r=S2(c)
19 r=S2((/(real(i),i=1,2)/)) ! See comment #1 of the PR
20 END SUBROUTINE S0
21 ! WAS NOT OK
22 SUBROUTINE S1
23 real :: r
24 r=0
25 r=r+S2(c)
26 r=r+S2((/(real(i),i=1,2)/)) ! See comment #1 of the PR
27 END SUBROUTINE S1
29 FUNCTION S2(c)
30 REAL, INTENT(IN) :: c(2)
31 s2=0
32 END FUNCTION S2
33 END MODULE M1
34 ! { dg-final { scan-tree-dump-times "pack" 0 "original" } }