Inheritance problem; or, selectively accessing procedures of parent class

Hi folks –

Run into an issue with Fortran class inheritance that has me scratching my head. Best demonstrated with an example program (attached).

test_inherit.f90 (1.2 KB)

I had expected the second call statement in the main program to indicate that eval_bar() is getting called – but no, it’s eval_foo(). Which brings me to my question: is there a way to call an overridden procedure of a parent class, in a way that keeps the other procedures of the parent class overridden? With reference to my example program, I’d like print_foo() to recognize that the dynamic type of the self argument is bar_t, and therefore call eval_bar() rather than eval_foo().

cheers,

Rich

If you don’t override print,

   type, extends(foo_t) :: bar_t
   contains
!      procedure :: print => print_bar
      procedure :: eval => eval_bar
   end type bar_t

then it appears to work the way you expect it too:

$ ./test_inherit 
 str isevaled by foo!                                                  
 str isevaled by bar!                            

Indeed. But the need to override print comes if I want extend its behavior – add on some functionality before calling print_foo. The kicker is that the dynamic type of self then seems to get forgotten.

I think I see your point. Would the following work for you:

   subroutine print_bar(self)
      class(bar_t), intent(in) :: self

      print *, "Add bar behavior"
      call print_foo(self)

   end subroutine print_bar

Other OO languages seem to get this kind of behavior correct. I’m surprised (and a little worried) that Fortran can’t. Or maybe this is a bug?

Yes, that would work. But then I have to access the print routine via its specific name rather than its binding name. That seems really gnarly.

Maybe like this:

   type :: foo_t
   contains
      procedure, private, non_overridable :: private_print => print_foo
      procedure :: print => print_foo
      procedure :: eval => eval_foo
   end type foo_t

! ...

   subroutine print_bar(self)
      class(bar_t), intent(in) :: self

      print *, "Add bar behavior"
!      call self%foo_t%print()         ! --> wrong dynamic type
!      call print_foo(self)            ! --> needs specific name
      call self%private_print()           

   end subroutine print_bar

I suppose it would be cleaner to implement foo’s print by calling private_print, instead of binding the same procedure twice. Then children overriding the procedure, can just add the extra functionality they need.

1 Like

Yes there is one, with caveats.

You want to call the procedure from up at foo_t, but you want to keep it polymorphic as you want the internal calls to be this way. You can’t do it using the parent accessor, because self%foo_t is of the non-polymorphic type(foo_t) anyways, so it will call all functions from that same type.

I would do it this way. Declare for the same routine both the print generic and a nopass interface to it. So, you can pass any polymorphic downstream type that extends(foo_t) as an argument to it, it’s just a little uglier to call it but still a oneliner:

   type :: foo_t
   contains
      procedure, nopass, private :: print_foo
      procedure :: print => print_foo
      procedure :: eval => eval_foo
   end type foo_t
![...]

   subroutine print_bar(self)
      class(bar_t), intent(in) :: self

      call self%print_foo(self) ! Ugly but works!
      ! you were still callling self%foo_t so it's not a big deal uglier

   end subroutine print_bar

Full example here

That’s a nice combination of the previous two approaches shown. Which communicates better the intent, that it’s to be used as an internal “service” routine?

That’s a nice approach, but will only work if foo_t and bar_t are defined in the same module. Otherwise, the private attribute on print_foo will have to be removed, right?

1 Like

Just for the record, C++ works the same way as Fortran does:

#include <string>
#include <iostream>

class foo {
public:
    void print() { std::cout << "string is " + eval() << '\n'; }
    std::string eval() { return "evaled by foo!"; }
};


class bar : public foo {
public:
    
    void print() { 
        std::cout << "now in bar\n";
        foo::print(); 
    }

    std::string eval() { return "evaled by bar!"; }
};

int main(int argc, char const *argv[])
{
    foo f;
    bar b;

    f.print();
    b.print();

    return 0;
}
$ g++-13 -Wall test_inherit.cpp 
$ ./a.out
string is evaled by foo!
now in bar
string is evaled by foo!

Edit: the C++ class works the way @rhtownsend expects it would, if I add the virtual attribute in the base class:

    virtual void print() { std::cout << "string is " + this->eval() << '\n'; }
    virtual std::string eval() { return "evaled by foo!"; }

Thanks for the reminder about virtual functions – I think that was what I was remembering, in my belief that other OO languages behave in the manner I had described.

I don’t think Fortran allows this kind of virtual procedure support, but I may be wrong…

There is abstract and deferred; I tried to use them but it didn’t change the outcome that when the dynamic type is foo_t it calls its own method, and not the over-riding child one.