da9ad92397
2007-12-10 Tobias Burnus <burnus@net-b.de> PR fortran/34425 * interface.c (get_expr_storage_size): Use signed integer when obtaining the bounds. 2007-12-10 Tobias Burnus <burnus@net-b.de> PR fortran/34425 * gfortran.dg/argument_checking_10.f90: New. From-SVN: r130752
17 lines
310 B
Fortran
17 lines
310 B
Fortran
! { dg-do compile }
|
|
!
|
|
! PR fortran/34425
|
|
!
|
|
! Contributed by Joost VandeVondele
|
|
!
|
|
IMPLICIT NONE
|
|
INTEGER :: i(-1:1)
|
|
INTEGER :: j(-2:-1)
|
|
CALL S(i)
|
|
CALL S(j) ! { dg-warning "Actual argument contains too few elements for dummy argument 'i' .2/3." }
|
|
CONTAINS
|
|
SUBROUTINE S(i)
|
|
INTEGER :: i(0:2)
|
|
END SUBROUTINE
|
|
END
|