Here is the source code:
!==================================================================================================
module InitValModeClass
implicit none
! Declare Basic Class and Interfaces for Initialize Data Procedures
type, public :: InitCommonMain
integer(kind=4) :: x
contains
end type InitCommonMain
! Declare Extended Class and Methods for Different Mode Combinations
!--------------------------------
type, public, extends (InitCommonMain) :: InitParaRec2SP
integer(kind=4) :: aaa, bbb, ccc
contains
procedure, nopass, public :: initParamFldPls => InitParaRec2SP_initParamFldPls
end type InitParaRec2SP
! Restrict Accessing to the Subroutines with Real Name
private :: InitParaRec2SP_initParamFldPls
!--------------------------------
type, public, extends (InitCommonMain) :: InitParaRec3SP
integer(kind=4) :: aaa, bbb, ccc
contains
procedure, nopass, public :: initParamFldPls => InitParaRec3SP_initParamFldPls
end type InitParaRec3SP
! Restrict Accessing to the Subroutines with Real Name
private :: InitParaRec3SP_initParamFldPls
!******************************************************************************************
! Declare Wrapper Module from Various Class
type :: InitProcedWrap
class(InitCommonMain), allocatable :: subprocedure
contains
procedure, pass(this), public :: createSubProced => InitProcedWrap_createSubProced
end type InitProcedWrap
! Restrict Accessing to the Subroutines with Real Name
private :: InitProcedWrap_createSubProced
!******************************************************************************************
! Declare Instance Process from Wrapper Class
type (InitProcedWrap), save :: initParaBranch
!******************************************************************************************
contains
!------------------------------------------------------------------------------------------
subroutine InitParaRec2SP_initParamFldPls()
implicit none
end subroutine InitParaRec2SP_initParamFldPls
!------------------------------------------------------------------------------------------
subroutine InitParaRec3SP_initParamFldPls()
implicit none
end subroutine InitParaRec3SP_initParamFldPls
!------------------------------------------------------------------------------------------
subroutine InitProcedWrap_createSubProced(this)
implicit none
class(InitProcedWrap), intent(inout) :: this
!allocate(this%subprocedure)
print*,InitParaRec2SP(6, 7, 8, 9)
this%subprocedure = InitParaRec2SP(11, 12, 13, 14)
print*,this%subprocedure
end subroutine InitProcedWrap_createSubProced
!------------------------------------------------------------------------------------------
end module InitValModeClass
!==================================================================================================
In the command “this%subprocedure = InitParaRec2SP(11, 12, 13, 14)
” I do the class assignment using polymorphism, but I got “6 7 8 9
” and “11
” respectively from two print command. It seems that the type “subprocedure
” does not inherit the extended type “InitParaRec2SP
”. How can I fix it?