Understanding the need for class variables and select type

I have no experience with OOP in any language and am trying to understand how it works in Fortran. Trying some code, it seemed that Fortran required select type for a class variable even when the type should be known at compile time. I think the reason is that it’s possible to have situations where the type cannot be known at compile time. Since select type seems a bit verbose, and since it has some run time cost, is it fair to say that one should avoid class variables and use types instead unless their flexibility is needed?

module m
implicit none
type :: a
  integer :: i
end type
!
type, extends(a) :: b
  integer :: j
end type
!
contains
subroutine set(c)
! c can be either type(a) or type(b) upon return
class(a), intent(out), allocatable :: c
real :: x
call random_number(x)
if (x > 0.5) then
   c = a(i=3)
else
   c = b(i=3,j=4)
end if
end subroutine set
end module m

program poly
use m
implicit none
class(a), allocatable :: c, d
type(b) :: z
integer :: k
z = b(i=3,j=4)
print*,z%i,z%j
c = a(i=3)
! print*,c%i,c%j ! I understand why this does not work.
c = b(i=3,j=4)
! Although c has type b here, sometimes the type of c is known only at run-time. 
! print*,c%i,c%j ! Error: 'j' at (1) is not a member of the 'a' structure
select type (c)
   type is (b)
      print*,c%i,c%j ! works within select type
end select
do k=1,10
   call set(d) ! At compile time, type of d is unknown.
   print*,same_type_as(c,d)
end do
end program poly
2 Likes

My recommendations are that one should use type, or carefully design deferred type bound procedures defined by the type that one will declare variables of class of such that any select types will be unnecessary.

2 Likes

@beliavsky, for a good introduction to OOP in Fortran I highly recommend the chapter on Object-Oriented programming in Stephen Chapman’, “Fortran for Scientists and Engineers (4th edition”, McGraw-Hill. When I first starting trying to learn OOP I struggled with a lot of the concepts because they were usually described in languages (C++, Smalltalk, etc) that I had no experience with. Just being able to see the concepts expressed in Fortran was a big help, plus I think Chapman’s discussion of OOP is one of the clearest and easiest to understand that I’ve seen for any language. Also, this book appears to have undergone a large drop in price lately. It was around $335 dollars at one time. Amazon currently lists the paperback version at $127 and the eBook at $67

3 Likes

Reading Metcalf/Reid/Cohen and Chapman, I was able to write my first abstract type with a deferred procedure. As said above, with abstract types one can get run-time polymorphism without the need for select type.

module person_mod
implicit none
!
type, abstract, public :: person
  character (len=20) :: name
  contains
    procedure(display_p), deferred :: display 
end type person
!
abstract interface
   subroutine display_p(this)
   import person
   implicit none
   class(person), intent(in) :: this
   end subroutine display_p
end interface
!
type, extends(person) :: worker
  integer :: pay
  contains
    procedure :: display => display_worker
end type
!
type, extends(person) :: student
  integer :: grade
  contains
    procedure :: display => display_student
end type
character (len=*), parameter :: fmt_d = "(3a8,i8)"
!
contains
!
subroutine display_worker(this)
class(worker), intent(in) :: this
print fmt_d,"name = ",this%name," pay =",this%pay
end subroutine display_worker
!
subroutine display_student(this)
class(student), intent(in) :: this
print fmt_d,"name = ",this%name," grade =",this%grade
end subroutine display_student
!
end module person_mod
!
program test_person
use person_mod, only: person, worker, student
implicit none
type(worker)  :: w
type(student) :: s
class(person), allocatable :: p
w = worker("Ed",50000)
s = student("Ann",11)
call w%display()
p = w
call p%display()
call s%display()
p = s ! p has new type
call p%display()
end program test_person

Output:

 name = Ed         pay =   50000
 name = Ed         pay =   50000
 name = Ann      grade =      11
 name = Ann      grade =      11
2 Likes