URL
https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [internal_pack_4.f90] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do run }! { dg-options "-fdump-tree-original" }!! PR fortran/36132!! Before invalid memory was accessed because an absent, optional! argument was packed before passing it as absent actual.! Getting it to crash is difficult, but valgrind shows the problem.!MODULE M1INTEGER, PARAMETER :: dp=KIND(0.0D0)CONTAINSSUBROUTINE S1(a)REAL(dp), DIMENSION(45), INTENT(OUT), &OPTIONAL :: aif (present(a)) call abort()END SUBROUTINE S1SUBROUTINE S2(a)REAL(dp), DIMENSION(:, :), INTENT(OUT), &OPTIONAL :: aCALL S1(a)END SUBROUTINEEND MODULE M1USE M1CALL S2()END! { dg-final { scan-tree-dump-times "a != 0B \\? \\\(.*\\\) _gfortran_internal_pack" 1 "original" } }! { dg-final { scan-tree-dump-times "if \\(a != 0B &&" 1 "original" } }! { dg-final { cleanup-tree-dump "original" } }
