Abstract type with private deferred type-bound procedures

Hi folks –

I’ve a question about my understanding of abstract classes with deferred type-bound procedures (TBPs) that have private accessibility. I attach some example code that illustrates my question. The abstract base_t type has a pair of TBPs (do_real_scalar, do_real_array) that have private accessibility, but a generic (do_real) that serves as the public interface to these procedures. The non-abstract printer_t type subclasses base_t and provides definitions for do_real_scalar and do_real_array.

This code compiles and gives the expected (to me) results with gfortran, but I’m not sure how to interpret this apparent success. It’s my understanding that the private TBPs of a parent class are completely invisible to a subclass, and so when I define do_real_scalar and do_real_array in printer_t, I’m not implementing or overriding routines from base_t, I’m just adding a couple of new TBPs.

But in this case the generic do_real inherited from base_t correctly picks up on the fact that it should bind to the do_real_scalar and do_real_array TBPs defined in printer_t.

Are there special rules in the Fortran standard governing the semantics of deferred private components?

Thanks!

Rich

test_private_deferred.f90 (1.5 KB)

1 Like
~/temp> nagfor test_private.f90 
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
Error: test_private.f90, line 34: Cannot extend abstract type BASE_T because it has a private deferred type-bound procedure DO_REAL_SCALAR
       detected at ::@PRINTER_T
Error: test_private.f90, line 34: Cannot extend abstract type BASE_T because it has a private deferred type-bound procedure DO_REAL_ARRAY
       detected at ::@PRINTER_T

So, this seems to imply that Fortran does not allow abstract types that provide public generic interfaces but have the specific (deferred) routines behind the generic interface be private. That seems to be an oversight, no?

Well it does, but it seems like you need to implement the deferred procedures in the scope where they are visible:

module define_printer_m

   implicit none

   type, abstract :: base_t
   contains
      private
      procedure(do_real_scalar_iface), deferred :: do_real_scalar
      procedure(do_real_array_iface), deferred  :: do_real_array
      generic, public                           :: do_real => do_real_scalar, do_real_array
   end type base_t

   abstract interface
      subroutine do_real_scalar_iface(self, x)
         import base_t
         class(base_t), intent(in) :: self
         real, intent(in)          :: x
      end subroutine do_real_scalar_iface
      subroutine do_real_array_iface(self, x)
         import base_t
         class(base_t), intent(in) :: self
         real, intent(in)          :: x(:)
      end subroutine do_real_array_iface
   end interface

   type, extends(base_t) :: printer_t
   contains
      private
      procedure :: do_real_scalar => do_real_scalar_p
      procedure :: do_real_array => do_real_array_p
   end type printer_t

contains

   subroutine do_real_scalar_p(self, x)
      class(printer_t), intent(in) :: self
      real, intent(in)             :: x
      print *, x
   end subroutine do_real_scalar_p

   subroutine do_real_array_p(self, x)
      class(printer_t), intent(in) :: self
      real, intent(in)             :: x(:)
      integer :: i
      print *, x
   end subroutine do_real_array_p

   subroutine print_1234()
      type(printer_t) :: p 
      call p%do_real_array([1.,2.,3.,4.])
   end subroutine

end module

Tested with nagfor, ifx, and flang.

Unlike what happens in some other languages, in Fortran the public|private attributes apply to the module, not to the derived type. So you can only implement a private, deferred TBP within the same module.

For your test, you’re also allowed, outside of the define_base_m module, to extend base_t with components that may have the same names as the private ones in base_t, the do_real_scalar and do_real_array in printer_t should have been considered completely different TBPs (even if they have the same names). That’s actually the error I get when trying to compile with ifort/ifx —that the deferred TBPs remain unimplemented and therefore printer_t should be abstract.

And if you make the deferred TBPs public, they must also be public for the extended type —by the Liskov substitution principle.

1 Like

Coming here to ask this (armed with a small reproducer) was a good idea. Trying out a few compilers first would have been a (marginally) better idea. Intel’s ifx and LLVM Flang reject the program (like NAG’s compiler does).

Compilers are wrong all the time, so it is hard to say that they determine any measure of correctness. :slight_smile:

2 Likes