Skip to content

Commit

Permalink
Merge pull request #510 from Warwick-Plasma/photon_bug_fix
Browse files Browse the repository at this point in the history
Photon initialisation fix (issue #502)
  • Loading branch information
Status-Mirror authored Jun 26, 2023
2 parents fdfd6f3 + d187a5e commit 724471f
Show file tree
Hide file tree
Showing 6 changed files with 63 additions and 0 deletions.
7 changes: 7 additions & 0 deletions epoch1d/src/physics_packages/injectors.F90
Original file line number Diff line number Diff line change
Expand Up @@ -307,6 +307,13 @@ SUBROUTINE run_single_injector(injector)
#ifndef PER_SPECIES_WEIGHT
density = MIN(density, injector%density_max)
new%weight = weight_fac * density
#endif
#if defined(PHOTONS) || defined(BREMSSTRAHLUNG)
! For photons, assign additional variable used in photon particle-push
IF (species_list(injector%species)%species_type == c_species_id_photon) &
THEN
new%particle_energy = SQRT(SUM(new%part_p**2)) * c
END IF
#endif
CALL add_particle_to_partlist(plist, new)
END DO
Expand Down
14 changes: 14 additions & 0 deletions epoch1d/src/user_interaction/helper.F90
Original file line number Diff line number Diff line change
Expand Up @@ -92,6 +92,9 @@ SUBROUTINE auto_load
TYPE(particle_species), POINTER :: species
INTEGER :: i0, i1, iu, io
TYPE(initial_condition_block), POINTER :: ic
#if defined(PHOTONS) || defined(BREMSSTRAHLUNG)
TYPE(particle), POINTER :: current
#endif

IF (pre_loading .AND. n_species > 0) THEN
i0 = 1 - ng
Expand Down Expand Up @@ -141,6 +144,17 @@ SUBROUTINE auto_load
ELSE IF (species%ic_df_type == c_ic_df_arbitrary) THEN
CALL setup_particle_dist_fn(species, species_drift)
END IF

#if defined(PHOTONS) || defined(BREMSSTRAHLUNG)
! For photons, assign additional variable used in photon particle-push
IF (species_list(ispecies)%species_type == c_species_id_photon) THEN
current => species%attached_list%head
DO WHILE (ASSOCIATED(current))
current%particle_energy = SQRT(SUM(current%part_p**2)) * c
current => current%next
END DO
END IF
#endif
END DO

IF (pre_loading) RETURN
Expand Down
7 changes: 7 additions & 0 deletions epoch2d/src/physics_packages/injectors.F90
Original file line number Diff line number Diff line change
Expand Up @@ -366,6 +366,13 @@ SUBROUTINE run_single_injector(injector)
#ifndef PER_SPECIES_WEIGHT
density = MIN(density, injector%density_max)
new%weight = weight_fac * density
#endif
#if defined(PHOTONS) || defined(BREMSSTRAHLUNG)
! For photons, assign additional variable used in photon particle-push
IF (species_list(injector%species)%species_type == c_species_id_photon) &
THEN
new%particle_energy = SQRT(SUM(new%part_p**2)) * c
END IF
#endif
CALL add_particle_to_partlist(plist, new)
END DO
Expand Down
14 changes: 14 additions & 0 deletions epoch2d/src/user_interaction/helper.F90
Original file line number Diff line number Diff line change
Expand Up @@ -98,6 +98,9 @@ SUBROUTINE auto_load
TYPE(particle_species), POINTER :: species
INTEGER :: i0, i1, iu, io
TYPE(initial_condition_block), POINTER :: ic
#if defined(PHOTONS) || defined(BREMSSTRAHLUNG)
TYPE(particle), POINTER :: current
#endif

IF (pre_loading .AND. n_species > 0) THEN
i0 = 1 - ng
Expand Down Expand Up @@ -147,6 +150,17 @@ SUBROUTINE auto_load
ELSE IF (species%ic_df_type == c_ic_df_arbitrary) THEN
CALL setup_particle_dist_fn(species, species_drift)
END IF

#if defined(PHOTONS) || defined(BREMSSTRAHLUNG)
! For photons, assign additional variable used in photon particle-push
IF (species_list(ispecies)%species_type == c_species_id_photon) THEN
current => species%attached_list%head
DO WHILE (ASSOCIATED(current))
current%particle_energy = SQRT(SUM(current%part_p**2)) * c
current => current%next
END DO
END IF
#endif
END DO

IF (pre_loading) RETURN
Expand Down
7 changes: 7 additions & 0 deletions epoch3d/src/physics_packages/injectors.F90
Original file line number Diff line number Diff line change
Expand Up @@ -403,6 +403,13 @@ SUBROUTINE run_single_injector(injector)
#ifndef PER_SPECIES_WEIGHT
density = MIN(density, injector%density_max)
new%weight = weight_fac * density
#endif
#if defined(PHOTONS) || defined(BREMSSTRAHLUNG)
! For photons, assign additional variable used in photon particle-push
IF (species_list(injector%species)%species_type == c_species_id_photon) &
THEN
new%particle_energy = SQRT(SUM(new%part_p**2)) * c
END IF
#endif
CALL add_particle_to_partlist(plist, new)
END DO
Expand Down
14 changes: 14 additions & 0 deletions epoch3d/src/user_interaction/helper.F90
Original file line number Diff line number Diff line change
Expand Up @@ -104,6 +104,9 @@ SUBROUTINE auto_load
TYPE(particle_species), POINTER :: species
INTEGER :: i0, i1, iu, io
TYPE(initial_condition_block), POINTER :: ic
#if defined(PHOTONS) || defined(BREMSSTRAHLUNG)
TYPE(particle), POINTER :: current
#endif

IF (pre_loading .AND. n_species > 0) THEN
i0 = 1 - ng
Expand Down Expand Up @@ -153,6 +156,17 @@ SUBROUTINE auto_load
ELSE IF (species%ic_df_type == c_ic_df_arbitrary) THEN
CALL setup_particle_dist_fn(species, species_drift)
END IF

#if defined(PHOTONS) || defined(BREMSSTRAHLUNG)
! For photons, assign additional variable used in photon particle-push
IF (species_list(ispecies)%species_type == c_species_id_photon) THEN
current => species%attached_list%head
DO WHILE (ASSOCIATED(current))
current%particle_energy = SQRT(SUM(current%part_p**2)) * c
current => current%next
END DO
END IF
#endif
END DO

IF (pre_loading) RETURN
Expand Down

0 comments on commit 724471f

Please sign in to comment.