[to-be-committed] [RISC-V] Use Zbkb for general 64 bit constants when profitable
[official-gcc.git] / gcc / testsuite / gfortran.dg / internal_pack_4.f90
blob9de09ab072b5440fad63ba32e13792e1cdbc8d07
1 ! { dg-do run }
3 ! PR fortran/36132
5 ! Before invalid memory was accessed because an absent, optional
6 ! argument was packed before passing it as absent actual.
7 ! Getting it to crash is difficult, but valgrind shows the problem.
9 MODULE M1
10 INTEGER, PARAMETER :: dp=KIND(0.0D0)
11 CONTAINS
12 SUBROUTINE S1(a)
13 REAL(dp), DIMENSION(45), INTENT(OUT), &
14 OPTIONAL :: a
15 if (present(a)) STOP 1
16 END SUBROUTINE S1
17 SUBROUTINE S2(a)
18 REAL(dp), DIMENSION(:, :), INTENT(OUT), &
19 OPTIONAL :: a
20 CALL S1(a)
21 END SUBROUTINE
22 END MODULE M1
24 USE M1
25 CALL S2()
26 END