tem_sparta_test Program

Uses

  • program~~tem_sparta_test~~UsesGraph program~tem_sparta_test tem_sparta_test module~tem_general_module tem_general_module program~tem_sparta_test->module~tem_general_module module~tem_logging_module tem_logging_module program~tem_sparta_test->module~tem_logging_module module~env_module env_module program~tem_sparta_test->module~env_module module~flu_binding flu_binding program~tem_sparta_test->module~flu_binding module~tem_utestenv_module tem_utestEnv_module program~tem_sparta_test->module~tem_utestenv_module mpi mpi program~tem_sparta_test->mpi module~tem_sparta_module tem_Sparta_module program~tem_sparta_test->module~tem_sparta_module module~aotus_module aotus_module program~tem_sparta_test->module~aotus_module module~tem_general_module->module~tem_logging_module module~tem_general_module->module~env_module module~tem_general_module->module~aotus_module module~tem_restart_module tem_restart_module module~tem_general_module->module~tem_restart_module tem_precice_module tem_precice_module module~tem_general_module->tem_precice_module module~tem_balance_module tem_balance_module module~tem_general_module->module~tem_balance_module module~tem_timer_module tem_timer_module module~tem_general_module->module~tem_timer_module module~tem_abortcriteria_module tem_abortCriteria_module module~tem_general_module->module~tem_abortcriteria_module module~tem_simcontrol_module tem_simControl_module module~tem_general_module->module~tem_simcontrol_module tem_sparse_comm_module tem_sparse_comm_module module~tem_general_module->tem_sparse_comm_module module~tem_comm_env_module tem_comm_env_module module~tem_general_module->module~tem_comm_env_module module~tem_comm_module tem_comm_module module~tem_general_module->module~tem_comm_module module~tem_tools_module tem_tools_module module~tem_general_module->module~tem_tools_module module~tem_aux_module tem_aux_module module~tem_general_module->module~tem_aux_module module~tem_solvehead_module tem_solveHead_module module~tem_general_module->module~tem_solvehead_module module~tem_status_module tem_status_module module~tem_general_module->module~tem_status_module module~tem_logging_module->module~env_module module~tem_logging_module->module~aotus_module module~aot_table_module aot_table_module module~tem_logging_module->module~aot_table_module module~env_module->module~flu_binding module~env_module->mpi module~env_module->module~aotus_module iso_fortran_env iso_fortran_env module~env_module->iso_fortran_env module~tem_utestenv_module->module~tem_general_module module~tem_utestenv_module->module~tem_logging_module module~tem_utestenv_module->module~flu_binding module~tem_utestenv_module->module~aotus_module module~treelmesh_module treelmesh_module module~tem_utestenv_module->module~treelmesh_module iso_c_binding iso_c_binding module~tem_utestenv_module->iso_c_binding module~tem_property_module tem_property_module module~tem_utestenv_module->module~tem_property_module module~tem_bc_prop_module tem_bc_prop_module module~tem_utestenv_module->module~tem_bc_prop_module module~tem_sparta_module->module~tem_logging_module module~tem_sparta_module->module~env_module module~tem_sparta_module->mpi module~tem_float_module tem_float_module module~tem_sparta_module->module~tem_float_module module~tem_sparta_module->module~tem_aux_module

Calls

program~~tem_sparta_test~~CallsGraph program~tem_sparta_test tem_sparta_test proc~tem_output_sparta tem_output_sparta program~tem_sparta_test->proc~tem_output_sparta proc~tem_destroy_sparta tem_destroy_sparta program~tem_sparta_test->proc~tem_destroy_sparta proc~fin_env fin_env program~tem_sparta_test->proc~fin_env proc~open_config_chunk open_config_chunk program~tem_sparta_test->proc~open_config_chunk proc~tem_start tem_start program~tem_sparta_test->proc~tem_start mpi_reduce mpi_reduce program~tem_sparta_test->mpi_reduce mpi_barrier mpi_barrier program~tem_sparta_test->mpi_barrier proc~tem_logging_load_primary tem_logging_load_primary program~tem_sparta_test->proc~tem_logging_load_primary proc~tem_balance_sparta tem_balance_sparta program~tem_sparta_test->proc~tem_balance_sparta proc~tem_init_sparta tem_init_sparta program~tem_sparta_test->proc~tem_init_sparta mpi_finalize mpi_finalize proc~fin_env->mpi_finalize proc~tem_init_solvehead tem_init_solveHead proc~tem_start->proc~tem_init_solvehead proc~tem_comm_env_init tem_comm_env_init proc~tem_start->proc~tem_comm_env_init proc~tem_simcontrol_start tem_simControl_start proc~tem_start->proc~tem_simcontrol_start proc~tem_addtimer tem_addTimer proc~tem_start->proc~tem_addtimer proc~tem_starttimer tem_startTimer proc~tem_start->proc~tem_starttimer proc~init_env init_env proc~tem_start->proc~init_env proc~aot_table_open aot_table_open proc~tem_logging_load_primary->proc~aot_table_open proc~aot_table_close aot_table_close proc~tem_logging_load_primary->proc~aot_table_close proc~tem_logging_load tem_logging_load proc~tem_logging_load_primary->proc~tem_logging_load proc~tem_logging_init_primary tem_logging_init_primary proc~tem_logging_load_primary->proc~tem_logging_init_primary mpi_exscan mpi_exscan proc~tem_balance_sparta->mpi_exscan proc~tem_set_sparta tem_set_sparta proc~tem_balance_sparta->proc~tem_set_sparta mpi_allreduce mpi_allreduce proc~tem_balance_sparta->mpi_allreduce

Contents

Source Code


Variables

Type AttributesNameInitial
integer :: iError
integer :: myrank
integer :: nprocs
integer :: comm
type(flu_State) :: conf
type(tem_general_type) :: general
logical :: OK =.false.
logical :: correct =.false.
real(kind=rk), allocatable:: weight(:)
integer :: myElems
integer(kind=long_k) :: offset
type(tem_sparta_type) :: sparta

Source Code

program tem_sparta_test
  use mpi
  use env_module,               only: rk, init_env, fin_env, long_k
  use tem_utestEnv_module,  only: cubeconf
  use tem_sparta_module, only: tem_sparta_type, tem_balance_sparta, &
    &                          tem_init_sparta, tem_destroy_sparta, &
    &                          tem_output_sparta
  use tem_logging_module,    only: logUnit, tem_logging_load_primary
  use tem_general_module,    only: tem_general_type, tem_start

  use aotus_module,          only: open_config_chunk
  use flu_binding,           only: flu_state

  implicit none

  ! MPI variables
  integer         :: iError
  integer         :: myrank
  integer         :: nprocs
  integer         :: comm
  type(flu_state) :: conf
  type(tem_general_type) :: general

  logical :: OK = .false.
  logical :: correct = .false.

  ! main variables
  real(kind=rk), allocatable :: weight(:)
  integer :: myElems
  integer(kind=long_k) :: offset
  type( tem_sparta_type ) :: sparta

  call tem_start('TREELM unit test', 'utest', general)
  comm = general%proc%comm
  myrank = general%proc%rank
  nprocs = general%proc%comm_size
  if ( nprocs /= 5 ) stop

  ! Open the configuration file 
  call open_config_chunk(L = conf, chunk = trim(cubeconf))
  ! load and initialize logUnit
  call tem_logging_load_primary(conf = conf,  &
    &                           rank = myrank )

  allocate( weight(5) )
  myElems = 5
  select case ( myrank )
    case (0)
      weight = [ 5.0, 3.0, 1.0, 2.0, 1.0 ]
    case (1)
      weight = [ 4.0, 6.0, 1.0, 3.0, 2.0 ]
    case (2)
      weight = [ 1.0, 3.0, 1.0, 1.0, 1.0 ]
    case (3)
      weight = [ 1.0, 9.0, 1.0, 1.0, 1.0 ]
    case (4)
      weight = [ 1.0, 1.0, 1.0, 1.0, 1.0 ]
    case default
      stop
  end select

  ! write(*,"(A,I0,A,F7.1)") "Before balance, rank: ", myrank, ", my workload: ", sum(weight)
  call tem_init_sparta( sparta, nprocs )
  call tem_balance_sparta(weight, myrank, nprocs, comm, myElems, offset, &
    &                    sparta )
  call tem_output_sparta( sparta, logUnit(1) )
  write(*,"(3(A,I2),A,F5.1)") "After balance, rank: ", myrank, &
    &                      ", myElems: ", myElems, &
    &                      ", offset: ", offset, &
    &                      ", my workload: ", sum(weight)

  if (myrank == 0 .and. myElems == 4 .and. offset == 0) then
    OK = .true.
  else if (myrank == 1 .and. myElems == 3 .and. offset == 4) then
    OK = .true.
  else if (myrank == 2 .and. myElems == 5 .and. offset == 7) then
    OK = .true.
  else if (myrank == 3 .and. myElems == 5 .and. offset == 12) then
    OK = .true.
  else if (myrank == 4 .and. myElems == 8 .and. offset == 17) then
    OK = .true.
  else
    OK = .false.
  end if

  call mpi_reduce( OK, correct, 1, mpi_logical, mpi_land, 0, comm, iError )

  call tem_destroy_sparta( sparta )

  call MPI_Barrier(comm, iError)

  if ( myrank == 0 ) then
    if ( .not. correct ) then
      write(*,"(3(A,I0),A,F7.1)") "After  balance, rank: ", myrank, &
        &                      ", myElems: ", myElems, &
        &                      ", offset: ", offset, &
        &                      ", my workload: ", sum(weight)
      write(*,*) "FAILED"
    else
      write(*,*) "PASSED"
    end if
  end if

  deallocate( weight )

  call fin_env()

end program tem_sparta_test