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 have moved to the Altera Community. Existing Intel Community members can sign in with their current credentials.

Unexpected compiler error #6303 with the use of defined assignment

FortranFan
Honored Contributor III
1,867 Views

Dear Steve et al. at Intel,

The code shown below fails to compile with error #6303 using Intel Fortran compiler version 13.1.0.149.

It compiles successfully with gfortran 4.9 and executes as I would expect.

Would it be possible for you to review the code for correctness using the latest version of Intel compiler and if kosher, can you please consider adding this to your tracking system?

This seems related to the issues discussed in this forum topic, http://software.intel.com/en-us/forums/topic/506013, but in an opposite sense.  That is, in that topic, the situation was a failure by the compiler to check a standards violation but in this case, the compiler seems to flag an error when there may not be any.

Thanks much,

[fortran]

   MODULE TestMod

 

      !.. Explicit declarations

      IMPLICIT NONE

   

      !.. All entities private

      PRIVATE

 

!.. Accessor class

      TYPE, ABSTRACT, PUBLIC :: MyPropClassAbstract

      CONTAINS

         PRIVATE

         PROCEDURE(SetAbstract), PASS(This), DEFERRED :: Set

         GENERIC, PUBLIC :: ASSIGNMENT(=) => Set

      END TYPE MyPropClassAbstract

   

!.. Abstract Interface for Get, Set methods

      ABSTRACT INTERFACE

   

         PURE ELEMENTAL SUBROUTINE SetAbstract(This, Value)

      

            IMPORT :: MyPropClassAbstract

         

            !.. Argument list

            CLASS(MyPropClassAbstract), INTENT(OUT) :: This

            CLASS(*), INTENT(IN)                    :: Value

           

         END SUBROUTINE

      

      END INTERFACE

   

      !.. Integer Type

      TYPE, EXTENDS(MyPropClassAbstract), PUBLIC :: MyIntProp

         PRIVATE

         INTEGER :: MyValue

      CONTAINS

         PROCEDURE, PASS(This) :: Get => GetInt

         PROCEDURE, PASS(This) :: Set => SetInt

         GENERIC, PUBLIC :: ASSIGNMENT(=) => Get

      END TYPE MyIntProp

 

   CONTAINS

 

      !.. Get value of integer type

      PURE ELEMENTAL SUBROUTINE GetInt(Value, This)

   

         !.. Argument list

         INTEGER, INTENT(INOUT)       :: Value

         CLASS(MyIntProp), INTENT(IN) :: This

      

         !..

         Value = This%MyValue

   

         RETURN

   

      END SUBROUTINE GetInt

 

      !.. Set value of integer type

      PURE ELEMENTAL SUBROUTINE SetInt(This, Value)

   

         !.. Argument list

         CLASS(MyIntProp), INTENT(OUT) :: This

         CLASS(*), INTENT(IN)          :: Value

      

         !.. Process based on input type

         SELECT TYPE (Value)

            TYPE IS (INTEGER)

               This%MyValue = Value

            CLASS DEFAULT

            !.. Insert error handling here

            RETURN

         END SELECT

   

         RETURN

   

      END SUBROUTINE SetInt

 

   END MODULE TestMod

 

   PROGRAM TestFor

 

      USE TestMod, ONLY : MyIntProp

 

      IMPLICIT NONE

   

      INTEGER :: I

      INTEGER :: J

      TYPE(MyIntProp) :: TestInt   

 

      I = 5

      TestInt = I

      J = TestInt

   

      WRITE(6,91) I, J

         

      STOP

 

      !.. Format statements

 91   FORMAT(1X," I, J = ",I2,",",I2)

 

   END PROGRAM TestFor

[/fortran]

The compiler response is as shown below:

[plain]

1>------ Build started: Project: TestFor, Configuration: Debug Win32 ------

1>Compiling with Intel(R) Visual Fortran Compiler XE 13.1.0.149 [IA-32]...

1>TestMod.f90

1>TestFor.f90

1c:\\dev\\Fortran\\Test9\\sor\\TestFor.f90(12): error #6303: The assignment operation or the

binary expression operation is invalid for the data types of the two operands.  

1>compilation aborted for c:\\dev\\Fortran\\Test9\\sor\\TestFor.f90 (code 1)

1>

1>Build log written to

"file://\\c:\\dev\\Fortran\\Test9\\Debug\\Win32\\TestForBuildLog.htm"

1>TestFor - 2 error(s), 0 warning(s)

========== Build: 0 succeeded, 1 failed, 0 up-to-date, 0 skipped ==========

[/plain]

0 Kudos
9 Replies
FortranFan
Honored Contributor III
1,867 Views

Also, please note the problem seems to be related to defined assignment in the abstract type and its extension in the concrete type.  If the defined assignment in the abstract type is removed and the concrete type modified to include the assignment (as shown below), then the code compiles without errors and executes ok.

[fortran]

   MODULE TestMod

 

      !.. Explicit declarations

      IMPLICIT NONE

    

      !.. All entities private

      PRIVATE

 

!.. Accessor class

      TYPE, ABSTRACT, PUBLIC :: MyPropClassAbstract

      CONTAINS

         PRIVATE

         PROCEDURE(SetAbstract), PASS(This), DEFERRED :: Set

      !   GENERIC, PUBLIC :: ASSIGNMENT(=) => Set

      END TYPE MyPropClassAbstract

    

!.. Abstract Interface for Get, Set methods

      ABSTRACT INTERFACE

    

         PURE ELEMENTAL SUBROUTINE SetAbstract(This, Value)

       

            IMPORT :: MyPropClassAbstract

          

            !.. Argument list

            CLASS(MyPropClassAbstract), INTENT(OUT) :: This

            CLASS(*), INTENT(IN)                    :: Value

            

         END SUBROUTINE

       

      END INTERFACE

    

      !.. Integer Type

      TYPE, EXTENDS(MyPropClassAbstract), PUBLIC :: MyIntProp

         PRIVATE

         INTEGER :: MyValue

      CONTAINS

         PROCEDURE, PASS(This) :: Get => GetInt

         PROCEDURE, PASS(This) :: Set => SetInt

         GENERIC, PUBLIC :: ASSIGNMENT(=) => Get, Set

      END TYPE MyIntProp

 

   CONTAINS

 

      !.. Get value of integer type

      PURE ELEMENTAL SUBROUTINE GetInt(Value, This)

    

         !.. Argument list

         INTEGER, INTENT(INOUT)       :: Value

         CLASS(MyIntProp), INTENT(IN) :: This

       

         !..

         Value = This%MyValue

    

         RETURN

    

      END SUBROUTINE GetInt 

 

      !.. Set value of integer type

      PURE ELEMENTAL SUBROUTINE SetInt(This, Value)

    

         !.. Argument list

         CLASS(MyIntProp), INTENT(OUT) :: This

         CLASS(*), INTENT(IN)          :: Value

       

         !.. Process based on input type

         SELECT TYPE (Value)

            TYPE IS (INTEGER)

               This%MyValue = Value

            CLASS DEFAULT

            !.. Insert error handling here

            RETURN

         END SELECT

    

         RETURN

    

      END SUBROUTINE SetInt 

 

   END MODULE TestMod

 

   PROGRAM TestFor

 

      USE TestMod, ONLY : MyIntProp

 

      IMPLICIT NONE

    

      INTEGER :: I

      INTEGER :: J

      TYPE(MyIntProp) :: TestInt    

 

      I = 5

      TestInt = I

      J = TestInt

    

      WRITE(6,91) I, J

          

      STOP

 

      !.. Format statements

 91   FORMAT(1X," I, J = ",I2,",",I2)

 

   END PROGRAM TestFor

 

[/fortran]

 

0 Kudos
Steven_L_Intel1
Employee
1,867 Views

I think this is the same as http://software.intel.com/forums/topic/488776 ; Our issue ID is DPD200249796.

0 Kudos
FortranFan
Honored Contributor III
1,867 Views

If and when the Intel developers work on this problem, they might find it useful to keep a companion situation in mind, as shown below.  And that is about ambiguous interfaces for generic procedures.  This has been brought up in other forum topics, but I am thinking it may help to reiterate the point here.  The code below, a slight variation of the case in the original point, compiles without any errors in Intel Fortran and executes ok.  It’ll be better if the compiler gave an error instead, especially if certain settings are in effect (e.g., standard-semantics).  gfortran 4.9 correctly flags the error about the ambiguous interfaces for GetAbstract and SetAbstract procedures included in the generic assignment.

[fortran]

   MODULE TestMod

 

      !.. Explicit declarations

      IMPLICIT NONE

    

      !.. All entities private

      PRIVATE

 

!.. Accessor class

      TYPE, ABSTRACT, PUBLIC :: MyPropClassAbstract

      CONTAINS

         PRIVATE

         PROCEDURE(GetAbstract), PASS(This), DEFERRED :: Get

         PROCEDURE(SetAbstract), PASS(This), DEFERRED :: Set

         GENERIC, PUBLIC :: ASSIGNMENT(=) => Get, Set

      END TYPE MyPropClassAbstract

    

!.. Abstract Interface for Get, Set methods

      ABSTRACT INTERFACE

 

         PURE ELEMENTAL SUBROUTINE SetAbstract(This, Value)

       

            IMPORT :: MyPropClassAbstract

          

            !.. Argument list

            CLASS(MyPropClassAbstract), INTENT(OUT) :: This

            CLASS(*), INTENT(IN)                    :: Value

            

         END SUBROUTINE

 

         PURE ELEMENTAL SUBROUTINE GetAbstract(Value, This)

       

            IMPORT :: MyPropClassAbstract

          

            !.. Argument list

            CLASS(*), INTENT(OUT)                  :: Value

            CLASS(MyPropClassAbstract), INTENT(IN) :: This

            

         END SUBROUTINE

       

 

      END INTERFACE

    

      !.. Integer Type

      TYPE, EXTENDS(MyPropClassAbstract), PUBLIC :: MyIntProp

         PRIVATE

         INTEGER :: MyValue

      CONTAINS

         PROCEDURE, PASS(This) :: Get => GetInt

         PROCEDURE, PASS(This) :: Set => SetInt

      !   GENERIC, PUBLIC :: ASSIGNMENT(=) => Get, Set

      END TYPE MyIntProp

 

   CONTAINS

 

      !.. Get value of integer type

      ELEMENTAL SUBROUTINE GetInt(Value, This)

    

         !.. Argument list

         CLASS(*), INTENT(OUT)        :: Value

         CLASS(MyIntProp), INTENT(IN) :: This

       

         !.. Process based on input type

         SELECT TYPE (Value)

            TYPE IS (INTEGER)

               Value = This%MyValue

            CLASS DEFAULT

            !.. Insert error handling here

            RETURN

         END SELECT

    

         RETURN

    

      END SUBROUTINE GetInt 

 

      !.. Set value of integer type

      PURE ELEMENTAL SUBROUTINE SetInt(This, Value)

    

         !.. Argument list

         CLASS(MyIntProp), INTENT(OUT) :: This

         CLASS(*), INTENT(IN)          :: Value

       

         !.. Process based on input type

         SELECT TYPE (Value)

            TYPE IS (INTEGER)

               This%MyValue = Value

            CLASS DEFAULT

            !.. Insert error handling here

            RETURN

         END SELECT

    

         RETURN

    

      END SUBROUTINE SetInt 

 

   END MODULE TestMod

 

   PROGRAM TestFor

 

      USE TestMod, ONLY : MyIntProp

 

      IMPLICIT NONE

    

      INTEGER :: I

      INTEGER :: J

      TYPE(MyIntProp) :: TestInt    

 

      I = 5

      TestInt = I

      J = TestInt

    

      WRITE(6,91) I, J

          

      STOP

 

      !.. Format statements

 91   FORMAT(1X," I, J = ",I2,",",I2)

 

   END PROGRAM TestFor

 

[/fortran]

 

0 Kudos
Steven_L_Intel1
Employee
1,867 Views

Yes, we've had this discussion already at http://software.intel.com/en-us/forums/topic/506691

0 Kudos
FortranFan
Honored Contributor III
1,867 Views

Steve Lionel (Intel) wrote:

I think this is the same as http://software.intel.com/forums/topic/488776  Our issue ID is DPD200249796.

Steve,

Thanks.

While the issue in DPD200249796 appears closely related to mine, I'm not convinced they are exactly the same or that a fix to DPD200249796 will necessarily resolve mine:

  • for one thing, the compiler error (#6303) I get is not the same as the errors listed in the topic 488776; yeah, sure they might be variations of the same theme but there could be subtle differences too,
  • secondly, and perhaps more importantly, what I'm doing is also adding another assignment to that declared in the abstract whereas in topic 488776, the concrete (child) is simply implementing the deferred assignment,
  • third, I show a couple of scenarios in quote #1 and quote #3 where Intel Fortran compiles and executes ok which appear different from various observations in topic 488776.

But I'll wait until DPD200249796 is fixed and I can get that compiler version.

Regards,

0 Kudos
Steven_L_Intel1
Employee
1,867 Views

I added your program to that issue - it is probably related.

0 Kudos
FortranFan
Honored Contributor III
1,867 Views

Steve Lionel (Intel) wrote:

Yes, we've had this discussion already at http://software.intel.com/en-us/forums/topic/506691

Steve,

Is there a tracking incident for developers for the generic procedure disambiguation issue in topic 506691?  Or do you think it requires more investigation by the compiler team in terms of how Intel Fortran compiler should behave in such cases?  FWIW, gfortran 4.8.1 and 4.9 flags it as an error with an easily understandable message.

Thanks,

0 Kudos
FortranFan
Honored Contributor III
1,867 Views

Steve Lionel (Intel) wrote:

I added your program to that issue - it is probably related.

Steve,

A general question: how do you and the Intel team view additional code snippets being submitted on known issues like the one in topic 506991?  Is that creating clutter?  Or is it thought of as "more the merrier"?  Would these code samples be of any help to the compiler team in terms of unit tests?

Note as I hinted at previously, I was consciously aware of topic 506691 but I simply assumed you all and the Intel forum readers wouldn't mind another example.  Was I wrong to assume as such?

And while I think I've read topic 488776 previously, I'd forgotten about it when I submitted this topic.  I'm now wondering if I'd remembered about it, should I not have created another posting?

As always, thanks much for your input and all your attention.

0 Kudos
Steven_L_Intel1
Employee
1,867 Views

I don't mind additional postings. Sometimes you have a variant on a problem that the original example doesn't exercise.

The ambiguity issue is DPD200253987.

0 Kudos
Reply