Commit 6479f45b by Andre Vehreschild

re PR fortran/77785 ([Coarray] ICE in gfc_get_caf_token_offset, at fortran/trans-expr.c:1990)

gcc/fortran/ChangeLog:

2016-12-13  Andre Vehreschild  <vehre@gcc.gnu.org>

	PR fortran/77785
	* resolve.c (resolve_symbol): Correct attr lookup to the _data
	component.
	* trans-array.c (gfc_alloc_allocatable_for_assignment): Indirect ref
	pointers and references before retrieving the caf-token.

gcc/testsuite/ChangeLog:

2016-12-13  Andre Vehreschild  <vehre@gcc.gnu.org>

	PR fortran/77785
	* gfortran.dg/coarray_38.f90: Added expecting error message.
	* gfortran.dg/coarray_41.f90: New test.
	* gfortran.dg/coarray_class_2.f90: New test.

From-SVN: r243614
parent b37a5b97
2016-12-13 Andre Vehreschild <vehre@gcc.gnu.org>
PR fortran/77785
* resolve.c (resolve_symbol): Correct attr lookup to the _data
component.
* trans-array.c (gfc_alloc_allocatable_for_assignment): Indirect ref
pointers and references before retrieving the caf-token.
2016-12-13 Janus Weil <janus@gcc.gnu.org>
Paul Thomas <pault@gcc.gnu.org>
......
......@@ -14044,8 +14044,8 @@ resolve_symbol (gfc_symbol *sym)
if (flag_coarray == GFC_FCOARRAY_LIB && sym->ts.type == BT_CLASS
&& sym->ts.u.derived && CLASS_DATA (sym)
&& CLASS_DATA (sym)->attr.codimension
&& (sym->ts.u.derived->attr.alloc_comp
|| sym->ts.u.derived->attr.pointer_comp))
&& (CLASS_DATA (sym)->ts.u.derived->attr.alloc_comp
|| CLASS_DATA (sym)->ts.u.derived->attr.pointer_comp))
{
gfc_error ("Sorry, allocatable/pointer components in polymorphic (CLASS) "
"type coarrays at %L are unsupported", &sym->declared_at);
......
......@@ -9337,6 +9337,8 @@ gfc_alloc_allocatable_for_assignment (gfc_loopinfo *loop,
if (token == NULL_TREE)
{
tmp = gfc_get_tree_for_caf_expr (expr1);
if (POINTER_TYPE_P (TREE_TYPE (tmp)))
tmp = build_fold_indirect_ref (tmp);
gfc_get_caf_token_offset (&caf_se, &token, NULL, tmp, NULL_TREE,
expr1);
token = gfc_build_addr_expr (NULL_TREE, token);
......
2016-12-13 Andre Vehreschild <vehre@gcc.gnu.org>
PR fortran/77785
* gfortran.dg/coarray_38.f90: Added expecting error message.
* gfortran.dg/coarray_41.f90: New test.
* gfortran.dg/coarray_class_2.f90: New test.
2016-12-13 Carl Love <cel@us.ibm.com>
* gcc.target/powerpc/builtins-3.c: Add new test of the test suite
......
......@@ -92,7 +92,7 @@ end type t
type t2
class(t), allocatable :: caf2[:]
end type t2
class(t), save, allocatable :: caf[:]
class(t), save, allocatable :: caf[:] ! { dg-error "Sorry, allocatable/pointer components in polymorphic" }
type(t) :: x
type(t2) :: y
......
! { dg-do run }
! { dg-options "-fcoarray=lib -lcaf_single" }
program coarray_41
integer, allocatable :: vec(:)[:,:]
allocate(vec(10)[2,*], source= 37)
if (.not. allocated(vec)) error stop
call foo(vec)
if (any(vec /= 42)) error stop
deallocate(vec)
contains
subroutine foo(gv)
integer, allocatable, intent(inout) :: gv(:)[:,:]
integer, allocatable :: gvin(:)
allocate(gvin, mold=gv)
gvin = 5
gv = gv + gvin
end subroutine foo
end program coarray_41
! { dg-do compile }
! { dg-options "-fcoarray=lib" }
! Check that error message is presented as long as polymorphic coarrays are
! not implemented.
module maccscal
type t
real, allocatable :: a
end type
contains
subroutine s(x) ! { dg-error "Sorry, allocatable/pointer components in polymorphic \\(CLASS\\)" }
class(t) :: x[*]
allocate (x%a)
end
end
module mptrscal
type t
real, pointer :: a
end type
contains
subroutine s(x) ! { dg-error "Sorry, allocatable/pointer components in polymorphic \\(CLASS\\)" }
class(t) :: x[*]
allocate (x%a)
end
end
module mallarr
type t
real, allocatable :: a(:)
end type
contains
subroutine s(x) ! { dg-error "Sorry, allocatable/pointer components in polymorphic \\(CLASS\\)" }
class(t) :: x[*]
allocate (x%a(2))
end
end
module mptrarr
type t
real, pointer :: a(:)
end type
contains
subroutine s(x) ! { dg-error "Sorry, allocatable/pointer components in polymorphic \\(CLASS\\)" }
class(t) :: x[*]
allocate (x%a(2))
end
end
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