Skip to content

Commit

Permalink
Better radiation setup bookkeeping. Now setup takes less time.
Browse files Browse the repository at this point in the history
  • Loading branch information
DavidSagan committed Oct 2, 2023
1 parent f6eab35 commit 0ddcb0b
Show file tree
Hide file tree
Showing 8 changed files with 1,439 additions and 63 deletions.
18 changes: 17 additions & 1 deletion bmad/code/create_element_slice.f90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ recursive subroutine create_element_slice (sliced_ele, ele_in, l_slice, offset,

real(rp) l_slice, offset, in_len, r, p0c_set
integer i
logical include_upstream_end, include_downstream_end, err_flag, err2_flag
logical include_upstream_end, include_downstream_end, err_flag, err2_flag, rad_map_stale

character(*), parameter :: r_name = 'create_element_slice'

Expand All @@ -55,11 +55,15 @@ recursive subroutine create_element_slice (sliced_ele, ele_in, l_slice, offset,

! Save values from old_slice if present in case the old_slice actual arg is same as sliced_ele.

rad_map_stale = .true.
ele0%value(l$) = 0
if (present(old_slice)) then
ele0%value(p0c$) = old_slice%value(p0c$)
ele0%value(e_tot$) = old_slice%value(e_tot$)
ele0%ref_time = old_slice%ref_time
ele0%value(l$) = old_slice%value(l$)
time_ref_orb_out = old_slice%time_ref_orb_out
if (associated(old_slice%rad_map)) rad_map_stale = old_slice%rad_map%stale
endif

!
Expand Down Expand Up @@ -129,6 +133,18 @@ recursive subroutine create_element_slice (sliced_ele, ele_in, l_slice, offset,
call makeup_super_slave1 (sliced_ele, ele_in, offset, param, include_upstream_end, include_downstream_end, err2_flag)
if (err2_flag) return

! See if %rad_map can be saved. Can only do this if the old_slice is the same as the new one.
! Therefore cannot save with wigglers and other elements which are not uniform longitudinally

if (present(old_slice) .and. .not. rad_map_stale .and. .not. include_upstream_end .and. &
.not. include_downstream_end .and. ele0%value(l$) == sliced_ele%value(l$) .and. &
(ele_in%tracking_method == bmad_standard$ .or. ele_in%field_calc == bmad_standard$)) then
select case (ele_in%key)
case (sbend$, quadrupole$, sextupole$, octupole$)
sliced_ele%rad_map%stale = .false.
end select
endif

! For a sliced taylor element the %taylor%term components point to the lord components.
! The routine deallocate_ele_pointers will only nullify and never deallocate these components of a slice_slave.

Expand Down
2 changes: 1 addition & 1 deletion bmad/doc/cover-page.tex
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

\begin{flushright}
\large
Revision: September 28, 2023 \\
Revision: September 30, 2023 \\
\end{flushright}

\pdfbookmark[0]{Preamble}{Preamble}
Expand Down
114 changes: 57 additions & 57 deletions bmad/doc/list-element-attributes.tex

Large diffs are not rendered by default.

2 changes: 1 addition & 1 deletion bmad/low_level/track_a_foil.f90
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,7 @@ subroutine track_a_foil (orbit, ele, param, mat6, make_matrix)

! Charge

n = nint(ele0%value(final_charge$))
n = nint(ele%value(final_charge$))
orbit%species = set_species_charge(orbit%species, n)

!
Expand Down
4 changes: 3 additions & 1 deletion bmad/modules/radiation_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -85,12 +85,13 @@ subroutine track1_radiation (orbit, ele, edge)
if (ele%value(l$) == 0) return
if (ele%tracking_method == taylor$ .and. ele%mat6_calc_method == taylor$) return
select case (ele%key)
case (drift$, taylor$, multipole$, ab_multipole$, mask$, marker$); return
case (drift$, pipe$, taylor$, multipole$, ab_multipole$, mask$, marker$); return
end select

! Use stochastic and damp mats

call radiation_map_setup(ele)
if (.not. associated(ele%rad_map)) return

if (edge == start_edge$) then
rad_map = ele%rad_map%rm0
Expand Down Expand Up @@ -171,6 +172,7 @@ subroutine radiation_map_setup (ele, ref_orbit_in, err_flag)
if (present(err_flag)) err_flag = .false.

if (ele%value(l$) == 0 .or. ele%key == taylor$) return ! Does not produce radiation.

if (.not. associated(ele%rad_map)) allocate(ele%rad_map)
if (.not. ele%rad_map%stale .and. .not. present(ref_orbit_in)) return
ele%rad_map%stale = .false.
Expand Down
6 changes: 5 additions & 1 deletion bmad/multiparticle/beam_utils.f90
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ module beam_utils
subroutine track1_bunch_hom (bunch, ele, direction, bunch_track)

use ptc_interface_mod, only: ele_to_taylor

use radiation_mod, only: radiation_map_setup
implicit none

type (bunch_struct) bunch
Expand Down Expand Up @@ -66,6 +66,7 @@ subroutine track1_bunch_hom (bunch, ele, direction, bunch_track)
wake_ele => pointer_to_wake_ele(ele, ds_wake)
if (.not. associated (wake_ele) .or. (.not. bmad_com%sr_wakes_on .and. .not. bmad_com%lr_wakes_on)) then

if (bmad_com%radiation_damping_on .or. bmad_com%radiation_fluctuations_on) call radiation_map_setup(ele)
!$OMP parallel do if (thread_safe)
do j = 1, size(bunch%particle)
if (bunch%particle(j)%state /= alive$) cycle
Expand All @@ -83,6 +84,7 @@ subroutine track1_bunch_hom (bunch, ele, direction, bunch_track)
! For zero length elements just track the element.

if (ele%value(l$) == 0) then
if (bmad_com%radiation_damping_on .or. bmad_com%radiation_fluctuations_on) call radiation_map_setup(ele)
!$OMP parallel do if (thread_safe)
do j = 1, size(bunch%particle)
if (bunch%particle(j)%state /= alive$) cycle
Expand All @@ -106,6 +108,7 @@ subroutine track1_bunch_hom (bunch, ele, direction, bunch_track)

if (half_ele%tracking_method == taylor$ .and. .not. associated(half_ele%taylor(1)%term)) call ele_to_taylor(half_ele, branch%param)

if (bmad_com%radiation_damping_on .or. bmad_com%radiation_fluctuations_on) call radiation_map_setup(half_ele)
!$OMP parallel do if (thread_safe)
do j = 1, size(bunch%particle)
if (bunch%particle(j)%state /= alive$) cycle
Expand Down Expand Up @@ -138,6 +141,7 @@ subroutine track1_bunch_hom (bunch, ele, direction, bunch_track)
call create_element_slice (half_ele, ele, ds_wake, 0.0_rp, branch%param, .true., .false., err_flag)
endif

if (bmad_com%radiation_damping_on .or. bmad_com%radiation_fluctuations_on) call radiation_map_setup(ele)
!$OMP parallel do if (thread_safe)
do j = 1, size(bunch%particle)
if (bunch%particle(j)%state /= alive$) cycle
Expand Down
2 changes: 1 addition & 1 deletion tao/version/tao_version_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,5 @@
!-

module tao_version_mod
character(*), parameter :: tao_version_date = "2023/09/29 01:32:20"
character(*), parameter :: tao_version_date = "2023/09/30 14:19:56"
end module
Loading

0 comments on commit 0ddcb0b

Please sign in to comment.