- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I think the following code is alright but Intel Fortran compiler 17.0 update 1 gives an unexpected error:
module parent_m
implicit none
private
type, public, abstract :: parent_t
private
contains
procedure(Iassign_parent), pass(lhs), deferred :: assign_parent
procedure(Ireal_times_parent), pass(rhs), deferred :: real_times_parent
procedure(Iparent_op_parent), pass(lhs), deferred :: parent_add_parent
! operators
generic :: assignment(=) => assign_parent
generic :: operator(+) => parent_add_parent
generic :: operator(*) => real_times_parent
end type parent_t
abstract interface
pure subroutine Iassign_parent(lhs, rhs)
!< Operator `=`.
import :: parent_t
class(parent_t), intent(inout) :: lhs
class(parent_t), intent(in) :: rhs
end subroutine Iassign_parent
function Ireal_times_parent(lhs, rhs) result( res )
!< Operator `real * type`.
import :: parent_t
real, intent(in) :: lhs
class(parent_t), intent(in) :: rhs
class(parent_t), allocatable :: res
end function Ireal_times_parent
function Iparent_op_parent(lhs, rhs) result( res )
!< Symmetric operator `type.op.type`.
import :: parent_t
class(parent_t), intent(in) :: lhs
class(parent_t), intent(in) :: rhs
class(parent_t), allocatable :: res
end function Iparent_op_parent
end interface
end module parent_m
module child_m
use parent_m, only : parent_t
implicit none
private
type, extends(parent_t), public :: child_t
private
contains
procedure, pass(lhs) :: assign_parent => assign_child !< Operator `=`.
procedure, pass(rhs) :: real_times_parent !< Operator `real * type`.
procedure, pass(lhs) :: parent_add_parent => child_add_parent !< Operator `+`.
end type child_t
contains
pure subroutine assign_child(lhs, rhs)
!< Operator `=`.
class(child_t), intent(inout) :: lhs
class(parent_t), intent(in) :: rhs
return
end subroutine assign_child
function real_times_parent(lhs, rhs) result( res )
!< Operator `real * cons`.
real, intent(in) :: lhs
class(child_t), intent(in) :: rhs
class(parent_t), allocatable :: res
allocate ( child_t :: res )
return
end function real_times_parent
function child_add_parent(lhs, rhs) result( res )
!< Operator `+`.
class(child_t), intent(in) :: lhs
class(parent_t), intent(in) :: rhs
class(parent_t), allocatable :: res
allocate ( child_t :: res )
return
end function child_add_parent
end module child_m
module m
use parent_m, only : parent_t
use child_m, only : child_t
implicit none
contains
subroutine sub1( foo, bar )
class(parent_t), allocatable, intent(inout) :: foo
class(parent_t), intent(inout) :: bar
select type ( bar )
type is ( child_t )
bar = 0.5 * foo
class default
end select
return
end subroutine sub1
subroutine sub2( foobar )
class(parent_t), intent(inout) :: foobar
type(child_t) :: foo
type(child_t) :: bar
select type ( foobar )
type is ( child_t )
foobar = 0.5 * ( foo + bar )
class default
end select
return
end subroutine sub2
end module m
Upon compilation,
Compiling with Intel(R) Visual Fortran Compiler 17.0.1.143 [Intel(R) 64]... m.f90 m.f90(34): error #6633: The type of the actual argument differs from the type of the dummy argument. ifort: error #10298: problem during post processing of parallel object compilation compilation aborted for m.f90 (code 1)
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
FWIW, the code in the original post compiles successfully with gfortran.
From what I can see, the instructions in procedure sub2 in module m where the compiler gives an error are equivalent to those in sub1, but sub1 compiles ok.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I've seen this before and am pretty sure I escalated it before I retired. The issue is that the compiler isn't properly recognizing that foo+bar is of a compatible type. A workaround is to do the add to a temp and use that:
subroutine sub2( foobar )
class(parent_t), intent(inout) :: foobar
type(child_t) :: foo
type(child_t) :: bar
type(child_t) :: temp
select type ( foobar )
type is ( child_t )
temp = foo + bar
foobar = 0.5 * ( temp)
class default
end select
return
end subroutine sub2
Kevin or one of the other Intel folks can find the escalation and add this report to it.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve Lionel (Ret.) wrote:
I've seen this before and am pretty sure I escalated it before I retired. The issue is that the compiler isn't properly recognizing that foo+bar is of a compatible type. A workaround is to do the add to a temp and use that ..
Kevin or one of the other Intel folks can find the escalation and add this report to it.
Thanks Steve. This was actually driven by a discussion on comp.lang.fortran and OP is indeed using the workaround you suggest.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Dear FortranFan and Steve,
thank you very much for your help, it is very very appreciated.
As FortranFan said, I am already using the Steve's workaround, that is viable for simple math, but for more complex it becomes somehow unclear.
Is this also an issue for Intel 17.0.2 (update 2)? I am going to update my current update 1...
My best regards.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It is still an issue in 17.0.2.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It relates to this post (linked to DPD200413156). That issue is not currently fixed. I added this additional test case to the existing internal tracking id.
(Internal tracking id: DPD200371156)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank you Steve!
Dear Kevin, thank you too, your help is really appreciated.
Indeed, Francesco and I are working together :-) This is issue occurred to both working to together, but in different projects, thus we were not sure it was due to the same reason. Thank you for the clarification.
My best regards.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Dear all,
I have just joined the 2018 beta testing initiative. With the fresh installed parallel studio xe 2018 beta I got the same error
┌╼ stefano@zaghi(01:01 PM Thu Apr 13) desk {intel-18.0.0.beta - Intel Parallel Studio XE 2018.0.0 beta}
├───╼ ~/fortran/compilers_bug/intel_abstract_types_operators 1 files, 12Kb
└──────╼ ifort -c abstract_types_operator.f90
abstract_types_operator.f90(134): error #6633: The type of the actual argument differs from the type of the dummy argument.
foobar = 0.5 * ( foo + bar )
---------------------------------^
compilation aborted for abstract_types_operator.f90 (code 1)
My best regards
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The internal tracking id linked to that case (DPD200413156) is not fixed yet.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Haven't tried this, how about:
subroutine sub2( foobar ) class(parent_t), intent(inout) :: foobar type(child_t) :: foo type(child_t) :: bar select type ( foobar ) type is ( child_t ) foobar = 0.5 * ( child_t(foo + bar) ) ! using constructor class default end select return end subroutine sub2
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Dear Jim,
thank you for your suggestion. I do not know why, but I did not received an alert of your message, thus I miss it until now. Later today I'll try it.
My best regards.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
FWIW, if the error carrot (^) moves from the + to the *, then use
foobar = child_t(0.5 * ( child_t(foo + bar) ) ) ! using two constructors
Jim Dempsey
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page