Declaring variable with class keyword

Recently I had a performance issue which was due to the need for creating a class header when calling a type-bound procedure if the object is declared with a type keyword. To be precise for a type mytype I have a variable “type(mytype) :: x” and I want to call a method sub as “call x%sub(…)”. This requires to create a class header data block, i.e. internally create a variable “class(mytype) :: x_cls” with the data of x. In a tight performance-critical loop, this increases runtime measurably (in real-world code, I am not talking about micro-benchmarks). It is not a huge increase, but it did slightly hurt a couple of times.

One of my solution is to declare this variable x_cls explicitly with a pointer attribute and add a line x_cls => x before any loops. Then everything is fine performance-wise. However, the code becomes less readable.
Or I add allocatable or pointer attribute to x and allocate it. Both solutions have its drawbacks.

So I wonder: Why is it not possible to declare a variable as “class(mytype) :: x”, meaning a variable of just that type but with the class header created right-away? As far as I can surmise from the compiler assembly output, this is what compilers do anyway, in a sense.
In particular if dealing with components of derived types, where it is not possible to create the auxiliary class variable outside the loop (because it is just a component [declared with type keyword] of the object which passed around), or where I do not want to add the overhead and hassle of allocate or pointer attribute, this would be helpful avoiding any performance issues right away.

Has there already been any discussions on this? I did not find much on the topic.

Can you show a small program that exhibits this? It will be clearer than your otherwise eloquent description :wink: . (I am suffering from a somewhat related performance problem - see elsethread.)

Sure. I cannot find my old microbenchmarks, which show the performance loss. For me, the relevant part is, that I can see the performance loss in my real code, and that I can restore performance by using class variables outside any big loops. But the code below (which does not do anything useful) shows the problem and some simple techniques to avoid the overhead. A simple “class(…) :: variable” could avoid the additional code. And that is my question, why is it not allowed in fortran.

module mod

implicit none
private

type, public :: t_component
   integer :: i = 0
contains
   procedure :: foo
end type t_component

type, public :: t_container
   type(t_component) :: x = t_component()
contains
   procedure :: bar
end type t_container


contains

subroutine foo(a, i)
   class(t_component), intent(inout) :: a
   integer, intent(in) :: i
   a%i = i
end subroutine foo

subroutine bar(b, i)
   class(t_container), intent(inout) :: b
   integer, intent(in) :: i
   ! class header needs to be created
   call b%x%foo(i)
end subroutine bar

end module mod



program type_class

use mod
implicit none

integer :: i
type(t_container), dimension(1:10), target :: p
class(t_container), dimension(:), pointer :: p_cls

do i = 1,10
   ! creation of temporary class header required,
   ! if the compiler is "dumb" or the code more complex,
   ! then creation is done for each iteration
   call p(i)%x%foo(i**2)
end do

! do class header creation just once for p_cls, but inside bar, there is still one class header creation
p_cls => p
do i = 1,10
   call p_cls(i)%bar(i**2)
end do

end program type_class

edit: removed x_cls variable, as it was not used

1 Like

Why do you think you need the indirection? The following works fine for me.

module mod

implicit none
private

type, public :: t_component
   integer :: i = 0
contains
   procedure :: foo
end type t_component

type, public :: t_container
   type(t_component) :: x = t_component()
contains
   procedure :: bar
end type t_container

contains

subroutine foo(a, i)
   class(t_component), intent(inout) :: a
   integer, intent(in) :: i
   a%i = i
end subroutine foo

subroutine bar(b, i)
   class(t_container), intent(inout) :: b
   integer, intent(in) :: i
   ! class header needs to be created
   call b%x%foo(i)
end subroutine bar

end module mod

program type_class

use mod
implicit none

integer :: i
type(t_container), dimension(1:10) :: p

do i = 1, 10
    call p(i)%bar(i**2)
end do

do i = 1,10
   print *, p(i)%x%i
end do

end program type_class
$ gfortran type_class.f90
$ ./a.out                
           1
           4
           9
          16
          25
          36
          49
          64
          81
         100

@martin,

Note the performance issue you allude to has no basis based on the information presented.

You will realize having a minimal working example of any issue generally but in your case specifically is critically important.

Additionally, you will know toward the coding and the consumption of objects in one’s programs, object-oriented analysis (OOA) is vitally important and it needs to precede object-oriented design (OOD) and only then should one technically proceed to object-oriented programming (OOP) where one may need to either employ polymorphism (in Fortran parlance, CLASS keyword per your thread title) or more importantly, design to not do so which is often a crucial decision to enable better performance.

You will also know composition vs inheritance is a key consideration during the OOA phase itself that then carries over on to the OOD stage. There are times when composition is apt but in some instances, inheritance may be better suited.

I suggest you share sufficient details on such aspects so you yourself and perhaps equally importantly, other readers now and future can derive useful rather than misleading information from the Discourse. Otherwise you run the risk of discussions in vacuo.

Out of curiosity, how can we check whether “class header” is created in the generated code? As mentioned in the first post, do we need to look at the generated assembly code in detail? (or some intermediate code from the compiler?)

(Also, I am assuming that “class header” is some internal descriptor that holds additional metadata for polymorphism; is this correct?)

RE “Why is it not possible to declare a variable as “class(mytype) :: x”", is it probably because the size of x cannot be determined at compile time?

I’m not a 100% sure what OP means by “class header”, it’s not a term I’ve heard before. Also, I’m by no means any expert of what a compiler actually does to the source code to produce a binary. However, my understanding of this is as follows (compiler experts, feel free to correct me!):

Each time you call a type bound procedure - e.g. call x%foo() on a variable of type class(some_t), allocatable :: x or an argument class(some_t) :: x then the compiler will generate code that at runtime will fetch a pointer to that procedure from a vtable. This is necessary because inheritance means that the procedure might have been overloaded somewhere and that is impossible to know at compile time. Compared to doing call x%foo() on type(some_t) :: x this most certainly is a runtime overhead. Whether it is significant will depend on the cost of the procedure call and maybe on how well the compiler can optimize the code.

This is correct. Since class(mytype) can be one of several concrete types (type, extends(mytype) :: foo_t, type, extends(mytype) :: bar_t and so on) the size of the variable cannot be known at compile time. So in order to use class(mytype) a pointer is needed, either as class(mytype), allocatable :: x or class(mytype), pointer :: x.

2 Likes

I need a couple of days to prepare my old micro-benchmarks…

I was pointed out that “class header” is correctly called “type descriptor”. Sorry for the confusion this inadequate term has caused.
And contrary to what you write, the type descriptor needs to be created (and this causes measurable performance loss in some cases) if I use call x%foo(…) for a variable declared as type(…) :: x. On the other hand, if x is declared with class (e.g. as dummy argument or with allocatable attribute), then the type descriptor is there and no overhead can be measured in my real-world code. So starting off with class avoids the overhead. I have looked at compiler assembler output, and access to vtable pointers is indeed negligible. But creating the type descriptor of about 50-100 bytes (?) might be bad.

The size of class(mytype) is known at compile time if mytype is indeed mytype and not some extended one.
If I do an allocate(x, mold=mytype()), then the size is well-defined.
The compiler internally uses such a variable (as far as I can see, type descriptor is on the stack, with pointer to the original object) to execute a call x%foo(), because x becomes the first argument (assuming no pass(…) attribute) declared as class(mytype). So descriptor is required.

So why not make this available right away to avoid the overhead of using allocation or pointer juggling (like I did in my example).
Often, objects come into life through allocation and are declared with class, so that is no concern (in this case, an object pool might be in place to avoid the overhead of allocate). But once in a while, I have objects of a specific type, declared with type, and with type bound procedure. And in 4 or 5 cases in my real code I could see the performance difference. So this is a real performance worry and the origin of my question.

2 Likes

The size is known in your allocate statement, but not at the point of declaration. At the moment a variable must be either allocatable or pointer in order use allocate. There’s nothing stopping you from doing:

class(mytype), allocatable ::x
allocate(x, mold=mytype())
deallocate(x)
allocate(x, mold=type_that_extends_mytype())

Reasoning about this at compile time in order to put aside enough space on the stack for the variable would be very challenging for the compiler. This restriction is also consistent with other programming languages, at least the one I can think of right now. In C++ for example, working with a virtual base class requires a pointer, either MyType*, std::unique_ptr<MyType> or similar.