tem_variable_load_single Subroutine

public subroutine tem_variable_load_single(me, conf, parent, iError, key, nComp, openTable, load_solvervar)

Reading a single variable from the Lua configuration.

Arguments

Type IntentOptional Attributes Name
type(tem_variable_type), intent(out) :: 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) :: parent

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

integer, intent(out) :: iError

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

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

key for a single variable

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.

logical, intent(in), optional :: openTable

if variable table is already opened, set openTable = .false.

procedure(tem_load_solverVar_method), optional :: load_solvervar

A method to load solver specific variables.


Calls

proc~~tem_variable_load_single~~CallsGraph proc~tem_variable_load_single tem_variable_load_single proc~tem_horizontalspacer tem_horizontalSpacer proc~tem_variable_load_single->proc~tem_horizontalspacer 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~upper_to_lower upper_to_lower proc~tem_variable_load_single->proc~upper_to_lower proc~aot_table_open aot_table_open proc~tem_variable_load_single->proc~aot_table_open proc~aot_get_val aot_get_val proc~tem_variable_load_single->proc~aot_get_val proc~tem_abort tem_abort proc~tem_variable_load_single->proc~tem_abort proc~aot_table_close aot_table_close proc~tem_variable_load_single->proc~aot_table_close 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_get_val proc~load_variable_operation->proc~tem_abort proc~load_variable_operation->proc~aot_table_close 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~tem_load_spacetime_single proc~aot_table_length aot_table_length proc~tem_load_spacetime_table->proc~aot_table_length proc~tem_reduction_transient_load->proc~aot_table_open proc~tem_reduction_transient_load->proc~tem_abort proc~tem_reduction_transient_load->proc~aot_table_close proc~tem_reduction_transient_load->proc~aot_get_val~2

Called by

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

Contents


Source Code

  subroutine tem_variable_load_single( me, conf, parent, iError, key, nComp, &
    &                                  openTable, load_solvervar )
    ! --------------------------------------------------------------------------!
    !> The variable to read from the Lua script(conf) and fill
    type(tem_variable_type), 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, intent(in) :: parent

    !> key for a single variable
    character(len=*), optional, intent(in) :: key

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

    !> 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

    !> if variable table is already opened, set openTable = .false.
    logical, optional, intent(in) :: openTable

    !> A method to load solver specific variables.
    procedure(tem_load_solvervar_method), optional :: load_solvervar
    ! --------------------------------------------------------------------------!
    integer :: local_thandle, local_error
    logical :: openTable_loc
    character(len=LabelLen) :: local_key
    character(len=LabelLen) :: varname
    ! --------------------------------------------------------------------------!
    call tem_horizontalSpacer(fUnit = logUnit(1))
    ! if variable table is already opened then openTable = .false.
    if( present(openTable) ) then
      openTable_loc = openTable
    else
      openTable_loc = .true.
    end if

    local_thandle = parent
    if (openTable_loc) then
      if ( present(key) ) then

        local_key = trim(key)

        ! Attempt to read the variable as a single identifier.
        ! (Reference to another variable)
        call aot_get_val( L       = conf,    &
          &               thandle = parent,  &
          &               val     = varname, &
          &               ErrCode = iError,  &
          &               key     = key      )

        ! If this succeeds, take it and set the variable with the
        ! name of the key to be a combine operation (providing an alias).
        if (iError == 0) then
          me%label = trim(key)
          ! Negative number of components will inherit the components from
          ! the referred variable.
          me%nComponents = -1
          me%vartype = 'operation'
          me%opertype = 'combine'
          allocate(me%input_varName(1))
          me%input_varName(1) = varname
        end if

      else

        local_key = 'variable'

      end if

      call aot_table_open( L       = conf,          &
        &                  thandle = local_thandle, &
        &                  parent  = parent,        &
        &                  key     = local_key      )
    end if

    ! Get the name of the variable
    call aot_get_val( L       = conf,          &
      &               thandle = local_thandle, &
      &               val     = me%label,      &
      &               ErrCode = iError,        &
      &               key     = 'name',        &
      &               pos     = 1,             &
      &               default = key            )

    if (iError /= 0) then
      write(logUnit(1),*) 'Unable to load "name" with pos and label.'
      return
    end if

    write(logUnit(1),*) 'Loading variable ', trim(me%label)

    ! Get the number of components for this variable
    call aot_get_val( L       = conf,           &
      &               thandle = local_thandle,  &
      &               val     = me%nComponents, &
      &               ErrCode = iError,         &
      &               key     = 'ncomponents',  &
      &               pos     = 2,              &
      &               default = nComp           )

    if( iError /= 0 ) then
      write(logUnit(1),*) 'No ncomponents specified for variable ' &
        &                 //trim( me%label )
      return
    end if

    write(logUnit(5),*) '  nComponents ', me%nComponents

    ! Do not proceed, if the number of provided components
    ! does not match the number of expect components.
    if (present(nComp)) then
      if (nComp /= me%nComponents) RETURN
    end if

    ! load variable type
    call aot_get_val( L       = conf,           &
      &               thandle = local_thandle,  &
      &               val     = me%varType,     &
      &               ErrCode = iError,         &
      &               default = 'none',         &
      &               key     = 'vartype'       )

    select case(trim(me%varType))
    case('operation')
      call load_variable_operation( me     = me,            &
        &                           conf   = conf,          &
        &                           parent = local_thandle, &
        &                           iError = iError         )
      ! if operation table is not loaded successfully. this variable
      ! cannot be added to variable system
      if (iError /= 0) return

    case('st_fun')
      ! In case we have a space time function, we try to read the evaluation
      ! type, This is only needed for variables of type space time function as
      ! they can have several space time functions providing values and thus
      ! there are use cases where these space time functions have to be merged
      ! differently.
      ! The default is to add all values, if several space time functions
      ! provide values for a given request.
      call aot_get_val( L       = conf,          &
        &               thandle = local_thandle, &
        &               val     = me%evalType,   &
        &               ErrCode = local_Error,   &
        &               key     = 'evaltype',    &
        &               default = 'add'          )
      me%evalType = upper_to_lower(me%evalType)

      write(logUnit(1),*) 'loading the spacetime functions for variable '//    &
        &             trim( me%label )
      call tem_load_spacetime( me     = me%st_fun,       &
        &                      conf   = conf,            &
        &                      parent = local_thandle,   &
        &                      nComp  = me%nComponents,  &
        &                      key    = 'st_fun' )

      if (.not. allocated(me%st_fun)) then
        write(logUnit(1),*) 'Error: no stfun found for '//trim(me%label)
        write(logUnit(1),*) 'If you define a variable with a stfun, this has'
        write(logUnit(1),*) 'to be properly defined.'
        write(logUnit(1),*) 'Check your variable definition!'
        call tem_abort()
      else
        if (size(me%st_fun) == 0) then
          write(logUnit(1),*) 'Error: no stfun found for '//trim(me%label)
          write(logUnit(1),*) 'If you define a variable with a stfun, this has'
          write(logUnit(1),*) 'to be properly defined.'
          write(logUnit(1),*) 'Check your variable definition!'
          call tem_abort()
        end if
      end if

    case default
      iError = 1
      if (present(load_solverVar)) then
        call load_solverVar(L         = conf,                &
          &                 parent    = local_thandle,       &
          &                 specifics = me%solver_specifics, &
          &                 appender  = me%append_solvervar, &
          &                 iError    = iError               )
      end if
      if (iError /= 0) then
        call tem_abort( 'Error: varType '                                       &
          & // trim(me%varType)                                                 &
          & // ' not supported! Supported varType are "st_fun" and "operation"' )
      end if
    end select

    if (present(key)) call aot_table_close( L = conf, thandle = local_thandle)

  end subroutine tem_variable_load_single