Define variables as same kind as class(*)?

At FortranTip, Filipe Guimarães asked

Is there an “assumed kind” or a way to test the kind of a variable when using class() or type()? I’d like a funct. or subr. to receive single or double precision, and depending on the kind, do different things (even better if I could define variables of the same [unknown] kind)

The answer to the main question is yes, using select type on a class(*) argument, as shown by the code below, but is it possible to “define variables of the same [unknown] kind”?

module check_kind_mod
use iso_fortran_env, only: real32, real64
implicit none
contains
subroutine sub(x)
class(*), intent(in) :: x
select type (x)
   type is (real(real32))
      print*,"type is real32"
   type is (real(real64))
      print*,"type is real64"
end select
end subroutine sub
end module check_kind_mod
!
program main
use check_kind_mod
implicit none
call sub(1.0)
call sub(1.0d0)
end program main
! output:
!  type is real32
!  type is real64

The only options that come to my mind are:

  1. Predefine variables of all types that may be used and then assign the passed polymorphic object to one of them in select type construct
  2. Define additional pointer(s) of class(*) and allocate it/them in select type. This option, however, won’t take you out of the use of select type again to make anything with those pointers
module check_kind_mod
  use iso_fortran_env, only: real32, real64
  implicit none
contains
  subroutine sub(x)
    class(*), intent(in) :: x
    class(*), pointer :: var
    real(real32) :: rvar
    real(real64) :: dvar
    select type (x)
    type is (real(real32))
      allocate(real(real32) :: var)
      rvar = x
      call sub32(rvar)
    type is (real(real64))
      allocate(real(real64) :: var)
      dvar = x
      call sub64(dvar)
    end select
    call sub2(var)
  end subroutine sub
  subroutine sub32(v)
    real(real32) :: v
    print*,"type is real32",kind(v)
  end subroutine sub32
  subroutine sub64(v)
    real(real64) :: v
    print*,"type is real64",kind(v)
  end subroutine sub64
  subroutine sub2(v)
    class(*), pointer :: v
    select type (v)
      type is (real(real32))
      ! ...
      type is (real(real64))
      ! ...
    end select
  end subroutine sub2
end module check_kind_mod
!
program main
use check_kind_mod
implicit none
call sub(1.0)
call sub(1.0d0)
end program main
! output:
!  type is real32    4
!  type is real64    8

For allocation I think the following would do the trick:

subroutine sub(x)
class(*), intent(in) :: x

class(*), allocatable :: val

allocate(val, mold=x) 
end subroutine sub

In order to actually do useful things with the variable one need to use select type to check for the concrete type first though…

1 Like

One can use BLOCK to define variables of the kind in the type is statement. Now the module is

module check_kind_mod
use iso_fortran_env, only: real32, real64
implicit none
contains
subroutine sub(x)
class(*), intent(in) :: x
select type (x)
   type is (real(real32))
   block
       real(real32) :: y,z
       print*,"type is real32"
   end block
   type is (real(real64))
   block
       real(real64) :: y,z
       print*,"type is real64"
   end block
end select
end subroutine sub
end module check_kind_mod
1 Like