Commit 0126595f by Tobias Burnus Committed by Tobias Burnus

re PR fortran/48889 (f951: internal compiler error: in gfc_is_constant_expr, at fortran/expr.c:906)

2011-05-11  Tobias Burnus  <burnus@net-b.de>

        PR fortran/48889
        * expr.c (gfc_is_constant_expr): Use e->value.function.esym
        instead of e->symtree->n.sym, if available.

2011-05-11  Tobias Burnus  <burnus@net-b.de>

        PR fortran/48889
        * gfortran.dg/generic_24.f90: New.

From-SVN: r173674
parent 8da1c70b
2011-05-11 Tobias Burnus <burnus@net-b.de>
PR fortran/48889
* expr.c (gfc_is_constant_expr): Use e->value.function.esym
instead of e->symtree->n.sym, if available.
2011-05-07 Eric Botcazou <ebotcazou@adacore.com>
* f95-lang.c (global_bindings_p): Return bool and simplify.
......
......@@ -893,6 +893,9 @@ gfc_is_constant_expr (gfc_expr *e)
case EXPR_FUNCTION:
case EXPR_PPC:
case EXPR_COMPCALL:
gcc_assert (e->symtree || e->value.function.esym
|| e->value.function.isym);
/* Call to intrinsic with at least one argument. */
if (e->value.function.isym && e->value.function.actual)
{
......@@ -901,13 +904,14 @@ gfc_is_constant_expr (gfc_expr *e)
return 0;
}
/* Make sure we have a symbol. */
gcc_assert (e->symtree);
sym = e->symtree->n.sym;
/* Specification functions are constant. */
/* F95, 7.1.6.2; F2003, 7.1.7 */
sym = NULL;
if (e->symtree)
sym = e->symtree->n.sym;
if (e->value.function.esym)
sym = e->value.function.esym;
if (sym
&& sym->attr.function
&& sym->attr.pure
......
2011-05-11 Tobias Burnus <burnus@net-b.de>
PR fortran/48889
* gfortran.dg/generic_24.f90: New.
2011-05-11 Richard Guenther <rguenther@suse.de>
PR tree-optimization/15256
......
! { dg-do compile }
!
! PR fortran/48889
!
! Thanks for
! reporting to Lawrence Mitchell
! for the test case to David Ham
!
module sparse_tools
implicit none
private
type csr_foo
integer, dimension(:), pointer :: colm=>null()
end type csr_foo
type block_csr_matrix
type(csr_foo) :: sparsity
end type block_csr_matrix
interface attach_block
module procedure block_csr_attach_block
end interface
interface size
module procedure sparsity_size
end interface
public :: size, attach_block
contains
subroutine block_csr_attach_block(matrix, val)
type(block_csr_matrix), intent(inout) :: matrix
real, dimension(size(matrix%sparsity%colm)), intent(in), target :: val
end subroutine block_csr_attach_block
pure function sparsity_size(sparsity, dim)
integer :: sparsity_size
type(csr_foo), intent(in) :: sparsity
integer, optional, intent(in) :: dim
end function sparsity_size
end module sparse_tools
module global_numbering
use sparse_tools
implicit none
type ele_numbering_type
integer :: boundaries
end type ele_numbering_type
type element_type
integer :: loc
type(ele_numbering_type), pointer :: numbering=>null()
end type element_type
type csr_sparsity
end type csr_sparsity
interface size
module procedure sparsity_size
end interface size
contains
pure function sparsity_size(sparsity, dim)
integer :: sparsity_size
type(csr_sparsity), intent(in) :: sparsity
integer, optional, intent(in) :: dim
end function sparsity_size
subroutine make_boundary_numbering(EEList, xndglno, ele_n)
type(csr_sparsity), intent(in) :: EEList
type(element_type), intent(in) :: ele_n
integer, dimension(size(EEList,1)*ele_n%loc), intent(in), target ::&
& xndglno
integer, dimension(ele_n%numbering%boundaries) :: neigh
integer :: j
j=size(neigh)
end subroutine make_boundary_numbering
end module global_numbering
module sparse_matrices_fields
use sparse_tools
implicit none
type scalar_field
real, dimension(:), pointer :: val
end type scalar_field
contains
subroutine csr_mult_T_scalar(x)
type(scalar_field), intent(inout) :: x
real, dimension(:), allocatable :: tmp
integer :: i
i=size(x%val)
end subroutine csr_mult_T_scalar
end module sparse_matrices_fields
program test
use sparse_matrices_fields
use global_numbering
end program test
! { dg-final { cleanup-modules "sparse_tools sparse_matrices_fields global_numbering" } }
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