I’ve been trying to better understand polymorphic behavior of derived types in fortran. I know there are compiler writers and fortran standard experts here, so hopefully they can help explain some questions I have. The godbolt link below has all the code. I will go through it a bit at a time.
The dostuff()
procedure below updates the member variable, then calls dostuff2()
, which is polymorphic, and dostuff3()
, which is not (non_overridable
).
type :: A
integer :: mem = 0
contains
procedure, pass :: dostuff
procedure, pass :: dostuff2
procedure, pass, non_overridable :: dostuff3
end type
contains
subroutine dostuff(self, i)
class(A), intent(inout) :: self
integer, intent(in) :: i
self%mem = self%mem +1501*i
call self%dostuff2(i)
call self%dostuff3(i)
end subroutine
subroutine dostuff2(self, i)
class(A), intent(inout) :: self
integer, intent(in) :: i
self%mem = self % mem + 3001*i
end subroutine
subroutine dostuff3(self, i)
class(A), intent(inout) :: self
integer, intent(in) :: i
self%mem = self%mem + 4501 *i
end subroutine
Both gfortran and ifort successfully inline dostuff3()
, but the call to dostuff2()
is definitely going through a vtable. Here’s the gfortran assembly, which is clearer IMHO:
imul edx, ebp, 1501 // update self %mem in dostuff()
add DWORD PTR [rax], edx
mov rax, QWORD PTR [rdi+8] // get vtable pointer
imul ebp, ebp, 4501 // precompute dostuff3()
call [QWORD PTR [rax+56]] // call dostuff2()
This is all perfectly fine and makes sense. My problem with it is that I had no idea I was always running through a virtual table to make these functions calls! I mean, it makes sense NOW, but it never occurred to me that ALL of these functions were virtual functions, even when I never intended the type to be extended!
My takeaway from this is that almost all type-bound procedures should be marked non_overridable
. Maybe you don’t use types this way, but I do.
The next interesting tidbit is this snippet of code
subroutine poly(obj,i)
class(A), intent(inout) :: obj
integer, intent(in) :: i
call obj%dostuff(i)
end subroutine
subroutine not_poly(obj,i)
type(A), intent(inout) :: obj
integer, intent(in) :: i
call obj%dostuff(i)
end subroutine
The only difference here is that the first uses class(A)
, while the second uses type(A)
. I wanted to see if type(A)
meant “This is a non-polymorphic object and should be treated as such”. What is the difference between using type(A)
vs. class(A)
?
For the poly()
subroutine, both gfortran and ifort immediately delegate to the virtual table. Makes sense.
For the not_poly()
subroutine, gfortran successfully devirtualizes the call to dostuff()
, but NOT the call to dostuff2()
. It does inline the call to dostuff3()
.
For you experts out there, is this expected behavior, or is it a failure of the compiler to devirtualize the second level of function calls?
For the not_poly()
subroutine, intel…well…I have no idea what intel is doing, but it still looks like it is devirtualizing the first call to dostuff()
, but not the other 2. There are 2 function calls that … probably … come from the virtual table? I’m really not sure. Does anyone understand the assembly output from intel for this subroutine? (Below, or in the godbolt link above.)
Thanks for the help!
mov QWORD PTR [56+rsp], offset flat: _TBPLIST_PACK_0
xor eax, eax
mov rcx, QWORD PTR [56+rsp]
mov QWORD PTR [48+rsp], offset flat: _DYNTYPE_PACK_0
imul edx, DWORD PTR [r14], 1501
mov QWORD PTR [64+rsp], rax
mov QWORD PTR [80+rsp], rax
mov QWORD PTR [96+rsp], rax
mov QWORD PTR [88+rsp], rax
mov QWORD PTR [72+rsp], rax
mov QWORD PTR [104+rsp], offset flat: _INFO_LIST_PACK_0
mov QWORD PTR [112+rsp], rax
mov QWORD PTR [8+rsp], 4
mov QWORD PTR [32+rsp], rax
mov QWORD PTR [rsp], rdi
mov QWORD PTR [16+rsp], rax
mov QWORD PTR [24+rsp], 3
add DWORD PTR [rdi], edx
lea rdi, QWORD PTR [rsp]
call QWORD PTR [8+rcx] // call here to vtable?
mov rax, QWORD PTR [56+rsp]
lea rdi, QWORD PTR [rsp]
mov rsi, r14
call QWORD PTR [16+rax] // call here to dostuff3()?