Commit a50ba82d by Francois-Xavier Coudert Committed by François-Xavier Coudert

re PR fortran/31119 (-fbounds-check: Check for presence of optional arguments…

re PR fortran/31119 (-fbounds-check: Check for presence of optional arguments before bound checking)

	PR fortran/31119

	* trans-array.c (gfc_conv_ss_startstride): Only perform bounds
	checking for optional args when they are present.

	* gfortran.dg/bounds_check_9.f90: New test.
	* gfortran.dg/bounds_check_fail_2.f90: New test.

From-SVN: r128587
parent bf962a2a
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
......
......@@ -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);
......
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)
! { 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
! { 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" }
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment