tem_load_depend_vector Subroutine

private subroutine tem_load_depend_vector(me, conf, parent, label, requireCond)

Load variables, parent scheme and conditions defined in lua file. This routine serves as a wrapper and calls the single routine which loads the various arguments

Arguments

Type IntentOptional Attributes Name
type(tem_depend_type), intent(inout), allocatable :: me(:)

list of depend types to be filled

type(flu_State), intent(in) :: conf

lua state to read from

integer, intent(in) :: parent

parent table identifier

character(len=*), intent(in) :: label

label to identify depend type

logical, intent(in), optional :: requireCond

if true? load condition table for each variable


Calls

proc~~tem_load_depend_vector~~CallsGraph proc~tem_load_depend_vector tem_load_depend_vector proc~tem_horizontalspacer tem_horizontalSpacer proc~tem_load_depend_vector->proc~tem_horizontalspacer proc~tem_load_depend_single tem_load_depend_single proc~tem_load_depend_vector->proc~tem_load_depend_single proc~aot_table_open aot_table_open proc~tem_load_depend_vector->proc~aot_table_open proc~aot_table_close aot_table_close proc~tem_load_depend_vector->proc~aot_table_close proc~aot_table_length aot_table_length proc~tem_load_depend_vector->proc~aot_table_length proc~tem_load_depend_single->proc~aot_table_open proc~tem_load_depend_single->proc~aot_table_close proc~tem_load_condition tem_load_condition proc~tem_load_depend_single->proc~tem_load_condition proc~tem_abort tem_abort proc~tem_load_depend_single->proc~tem_abort proc~aot_get_val aot_get_val proc~tem_load_depend_single->proc~aot_get_val proc~tem_load_condition->proc~aot_table_open proc~tem_load_condition->proc~aot_table_close proc~tem_load_condition->proc~aot_table_length proc~tem_load_cond_single tem_load_cond_single proc~tem_load_condition->proc~tem_load_cond_single mpi_abort mpi_abort proc~tem_abort->mpi_abort proc~tem_load_cond_single->proc~tem_abort proc~tem_load_cond_single->proc~aot_get_val

Called by

proc~~tem_load_depend_vector~~CalledByGraph proc~tem_load_depend_vector tem_load_depend_vector interface~tem_load_depend tem_load_depend interface~tem_load_depend->proc~tem_load_depend_vector

Contents


Source Code

  subroutine tem_load_depend_vector(me, conf, parent, label, requireCond)
    !---------------------------------------------------------------------------
    !> list of depend types to be filled
    type(tem_depend_type), allocatable, intent(inout) :: me(:)
    !> lua state to read from
    type(flu_state), intent(in) :: conf
    !> parent table identifier
    integer, intent(in)        :: parent
    !> label to identify depend type
    character(len=*), intent(in) :: label
    !> if true? load condition table for each variable
    logical, optional, intent(in) :: requireCond
    !---------------------------------------------------------------------------
    integer :: iDep, nDeps
    integer :: dep_handle ! local depend table handle
    integer :: dep_sub_handle ! local depend table handle
    !---------------------------------------------------------------------------
    call tem_horizontalSpacer(fUnit = logUnit(1))
    write(logUnit(1),*) 'loading depend table of: '//trim(label)

    ! Open the depend table
    call aot_table_open( L       = conf,                                       &
      &                  parent  = parent,                                     &
      &                  thandle = dep_handle,                                 &
      &                  key     = 'depend' )

    if (dep_handle .ne. 0) then
      ! Check if there are multiple members inside depend
      call aot_table_open( L       = conf,                                     &
        &                  parent  = dep_handle,                               &
        &                  thandle = dep_sub_handle,                           &
        &                  pos     = 1 )
      ! If there is only one member, call the load routine once
      if (dep_sub_handle .eq. 0) then
        allocate(me(1))
        call aot_table_close( L = conf, thandle = dep_sub_handle )
        call tem_load_depend_single( me          = me(1),      &
          &                          conf        = conf,       &
          &                          parent      = dep_handle, &
          &                          label       = label,      &
          &                          requireCond = requireCond )
      else
        call aot_table_close( L = conf, thandle = dep_sub_handle )
        nDeps = aot_table_length( L = conf, thandle = dep_handle )
        allocate( me( nDeps ))

        ! Read the subtables individually
        do iDep = 1, nDeps
          call aot_table_open( L       = conf,                                 &
            &                  parent  = dep_handle,                           &
            &                  thandle = dep_sub_handle,                       &
            &                  pos     = iDep )

          call tem_load_depend_single( me          = me(iDep),       &
            &                          conf        = conf,           &
            &                          parent      = dep_sub_handle, &
            &                          label       = label,          &
            &                          requireCond = requireCond     )

          call aot_table_close( L = conf, thandle = dep_sub_handle )
        end do
      end if
    else
      write(logUnit(1),*) 'depend table is not defined'
    end if

    call aot_table_close( L = conf, thandle = dep_handle )
    call tem_horizontalSpacer(fUnit = logUnit(1))

  end subroutine tem_load_depend_vector