Skip to content

Commit

Permalink
Improve name to duplicate communicator
Browse files Browse the repository at this point in the history
  • Loading branch information
Frederick Stein authored and fstein93 committed Feb 6, 2023
1 parent ca94894 commit a4dddda
Show file tree
Hide file tree
Showing 7 changed files with 8 additions and 8 deletions.
2 changes: 1 addition & 1 deletion src/dbt/tas/dbt_tas_split.F
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,7 @@ SUBROUTINE dbt_tas_create_split_rows_or_cols(split_info, mp_comm, ngroup, igroup
IF (own_comm_prv) THEN
split_info%mp_comm = mp_comm
ELSE
CALL split_info%mp_comm%dup(mp_comm)
CALL split_info%mp_comm%from_dup(mp_comm)
END IF

split_info%igroup = igroup
Expand Down
2 changes: 1 addition & 1 deletion src/mpiwrap/message_passing.F
Original file line number Diff line number Diff line change
Expand Up @@ -506,7 +506,7 @@ MODULE message_passing
PROCEDURE, PUBLIC, PASS(comm1), NON_OVERRIDABLE :: compare => mp_comm_compare
PROCEDURE, PUBLIC, PASS(comm1), NON_OVERRIDABLE :: rank_compare => mp_rank_compare

PROCEDURE, PUBLIC, PASS(comm2), NON_OVERRIDABLE :: dup => mp_comm_dup
PROCEDURE, PUBLIC, PASS(comm2), NON_OVERRIDABLE :: from_dup => mp_comm_dup
PROCEDURE, PUBLIC, PASS(comm), NON_OVERRIDABLE :: free => mp_comm_free

PROCEDURE, PUBLIC, PASS(comm), NON_OVERRIDABLE :: environ => mp_environ_l
Expand Down
2 changes: 1 addition & 1 deletion src/pw/pw_grids.F
Original file line number Diff line number Diff line change
Expand Up @@ -132,7 +132,7 @@ SUBROUTINE pw_grid_create(pw_grid, pe_group, local)
pw_grid%id_nr = grid_tag

! parallel info
CALL pw_grid%para%group%dup(pe_group)
CALL pw_grid%para%group%from_dup(pe_group)
CALL pw_grid%para%group%environ(pw_grid%para%group_size, &
pw_grid%para%my_pos)
pw_grid%para%group_head_id = 0
Expand Down
2 changes: 1 addition & 1 deletion src/pw/realspace_grid_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -352,7 +352,7 @@ SUBROUTINE rs_grid_create_descriptor(desc, pw_grid, input_settings, border_point
END IF
desc%group_dim(:) = n_slices(:)
CALL desc%group%dup(pw_grid%para%group)
CALL desc%group%from_dup(pw_grid%para%group)
CALL desc%group%environ(desc%group_size, desc%my_pos)
IF (ALL(n_slices == 1)) THEN
Expand Down
2 changes: 1 addition & 1 deletion src/qmmm_pw_grid.F
Original file line number Diff line number Diff line change
Expand Up @@ -177,7 +177,7 @@ SUBROUTINE pw_grid_create_copy_no_pbc(pw_grid_in, pw_grid_out, pw_mode)
pw_grid_out%para%pos_of_x => pos_of_x
pw_grid_out%para%rs_dims = pw_grid_in%para%rs_dims
IF (PRODUCT(pw_grid_in%para%rs_dims) /= 0) THEN
CALL pw_grid_out%para%rs_group%dup(pw_grid_in%para%rs_group)
CALL pw_grid_out%para%rs_group%from_dup(pw_grid_in%para%rs_group)
END IF
pw_grid_out%para%rs_pos = pw_grid_in%para%rs_pos
pw_grid_out%para%rs_mpo = pw_grid_in%para%rs_mpo
Expand Down
2 changes: 1 addition & 1 deletion src/start/cp2k_runs.F
Original file line number Diff line number Diff line change
Expand Up @@ -548,7 +548,7 @@ RECURSIVE SUBROUTINE farming_run(input_declaration, root_section, para_env, init
ELSE
! all processes are slaves
IF (output_unit > 0) WRITE (output_unit, FMT="(T2,A)") "FARMING| using a slave-only setup"
CALL slave_group%dup(para_env%group)
CALL slave_group%from_dup(para_env%group)
CALL slave_group%environ(num_slaves, slave_rank)
END IF
IF (output_unit > 0) WRITE (output_unit, FMT="(T2,A,I0)") "FARMING| number of slaves ", num_slaves
Expand Down
4 changes: 2 additions & 2 deletions src/tmc/tmc_setup.F
Original file line number Diff line number Diff line change
Expand Up @@ -369,7 +369,7 @@ SUBROUTINE do_analyze_files(input_declaration, root_section, para_env)
! create a TMC environment (also to have a params environment)
CALL tmc_env_create(tmc_env)
! duplicate communicator
CALL my_mpi_world%dup(para_env%group)
CALL my_mpi_world%from_dup(para_env%group)
! -- spiltting communicators
CALL comm%from_split(my_mpi_world, para_env%mepos, 0)
CALL cp_para_env_create(para_env=tmc_env%tmc_comp_set%para_env_m_ana, &
Expand Down Expand Up @@ -868,7 +868,7 @@ SUBROUTINE tmc_redistributing_cores(tmc_comp_set, para_env, ana_on_the_fly, &
CPWARN(" mpi ranks are unused, but can be used for analysis.")

! duplicate communicator
CALL my_mpi_world%dup(para_env%group)
CALL my_mpi_world%from_dup(para_env%group)

! determine the master node
IF (para_env%mepos == para_env%num_pe - 1) THEN
Expand Down

0 comments on commit a4dddda

Please sign in to comment.