Generic programming by renaming module imports

Here is an idea for generic programming I had. You may wish, for example, to have a derived type for a time series

type :: time_series_t
   type(time_t), allocatable :: times(:) ! (nobs)
   real        , allocatable :: x(:)     ! (nobs)
end type time_series_t

where the definition of type :: time_t is flexible. It could contain [year,month] or [year,month,day] or [year,month,day,hour,minute]. In the past I have duplicated code and created separate time series derived types for these cases, but I wonder if module entity renaming can avoid this. The code

module date_mod
implicit none
interface str
   module procedure str_ymd, str_ym
end interface str
type :: date_ymd_t
   integer :: year, month, day
end type date_ymd_t
!
type :: date_ym_t
   integer :: year, month
end type date_ym_t
!
contains
function str_ymd(date) result(s)
type(date_ymd_t), intent(in) :: date
character (len=20)           :: s
write (s,"(i4.4,2('-',i2.2))") date%year, date%month, date%day
end function str_ymd
!
function str_ym(date) result(s)
type(date_ym_t), intent(in) :: date
character (len=20)           :: s
write (s,"(i4.4,'-',i2.2)") date%year, date%month
end function str_ym
end module date_mod
!
module time_series_mod
use date_mod, only: time_t => date_ymd_t, str
implicit none
type :: time_series_t
   type(time_t), allocatable :: times(:) ! (nobs)
   real        , allocatable :: x(:)     ! (nobs)
end type time_series_t
contains
!
subroutine display_time_series(ts)
type(time_series_t), intent(in) :: ts
integer                         :: i,nobs
nobs = size(ts%times)
do i=1,nobs
   print "(a,1x,f0.4)",trim(str(ts%times(i))),ts%x(i)
end do
end subroutine display_time_series
!
subroutine read_time_series(ts,iu)
type(time_series_t), intent(out) :: ts
integer            , intent(in)  :: iu
integer                          :: i,nobs
read (iu,*) nobs
call alloc_time_series(ts,nobs)
do i=1,nobs
   read (iu,*) ts%times(i),ts%x(i)
end do
end subroutine read_time_series
!
subroutine alloc_time_series(ts,nobs)
type(time_series_t), intent(out) :: ts
integer            , intent(out) :: nobs
allocate (ts%times(nobs),ts%x(nobs))
end subroutine alloc_time_series
end module time_series_mod
!
program main
use time_series_mod
implicit none
type(time_series_t) :: ts
integer, parameter :: iu = 20
character (len=*), parameter :: data_file = "ymd.txt" ! "ymd.txt"
open (unit=iu,file=data_file,action="read")
call read_time_series(ts,iu)
call display_time_series(ts)
end program main

for data file ymd.txt

2
2022 3 6 10.0
2022 3 7 11.0

gives output

2022-03-06 10.0000
2022-03-07 11.0000

and changing time_t => date_ymd_t to time_t => date_ym_t and using data file ym.txt

2
2022 2 10.0
2022 3 11.0

gives output

2022-02 10.0000
2022-03 11.0000

I wonder if this approach scales. It does rely on

read (iu,*) ts%times(i),ts%x(i)

effectively being expanded to

read (iu,*) ts%times(i)%year,ts%times(i)%month,ts%x(i)

or

read (iu,*) ts%times(i)%year,ts%times(i)%month,ts%times(i)%day,ts%x(i)

depending on what time_t refers to. Perhaps there is a better way to get this functionality
using the OOP features of modern Fortran.

Note that with a bit of module juggling you can combine the two implementations in the same program:

module united_timeseries
     use time_series_type1,  time_series_type1 => time_series_t
     use time_series_type2,  time_series_type2 => time_series_t

where the individual time series types have to be in a separate module, but the include statement helps to share the code. It does take some juggling, I admit, so less than ideal, but at least you can hide it from the user.

I would make time_t abstract, then have date_ym_t and date_ymd_t extend it. Then times component of time_series_t can be class(time_t). There’s a few more details to work out in terms of reading and writing, but you’re just about there with your example anyways, so I suspect you could figure that much out, or come back with more specific questions. Good luck.

1 Like