Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
Announcements
FPGA community forums and blogs on community.intel.com are migrating to the new Altera Community and are read-only. For urgent support needs during this transition, please visit the FPGA Design Resources page or contact an Altera Authorized Distributor.
29285 Discussions

Superfluous GENERIC OPERATOR specification in extended derived type generated no errors or warnings

FortranFan
Honored Contributor III
1,105 Views

Dear Steve et al. at Intel,

Can you please review the code shown below and check whether it is ok to have a superfluous GENERIC OPERATOR specification in an extended derived type that is simply a copy of one in the abstract parent?  See lines 17 and 47 in the code snippet, a heavily simplified version of my actual type.

This code compiles without any errors or warnings in Intel Fortran XE 2013, Update 1 even if standards checking is turned on.

However, gfortran 4.9 flags an error saying the two procedures for the + operator are ambiguous.

It looks ok to me even though in my actual code, the specification in the child was just by accident, I have no need for it, and I've since removed it. But if gfortran is correct, it will help to get Intel Fortran to generate some sort of error or a warning.

Since a few other trouble incidents have come up recently in connection with resolution of ambiguous references in GENERIC statements in extended derived types, this example may possibly be of interest to your developers. If appropriate, please attach this to one or more of those tracking incidents.

Thanks much.

[fortran]

   MODULE m

 

      IMPLICIT NONE

 

      !..

      PRIVATE

 

      !.. Mnemonic constants

      INTEGER, PARAMETER, PUBLIC :: IMISS = -9999

 

      TYPE, ABSTRACT, PUBLIC :: p

         PRIVATE

      CONTAINS

         PRIVATE

         PROCEDURE(IAdd_p), PASS(Lhs), DEFERRED   :: Add_p

         PROCEDURE(IInit_p), PASS(This), DEFERRED, PUBLIC :: Init

         GENERIC, PUBLIC :: OPERATOR(+) => Add_p

      END TYPE p

 

      ABSTRACT INTERFACE

 

         PURE ELEMENTAL FUNCTION IAdd_p(Lhs, Rhs) RESULT(LhsPlusRhs)

            IMPORT :: p

            !.. Argument list

            CLASS(p), INTENT(IN)  :: Lhs

            CLASS(p), INTENT(IN)  :: Rhs

            !.. Function result

            CLASS(p), ALLOCATABLE :: LhsPlusRhs

         END FUNCTION IAdd_p

 

         PURE ELEMENTAL SUBROUTINE IInit_p(This, InitVal)

            IMPORT :: p

            !.. Argument list

            CLASS(p), INTENT(INOUT) :: This

            INTEGER, INTENT(IN)     :: InitVal

         END SUBROUTINE IInit_p

 

      END INTERFACE

 

      TYPE, EXTENDS(p), PUBLIC :: c

         PRIVATE

         INTEGER :: foo

      CONTAINS

         PRIVATE

         PROCEDURE, PASS(Lhs) :: Add_p => Add_c

         PROCEDURE, PASS(This), PUBLIC :: Init => Init_c

         GENERIC, PUBLIC :: OPERATOR(+) => Add_p

      END TYPE c

 

   CONTAINS

 

      PURE ELEMENTAL FUNCTION Add_c(Lhs, Rhs) RESULT(LhsPlusRhs)

 

         !.. Argument list

         CLASS(c), INTENT(IN)  :: Lhs

         CLASS(p), INTENT(IN)  :: Rhs

         !.. Function result

         CLASS(p), ALLOCATABLE :: LhsPlusRhs

 

         !.. Local variables

         INTEGER :: Istat

         TYPE(c), ALLOCATABLE :: NewChild

 

         !..

         ALLOCATE(NewChild, SOURCE=Lhs, STAT=Istat)

         IF (Istat /= 0) THEN

            ALLOCATE( c :: LhsPlusRhs, STAT=Istat)

            IF (Istat == 0) THEN

               CALL LhsPlusRhs%Init(IMISS)

            END IF

            !.. Insert error handling here

            RETURN

         END IF

 

         SELECT TYPE(Rhs)

            CLASS IS (c)

               NewChild%foo = Lhs%foo + Rhs%foo

            CLASS DEFAULT

               !.. Not yet supported

               NewChild%foo = IMISS

         END SELECT

 

         !..

         CALL MOVE_ALLOC( NewChild, LhsPlusRhs )

 

         !..

         RETURN

 

      END FUNCTION Add_c

 

      PURE ELEMENTAL SUBROUTINE Init_c(This, InitVal)

 

         !.. Argument list

         CLASS(c), INTENT(INOUT) :: This

         INTEGER, INTENT(IN)     :: InitVal

 

         !..

         This%foo = InitVal

 

         RETURN

 

      END SUBROUTINE Init_c

 

   END MODULE m

[/fortran]

0 Kudos
9 Replies
Steven_L_Intel1
Employee
1,105 Views

I can't identify any text in the standard forbidding this usage. You should ask the gfortran folks what the basis for the error is.

0 Kudos
FortranFan
Honored Contributor III
1,105 Views

Thanks Steve for taking a look.  Will do as you suggest.

0 Kudos
Steven_L_Intel1
Employee
1,105 Views

I tried gfortran - it complains:

$ gfortran U508187.f90
U508187.f90:47.42:

         GENERIC, PUBLIC :: OPERATOR(+) => Add_p
                                          1
Error: 'add_c' and 'iadd_p' for GENERIC '+' at (1) are ambiguous
U508187.f90:65.18-35:

         ALLOCATE(NewChild, SOURCE=Lhs, STAT=Istat)
                  1                2
Error: Type of entity at (1) is type incompatible with source-expr at (2)

Then I tried NAG Fortran. It picked up on a problem neither ifort nor gfortran did:

Error: U508187.f90, line 22: Elemental function IADD_P must not be allocatable

Yes indeed:

C1290 The result variable of an elemental function shall be scalar, shall not have the POINTER or ALLOCATABLE attribute, and shall not have a type parameter that is defined by an expression that is not a constant expression.

If I rework the code to remove the ALLOCATABLE aspect, NAG Fortran complains:

Error: U508187A.f90, line 104: Ambiguous specific type-bound procedures ADD_P and ADD_P for type-bound generic OPERATOR(+) in type C

Ok, at least this makes more sense than the gfortran message. I could be convinced that this is in fact not allowed. Even though the declaration in the abstract type p specifies the same procedure, it IS extending the generic and you then have two procedures in the generic for the same operation. Because they specify the same procedure, I guess that is ambiguous, though the wording of the standard doesn't explicitly exclude this.

More investigation is needed - and I will escalate the missing error for the allocatable elemental function value.

0 Kudos
Steven_L_Intel1
Employee
1,105 Views

Ah, the ELEMENTAL error was already filed as issue DPD200247686.

0 Kudos
FortranFan
Honored Contributor III
1,105 Views

Thanks Steve.  The point about ELEMENTAL attribute makes sense - I think I've seen the forum topic and the issue ID, but I forgot about that.

Re: the type incompatibility error:

Steve Lionel wrote:

$ gfortran U508187.f90
...
U508187.f90:65.18-35:

ALLOCATE(NewChild, SOURCE=Lhs, STAT=Istat)
                            1                           2
Error: Type of entity at (1) is type incompatible with source-expr at (2)

gfortran 4.9 doesn't raise that, nor does Intel Fortran.  Perhaps it is a bug in gfortran that got fixed in 4.9?

 

0 Kudos
Steven_L_Intel1
Employee
1,105 Views

Possibly - I have 4.8.

0 Kudos
Steven_L_Intel1
Employee
1,105 Views

Generic issue is DPD200237442.

0 Kudos
Steven_L_Intel1
Employee
1,105 Views

Both of these issues are fixed in 15.0 Update 2, available now from the Intel Registration Center.

0 Kudos
FortranFan
Honored Contributor III
1,105 Views

Glad to read this,

0 Kudos
Reply