tem_open_distconf Subroutine

public subroutine tem_open_distconf(L, fileName, proc)

Read a Lua file on the first process and distribute it to all.

Todo

HK: Maybe deprecate and remove this routine in favor of TEM_open_distconf_array to avoid code duplication? Or keep it around and put a generic interface in place?

This is a drop in replacement for open_config_file from Aotus and allows the scalable processing of Lua files, as they are read by a single process and then streamed to all in proc. There should be no restrictions on the Lua scripts themselves in this method, as it uses an overloading of the require mechanism in Lua itself to replace the file searches by lookups of buffered Lua code snippets. The execution of the Lua script itself is not changed.

Arguments

Type IntentOptional Attributes Name
type(flu_State) :: L
character(len=*), intent(in) :: fileName
type(tem_comm_env_type), intent(in) :: proc

Process description to use.


Source Code

  subroutine tem_open_distconf(L, fileName, proc)
    ! -------------------------------------------------------------------- !
    type(flu_State) :: L !< Opened Lua state with the loaded script.
    character(len=*), intent(in) :: fileName !< Name of the file to open.
    !> Process description to use.
    type(tem_comm_env_type), intent(in) :: proc
    ! -------------------------------------------------------------------- !
    type(cbuf_type) :: scriptbuf
    type(cbuf_type) :: modbuf
    integer :: iError
    integer :: comm
    integer :: nProcs
    integer :: nFiles
    integer :: bufsize
    integer :: iFile
    character(len=labelLen), allocatable :: req_label(:)
    character(len=pathLen), allocatable  :: req_file(:)
    ! -------------------------------------------------------------------- !

    comm = proc%comm
    nProcs = proc%comm_size

    if (nProcs > 1) then

      if ( proc%isRoot ) then
        ! Only rank 0 reads and executes the config file, while doing so, it
        ! keeps track of all the required files.
        call tem_require_track_rq(L)
        call open_config_file(L, trim(filename), buffer=scriptbuf)
        call tem_get_required_Lua( L, fileList = req_file, &
          &                        labelList = req_label   )
        nFiles = size(req_Label)
      else
        ! Open the configuration on all other processes with the rq_store
        ! loaded:
        call tem_require_rq_store(L)
        ! this is necessary to suppress valgrind debug output
        nFiles = 0
      end if

      ! Broadcast the number of required files
      ! MPI_BCAST(BUFFER, COUNT, DATATYPE, ROOT, COMM, IERROR)
      call MPI_Bcast(nFiles, 1, MPI_INTEGER, proc%root, comm, iError)

      if ( .not. proc%isRoot ) allocate(req_label(nFiles))
      if ( .not. proc%isRoot ) allocate(req_file(nFiles))

      ! Broadcast the module names
      call MPI_Bcast( req_label, nFiles*labelLen, MPI_CHARACTER, proc%root, &
        &             comm, iError                                          )
      ! Broadcast the file names
      call MPI_Bcast( req_file, nFiles*pathLen, MPI_CHARACTER, proc%root, &
        &             comm, iError                                        )

      ! Now go on opening all required files
      do iFile=1,nFiles
        if ( proc%isRoot ) then
          call tem_pop_from_track_rq(L, trim(req_label(iFile)), modbuf)
          bufsize = size(modbuf%buffer)
        end if
        ! Broadcast the loaded script to all processes.
        ! MPI_BCAST(BUFFER, COUNT, DATATYPE, ROOT, COMM, IERROR)
        call MPI_Bcast(bufsize, 1, MPI_INTEGER, proc%root, comm, iError)
        if ( .not. proc%isRoot ) allocate(modbuf%buffer(bufsize))
        call MPI_Bcast( modbuf%buffer, bufsize, MPI_CHARACTER, proc%root, &
          &             comm, iError                                      )
        if ( .not. proc%isRoot ) then
          call tem_push_to_rq_store( L,                                 &
            &                        modname  = trim(req_label(iFile)), &
            &                        filename = trim(req_file(iFile)),  &
            &                        buffer   = modbuf%buffer           )
          deallocate(modbuf%buffer)
        else
          call flu_free_cbuf(modbuf)
        end if
      end do

      ! Broadcast the loaded script to all processes.
      if ( proc%isRoot ) bufsize = size(scriptbuf%buffer)
      ! MPI_BCAST(BUFFER, COUNT, DATATYPE, ROOT, COMM, IERROR)
      call MPI_Bcast(bufsize, 1, MPI_INTEGER, proc%root, comm, iError)
      if ( .not. proc%isRoot ) allocate(scriptbuf%buffer(bufsize))
      call MPI_Bcast( scriptbuf%buffer, bufsize, MPI_CHARACTER, proc%root, &
        &             comm, iError                                         )

      if ( .not. proc%isRoot ) then
        call open_config_buffer(L = L, buffer = scriptbuf%buffer)
        deallocate(scriptbuf%buffer)
      else
        call flu_free_cbuf(scriptbuf)
      end if

    else

      ! Only a single process, no need for broadcasting.
      call open_config_file(L = L, filename = trim(fileName))

    end if

  end subroutine tem_open_distconf