re PR fortran/32880 (User operator & allocatable TYPE components: wrong deallocate)
2007-07-28 Paul Thomas <pault@gcc.gnu.org> PR fortran/32880 * trans-expr.c (gfc_trans_scalar_assign): Revert to fixed order for lse and rse pre expressions, for derived types with allocatable components. Instead, assign the lhs to a temporary and deallocate after the assignment. 2007-07-28 Paul Thomas <pault@gcc.gnu.org> PR fortran/32880 * gfortran.dg/alloc_comp_assign_6.f90: New test. From-SVN: r127011
This commit is contained in:
parent
9587952bbf
commit
b8247b1389
@ -1,3 +1,11 @@
|
||||
2007-07-28 Paul Thomas <pault@gcc.gnu.org>
|
||||
|
||||
PR fortran/32880
|
||||
* trans-expr.c (gfc_trans_scalar_assign): Revert to fixed order
|
||||
for lse and rse pre expressions, for derived types with
|
||||
allocatable components. Instead, assign the lhs to a temporary
|
||||
and deallocate after the assignment.
|
||||
|
||||
2007-07-28 Janne Blomqvist <jb@gcc.gnu.org>
|
||||
|
||||
PR fortran/32909
|
||||
|
@ -3512,25 +3512,20 @@ gfc_trans_scalar_assign (gfc_se * lse, gfc_se * rse, gfc_typespec ts,
|
||||
}
|
||||
|
||||
/* Deallocate the lhs allocated components as long as it is not
|
||||
the same as the rhs. */
|
||||
the same as the rhs. This must be done following the assignment
|
||||
to prevent deallocating data that could be used in the rhs
|
||||
expression. */
|
||||
if (!l_is_temp)
|
||||
{
|
||||
tmp = gfc_deallocate_alloc_comp (ts.derived, lse->expr, 0);
|
||||
tmp = gfc_evaluate_now (lse->expr, &lse->pre);
|
||||
tmp = gfc_deallocate_alloc_comp (ts.derived, tmp, 0);
|
||||
if (r_is_var)
|
||||
tmp = build3_v (COND_EXPR, cond, build_empty_stmt (), tmp);
|
||||
gfc_add_expr_to_block (&lse->pre, tmp);
|
||||
gfc_add_expr_to_block (&lse->post, tmp);
|
||||
}
|
||||
|
||||
if (r_is_var)
|
||||
{
|
||||
gfc_add_block_to_block (&block, &lse->pre);
|
||||
gfc_add_block_to_block (&block, &rse->pre);
|
||||
}
|
||||
else
|
||||
{
|
||||
gfc_add_block_to_block (&block, &rse->pre);
|
||||
gfc_add_block_to_block (&block, &lse->pre);
|
||||
}
|
||||
gfc_add_block_to_block (&block, &rse->pre);
|
||||
gfc_add_block_to_block (&block, &lse->pre);
|
||||
|
||||
gfc_add_modify_expr (&block, lse->expr,
|
||||
fold_convert (TREE_TYPE (lse->expr), rse->expr));
|
||||
|
@ -1,3 +1,8 @@
|
||||
2007-07-28 Paul Thomas <pault@gcc.gnu.org>
|
||||
|
||||
PR fortran/32880
|
||||
* gfortran.dg/alloc_comp_assign_6.f90: New tests.
|
||||
|
||||
2007-07-28 Rask Ingemann Lambertsen <rask@sygehus.dk>
|
||||
|
||||
PR testsuite/32471
|
||||
|
55
gcc/testsuite/gfortran.dg/alloc_comp_assign_6.f90
Normal file
55
gcc/testsuite/gfortran.dg/alloc_comp_assign_6.f90
Normal file
@ -0,0 +1,55 @@
|
||||
! { dg-do run }
|
||||
! Tests the fix for pr32880, in which 'res' was deallocated
|
||||
! before it could be used in the concatenation.
|
||||
! Adapted from vst28.f95, in Lawrie Schonfeld's iso_varying_string
|
||||
! testsuite, by Tobias Burnus.
|
||||
!
|
||||
module iso_varying_string
|
||||
type varying_string
|
||||
character(LEN=1), dimension(:), allocatable :: chars
|
||||
end type varying_string
|
||||
interface assignment(=)
|
||||
module procedure op_assign_VS_CH
|
||||
end interface assignment(=)
|
||||
interface operator(//)
|
||||
module procedure op_concat_VS_CH
|
||||
end interface operator(//)
|
||||
contains
|
||||
elemental subroutine op_assign_VS_CH (var, exp)
|
||||
type(varying_string), intent(out) :: var
|
||||
character(LEN=*), intent(in) :: exp
|
||||
integer :: length
|
||||
integer :: i_char
|
||||
length = len(exp)
|
||||
allocate(var%chars(length))
|
||||
forall(i_char = 1:length)
|
||||
var%chars(i_char) = exp(i_char:i_char)
|
||||
end forall
|
||||
end subroutine op_assign_VS_CH
|
||||
elemental function op_concat_VS_CH (string_a, string_b) result (concat_string)
|
||||
type(varying_string), intent(in) :: string_a
|
||||
character(LEN=*), intent(in) :: string_b
|
||||
type(varying_string) :: concat_string
|
||||
len_string_a = size(string_a%chars)
|
||||
allocate(concat_string%chars(len_string_a+len(string_b)))
|
||||
if (len_string_a >0) &
|
||||
concat_string%chars(:len_string_a) = string_a%chars
|
||||
if (len (string_b) > 0) &
|
||||
concat_string%chars(len_string_a+1:) = string_b
|
||||
end function op_concat_VS_CH
|
||||
end module iso_varying_string
|
||||
|
||||
program VST28
|
||||
use iso_varying_string
|
||||
character(len=10) :: char_a
|
||||
type(VARYING_STRING) :: res
|
||||
char_a = "abcdefghij"
|
||||
res = char_a(5:5)
|
||||
res = res//char_a(6:6)
|
||||
if(size(res%chars) /= 2 .or. any(res%chars /= ['e','f'])) then
|
||||
write(*,*) 'ERROR: should be ef, got: ', res%chars, size(res%chars)
|
||||
call abort ()
|
||||
end if
|
||||
end program VST28
|
||||
|
||||
! { dg-final { cleanup-modules "iso_varying_string" } }
|
Loading…
Reference in New Issue
Block a user