diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog index ad04007c119f9e5d263ca8902371c3353a6219c0..c79242d9dd5cce9d31a4ef1e743be79fb6b1cb8e 100644 --- a/gcc/fortran/ChangeLog +++ b/gcc/fortran/ChangeLog @@ -1,3 +1,9 @@ +2007-09-18 Francois-Xavier Coudert <fxcoudert@gcc.gnu.org> + + PR fortran/31119 + * trans-array.c (gfc_conv_ss_startstride): Only perform bounds + checking for optional args when they are present. + 2007-09-18 Tobias Burnus <burnus@net-b.de> PR fortran/33231 diff --git a/gcc/fortran/trans-array.c b/gcc/fortran/trans-array.c index 1e02b81167fafd2b068a68d7facb1fc31898a303..64a62dbd018d62be050f2f0bd9721414c375ff03 100644 --- a/gcc/fortran/trans-array.c +++ b/gcc/fortran/trans-array.c @@ -2993,8 +2993,22 @@ gfc_conv_ss_startstride (gfc_loopinfo * loop) others against this. */ if (size[n]) { - tree tmp3 - = fold_build2 (NE_EXPR, boolean_type_node, tmp, size[n]); + tree tmp3; + + tmp3 = fold_build2 (NE_EXPR, boolean_type_node, tmp, size[n]); + + /* For optional arguments, only check bounds if the + argument is present. */ + if (ss->expr->symtree->n.sym->attr.optional + || ss->expr->symtree->n.sym->attr.not_always_present) + { + tree cond; + + cond = gfc_conv_expr_present (ss->expr->symtree->n.sym); + tmp3 = fold_build2 (TRUTH_AND_EXPR, boolean_type_node, + cond, tmp3); + } + asprintf (&msg, "%s, size mismatch for dimension %d " "of array '%s' (%%ld/%%ld)", gfc_msg_bounds, info->dim[n]+1, ss->expr->symtree->name); diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog index 5043613375e409b5e36b368634027e29ad3a529c..b0e1b9fa6cd1ce8f37825dac85cb400feca76af9 100644 --- a/gcc/testsuite/ChangeLog +++ b/gcc/testsuite/ChangeLog @@ -1,3 +1,9 @@ +2007-09-18 Francois-Xavier Coudert <fxcoudert@gcc.gnu.org> + + PR fortran/31119 + * gfortran.dg/bounds_check_9.f90: New test. + * gfortran.dg/bounds_check_fail_2.f90: New test. + 2007-09-18 Paolo Carlini <pcarlini@suse.de> PR c++/33462 (again) diff --git a/gcc/testsuite/gfortran.dg/bounds_check_9.f90 b/gcc/testsuite/gfortran.dg/bounds_check_9.f90 new file mode 100644 index 0000000000000000000000000000000000000000..c0abd2896ece95821dc844fce39eacd977be29c7 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/bounds_check_9.f90 @@ -0,0 +1,36 @@ +! { dg-do run } +! { dg-options "-fbounds-check" } +! PR fortran/31119 +! +module sub_mod +contains +elemental subroutine set_optional(i,idef,iopt) + integer, intent(out) :: i + integer, intent(in) :: idef + integer, intent(in), optional :: iopt + if (present(iopt)) then + i = iopt + else + i = idef + end if + end subroutine set_optional + + subroutine sub(ivec) + integer, intent(in), optional :: ivec(:) + integer :: ivec_(2) + call set_optional(ivec_,(/1,2/)) + if (any (ivec_ /= (/1, 2/))) call abort + call set_optional(ivec_,(/1,2/),ivec) + if (present (ivec)) then + if (any (ivec_ /= ivec)) call abort + else + if (any (ivec_ /= (/1, 2/))) call abort + end if + end subroutine sub +end module sub_mod + +program main + use sub_mod, only: sub + call sub() + call sub((/4,5/)) +end program main diff --git a/gcc/testsuite/gfortran.dg/bounds_check_fail_2.f90 b/gcc/testsuite/gfortran.dg/bounds_check_fail_2.f90 new file mode 100644 index 0000000000000000000000000000000000000000..bb2c247bf311c683706094bb51580c735ef57a1f --- /dev/null +++ b/gcc/testsuite/gfortran.dg/bounds_check_fail_2.f90 @@ -0,0 +1,39 @@ +! { dg-do run } +! { dg-options "-fbounds-check" } +! { dg-shouldfail "foo" } +! +! PR 31119 +module sub_mod +contains + elemental subroutine set_optional(i,idef,iopt) + integer, intent(out) :: i + integer, intent(in) :: idef + integer, intent(in), optional :: iopt + if (present(iopt)) then + i = iopt + else + i = idef + end if + end subroutine set_optional + + subroutine sub(ivec) + integer , intent(in), optional :: ivec(:) + integer :: ivec_(2) + call set_optional(ivec_,(/1,2/)) + if (any (ivec_ /= (/1,2/))) call abort + call set_optional(ivec_,(/1,2/),ivec) + if (present (ivec)) then + if (any (ivec_ /= ivec)) call abort + else + if (any (ivec_ /= (/1,2/))) call abort + end if + end subroutine sub +end module sub_mod + +program main + use sub_mod, only: sub + call sub() + call sub((/4,5/)) + call sub((/4/)) +end program main +! { dg-output "Fortran runtime error: Array bound mismatch" }