This is a follow up question from a thread I've started earlier here.
Basically, what I want to achieve is defining a deferred type which automatically assigns primitive types (real, integer, character and logical). You can see a working example when following the above link and it compiles with gcc version 7.3.0
and ifort version 18.0.0
.
I have now extended the code in order to "use" the deferred data type without knowing what primitive type is assigned. This works by overriding basic operators. For the sake of simplicity I've only included the +
operator in the following example. The example works and compiles with gfortran but does give me an error when compiling with ifort :
error #6303: The assignment operation or the binary expression operation is invalid for the data types of the two operands. [PLUS_FUNC_CLASS] c%i = a%i + b%i
Does anyone know what the problem is here? I've already googled the error but I could not find out what I'm doing wrong.
in order to match the precision I used the following compile flags
ifort -r8 -i8 tst.f90
gfortran -fdefault-real-8 -fdefault-integer-8 -fdefault-double-8 tst.f90
Here's the sample code:
module DervType
implicit none
type, public :: mytype
real :: r
integer :: i
character(len=:), allocatable :: c
logical :: l
end type
interface assignment(=)
module procedure equal_func_class
end interface
interface operator(+)
module procedure plus_func_class
end interface
contains
subroutine equal_func_class(a,b)
type(mytype), intent(out):: a
class(*), intent(in) :: b
select type (b)
type is (mytype)
print *, "is mytype"
if ( .not. a%r == b%r ) a%r = b%r !! <-- ugly, but necessary not to end up in an endless loop when reassigning mytype (only testing and assigning real here)
type is (real)
print *, "is real"
a%r = b
type is (integer)
print *, "is int"
a%i = b
type is (character(len=*))
print *, "is char"
a%c = b
type is (logical)
print *, "is logical"
a%l = b
end select
return
end subroutine equal_func_class
recursive function plus_func_class(a,b) result(c)
class(*), intent(in) :: a
class(*), intent(in) :: b
type(mytype) :: c
select type (a)
type is (mytype)
print *, "left side is mytype"
!! -------------------------------
!! only testing one case here and only real operations are
!! taken care of!
!! -------------------------------
select type (b)
type is (mytype)
print *, "right side is mytype"
c%i = a%i + b%i !! <-- this is where ifort throws the error
c%r = a%r + b%r !! <-- this is where ifort throws the error
type is (real)
print *, "right side is real", a%r
c = a%r + b
end select
!! do similar logic when the operands changing sides
type is (real)
print *, "left side is real"
end select
!c = 1.
return
end function plus_func_class
end module DervType
program TestType
use DervType
implicit none
type(mytype) :: test, test2, res, res2
real, parameter :: tt = 2.
test = 1.
test = 1
test = "Hey Tapir"
test = .true.
test2 = 2.
test = test2
print *, "test = ", test%r
res = test + 1.0
res2 = test + tt
print *, "Calculation 1 (real) : ", res%r
print *, "Calculation 2 (real) : ", res2%r
end program TestType
When compiling with gfortran
and running the program this gives the following output:
is real
is int
is char
is logical
is real
is mytype
test = 2.0000000000000000
left side is mytype
right side is real 2.0000000000000000
is real
is mytype
left side is mytype
right side is real 2.0000000000000000
is real
is mytype
Calculation 1 (real) : 3.0000000000000000
Calculation 2 (real) : 4.0000000000000000
Let's cut this example program down to something more manageable:
module DervType
implicit none
type mytype
integer i
end type mytype
interface operator(+)
module procedure plus_func_class
end interface
contains
recursive function plus_func_class(a,b) result(c)
class(*), intent(in) :: a
class(*), intent(in) :: b
type(mytype) :: c
c%i = 1+1
end function plus_func_class
end module DervType
ifort 18.0.3 for me complains about this:
error #6303: The assignment operation or the binary expression operation is invalid for the data types of the two operands. [PLUS_FUNC_CLASS]
c%i = 1+1
-----------^
Familiar?
Well, it looks like because we have the arguments to plus_func_class
as unlimited polymorphic ifort is deciding to take this function as a specific procedure for the generic operator(+)
with the expression 1+1
. (Remove the recursive
prefix to see further.)
We don't want it to do that. Can we persuade it not to?
We want our true function to consider cases where either the left-hand side or the right-hand side are of class(mytype)
, as we don't care to reimplement intrinsic+intrinsic
. I won't write out details, but you can implement the function twice: once with LHS class(mytype)
and RHS class(*)
, and once with the LHS class(*)
and the RHS class(mytype)
.
Even if one initially views this approach simply as a "compiler bug workaround", it's really worth implementing the defined operation without using unlimited polymorphic arguments for both sides of the addition operation
When you want to create a new type mytype2
you don't want to define the operation with the function plus_func_class
. You'd need to though, because you'll have an ambiguous interface if you create a new specific function for generic operator(+)
.