Type-bound procedure with non-polymorphic argument of the same type: strategies?

I’m trying to avoid copy/paste of code for several classes and would like to do it with an abstract type and polymorphism, but haven’t had any success so far.

Here’s an example of what I’m trying to do :

module base
        implicit none

        type, abstract :: t
        end type t

        type, extends(t) :: t2
                integer :: i=0
                ! etc.
        end type t2

        abstract interface ! should be instantiated for all classes
        subroutine unique(tt,tunique)
            class(t), allocatable, intent(in) :: tt(:)
            class(t), allocatable, intent(out) :: tunique(:) ! same type as tt
            if (.not.allocated(tt)) then
               allocate(tunique(0),mold=tt)
            else
               allocate(tunique(1),source=tt(1))
            endif
        end subroutine unique
       end interface
end module base
program test_transfer
        use base
        type(t2), allocatable :: a(:),b(:)

        allocate(a(2))
        call unique(a,b)

        print *, size(b)
end program test

I’ve named it unique in the example cause it’s one of the things I’d do with it, i.e., filtering unique elements of a derived type out of an array. I want to have a subroutine that is:

  • defined in each extended type
  • only operates with arguments of the same type
  • has to do some allocation
  • the interface (and hopefully the actual implementation) is only defined once, in the abstract class file

I know the standard doesn’t allow this, but I’m struggling copying and pasting code in several several classes. I wonder if anyone from the community has suggestions on how to achieve something similar with the smallest amount of code?

Templates will (hopefully) help with these kinds of things, but I haven’t found a good way to accomplish it for now without just biting the bullet and duplicating the code.

I don’t know if it fits to your problem, but here it how I approach such situation:

First you define your Abstract class that is the “contract” (all classes inheriting will have to follow that model) and then you create a Base class where you either provide the basic implementation or an error stop "Not Implemented".

Then, all classes that extends the Base class will have to follow the Abstract class, but you will not need to implement the ones you already defined, unless you want to change it’s behavior.

I did that in a set of Solver classes that I wanted to share the same export and plot methods, but I also wanted stricter rules about its derived types.

@14ngp @everythingfunctional Right,

that’s what I also do most of the times when the arguments are scalars.
But in this case I have arrays of derived-type quantities, so right now I am

  • putting all these routines into a public interface, every time I define a new extended type
  • copying/pasting the code every time.

The other approach I was thinking about was to define a template routine and then pre-process it with an external program to instantiate all versions for each derived type, that’s a really ugly way to accomplish the same thing but at least there would be a single version of the source to edit.

It would have been nice to import that from a character(*), parameter string instead, but I don’t think there’s a way to tell the compiler to import a function from a string…

This may work but will give you a lot of runtime polymorphism to resolve

module base
  implicit none
  type, abstract :: t
  end type t
  type, extends(t) :: t2
    integer :: i=0
  contains
    generic :: assignment(=) => assign
    procedure :: assign=>subassign_t2
  end type t2
contains
  subroutine unique(tt,tunique)
    class(t), allocatable, intent(in) :: tt(:)
    class(t), allocatable, intent(out) :: tunique(:) ! same type as tt
    if(.not.allocated(tt)) then
      select type(x1=>tt)
      class is(t2)
        allocate(t2::tunique(0))
      class default
        !!catch here
      end select
    else
      select type(x1=>tt)
      class is(t2)
        allocate(t2::tunique(1))
        select type(x2=>tunique)
        class is(t2)
          x2(1)=x1(1)
        end select
      class default
        !!catch here
      end select
    end if
  end subroutine unique
  elemental subroutine subassign_t2(this,other)
    class(t2), intent(inout) :: this
    class(t2), intent(in) :: other
    this%i=other%i
  end subroutine subassign_t2
end module base
program test_transfer
  use base
  class(t), allocatable :: a(:),b(:)
  allocate(t2::a(2))
  call unique(a,b)
  print *, size(b)
end program test_transfer

Another option might be to put the subroutine body into an extra file and then

subroutine unique(tt,tunique)
  class(t), allocatable, intent(in) :: tt(:)
  class(t), allocatable, intent(out) :: tunique(:) ! same type as tt
#include "body.f90"
end subroutine unique

Then you have to replicate only the interface

@FedericoPerini,

Your description suggests your need is one that must be part of the Generics effort i.e., a templated approach. However the first revision toward this is only Fortran 202Y and it’s likely decades away from seeing the light of day in terms of actual implementations in processors. You also run the risk it may never make it into the FOSS compiler you use commonly.

So one can empathize with you looking for a workaround. Unfortunately trying to fit your filtering use case with polymorphism and inheritance is more trouble than these facilities are worth. I suggest you look for something far simpler and seemingly less elegant, say with INCLUDE files, and stick with explicit type safety.

module base_m
   ..
   type, abstract :: base_t
      ! any fields and methods as appropriate for a base class
   end type
   ..
end module base_m
module ext1_m
   ..
   use base_m ..
   ..
   type, extends(base_t) :: ext1_t
      .. ! any fields and methods as applicable for this extension type
   end type
   ..
   generic :: unique => unique_ext1
   ..
contains
   ..
   subroutine unique_ext1( tt, tunique )
      type(ext1_t), allocatable, intent(in) :: tt(:)
      type(ext1_t), allocatable, intent(out) :: tunique (:)
      include "make_unique.i90"
   end subroutine
..
end module

With the above, you reduce the duplication of code that forms the real crux of instructions. However for each extension type, you do replicate the boiler-plate type of code. And you can keep extending the generic interface so the consumers work with filtering with seemingly the same API.

Thank you @FortranFan and @rcs for the help,

your suggestions make me conclude that the include approach seems like the best way to go right now.

Actually, I think it’s more in the polymorphism realm: the “unique” function could well be defined in the abstract class, and we already have same-type allocation via the allocate(.., source=) option. What we can’t do is to write non-polymorphic assumed-type routines from a polymorphic class.

What I’m trying to say is that polymorphism ensures that all the type-bound functions that are needed for the generic routine (unique in this case) are defined on the abstract class, but yeah I’m no generics expert, so I may be wrong here.