Skip to content

Commit

Permalink
Merge branch '4.19-devel' into main
Browse files Browse the repository at this point in the history
  • Loading branch information
Status-Mirror committed Dec 4, 2024
2 parents 35411c5 + dd90056 commit 1d04650
Show file tree
Hide file tree
Showing 12 changed files with 71 additions and 21 deletions.
2 changes: 1 addition & 1 deletion SDF
Submodule SDF updated 4 files
+1 −1 C
+1 −1 FORTRAN
+1 −1 VisIt
+1 −1 utilities
2 changes: 1 addition & 1 deletion epoch1d/src/epoch1d.F90
Original file line number Diff line number Diff line change
Expand Up @@ -138,7 +138,7 @@ PROGRAM pic
END DO

! .TRUE. to over_ride balance fraction check
IF (npart_global > 0) CALL balance_workload(.TRUE.)
IF (npart_global > 0 .AND. use_pre_balance) CALL balance_workload(.TRUE.)

IF (use_current_correction) CALL calc_initial_current
CALL setup_bc_lists
Expand Down
2 changes: 1 addition & 1 deletion epoch1d/src/io/diagnostics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -874,7 +874,7 @@ SUBROUTINE output_routines(step, force_write) ! step = step index
END IF

#ifndef NO_PARTICLE_PROBES
IF (IAND(iomask(c_dump_probes), code) /= 0) THEN
IF (IAND(iomask(c_dump_probes), code) /= 0 .OR. restart_flag) THEN
CALL write_probes(sdf_handle, code, iomask(c_dump_probes))
END IF
#endif
Expand Down
2 changes: 1 addition & 1 deletion epoch1d/src/parser/evaluator_blocks.F90
Original file line number Diff line number Diff line change
Expand Up @@ -195,7 +195,7 @@ SUBROUTINE do_constant(opcode, simplify, parameters, err)

IF (opcode == c_const_xb) THEN
IF (parameters%use_grid_position) THEN
CALL push_on_eval(xb(parameters%pack_ix))
CALL push_on_eval(xb(parameters%pack_ix) + dx)
ELSE
CALL push_on_eval(parameters%pack_pos)
END IF
Expand Down
2 changes: 1 addition & 1 deletion epoch2d/src/epoch2d.F90
Original file line number Diff line number Diff line change
Expand Up @@ -138,7 +138,7 @@ PROGRAM pic
END DO

! .TRUE. to over_ride balance fraction check
IF (npart_global > 0) CALL balance_workload(.TRUE.)
IF (npart_global > 0 .AND. use_pre_balance) CALL balance_workload(.TRUE.)

IF (use_current_correction) CALL calc_initial_current
CALL setup_bc_lists
Expand Down
2 changes: 1 addition & 1 deletion epoch2d/src/io/diagnostics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -906,7 +906,7 @@ SUBROUTINE output_routines(step, force_write) ! step = step index
END IF

#ifndef NO_PARTICLE_PROBES
IF (IAND(iomask(c_dump_probes), code) /= 0) THEN
IF (IAND(iomask(c_dump_probes), code) /= 0 .OR. restart_flag) THEN
CALL write_probes(sdf_handle, code, iomask(c_dump_probes))
END IF
#endif
Expand Down
4 changes: 2 additions & 2 deletions epoch2d/src/parser/evaluator_blocks.F90
Original file line number Diff line number Diff line change
Expand Up @@ -195,7 +195,7 @@ SUBROUTINE do_constant(opcode, simplify, parameters, err)

IF (opcode == c_const_xb) THEN
IF (parameters%use_grid_position) THEN
CALL push_on_eval(xb(parameters%pack_ix))
CALL push_on_eval(xb(parameters%pack_ix) + dx)
ELSE
CALL push_on_eval(parameters%pack_pos(1))
END IF
Expand All @@ -221,7 +221,7 @@ SUBROUTINE do_constant(opcode, simplify, parameters, err)

IF (opcode == c_const_yb) THEN
IF (parameters%use_grid_position) THEN
CALL push_on_eval(yb(parameters%pack_iy))
CALL push_on_eval(yb(parameters%pack_iy) + dy)
ELSE
CALL push_on_eval(parameters%pack_pos(2))
END IF
Expand Down
17 changes: 15 additions & 2 deletions epoch2d/src/physics_packages/file_injectors.F90
Original file line number Diff line number Diff line change
Expand Up @@ -235,6 +235,7 @@ SUBROUTINE run_file_injection(injector)
REAL(num) :: next_time, time_to_bdy
REAL(num) :: vx, vy, gamma, inv_gamma_mass, iabs_p
REAL(num) :: x_start, y_start
REAL(num) :: low_in, high_in
TYPE(particle), POINTER :: new
TYPE(particle_list) :: plist
LOGICAL :: no_particles_added, skip_processor
Expand Down Expand Up @@ -375,13 +376,25 @@ SUBROUTINE run_file_injection(injector)
! particle
IF (boundary == c_bd_x_min .OR. boundary == c_bd_x_max) THEN
! Skip all processors which are at the wrong y position
IF (y_in <= y_min_local .OR. y_in > y_max_local) THEN
low_in = y_grid_mins(y_coords) - 0.5_num * dy
IF (y_coords == nprocy-1) THEN
high_in = y_grid_maxs(y_coords) + 0.5_num * dy
ELSE
high_in = y_grid_mins(y_coords+1) - 0.5_num * dy
END IF
IF (y_in <= low_in .OR. y_in > high_in) THEN
skip_processor = .TRUE.
END IF

ELSE IF (boundary == c_bd_y_min .OR. boundary == c_bd_y_max) THEN
! Skip all processors which are at the wrong x position
IF (x_in <= x_min_local .OR. x_in > x_max_local) THEN
low_in = x_grid_mins(x_coords) - 0.5_num * dx
IF (x_coords == nprocx-1) THEN
high_in = x_grid_maxs(x_coords) + 0.5_num * dx
ELSE
high_in = x_grid_mins(x_coords+1) - 0.5_num * dx
END IF
IF (x_in <= low_in .OR. x_in > high_in) THEN
skip_processor = .TRUE.
END IF
END IF
Expand Down
2 changes: 1 addition & 1 deletion epoch3d/src/epoch3d.F90
Original file line number Diff line number Diff line change
Expand Up @@ -138,7 +138,7 @@ PROGRAM pic
END DO

! .TRUE. to over_ride balance fraction check
IF (npart_global > 0) CALL balance_workload(.TRUE.)
IF (npart_global > 0 .AND. use_pre_balance) CALL balance_workload(.TRUE.)

IF (use_current_correction) CALL calc_initial_current
CALL setup_bc_lists
Expand Down
2 changes: 1 addition & 1 deletion epoch3d/src/io/diagnostics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -940,7 +940,7 @@ SUBROUTINE output_routines(step, force_write) ! step = step index
END IF

#ifndef NO_PARTICLE_PROBES
IF (IAND(iomask(c_dump_probes), code) /= 0) THEN
IF (IAND(iomask(c_dump_probes), code) /= 0 .OR. restart_flag) THEN
CALL write_probes(sdf_handle, code, iomask(c_dump_probes))
END IF
#endif
Expand Down
6 changes: 3 additions & 3 deletions epoch3d/src/parser/evaluator_blocks.F90
Original file line number Diff line number Diff line change
Expand Up @@ -195,7 +195,7 @@ SUBROUTINE do_constant(opcode, simplify, parameters, err)

IF (opcode == c_const_xb) THEN
IF (parameters%use_grid_position) THEN
CALL push_on_eval(xb(parameters%pack_ix))
CALL push_on_eval(xb(parameters%pack_ix) + dx)
ELSE
CALL push_on_eval(parameters%pack_pos(1))
END IF
Expand All @@ -221,7 +221,7 @@ SUBROUTINE do_constant(opcode, simplify, parameters, err)

IF (opcode == c_const_yb) THEN
IF (parameters%use_grid_position) THEN
CALL push_on_eval(yb(parameters%pack_iy))
CALL push_on_eval(yb(parameters%pack_iy) + dy)
ELSE
CALL push_on_eval(parameters%pack_pos(2))
END IF
Expand All @@ -247,7 +247,7 @@ SUBROUTINE do_constant(opcode, simplify, parameters, err)

IF (opcode == c_const_zb) THEN
IF (parameters%use_grid_position) THEN
CALL push_on_eval(zb(parameters%pack_iz))
CALL push_on_eval(zb(parameters%pack_iz) + dz)
ELSE
CALL push_on_eval(parameters%pack_pos(3))
END IF
Expand Down
49 changes: 43 additions & 6 deletions epoch3d/src/physics_packages/file_injectors.F90
Original file line number Diff line number Diff line change
Expand Up @@ -256,6 +256,7 @@ SUBROUTINE run_file_injection(injector)
REAL(num) :: next_time, time_to_bdy
REAL(num) :: vx, vy, vz, gamma, inv_gamma_mass, iabs_p
REAL(num) :: x_start, y_start, z_start
REAL(num) :: low_in, high_in
TYPE(particle), POINTER :: new
TYPE(particle_list) :: plist
LOGICAL :: no_particles_added, skip_processor
Expand Down Expand Up @@ -419,31 +420,67 @@ SUBROUTINE run_file_injection(injector)
! particle
IF (boundary == c_bd_x_min .OR. boundary == c_bd_x_max) THEN
! Skip all processors which are at the wrong y position
IF (y_in <= y_min_local .OR. y_in > y_max_local) THEN
low_in = y_grid_mins(y_coords) - 0.5_num * dy
IF (y_coords == nprocy-1) THEN
high_in = y_grid_maxs(y_coords) + 0.5_num * dy
ELSE
high_in = y_grid_mins(y_coords+1) - 0.5_num * dy
END IF
IF (y_in <= low_in .OR. y_in > high_in) THEN
skip_processor = .TRUE.
END IF
! Skip all processors which are at the wrong z position
IF (z_in <= z_min_local .OR. z_in > z_max_local) THEN
low_in = z_grid_mins(z_coords) - 0.5_num * dz
IF (z_coords == nprocz-1) THEN
high_in = z_grid_maxs(z_coords) + 0.5_num * dz
ELSE
high_in = z_grid_mins(z_coords+1) - 0.5_num * dz
END IF
IF (z_in <= low_in .OR. z_in > high_in) THEN
skip_processor = .TRUE.
END IF

ELSE IF (boundary == c_bd_y_min .OR. boundary == c_bd_y_max) THEN
! Skip all processors which are at the wrong x position
IF (x_in <= x_min_local .OR. x_in > x_max_local) THEN
low_in = x_grid_mins(x_coords) - 0.5_num * dx
IF (x_coords == nprocx-1) THEN
high_in = x_grid_maxs(x_coords) + 0.5_num * dx
ELSE
high_in = x_grid_mins(x_coords+1) - 0.5_num * dx
END IF
IF (x_in <= low_in .OR. x_in > high_in) THEN
skip_processor = .TRUE.
END IF
! Skip all processors which are at the wrong z position
IF (z_in <= z_min_local .OR. z_in > z_max_local) THEN
low_in = z_grid_mins(z_coords) - 0.5_num * dz
IF (z_coords == nprocz-1) THEN
high_in = z_grid_maxs(z_coords) + 0.5_num * dz
ELSE
high_in = z_grid_mins(z_coords+1) - 0.5_num * dz
END IF
IF (z_in <= low_in .OR. z_in > high_in) THEN
skip_processor = .TRUE.
END IF

ELSE IF (boundary == c_bd_z_min .OR. boundary == c_bd_z_max) THEN
! Skip all processors which are at the wrong x position
IF (x_in <= x_min_local .OR. x_in > x_max_local) THEN
low_in = x_grid_mins(x_coords) - 0.5_num * dx
IF (x_coords == nprocx-1) THEN
high_in = x_grid_maxs(x_coords) + 0.5_num * dx
ELSE
high_in = x_grid_mins(x_coords+1) - 0.5_num * dx
END IF
IF (x_in <= low_in .OR. x_in > high_in) THEN
skip_processor = .TRUE.
END IF
! Skip all processors which are at the wrong y position
IF (y_in <= y_min_local .OR. y_in > y_max_local) THEN
low_in = y_grid_mins(y_coords) - 0.5_num * dy
IF (y_coords == nprocy-1) THEN
high_in = y_grid_maxs(y_coords) + 0.5_num * dy
ELSE
high_in = y_grid_mins(y_coords+1) - 0.5_num * dy
END IF
IF (y_in <= low_in .OR. y_in > high_in) THEN
skip_processor = .TRUE.
END IF

Expand Down

0 comments on commit 1d04650

Please sign in to comment.