tem_load_depend_single Subroutine

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

Load single dependent variable of the scheme, in case of geomIncr: load the dependent variable as well as the conditions to be imposed for the geometry increase to take place.

Arguments

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

depend type to be filled

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

lua state to read from

integer, intent(in) :: parent

handle of parent table

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_single~~CallsGraph proc~tem_load_depend_single tem_load_depend_single proc~aot_table_open aot_table_open proc~tem_load_depend_single->proc~aot_table_open proc~tem_load_condition tem_load_condition proc~tem_load_depend_single->proc~tem_load_condition proc~aot_table_close aot_table_close proc~tem_load_depend_single->proc~aot_table_close proc~aot_get_val aot_get_val proc~tem_load_depend_single->proc~aot_get_val proc~tem_abort tem_abort proc~tem_load_depend_single->proc~tem_abort proc~tem_load_condition->proc~aot_table_open proc~tem_load_condition->proc~aot_table_close proc~tem_load_cond_single tem_load_cond_single proc~tem_load_condition->proc~tem_load_cond_single proc~aot_table_length aot_table_length proc~tem_load_condition->proc~aot_table_length mpi_abort mpi_abort proc~tem_abort->mpi_abort proc~tem_load_cond_single->proc~aot_get_val proc~tem_load_cond_single->proc~tem_abort

Called by

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

Contents


Source Code

  subroutine tem_load_depend_single( me, conf, parent, label, requireCond )
    !---------------------------------------------------------------------------
    !> depend type to be filled
    type(tem_depend_type), intent(inout) :: me
    !> lua state to read from
    type(flu_state), intent(in)          :: conf
    !> handle of parent table
    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, allocatable :: vError(:)
    integer :: cond_handle
    logical :: requireCond_loc
    !---------------------------------------------------------------------------

    ! if require condition is not present do not load condition table
    if (present(requireCond)) then
      requireCond_loc = requireCond
    else
      requireCond_loc = .false.
    end if

    ! Load the variable names
    call aot_get_val( val       = me%varName, &
      &               ErrCode   = vError,     &
      &               maxLength = 100,        &
      &               L         = conf,       &
      &               thandle   = parent,     &
      &               key       = 'variable'  )

    if ( any(btest(vError, aoterr_Fatal)) ) then
      write(logUnit(1),*) 'ERROR: could not load varnames for depend variable'
      call tem_abort()
    end if

    ! The below code snippet loads the conditions defined within depend table
    ! in the case of geometry increase, whereas in case this routine is called
    ! to load the depend table within schemes then conditions are not available
    ! and this load will not be effective in that case
    if (requireCond_loc) then
      call aot_table_open( L       = conf,                                     &
        &                  parent  = parent,                                  &
        &                  thandle = cond_handle,                              &
        &                  key     = 'condition')
      if (cond_handle /= 0) then
        ! condition table is defined
        ! close table and load with tem_load_condition
        call aot_table_close( L=conf, thandle = cond_handle )

        call tem_load_condition( me     = me%cond, &
          &                      conf   = conf,    &
          &                      parent = parent   )
      else
        write(logUnit(1),*) 'ERROR: Condition table is not defined in depend ' &
          &                 //'table of: '//trim(label)
        call tem_abort()
      end if ! Condition table defined

      ! check if there is condition for each variable
      if (size(me%cond) /= size(me%varname)) then
        write(logUnit(1),*) 'Error: Nr. of conditions \= Nr. of variables ' &
          &                 //'in depend table of: '//trim(label)
        write(logUnit(1),*) 'nCond: ', size(me%cond),  &
          &                 ' nVars: ', size(me%varname)
        call tem_abort()
      end if
    end if ! require condition

  end subroutine tem_load_depend_single