Skip to content

Commit

Permalink
Version v4.19.4
Browse files Browse the repository at this point in the history
  • Loading branch information
Status-Mirror authored and TomGoffrey committed Sep 7, 2024
1 parent 191b4c6 commit 727d5eb
Show file tree
Hide file tree
Showing 2 changed files with 58 additions and 8 deletions.
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
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 727d5eb

Please sign in to comment.