Skip to content

Commit 1d04650

Browse files
committed
Merge branch '4.19-devel' into main
2 parents 35411c5 + dd90056 commit 1d04650

File tree

12 files changed

+71
-21
lines changed

12 files changed

+71
-21
lines changed

SDF

epoch1d/src/epoch1d.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,7 @@ PROGRAM pic
138138
END DO
139139

140140
! .TRUE. to over_ride balance fraction check
141-
IF (npart_global > 0) CALL balance_workload(.TRUE.)
141+
IF (npart_global > 0 .AND. use_pre_balance) CALL balance_workload(.TRUE.)
142142

143143
IF (use_current_correction) CALL calc_initial_current
144144
CALL setup_bc_lists

epoch1d/src/io/diagnostics.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -874,7 +874,7 @@ SUBROUTINE output_routines(step, force_write) ! step = step index
874874
END IF
875875

876876
#ifndef NO_PARTICLE_PROBES
877-
IF (IAND(iomask(c_dump_probes), code) /= 0) THEN
877+
IF (IAND(iomask(c_dump_probes), code) /= 0 .OR. restart_flag) THEN
878878
CALL write_probes(sdf_handle, code, iomask(c_dump_probes))
879879
END IF
880880
#endif

epoch1d/src/parser/evaluator_blocks.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -195,7 +195,7 @@ SUBROUTINE do_constant(opcode, simplify, parameters, err)
195195

196196
IF (opcode == c_const_xb) THEN
197197
IF (parameters%use_grid_position) THEN
198-
CALL push_on_eval(xb(parameters%pack_ix))
198+
CALL push_on_eval(xb(parameters%pack_ix) + dx)
199199
ELSE
200200
CALL push_on_eval(parameters%pack_pos)
201201
END IF

epoch2d/src/epoch2d.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,7 @@ PROGRAM pic
138138
END DO
139139

140140
! .TRUE. to over_ride balance fraction check
141-
IF (npart_global > 0) CALL balance_workload(.TRUE.)
141+
IF (npart_global > 0 .AND. use_pre_balance) CALL balance_workload(.TRUE.)
142142

143143
IF (use_current_correction) CALL calc_initial_current
144144
CALL setup_bc_lists

epoch2d/src/io/diagnostics.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -906,7 +906,7 @@ SUBROUTINE output_routines(step, force_write) ! step = step index
906906
END IF
907907

908908
#ifndef NO_PARTICLE_PROBES
909-
IF (IAND(iomask(c_dump_probes), code) /= 0) THEN
909+
IF (IAND(iomask(c_dump_probes), code) /= 0 .OR. restart_flag) THEN
910910
CALL write_probes(sdf_handle, code, iomask(c_dump_probes))
911911
END IF
912912
#endif

epoch2d/src/parser/evaluator_blocks.F90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -195,7 +195,7 @@ SUBROUTINE do_constant(opcode, simplify, parameters, err)
195195

196196
IF (opcode == c_const_xb) THEN
197197
IF (parameters%use_grid_position) THEN
198-
CALL push_on_eval(xb(parameters%pack_ix))
198+
CALL push_on_eval(xb(parameters%pack_ix) + dx)
199199
ELSE
200200
CALL push_on_eval(parameters%pack_pos(1))
201201
END IF
@@ -221,7 +221,7 @@ SUBROUTINE do_constant(opcode, simplify, parameters, err)
221221

222222
IF (opcode == c_const_yb) THEN
223223
IF (parameters%use_grid_position) THEN
224-
CALL push_on_eval(yb(parameters%pack_iy))
224+
CALL push_on_eval(yb(parameters%pack_iy) + dy)
225225
ELSE
226226
CALL push_on_eval(parameters%pack_pos(2))
227227
END IF

epoch2d/src/physics_packages/file_injectors.F90

Lines changed: 15 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -235,6 +235,7 @@ SUBROUTINE run_file_injection(injector)
235235
REAL(num) :: next_time, time_to_bdy
236236
REAL(num) :: vx, vy, gamma, inv_gamma_mass, iabs_p
237237
REAL(num) :: x_start, y_start
238+
REAL(num) :: low_in, high_in
238239
TYPE(particle), POINTER :: new
239240
TYPE(particle_list) :: plist
240241
LOGICAL :: no_particles_added, skip_processor
@@ -375,13 +376,25 @@ SUBROUTINE run_file_injection(injector)
375376
! particle
376377
IF (boundary == c_bd_x_min .OR. boundary == c_bd_x_max) THEN
377378
! Skip all processors which are at the wrong y position
378-
IF (y_in <= y_min_local .OR. y_in > y_max_local) THEN
379+
low_in = y_grid_mins(y_coords) - 0.5_num * dy
380+
IF (y_coords == nprocy-1) THEN
381+
high_in = y_grid_maxs(y_coords) + 0.5_num * dy
382+
ELSE
383+
high_in = y_grid_mins(y_coords+1) - 0.5_num * dy
384+
END IF
385+
IF (y_in <= low_in .OR. y_in > high_in) THEN
379386
skip_processor = .TRUE.
380387
END IF
381388

382389
ELSE IF (boundary == c_bd_y_min .OR. boundary == c_bd_y_max) THEN
383390
! Skip all processors which are at the wrong x position
384-
IF (x_in <= x_min_local .OR. x_in > x_max_local) THEN
391+
low_in = x_grid_mins(x_coords) - 0.5_num * dx
392+
IF (x_coords == nprocx-1) THEN
393+
high_in = x_grid_maxs(x_coords) + 0.5_num * dx
394+
ELSE
395+
high_in = x_grid_mins(x_coords+1) - 0.5_num * dx
396+
END IF
397+
IF (x_in <= low_in .OR. x_in > high_in) THEN
385398
skip_processor = .TRUE.
386399
END IF
387400
END IF

epoch3d/src/epoch3d.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,7 @@ PROGRAM pic
138138
END DO
139139

140140
! .TRUE. to over_ride balance fraction check
141-
IF (npart_global > 0) CALL balance_workload(.TRUE.)
141+
IF (npart_global > 0 .AND. use_pre_balance) CALL balance_workload(.TRUE.)
142142

143143
IF (use_current_correction) CALL calc_initial_current
144144
CALL setup_bc_lists

epoch3d/src/io/diagnostics.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -940,7 +940,7 @@ SUBROUTINE output_routines(step, force_write) ! step = step index
940940
END IF
941941

942942
#ifndef NO_PARTICLE_PROBES
943-
IF (IAND(iomask(c_dump_probes), code) /= 0) THEN
943+
IF (IAND(iomask(c_dump_probes), code) /= 0 .OR. restart_flag) THEN
944944
CALL write_probes(sdf_handle, code, iomask(c_dump_probes))
945945
END IF
946946
#endif

0 commit comments

Comments
 (0)