Christoph90
Christoph90

Reputation: 673

How are function interfaces specified in abstract interface blocks for deferred binding as a type bound procedure?

I want to declare an abstract type abstract_tensor and specify some procedures (including their interfaces) that every type extending abstract_tensor must implement.

As an example, let's say I want every type extending abstract_tensor to have a type bound procedure sph that returns an instance of the concrete type and is a function, not a subroutine.

Here's a non-compiling implementation of that situation:

module tensors

  implicit none

  private
  public :: sym_tensor

  type, abstract :: abstract_tensor
   contains
     procedure(tr_interface), deferred :: tr
     procedure(sph_interface), deferred :: sph
  end type abstract_tensor

  abstract interface
     !! intrinsic return type works
     function tr_interface(self)
       import :: abstract_tensor
       class(abstract_tensor), intent(in) :: self
       real :: tr_interface
     end function tr_interface
     !! abstract return type not - how do I define the return type correctly here?
     function sph_interface(self)
       import :: abstract_tensor
       class(abstract_tensor), intent(in) :: self
       class(abstract_tensor) :: sph_interface
     end function sph_interface
  end interface

  type, extends(abstract_tensor) :: sym_tensor
     real :: xx = 0.0
     real :: yy = 0.0
     real :: zz = 0.0
     real :: xy = 0.0
     real :: yz = 0.0
     real :: xz = 0.0
   contains
     procedure :: tr => trace
     procedure :: sph => spherical_part
  end type sym_tensor

contains

  real function trace(self)
    class(sym_tensor), intent(in) :: self
    trace = self%xx + self%yy + self%zz
  end function trace

  type(sym_tensor) function spherical_part(self)
    class(sym_tensor), intent(in) :: self
    real :: tr
    tr = 1.0/3.0*self%tr()
    spherical_part = sym_tensor(tr, tr, tr, 0.0, 0.0, 0.0)
  end function spherical_part

end module tensors

program main

  use tensors, only: sym_tensor

  implicit none

  type(sym_tensor) :: t

end program main

Here, sym_tensor extends abstract_tensor and the type bound procedures tr and sph compute it's trace and hydrostatic part. The return type of the tr should be real, the return type of sph should be another sym_tensor.

How can I define the return type of sph_interface in the abstract interface block so that this compiles and forces every type extending the abstract type to implement such a function?

Upvotes: 3

Views: 212

Answers (1)

veryreverie
veryreverie

Reputation: 2981

In Fortran, all abstract polymorphic variables must be one of:

  • dummy variables
  • pointers
  • allocatables

Your abstract function

function sph_interface(self)
  import :: abstract_tensor
  class(abstract_tensor), intent(in) :: self
  class(abstract_tensor) :: sph_interface
end function sph_interface

returns a variable of class(abstract_tensor), which is an abstract polymorphic variable but not one of the above.

The easiest change is to make the return type allocatable:

function sph_interface(self)
  import :: abstract_tensor
  class(abstract_tensor), intent(in) :: self
  class(abstract_tensor), allocatable :: sph_interface
end function sph_interface

And then the sym_tensor implementation needs to have a matching signature:

function spherical_part(self)
  class(sym_tensor), intent(in) :: self
  class(abstract_tensor), allocatable :: spherical_part
  real :: tr
  tr = 1.0/3.0*self%tr()
  spherical_part = sym_tensor(tr, tr, tr, 0.0, 0.0, 0.0)
end function spherical_part

This will compile, but may well cause a segfault, because the compiler doesn't like the polymorphic assignment

spherical_part = sym_tensor(tr, tr, tr, 0.0, 0.0, 0.0)

you can solve this by replacing the simple assignment with a sourced allocation,

allocate(spherical_part, source=sym_tensor(tr, tr, tr, 0.0, 0.0, 0.0))

I am unsure if the sourced allocation is needed due to a limitation of the Fortran standard or a limitation of the compiler.

Upvotes: 2

Related Questions