Bug 46356 - [OOP] Erroneous procedure/intent error and ICE for class dummy argument
Summary: [OOP] Erroneous procedure/intent error and ICE for class dummy argument
Status: RESOLVED FIXED
Alias: None
Product: gcc
Classification: Unclassified
Component: fortran (show other bugs)
Version: 4.6.0
: P3 normal
Target Milestone: 4.7.0
Assignee: Not yet assigned to anyone
URL:
Keywords: rejects-valid
Depends on:
Blocks: 51754
  Show dependency treegraph
 
Reported: 2010-11-08 04:09 UTC by Ian Harvey
Modified: 2016-11-16 14:06 UTC (History)
4 users (show)

See Also:
Host:
Target:
Build:
Known to work:
Known to fail:
Last reconfirmed: 2010-11-08 08:31:03


Attachments

Note You need to log in before you can comment on or make changes to this bug.
Description Ian Harvey 2010-11-08 04:09:21 UTC
The following example, when compiled with gfortran 4.6 built from trunk source 166232 (20101103), rejects the following code with a dubious errror (PROCEDURE attribute conflicts with INTENT attribute in 'pvec') before the compiler dies with an ICE.

I believe the code is valid F2003.  It, and the subsequent variations below, are accepted by ifort 11.1.067.  

MODULE procedure_intent_nonsense
  IMPLICIT NONE  
  PRIVATE    
  TYPE, PUBLIC :: Parent
    INTEGER :: comp
  END TYPE Parent
  
  TYPE :: ParentVector
    INTEGER :: a
    ! CLASS(Parent), ALLOCATABLE :: a
  END TYPE ParentVector  
CONTAINS           
  SUBROUTINE vector_operation(pvec)     
    CLASS(ParentVector), INTENT(INOUT) :: pvec(:)
    INTEGER :: i    
    !---
    DO i = 1, SIZE(pvec)
      CALL item_operation(pvec(i))
    END DO  
    ! PRINT *, pvec(1)%a%comp
  END SUBROUTINE vector_operation
  
  SUBROUTINE item_operation(pvec)  
    CLASS(ParentVector), INTENT(INOUT) :: pvec
    !TYPE(ParentVector), INTENT(INOUT) :: pvec
  END SUBROUTINE item_operation
END MODULE procedure_intent_nonsense

Variants, which may all be just the result of the compiler thinking the pvec argument is a procedure...

If the ParentVector component is switched to being the CLASS(Parent) component and the PRINT statement in vector_operation is uncommented, a syntax error that appears to be spurious is generated.

Alternatively, if the pvec dummy in item_option is changed to be non-polymorphic, then two additional errors appear and the ICE disappears.  

One of the additional errors is "'array' argument of 'size' intrinsic at (1) must be an array", referring to the SIZE intrinsic in the DO statement.  The argument to the SIZE intrinsic is an array, so this error is spurious.

The other additional error is that there is a type mismatch with the argument for in the CALL to item_operation (passed CLASS(...) to TYPE(...)).  I believe this is also spurious.
Comment 1 janus 2010-11-08 08:31:03 UTC
(In reply to comment #0)
> The following example, when compiled with gfortran 4.6 built from trunk source
> 166232 (20101103), rejects the following code with a dubious errror (PROCEDURE
> attribute conflicts with INTENT attribute in 'pvec') before the compiler dies
> with an ICE.

Confirmed. Thanks for reporting.
Comment 2 janus 2010-11-08 09:32:26 UTC
Reduced test case:

  IMPLICIT NONE

  TYPE :: ParentVector
    INTEGER :: a
  END TYPE ParentVector  

CONTAINS       
    
  SUBROUTINE vector_operation(pvec)     
    CLASS(ParentVector), INTENT(INOUT) :: pvec(:)
    print *,pvec(1)%a
  END SUBROUTINE

END


Note: This error is due to the fact that gfortran currently does not really support CLASS arrays (which hopefully will change soon).
Comment 3 Paul Thomas 2011-12-11 20:42:32 UTC
Author: pault
Date: Sun Dec 11 20:42:23 2011
New Revision: 182210

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=182210
Log:
2011-12-11  Paul Thomas  <pault@gcc.gnu.org>
	Tobias Burnus  <burnus@gcc.gnu.org>

	PR fortran/41539
	PR fortran/43214
	PR fortran/43969
	PR fortran/44568
	PR fortran/46356
	PR fortran/46990
	PR fortran/49074
	* interface.c(symbol_rank): Return the rank of the _data
	component of class objects.
	(compare_parameter): Also compare the derived type of the class
	_data component for type mismatch.  Similarly, return 1 if the
	formal and _data ranks match.
	(compare_actual_formal): Do not compare storage sizes for class
	expressions. It is an error if an actual class array, passed to
	a formal class array is not full.
	* trans-expr.c (gfc_class_data_get, gfc_class_vptr_get,
	gfc_vtable_field_get, gfc_vtable_hash_get, gfc_vtable_size_get,
	gfc_vtable_extends_get, gfc_vtable_def_init_get,
	gfc_vtable_copy_get): New functions for class API.
	(gfc_conv_derived_to_class): For an array reference in an
	elemental procedure call retain the ss to provide the
	scalarized array reference. Moved in file.
	(gfc_conv_class_to_class): New function.
        (gfc_conv_subref_array_arg): Use the type of the
	class _data component as a basetype.
	(gfc_conv_procedure_call): Ensure that class array expressions
	have both the _data reference and an array reference. Use 
	gfc_conv_class_to_class to handle class arrays for elemental
	functions in scalarized loops, class array elements and full
	class arrays. Use a call to gfc_conv_subref_array_arg in order
	that the copy-in/copy-out for passing class arrays to derived
	type arrays occurs correctly.
	(gfc_conv_expr): If it is missing, add the _data component
	between a class object or component and an array reference.
	(gfc_trans_class_array_init_assign): New function.
	(gfc_trans_class_init_assign): Call it for array expressions.
	* trans-array.c (gfc_add_loop_ss_code): Do not use a temp for
	class scalars since their size will depend on the dynamic type.
	(build_class_array_ref): New function.
	(gfc_conv_scalarized_array_ref): Call build_class_array_ref.
	(gfc_array_init_size): Add extra argument, expr3, that represents
	the SOURCE argument. If present,use this for the element size.
	(gfc_array_allocate): Also add argument expr3 and use it when
	calling gfc_array_init_size.
	(structure_alloc_comps): Enable class arrays.
	* class.c (gfc_add_component_ref): Carry over the derived type
	of the _data component.
	(gfc_add_class_array_ref): New function.
	(class_array_ref_detected): New static function.
	(gfc_is_class_array_ref): New function that calls previous.
	(gfc_is_class_scalar_expr): New function.
	(gfc_build_class_symbol): Throw not implemented error for
	assumed size class arrays.  Remove error that prevents
	CLASS arrays.
	(gfc_build_class_symbol): Prevent pointer/allocatable conflict.
	Also unset codimension.
	(gfc_find_derived_vtab): Make 'copy' elemental and set the
	intent of the arguments accordingly.: 
	* trans-array.h : Update prototype for gfc_array_allocate.
	* array.c (gfc_array_dimen_size): Return failure if class expr.
	(gfc_array_size): Likewise.
	* gfortran.h : New prototypes for gfc_add_class_array_ref,
	gfc_is_class_array_ref and gfc_is_class_scalar_expr.
	* trans-stmt.c (trans_associate_var): Exclude class targets
	from test. Move the allocation of the _vptr to an earlier time
	for class objects.
	(trans_associate_var): Assign the descriptor directly for class
	arrays.
	(gfc_trans_allocate): Add expr3 to gfc_array_allocate arguments.
	Convert array element references into sections. Do not invoke
	gfc_conv_procedure_call, use gfc_trans_call instead.
	* expr.c (gfc_get_corank): Fix for BT_CLASS.
	(gfc_is_simply_contiguous): Exclude class from test.
	* trans.c (gfc_build_array_ref): Include class array refs.
	* trans.h : Include prototypes for class API functions that are
	new in trans-expr. Define GFC_DECL_CLASS(node).
	* resolve.c (check_typebound_baseobject ): Remove error for
	non-scalar base object.
	(resolve_allocate_expr): Ensure that class _data component is
	present. If array, call gfc_expr_to_intialize.
	(resolve_select): Remove scalar error for SELECT statement as a
	temporary measure.
	(resolve_assoc_var): Update 'target' (aka 'selector') as
	needed. Ensure that the target expression has the right rank.
	(resolve_select_type): Ensure that target expressions have a
	valid locus.
	(resolve_allocate_expr, resolve_fl_derived0): Fix for BT_CLASS.
	* trans-decl.c (gfc_get_symbol_decl): Set GFC_DECL_CLASS, where
	appropriate.
	(gfc_trans_deferred_vars): Get class arrays right.
	* match.c(select_type_set_tmp): Add array spec to temporary.
	(gfc_match_select_type): Allow class arrays.
	* check.c (array_check): Ensure that class arrays have refs.
	(dim_corank_check, dim_rank_check): Retrun success if class.
	* primary.c (gfc_match_varspec): Fix for class arrays and
	co-arrays. Make sure that class _data is present.
	(gfc_match_rvalue): Handle class arrays.
	*trans-intrinsic.c (gfc_conv_intrinsic_size): Add class array
	reference.
	(gfc_conv_allocated): Add _data component to class expressions.
	(gfc_add_intrinsic_ss_code): ditto.
	* simplify.c (simplify_cobound): Fix for BT_CLASS.
	(simplify_bound): Return NULL for class arrays.
	(simplify_cobound): Obtain correct array_spec. Use cotype as
	appropriate. Use arrayspec for bounds.

2011-12-11  Paul Thomas  <pault@gcc.gnu.org>
	Tobias Burnus  <burnus@gcc.gnu.org>

	PR fortran/41539
	PR fortran/43214
	PR fortran/43969
	PR fortran/44568
	PR fortran/46356
	PR fortran/46990
	PR fortran/49074
	* gfortran.dg/class_array_1.f03: New.
	* gfortran.dg/class_array_2.f03: New.
	* gfortran.dg/class_array_3.f03: New.
	* gfortran.dg/class_array_4.f03: New.
	* gfortran.dg/class_array_5.f03: New.
	* gfortran.dg/class_array_6.f03: New.
	* gfortran.dg/class_array_7.f03: New.
	* gfortran.dg/class_array_8.f03: New.
	* gfortran.dg/coarray_poly_1.f90: New.
	* gfortran.dg/coarray_poly_2.f90: New.
	* gfortran.dg/coarray/poly_run_1.f90: New.
	* gfortran.dg/coarray/poly_run_2.f90: New.
	* gfortran.dg/class_to_type_1.f03: New.
	* gfortran.dg/type_to_class_1.f03: New.
	* gfortran.dg/typebound_assignment_3.f03: Remove the error.
	* gfortran.dg/auto_dealloc_2.f90: Occurences of __builtin_free
	now 2.
	* gfortran.dg/class_19.f03: Occurences of __builtin_free now 8.


Added:
    trunk/gcc/testsuite/gfortran.dg/class_array_1.f03
    trunk/gcc/testsuite/gfortran.dg/class_array_2.f03
    trunk/gcc/testsuite/gfortran.dg/class_array_3.f03
    trunk/gcc/testsuite/gfortran.dg/class_array_4.f03
    trunk/gcc/testsuite/gfortran.dg/class_array_5.f03
    trunk/gcc/testsuite/gfortran.dg/class_array_6.f03
    trunk/gcc/testsuite/gfortran.dg/class_array_7.f03
    trunk/gcc/testsuite/gfortran.dg/class_array_8.f03
    trunk/gcc/testsuite/gfortran.dg/class_to_type_1.f03
    trunk/gcc/testsuite/gfortran.dg/coarray/poly_run_1.f90
    trunk/gcc/testsuite/gfortran.dg/coarray/poly_run_2.f90
    trunk/gcc/testsuite/gfortran.dg/coarray_poly_1.f90
    trunk/gcc/testsuite/gfortran.dg/coarray_poly_2.f90
    trunk/gcc/testsuite/gfortran.dg/type_to_class_1.f03
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/array.c
    trunk/gcc/fortran/check.c
    trunk/gcc/fortran/class.c
    trunk/gcc/fortran/expr.c
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/interface.c
    trunk/gcc/fortran/match.c
    trunk/gcc/fortran/primary.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/simplify.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/fortran/trans-array.h
    trunk/gcc/fortran/trans-decl.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/fortran/trans-intrinsic.c
    trunk/gcc/fortran/trans-stmt.c
    trunk/gcc/fortran/trans.c
    trunk/gcc/fortran/trans.h
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/auto_dealloc_2.f90
    trunk/gcc/testsuite/gfortran.dg/class_19.f03
    trunk/gcc/testsuite/gfortran.dg/typebound_assignment_3.f03
Comment 4 Tobias Burnus 2011-12-12 08:17:55 UTC
The original test case of comment 0 is now fixed. However, the reduced one of comment 2 still fails with:
  internal compiler error: in gfc_conv_descriptor_offset, at fortran/trans-array.c:210
Comment 5 Tobias Burnus 2012-01-04 10:25:53 UTC
(In reply to comment #4)
> the reduced one of comment 2 still fails with:
>   internal compiler error: in gfc_conv_descriptor_offset, at
> fortran/trans-array.c:210

The same error message one gets with Andrew Benson's code, cf.
  http://gcc.gnu.org/ml/fortran/2012-01/msg00028.html
Comment 6 Tobias Burnus 2012-01-04 19:13:40 UTC
(In reply to comment #5)
> The same error message one gets with Andrew Benson's code, cf.
>   http://gcc.gnu.org/ml/fortran/2012-01/msg00028.html

That's now PR 51754
Comment 7 Mikael Morin 2012-02-02 23:11:00 UTC
Author: mikael
Date: Thu Feb  2 23:10:55 2012
New Revision: 183853

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=183853
Log:
2012-02-02  Mikael Morin  <mikael@gcc.gnu.org>

	PR fortran/41587
	PR fortran/46356
	PR fortran/51754
	PR fortran/50981
	* class.c (insert_component_ref, class_data_ref_missing,
	gfc_fix_class_refs): New functions.
	* gfortran.h (gfc_fix_class_refs): New prototype.
	* trans-expr.c (gfc_conv_expr): Remove special case handling and call
	gfc_fix_class_refs instead.

2012-02-02  Mikael Morin  <mikael@gcc.gnu.org>

	PR fortran/41587
	* gfortran.dg/class_array_10.f03: New test.

	PR fortran/46356
	* gfortran.dg/class_array_11.f03: New test.

	PR fortran/51754
	* gfortran.dg/class_array_12.f03: New test.


Added:
    trunk/gcc/testsuite/gfortran.dg/class_array_10.f03
    trunk/gcc/testsuite/gfortran.dg/class_array_11.f03
    trunk/gcc/testsuite/gfortran.dg/class_array_12.f03
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/class.c
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/testsuite/ChangeLog
Comment 8 Mikael Morin 2012-02-02 23:25:51 UTC
(In reply to comment #4)
> The original test case of comment 0 is now fixed. However, the reduced one of
> comment 2 still fails with:
>   internal compiler error: in gfc_conv_descriptor_offset, at
> fortran/trans-array.c:210

That one is now gone as well.