tem_variable_load_vector Subroutine

public subroutine tem_variable_load_vector(me, conf, parent, key, vError, nComp, load_solvervar)

Load an array of variables from the configuration.

Arguments

Type IntentOptional Attributes Name
type(tem_variable_type), intent(out), allocatable :: me(:)

The variable to read from the Lua script(conf) and fill

type(flu_State) :: conf

Lua handle connected to the script to read the table from

integer, intent(in), optional :: parent

A parent table handle in which to look the current variable up

character(len=*), intent(in), optional :: key

key for array of variables

integer, intent(out), allocatable :: vError(:)

if Error .ne. 0 is variable is not loaded successfully.

integer, optional :: nComp

If the variable is expected to have a certain number of components, this can be provided with this argument.

If the definition of the variable does not match this, we will fail loading the variable.

procedure(tem_load_solverVar_method), optional :: load_solvervar

A method to load solver specific variables.


Calls

proc~~tem_variable_load_vector~~CallsGraph proc~tem_variable_load_vector tem_variable_load_vector proc~tem_horizontalspacer tem_horizontalSpacer proc~tem_variable_load_vector->proc~tem_horizontalspacer proc~tem_variable_load_single tem_variable_load_single proc~tem_variable_load_vector->proc~tem_variable_load_single proc~aot_table_open aot_table_open proc~tem_variable_load_vector->proc~aot_table_open proc~aot_table_close aot_table_close proc~tem_variable_load_vector->proc~aot_table_close proc~aot_table_length aot_table_length proc~tem_variable_load_vector->proc~aot_table_length proc~tem_variable_load_single->proc~tem_horizontalspacer proc~tem_variable_load_single->proc~aot_table_open proc~tem_variable_load_single->proc~aot_table_close proc~upper_to_lower upper_to_lower proc~tem_variable_load_single->proc~upper_to_lower interface~tem_load_spacetime tem_load_spacetime proc~tem_variable_load_single->interface~tem_load_spacetime proc~load_variable_operation load_variable_operation proc~tem_variable_load_single->proc~load_variable_operation proc~tem_abort tem_abort proc~tem_variable_load_single->proc~tem_abort proc~aot_get_val aot_get_val proc~tem_variable_load_single->proc~aot_get_val proc~tem_load_spacetime_single tem_load_spacetime_single interface~tem_load_spacetime->proc~tem_load_spacetime_single proc~tem_load_spacetime_table tem_load_spacetime_table interface~tem_load_spacetime->proc~tem_load_spacetime_table proc~load_variable_operation->proc~aot_table_open proc~load_variable_operation->proc~aot_table_close proc~load_variable_operation->proc~tem_abort proc~load_variable_operation->proc~aot_get_val proc~tem_reduction_transient_load tem_reduction_transient_load proc~load_variable_operation->proc~tem_reduction_transient_load mpi_abort mpi_abort proc~tem_abort->mpi_abort proc~tem_load_spacetime_single->proc~aot_table_open proc~tem_load_spacetime_single->proc~tem_abort proc~tem_load_spacetime_single->proc~tem_load_spacetime_single proc~load_spacetime_predefined load_spacetime_predefined proc~tem_load_spacetime_single->proc~load_spacetime_predefined proc~aot_exists aot_exists proc~tem_load_spacetime_single->proc~aot_exists interface~tem_load_shape tem_load_shape proc~tem_load_spacetime_single->interface~tem_load_shape proc~load_spacetime_asconst load_spacetime_asConst proc~tem_load_spacetime_single->proc~load_spacetime_asconst proc~aot_type_of aot_type_of proc~tem_load_spacetime_single->proc~aot_type_of proc~aot_reference_for aot_reference_for proc~tem_load_spacetime_single->proc~aot_reference_for proc~aot_fun_open aot_fun_open proc~tem_load_spacetime_single->proc~aot_fun_open proc~aot_fun_close aot_fun_close proc~tem_load_spacetime_single->proc~aot_fun_close proc~aot_get_val~2 aot_get_val proc~tem_load_spacetime_single->proc~aot_get_val~2 proc~tem_load_spacetime_table->proc~aot_table_open proc~tem_load_spacetime_table->proc~aot_table_close proc~tem_load_spacetime_table->proc~aot_table_length proc~tem_load_spacetime_table->proc~tem_load_spacetime_single proc~tem_reduction_transient_load->proc~aot_table_open proc~tem_reduction_transient_load->proc~aot_table_close proc~tem_reduction_transient_load->proc~tem_abort proc~tem_reduction_transient_load->proc~aot_get_val~2

Called by

proc~~tem_variable_load_vector~~CalledByGraph proc~tem_variable_load_vector tem_variable_load_vector interface~tem_variable_load tem_variable_load interface~tem_variable_load->proc~tem_variable_load_vector

Contents


Source Code

  subroutine tem_variable_load_vector( me, conf, parent, key, vError, nComp, &
    &                                  load_solvervar                        )
    ! --------------------------------------------------------------------------!
    !> The variable to read from the Lua script(conf) and fill
    type(tem_variable_type), allocatable, intent(out) :: me(:)

    !> Lua handle connected to the script to read the table from
    type(flu_state) :: conf

    !> A parent table handle in which to look the current variable up
    integer, optional, intent(in) :: parent

    !> key for array of variables
    character(len=*), optional, intent(in) :: key

    !> if Error .ne. 0 is variable is not loaded successfully.
    integer, allocatable, intent(out) :: vError(:)

    !> If the variable is expected to have a certain number of components,
    !! this can be provided with this argument.
    !!
    !! If the definition of the variable does not match this, we will fail
    !! loading the variable.
    integer, optional :: nComp

    !> A method to load solver specific variables.
    procedure(tem_load_solvervar_method), optional :: load_solvervar
    ! --------------------------------------------------------------------------!
    integer :: varhandle, nVars, varsubhandle, iVar, iError
    character(len=LabelLen) :: local_key
    ! --------------------------------------------------------------------------!
    call tem_horizontalSpacer(fUnit = logUnit(1))

    if( present( key )) then
      local_key = key
    else
      local_key = 'variable'
    endif

    ! Try to open the variable table
    call aot_table_open( L       = conf,            &
      &                  parent  = parent,          &
      &                  thandle = varhandle,       &
      &                  key     = trim(local_key ) )

    nVars = 0
    if (varhandle > 0) then
      ! Test whether the next thing is a table or not
      call aot_table_open( L       = conf,         &
        &                  parent  = varhandle,    &
        &                  thandle = varsubhandle, &
        &                  pos     = 1             )
      ! It is a table, so more than one variable is expected
      if (varsubhandle > 0) then
        call aot_table_close( L = conf, thandle = varsubhandle )
        nVars = aot_table_length( L = conf, thandle = varhandle )
        allocate(me(nVars))
        allocate(vError(nVars))

        do iVar = 1, nVars
          call aot_table_open( L       = conf,         &
            &                  parent  = varhandle,    &
            &                  thandle = varsubhandle, &
            &                  pos     = iVar          )

          call tem_variable_load_single( me             = me(iVar),      &
            &                            conf           = conf,          &
            &                            parent         = varsubhandle,  &
            &                            iError         = iError,        &
            &                            nComp          = nComp,         &
            &                            openTable      = .false.,       &
            &                            load_solvervar = load_solvervar )
          vError(iVar) = iError
          if (iError /= 0) then
            write(logUnit(1),*) 'Variable:'//trim(me(iVar)%label) &
              &        //' cannot be added to varSys'
          endif
          call aot_table_close( L = conf, thandle = varsubhandle )
        end do
      else ! it's not a table but a single variable
        nVars = 1
        allocate(me(nVars))
        allocate(vError(nVars))
        call tem_variable_load_single( me             = me(1),         &
          &                            conf           = conf,          &
          &                            parent         = varhandle,     &
          &                            iError         = iError,        &
          &                            nComp          = nComp,         &
          &                            openTable      = .false.,       &
          &                            load_solvervar = load_solvervar )
        vError(1) = iError
        if (iError /= 0) then
          write(logUnit(1),*) 'Variable:'//trim(me(iVar)%label) &
            &        //' cannot be added to varSys'
        endif
      end if
    else
      write(logUnit(1),*) 'Variable table not defined with key: ' &
        &                 //trim(local_key)
      allocate(me(nVars))
      allocate(vError(nVars))
    endif

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

  end subroutine tem_variable_load_vector