[Bug fortran/46356] New: Erroneous procedure/intent error and ICE for class dummy argument

ian_harvey at bigpond dot com gcc-bugzilla@gcc.gnu.org
Mon Nov 8 04:09:00 GMT 2010


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46356

           Summary: Erroneous procedure/intent error and ICE for class
                    dummy argument
           Product: gcc
           Version: 4.6.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: ian_harvey@bigpond.com


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.



More information about the Gcc-bugs mailing list