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.


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