- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This is based on an ongoing discussion at the comp.lang.fortran forum (https://groups.google.com/forum/#!topic/comp.lang.fortran/aFNK3FXqTUA) on generic operator bindings to specific type-bound procedures and their extensions with extended derived type. The simple code shown below is based on the postings in that thread as well as a companion thread at the gfortran gnu website. This code appears alright with respect to the latest Fortran standard and it compiles and executes as expected using gfortran 4.9. However, Intel Fortran compiler 15 raises an error which seems to be incorrect.
MODULE m !.. IMPLICIT NONE !.. PRIVATE TYPE, PUBLIC :: A_t !.. PRIVATE !.. INTEGER :: m_i = 0 CONTAINS !.. PRIVATE !.. PROCEDURE, PASS(This) :: A_sum => sum_i !.. GENERIC, PUBLIC :: OPERATOR(+) => A_sum END TYPE A_t TYPE, EXTENDS(A_t), PUBLIC :: C_t !.. PRIVATE !.. REAL :: m_r = 1.0 CONTAINS !.. PROCEDURE, PASS(This) :: A_sum => sum_r PROCEDURE, PASS(This) :: C_sum => sum_s !.. GENERIC, PUBLIC :: OPERATOR(+) => C_sum END TYPE C_t TYPE, PUBLIC :: S_t !.. PRIVATE !.. CHARACTER(LEN=6) :: m_s = "Hello!" END TYPE S_t CONTAINS FUNCTION sum_i(This, Rhs) RESULT(RetVal) !.. Argument list CLASS(A_t), INTENT(IN) :: This INTEGER, INTENT(IN) :: Rhs !.. Function result INTEGER :: RetVal RetVal = This%m_i + Rhs WRITE(*,*) 'In sum_i' !.. RETURN END FUNCTION sum_i FUNCTION sum_r(This, Rhs) RESULT(RetVal) !.. Argument list CLASS(C_t), INTENT(IN) :: This INTEGER, INTENT(IN) :: Rhs !.. Function result INTEGER :: RetVal RetVal = INT(This%m_r, KIND=KIND(RetVal)) + Rhs WRITE(*,*) 'In sum_r' !.. RETURN END FUNCTION sum_r FUNCTION sum_s(This, Rhs) RESULT(RetVal) !.. Argument list CLASS(C_t), INTENT(IN) :: This CLASS(S_t), INTENT(IN) :: Rhs !.. Function result CHARACTER(LEN=6) :: RetVal !.. IF (This%m_i == 0) THEN RetVal = Rhs%m_s END IF WRITE(*,*) 'In sum_s' !.. RETURN END FUNCTION sum_s END MODULE m PROGRAM p USE m, ONLY : A_t, C_t, S_t IMPLICIT NONE !.. Local variables TYPE(A_t) :: A TYPE(C_t) :: C TYPE(S_t) :: S INTEGER :: I CHARACTER(LEN=6) :: G !.. PRINT *, " Test #59: Generic Operator Extension " !.. I = A + 1 PRINT *, " I = ", I !.. I = C + 1 PRINT *, " I = ", I !.. G = C + S PRINT *, " G = ", G !.. STOP END PROGRAM p
The compiler error is as follows:
1>Compiling with Intel(R) Visual Fortran Compiler XE 15.0.0.108 [Intel(R) 64]... 1>TestFor.f90 1>TestFor.f90(21): error #6355: This binary operation is invalid for this data type.1>TestFor.f90(21): error #6549: An arithmetic or LOGICAL type is required in this context. 1>TestFor.f90(21): warning #6191: Fortran 2008 requires an arithmetic data type in this context. 1>TestFor.f90(21): error #6303: The assignment operation or the binary expression operation is invalid for the data types of the two operands. 1>compilation aborted for TestFor.f90 (code 1)
Note there is also another issue with Intel Fortran compiler giving an incorrect result if line 45 in module m i.e., if the generic operator + binding extension to another specific type-bound procedure is removed. This is part of the question at the comp.lang.fortran thread.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
FWIW, gfortran 4.9 gives the following result for the code shown above.
Test #59: Generic Operator Extension In sum_i I = 1 In sum_r I = 2 In sum_s G = Hello! Process returned 0 (0x0) execution time : 0.016 s Press any key to continue.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks, we'll take a look.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
My results for gfortran 5.0 and ifort on Windows were as quoted for linux.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I've gone through the comp.lang.fortran thread and the gcc thread it references. The program here differs substantially from what I see discussed in those threads, though there's a lot of back-and-forth and I may have missed something.
For the program presented here, I believe it should not compile, though the reason for that is different from what ifort says, in my opinion. Type C_t overrides the procedure A_sum, yet the non-passed dummy argument has a different type in the original and overriding procedures. This is not legal:
"The overriding and overridden type-bound procedures shall satisfy the following conditions:
...
- Dummy arguments that correspond by position shall have the same names and characteristics, except for the type of the passed-object dummy arguments"
This was brought up in the c.l.f thread. ifort should be disallowing that override and I will let the developers know.
But if I modify the program to avoid this issue, others arise, so I am still working on this.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve Lionel (Intel) wrote:
I've gone through the comp.lang.fortran thread and the gcc thread it references. The program here differs substantially from what I see discussed in those threads, though there's a lot of back-and-forth and I may have missed something.
...
Steve,
Yes, the issue I'm presenting here is different but the code and concept were "inspired" by the threads at comp.lang.fortran and gcc.
Steve Lionel (Intel) wrote:
...
in my opinion. Type C_t overrides the procedure A_sum, yet the non-passed dummy argument has a different type in the original and overriding procedures. This is not legal.
..
I'm not sure I understand: the overriding procedure for A_sum in type C_t is sum_r which has the same type of integer for the second (non-passed) dummy argument. So why is that not legal?
Perhaps you're thinking of the additional specific type-bound procedure of sum_s. But note this procedure is supposed to "extend" the generic operator of + with the binding at line 45. And from what I can understand, this is legal - is it not?
Thanks,
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Oops - I missed that the types are the same - too many variations to look at.
Extending the generic this way is correct. Let me play with this some more....
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Ok, this is the same as the issue reported in https://software.intel.com/en-us/forums/topic/534286 The bug tracking issue number is DPD200362489
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Fixed in 16.0.

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page