Dynamic user-procedure list initialization

Hi, I’m trying to refactor a code meant to enable users adding their own implementations. Not replacing a generic but actually adding to a list of procedures. I have come up with an idea but I’m not too happy with the initialization procedure, and pondering about possible efficiency issues so I would like to ask for any advice if this could be done in a better way:

Here a minimal working example:

code
! this should be in a mod_head.f90
module mod_head
! This module would be unique within the program and its objective is to group the needed
! functionalities and variables for the dynamic procedures creation
        implicit none
        
        type :: user_procedure
            procedure(abs_sub), pointer :: tsub => null()
        end type
        
        abstract interface
            subroutine abs_sub(self,x)
                import :: user_procedure
                class(user_procedure) :: self
                real(8), intent(in) :: x
            end subroutine
        end interface
        
        type(user_procedure), allocatable :: head_procedures(:)
        
        contains
        
        subroutine add_procedure(list,newsze)
            type(user_procedure), allocatable :: list(:)
            type(user_procedure), allocatable :: tempo(:)
            integer, intent(inout) :: newsze
            integer                   :: i
            !-------------------------------------------------
            if(.not.allocated(list)) then
                newsze = 1
                allocate( list( newsze ) )
            else 
                newsze = size( list ) + 1
                allocate( tempo( newsze ) )
                tempo(1:newsze-1)  = list(1:newsze-1) 
                call move_alloc( from=tempo , to=list )
            end if
        end subroutine add_procedure
        
end module mod_head

! this should be in a mod_user1.f90. This is the file the user should create
module mod_user1
! this is an example of what a stand alone user implementation could look like.
        use mod_head
        implicit none
        
        contains

        subroutine sub_user( self , x )
            class(user_procedure) :: self
            real(8), intent(in) :: x
            !----------------------------
            ! actual implementation
            print *, x
        end subroutine
end module

! this should be in a mod_user2.f90 This is another user file
module mod_user2
! this is an example of what a stand alone user implementation could look like.

        use mod_head
        implicit none
        
        contains
        
        subroutine sub_user( self , x )
            class(user_procedure) :: self
            real(8), intent(in) :: x
            !----------------------------
            ! actual implementation
            print *, x**2
        end subroutine
end module

program main
    use mod_head
    
    use mod_user1, only: sub1 => sub_user
    use mod_user2, only: sub2 => sub_user
    
    implicit none
    
    integer :: i, sze
    real(8) :: x
    !-----------------------

    call add_procedure(head_procedures,sze)
    head_procedures(sze)%tsub => sub1
    
    call add_procedure(head_procedures,sze)
    head_procedures(sze)%tsub => sub2
    
    x = 2.d0
    
    do i = 1, size(head_procedures)
        call head_procedures(i)%tsub(x)
    end do

end program main

This enables me to create an array of procedures dynamically, but since I had to define a procedure to reallocate the list and point to the new implementation on each user module I’m also obliged to do

use mod_user1, only: sub1 => sub_user
use mod_user2, only: sub2 => sub_user
...
call add_procedure(head_procedures,sze)
head_procedures(sze)%tsub => sub1
    
call add_procedure(head_procedures,sze)
head_procedures(sze)%tsub => sub2

somewhere in the main program.

In my actual code I already have several hundred procedures, so I would rather avoid having to explicitly write a call to this procedures also, or at least parametrize it. Ideally I would preferer to initialize the list of procedures at compile time with available user module files (Ex: I should be able to compile with only mod_user1.f90 if the other file is not present). Or at least to call the initialization at run-time at the very beginning of the program.

I’m thinking about using macros to get the job done but I’m not sure how to pass the name of found files, lets say with CMake, to some macro that shall proceed.

Any suggestions? Thank you in advance

I can think of two solutions:

  • Extend add_procedure with the argument sub1, so that you do not need the second statement.
  • Use automatic reallocation, something like:
head_procedures = [head_procedures, user_procedure(sub1)]

(the latter “user_procedure” is the constructor for the derived type user_procedure)

I have not tested the second solution, but I use similar constructions all the time ;). Though not often with procedure pointers. That is my only hesitation.

1 Like

That was a very good idea, thank you!! here an update of the m.w.e.

Code
module mod_head
        implicit none
        
        type :: user_procedure
               character(32) :: name = ''
               procedure(abs_sub), pointer, nopass :: tsub => null()
        end type
        
        abstract interface
            subroutine abs_sub(x)
                real(8), intent(in) :: x
            end subroutine
        end interface
        
        type(user_procedure), allocatable :: head_procedures(:)
        
        contains
        
        function constructor(usub,s) result(p)
            type(user_procedure) :: p
            procedure(abs_sub)  :: usub
            character(*), intent(in) :: s
            p%name = s
            p%tsub => usub
        end function
        
end module mod_head

 module mod_user_1
        implicit none
        contains
        
        subroutine sub_user( x )
            real(8), intent(in) :: x
            !----------------------------
            ! actual implementation
            print *, x
        end subroutine
end module

module mod_user_2
        implicit none
        contains
        
        subroutine sub_user( x )
            real(8), intent(in) :: x
            !----------------------------
            ! actual implementation
            print *, x**2
        end subroutine
end module

subroutine initialize_head()
    use mod_head
    use mod_user_1, only: sub_1 => sub_user
    use mod_user_2, only: sub_2 => sub_user
    !-----------------------
    head_procedures = [head_procedures,constructor( sub_1 , '1' )]
    head_procedures = [head_procedures,constructor( sub_2 , '2' )]
end subroutine initialize_head

program main
    use mod_head

    implicit none
    
    integer :: i
    real(8) :: x
    !-----------------------
    
    call initialize_head()
    
    x = 2.d0
    
    do i = 1, size(head_procedures)
        call head_procedures(i)%tsub(x)
    end do

end program main

This is much cleaner! still looking for a way to simplify the compilation such that it can be dynamically adapted if the mod_user_#.f90 files are found or not.

I am not entirely sure what you are looking for. If a user adds a source file to the mix, then it is up to the compiler and linker to do the right thing. CMake can certainly help, but you need a mechanism to recognise this in he source code. Could you elaborate on the way the user is supposed to contribute? I can imagine that the user edits a source file or it may be that it is arranged by explicltly loading a dynamic load library/shared object, based on input at run-time.

So, today the user adds his implementation by modifying a pre-existing file that gets bigger and bigger, for maintenance it becomes complicated. The idea is to split that into 1 procedure = 1 file. I also need to make sure that the user will only focus on his implementation and not with all the boiler plate for creating the project he’ll be compiling.
So at the end I will be able to guide the user with something like: Crete a file following a template and put it in a specific folder. To build the project and debug in windows (Visual Studio) relaunch the .sln, for linux launch nmake.

For the moment I found a lazy work around that might do the trick:
In the pre-processing step I can call a python file like:

Lets say the modules are inside a folder ‘lib’

lib_preprocess.py
import os

list_modules = [ f.lstrip('mod_user_').rstrip('.f90') for f in os.listdir(os.path.join( os.path.dirname( os.getcwd() ),  'lib' )) ]

with open('lib_preprocess.f90','w') as file:
    file.write('subroutine initialize_head()\n')
    file.write('    use mod_head\n')
    for name in list_modules:
        file.write('    use mod_user_'+name+', only: sub_'+name+' => sub_user\n')

    for name in list_modules:
        file.write('    head_procedures = [head_procedures,constructor( sub_'+name+' , \''+name+'\' )]\n')
    file.write('end subroutine initialize_head\n')

If I just have two files ‘mod_user_1.f90’ and ‘mod_user_2.f90’ this will create the following file which will have a constant signature name:

lib_preprocess.f90
subroutine initialize_head()
    use mod_head
    use mod_user_1, only: sub_1 => sub_user
    use mod_user_2, only: sub_2 => sub_user
    head_procedures = [head_procedures,constructor( sub_1 , '1' )]
    head_procedures = [head_procedures,constructor( sub_2 , '2' )]
end subroutine initialize_head

This enables me to just do ‘call initialize_head()’ somewhere in the main to get all available procedures in the list.

I’m still working on the idea, it is a very early prototype.

I would say the easiest solution is via CMake (it is not always easy, but you do not have to worry about VS solutions or makefiles then). You may want to use the Python script to scan for relevant source files and then create a file that refers to them in a convenient way.

1 Like

Yes, I’m working on a CMakeLists.txt file to create the project in a cross-platform compatible way and that calls the python script in order to parse the folders accordingly. :+1: