Fortran Polymorphism Assignment Issue

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?

Welcome to the forum, @kyran!

You cannot use list-directed format (*) for a polymorphic entity. So I wonder how you were able to compile and test the code. I have immediately got error from gfortran (similarly from ifx):

$ gfortran class_assign.f90 
class_assign.f90:54:28:

   54 |     print*,this%subprocedure
      |                            1
Error: Data transfer element at (1) cannot be polymorphic unless it is processed by a defined input/output procedure

It seems that the way to go is either to write a dedicated I/O procedure or do it “by hand” as follows:

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)
    select type (s => this%subprocedure)
      type is (InitParaRec2SP)
        print*, s%x, s%aaa, s%bbb, s%ccc
      class is (InitCommonMain)
        print*, s%x
      end select
  end subroutine InitProcedWrap_createSubProced

Then, a super-simple program

program m
  use InitValModeClass
  implicit none

  call initParaBranch%createSubProced()
end program m

produces expected output:

$ ifx class_assign.f90 
$ ./a.out
           6           7           8           9
          11          12          13          14

Hi, msz59. Thank you for your try out. When I was coding, I referred to the examples in the book 《Introduction to Programming with Fortran》 by Ian Chivers and Jane Sleightholme. I originally suggested that the with only one expression this%subprocedure = InitParaRec2SP(11, 12, 13, 14) I could assign the subprocedure to the extended type InitParaRec2SP. And this is how the example demonstrated in the book. However, your reply indicates that it should go through a type selection and then it’s explicit type can be determined. Is that right?

Well, as you see in my snippet, the assignment itself was left untouched and it is OK to assign an entity of a derived type (here, a type constructor) to a polymorphic object of proper class.
There are, however, restrictions on the use of such a polymorphic object, and it often requires select type construct to access its detailed content. I’m no expert on OOP in Fortran (or elsewhere) so maybe some other forumers can shed more light on the topic.

Sweet, thanks again for the clarification. By the way, I’m programming with f08, maybe it has additional feature supporting direct assignment.