tem_load_condition Subroutine

public subroutine tem_load_condition(me, conf, parent)

Load the condition table in case of convergence

Example:

 condition = {threshold = 2.0e-10, operator = '<='}

The tables inside condition table should be equal to the nVars If thats not the case we return an error message check single or multiple table

Arguments

Type IntentOptional Attributes Name
type(tem_condition_type), intent(inout), allocatable :: me(:)
type(flu_State), intent(in) :: conf
integer, intent(in) :: parent

Source Code

  subroutine tem_load_condition( me, conf, parent )
    ! -------------------------------------------------------------------- !
    !>
    type(tem_condition_type), allocatable, intent(inout) :: me(:)
    !>
    type(flu_state), intent(in)             :: conf
    !>
    integer, intent(in)                     :: parent
    ! -------------------------------------------------------------------- !
    integer :: cond_handle          ! handle for the condition table
    integer :: sub_cond_handle      ! handle for subtables inside condition
    integer :: nCond                ! number of conditions
    integer :: iCond                ! index for condition loop
    ! -------------------------------------------------------------------- !
    !! Open the condition table
    call aot_table_open( L       = conf,        &
      &                  parent  = parent,      &
      &                  thandle = cond_handle, &
      &                  key     = 'condition'  )
    !! The tables inside condition table should be equal to the nVars
    !! If thats not the case we return an error message
    nCond = aot_table_length( L=conf, thandle=cond_handle )
    !! check single or multiple table
    call aot_table_open( L       = conf,            &
      &                  parent  = cond_handle,     &
      &                  thandle = sub_cond_handle, &
      &                  pos     = 1                )

    if (sub_cond_handle == 0) then
      call aot_table_close( L = conf, thandle = sub_cond_handle )
      ! just one table within
      allocate ( me(1) )
      call tem_load_cond_single( me(1), conf, cond_handle )
    else
      ! IF there are more tables within condition
      call aot_table_close( L = conf, thandle = sub_cond_handle )
      allocate ( me(nCond) )
      do iCond = 1, nCond
        call aot_table_open( L       = conf,            &
          &                  parent  = cond_handle,     &
          &                  thandle = sub_cond_handle, &
          &                  pos     = iCond            )
        call tem_load_cond_single( me(iCond), conf, sub_cond_handle )
        call aot_table_close( L = conf, thandle = sub_cond_handle )
      end do
    end if ! sub condition check
    call aot_table_close(L=conf, thandle=cond_handle )

  end subroutine tem_load_condition