在 Fortran 扩展类型中指定多态组件

Specify polymorphic component in Fortran extended type

我正在编写一个定义两个派生类型的模块,每个派生类型都有一个具有公共父类型的派生类型组件,如下所示。

   type :: aux0
      integer :: a
   end type aux0

   type, extends(aux0) :: aux1
      integer :: b
   end type aux1

   type, extends(aux0) :: aux2
      integer :: c
   end type aux2

我想定义两个派生类型,每个派生类型分别具有 aux1aux2 类型的组件。我有几个例程,它们仅基于字段 aux % a(例如 fun1)执行一些工作。我想将这些方法绑定到 cplx1cplx2。因此,我为 cplx1cplx2 创建了一个公共父级,其字段 aux 为 class aux0 并编写了一个接口 class aux0 常用函数的变量。但是,我想在实际类型 cplx1cplx2 中指定 aux 组件的类型,因为一些其他函数需要字段 aux 的明确类型。我想知道这是如何或是否可行的。

module type

   ! ... aux# types definitions

   type :: cplx0
      class(aux0), allocatable :: aux(:)
   contains
      ! routines that use aux % a
      procedure, pass :: fun1
   end type cplx0

   type, extends(cplx0) :: cplx1
      ! type(aux1) :: aux(:) ! doesn't work
   contains
      ! routines that use aux % b
   end type cplx1

   type, extends(cplx0) :: cplx2
      ! type(aux2) :: aux(:)! doesn't work
   contains
      ! routines that use aux % c
   end type cplx2

contains 

   function fun1(self)
      class(cplx0) :: self
      integer      :: i
      do i = 1, size(self % aux)
         print *, self % aux(i) % a
      end do 
   end function fun1

  ! ... more functions

end module type

如果我取消注释 type(aux1),错误是

Error: Component ‘aux’ at (1) already in the parent type at (2)

这是可以理解的,但我想知道如何规避它。

这是不可能的。如果您想通过组件类型应用约束,基于在某种扩展层次结构中保存组件的类型,则需要在扩展中定义组件。

鉴于 post 中的示例代码,fun1 中的逻辑不需要绑定到 cplx 类型层次结构(它看起来不像是在cplx 层次结构将覆盖)。 fun1 中的逻辑可以在非类型绑定过程中,采用 aux 类型的多态对象,实现 cplx 的延迟绑定转发到。

Alternatively/more 通常,而不是 fun1 直接在 aux 组件上操作,让它通过绑定在该组件的等效项上操作。例如:

module aux_module
  implicit none

  type :: aux0
    integer :: a
  end type aux0

  type, extends(aux0) :: aux1
    integer :: b
  end type aux1

  type, extends(aux0) :: aux2
    integer :: c
  end type aux2
contains
  ! Really the logic in `fun1` from the question's example code
  ! doesn't have to be within a binding.  It could be factored out.
  subroutine proc2(aux)
    class(aux0), intent(in) :: aux(:)
    integer :: i
    do i = 1, size(aux)
      print *, aux(i) % a
    end do 
  end subroutine proc2
end module aux_module

module cplx_module
  use aux_module
  implicit none

  type, abstract :: cplx0
  contains
    ! Does this have to be a binding?
    procedure :: proc1
    procedure(cplx0_get_aux), deferred :: get_aux
  end type cplx0

  interface
    function cplx0_get_aux(c)
      import cplx0
      import aux0
      implicit none
      class(cplx0), intent(in), target :: c
      ! we return a pointer in case we want it to be on the 
      ! left hand side of an assignment statement.
      class(aux0), pointer :: cplx0_get_aux(:)
    end function cplx0_get_aux
  end interface

  type, extends(cplx0) :: cplx1
    type(aux1) :: aux(2)
  contains
    procedure :: get_aux => cplx1_get_aux
  end type cplx1

  type, extends(cplx0) :: cplx2
    type(aux2) :: this_doesnt_have_to_be_called_aux(3)
  contains
    procedure :: get_aux => cplx2_get_aux
  end type cplx2
contains
  ! The internals of this could just forward to proc2.
  subroutine proc1(self)
    class(cplx0), target :: self
    integer      :: i
    associate(the_aux => self%get_aux())
      do i = 1, size(the_aux)
        print *, the_aux(i) % a
      end do 
    end associate
  end subroutine proc1

  function cplx1_get_aux(c)
    class(cplx1), intent(in), target :: c
    class(aux0), pointer :: cplx1_get_aux(:)
    cplx1_get_aux => c%aux
  end function cplx1_get_aux

  function cplx2_get_aux(c)
    class(cplx2), intent(in), target :: c
    class(aux0), pointer :: cplx2_get_aux(:)
    cplx2_get_aux => c%this_doesnt_have_to_be_called_aux
  end function cplx2_get_aux
end module cplx_module

program p
  use cplx_module
  implicit none

  type(cplx1) :: c1
  type(cplx2) :: c2

  c1 = cplx1([aux1(a=1,b=2), aux1(a=11,b=22)])
  call c1%proc1
  ! call proc2(c1%aux)

  c2 = cplx2([aux2(a=1,c=2), aux2(a=11,c=22), aux2(a=111,c=222)])
  call c2%proc1
  ! call proc2(c2%this_doesnt_have_to_be_called_aux)
end program p