Defining a variant data type using a derived type with scalar allocatable components

One can get some of the functionality of a variant data type with a derived type having scalar allocatable components of the basic types, as shown below. I wonder if this is useful and whether it’s a better approach than defining a derived type with an unlimited polymorphic class(*) component.

module t_mod
implicit none
interface t
   module procedure set_int, set_real, set_character, set_logical
end interface t
type :: t
   private
   integer, allocatable :: i
   real   , allocatable :: x
   logical, allocatable :: b
   character (len=:), allocatable :: s
end type t
contains
!
elemental function set_int(i) result(a)
integer, intent(in) :: i
type(t) :: a
a%i = i
end function set_int
!
elemental function set_real(x) result(a)
real, intent(in) :: x
type(t) :: a
a%x = x
end function set_real
!
elemental function set_character(s) result(a)
character (len=*), intent(in) :: s
type(t) :: a
a%s = s
end function set_character
!
elemental function set_logical(b) result(a)
logical, intent(in) :: b
type(t)      :: a
a%b = b
end function set_logical
!
impure elemental subroutine print(a)
type(t), intent(in) :: a
if (allocated(a%i)) print*,a%i
if (allocated(a%x)) print*,a%x
if (allocated(a%s)) print*,a%s
if (allocated(a%b)) print*,a%b
end subroutine print
!
end module t_mod
!
program test_t
use t_mod
type(t), allocatable :: a(:)
a = [t([3,4]),t(5.2),t(["abc","def"]),t([.false.,.true.])]
call print(a)
end program test_t

Output:

           3
           4
   5.200000    
 abc
 def
 F
 T
1 Like

I’ve done this on some occasions and I think it’s the best way to mimic enums/tagged unions/variants/sum data types or whatever one wants to call them.

The downside is that one could end up with multiple of the variants allocated. By using class(*) that’s not a problem, but one loose a bit of static analysis since the value might be anything.

Overloading the assignment operator for the type might make the code slightly more elegant, though that is highly subjective :wink:

I wish Fortran could get proper support for such data types, they’re very useful in other languages!

1 Like