tem_load_reduction_spatial Subroutine

public subroutine tem_load_reduction_spatial(conf, redSpatial_config, parent, key)

read configuration file

Arguments

Type IntentOptional Attributes Name
type(flu_State) :: conf

handle for lua file

type(tem_reduction_spatial_config_type), intent(out) :: redSpatial_config

the reduction file to fill

integer, intent(in), optional :: parent

handle for reduce table

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

which key to open


Calls

proc~~tem_load_reduction_spatial~~CallsGraph proc~tem_load_reduction_spatial tem_load_reduction_spatial proc~tem_load_reduction_single tem_load_reduction_single proc~tem_load_reduction_spatial->proc~tem_load_reduction_single proc~aot_table_close aot_table_close proc~tem_load_reduction_spatial->proc~aot_table_close proc~aot_table_open aot_table_open proc~tem_load_reduction_spatial->proc~aot_table_open proc~aot_table_length aot_table_length proc~tem_load_reduction_spatial->proc~aot_table_length proc~aot_get_val~2 aot_get_val proc~tem_load_reduction_single->proc~aot_get_val~2 proc~tem_abort tem_abort proc~tem_load_reduction_single->proc~tem_abort proc~upper_to_lower upper_to_lower proc~tem_load_reduction_single->proc~upper_to_lower mpi_abort mpi_abort proc~tem_abort->mpi_abort

Called by

proc~~tem_load_reduction_spatial~~CalledByGraph proc~tem_load_reduction_spatial tem_load_reduction_spatial proc~tem_load_convergenceheader tem_load_convergenceHeader proc~tem_load_convergenceheader->proc~tem_load_reduction_spatial proc~tem_load_trackingconfig tem_load_trackingConfig proc~tem_load_trackingconfig->proc~tem_load_reduction_spatial proc~tem_convergence_load tem_convergence_load proc~tem_convergence_load->proc~tem_load_convergenceheader proc~tem_load_tracking tem_load_tracking proc~tem_load_tracking->proc~tem_load_trackingconfig proc~tem_abortcriteria_load tem_abortCriteria_load proc~tem_abortcriteria_load->proc~tem_convergence_load proc~tem_simcontrol_load tem_simControl_load proc~tem_simcontrol_load->proc~tem_abortcriteria_load

Contents


Source Code

  subroutine tem_load_reduction_spatial(conf, redSpatial_config, parent, key)
    ! ---------------------------------------------------------------------------
    !> handle for lua file
    type(flu_State) :: conf
    !> the reduction file to fill
    type(tem_reduction_spatial_config_type),intent(out) :: redSpatial_config
    !> handle for reduce table
    integer, optional,intent(in) :: parent
    !> which key to open
    character(len=*),optional,intent(in) :: key
    ! ---------------------------------------------------------------------------
    integer :: nEntries, handle, iPos
    character(len=labelLen) :: localKey
    integer, allocatable :: vErr(:) !, vErr_NonExistent(:)
    ! ---------------------------------------------------------------------------
    if( present( key )) then
      localKey = key
    else
      localKey = 'reduction'
    endif

    allocate( redSpatial_config%reduceType(1) )
    allocate( vErr(1)   )

    redSpatial_config%reduceType(1) = ''
    ! load reduction as scalar if failed then try to load as table
    call tem_load_reduction_single( conf       = conf,             &
      &                             handle     = parent,           &
      &                             reduceType = redSpatial_config &
      &                                         %reduceType(1),    &
      &                             key        = localKey,         &
      &                             iError     = vErr(1)           )

    ! try loading it as table
    if(btest(vErr(1), aoterr_NonExistent)) then
      ! write(logUnit(1),"(A)") 'Try load reduction as a table'
      call aot_table_open( L       = conf,      &
        &                  thandle = handle,    &
        &                  parent  = parent,    &
        &                  key     = localKey   )
      ! reduction defined as table
      if ( handle /= 0 ) then
        ! load entry inside a table
        nEntries = aot_table_length( L = conf, thandle = handle )
        ! write(logUnit(1),"(A,I0)") 'Table has entries: ', nEntries
        deallocate( redSpatial_config%reduceType )
        deallocate( vErr )
        allocate( redSpatial_config%reduceType( nEntries ) )
        allocate( vErr( nEntries ) )
        do iPos = 1, nEntries
          redSpatial_config%reduceType(iPos) = ''
          call tem_load_reduction_single( conf       = conf,              &
            &                             handle     = handle,            &
            &                             reduceType = redSpatial_config  &
            &                                         %reduceType(iPos),  &
            &                             pos        = iPos,              &
            &                             iError     = vErr(iPos)         )
        enddo
        redSpatial_config%active = .true.
      end if
      call aot_table_close(conf, handle)
    else
      ! write(logUnit(1),"(A)") 'Reduction is a single entry'
      redSpatial_config%active = .true.
      nEntries = 1
    endif

    if ( redSpatial_config%active ) then
      write(logUnit(3),"(A, I0)") '  Number of reductions loaded: ', nEntries
      write(logUnit(5),"(A)")     '  their reduceTypes are:'
      do iPos = 1, nEntries
        write(logUnit(5),"(A)")   '    '//trim(redSpatial_config &
          &                                     %reduceType(iPos))
      end do
    else
      deallocate( redSpatial_config%reduceType )
      allocate( redSpatial_config%reduceType(0) )
    end if


  end subroutine tem_load_reduction_spatial