Skip to content

Commit

Permalink
Merge pull request #602 from bmad-sim/devel/42
Browse files Browse the repository at this point in the history
Made customizing track1_bunch_hook with long_term_tracking easier.
  • Loading branch information
DavidSagan authored Oct 29, 2023
2 parents fa978c7 + 4d576ee commit 4af8674
Show file tree
Hide file tree
Showing 4 changed files with 141 additions and 55 deletions.
49 changes: 43 additions & 6 deletions bmad/multiparticle/beam_file_io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -134,7 +134,7 @@ subroutine write_ascii4_beam_file (file_name, beam, new_file, cols, lat)
character(20) col
character(200) name, col_out
character(600) line
character(12) colvec(20)
character(12) colvec(20), cfmt(20)
character(*), parameter :: r_name = 'write_ascii4_beam_file'

logical, optional :: new_file
Expand All @@ -148,7 +148,7 @@ subroutine write_ascii4_beam_file (file_name, beam, new_file, cols, lat)
call fullfilename (file_name, name)

if (logic_option(.true., new_file)) then
open (iu, file = name)
open (iu, file = name, recl = 600)
write (iu, '(a)') '!ASCII::3'
else
open (iu, file = name, access = 'append')
Expand Down Expand Up @@ -221,22 +221,59 @@ subroutine write_ascii4_beam_file (file_name, beam, new_file, cols, lat)
call headwrite_str('species', colvec, bunch%particle(:)%species, species_name(p%species))
call headwrite_str('location', colvec, bunch%particle(:)%location, location_name(p%location))

! Write table
! Write table header

write (iu, '(a)') '#'
line = '#'

do ic = 1, size(colvec)
col = colvec(ic)
if (col == '') cycle
select case (col)
case ('index');
case ('index', 'ix_ele', 'ix_branch', 'direction', 'time_dir')
write (line, '(a, a10)') trim(line), trim(col)
case ('s', 't', 'charge', 'p0c'); write (line, '(a, a22)') trim(line), trim(col)
case ('vec'); write (line, '(a, 6a22)') trim(line), 'x', 'px', 'y', 'py', 'z', 'pz'
case ('spin'); write (line, '(a, 6a22)') trim(line), 'spin_x', 'spin_y', 'spin_z'
case ('field'); write (line, '(a, 6a22)') trim(line), 'field_x', 'field_y'
case ('phase'); write (line, '(a, 6a22)') trim(line), 'phase_x', 'phase_y'
case ('state'); write (line, '(a, a13)') trim(line), 'state'
case ('species'); write (line, '(a, a12)') trim(line), 'spieces'
case ('location'); write (line, '(a, a12)') trim(line), 'location'
case default
call err_exit
end select
enddo

enddo
write (iu, '(a)') trim(line)

!

line = ''
do ip = 1, size(colvec)
col = colvec(ic)
if (col == '') cycle
select case (col)
case ('index'); write (line, '(a, i10)') trim(line), ip
case ('ix_ele'); write (line, '(a, i10)') trim(line), p%ix_ele
case ('ix_branch'); write (line, '(a, i10)') trim(line), p%ix_branch
case ('direction'); write (line, '(a, i10)') trim(line), p%direction
case ('time_dir'); write (line, '(a, i10)') trim(line), p%time_dir
case ('s'); write (line, '(a, 2es22.14)') trim(line), p%s
case ('t'); write (line, '(a, 2es22.14)') trim(line), p%t
case ('charge'); write (line, '(a, 2es22.14)') trim(line), p%charge
case ('p0c'); write (line, '(a, 2es22.14)') trim(line), p%p0c
case ('vec'); write (line, '(a, 2es22.14)') trim(line), p%vec
case ('spin'); write (line, '(a, 2es22.14)') trim(line), p%spin
case ('field'); write (line, '(a, 2es22.14)') trim(line), p%field
case ('phase'); write (line, '(a, 2es22.14)') trim(line), p%phase
case ('state'); write (line, '(a, a13)') trim(line), state_name(p%state)
case ('species'); write (line, '(a, a12)') trim(line), species_name(p%species)
case ('location'); write (line, '(a, a12)') trim(line), location_name(p%location)
end select
enddo
write (iu, '(a)') trim(line)

enddo


close (iu)
Expand Down
51 changes: 3 additions & 48 deletions bsim/long_term_tracking/track1_bunch_hook.f90
Original file line number Diff line number Diff line change
Expand Up @@ -37,54 +37,9 @@ subroutine track1_bunch_hook (bunch, ele, err, centroid, direction, finished, bu

logical err, finished

! Rampers are only applied to the element once per bunch. That is, it is assumed
! that the ramper control function variation is negligible over the time scale of a bunch passage.
! To evaluate multiple times in a bunch passage would, in general, be wrong if using ran() or ran_gauss().
! The reason to separate this routine from ltt_track1_bunch_hook is to allow for the possibility
! to add custom functionality by overriding track1_bunch_hook.

err = .false.
finished = .false.
if (.not. ltt_params_global%ramping_on) return
if (ltt_params_global%ramp_update_each_particle) return

n = ltt_com_global%n_ramper_loc
if (n == 0) return

t = sum(bunch%particle%t, bunch%particle%state == alive$) / &
count(bunch%particle%state == alive$) + 0.5_rp * ele%value(delta_ref_time$) + &
ltt_params_global%ramping_start_time

do ir = 1, ltt_com_global%n_ramper_loc
do iv = 1, size(ltt_com_global%ramper(ir)%ele%control%var)
if (ltt_com_global%ramper(ir)%ele%control%var(iv)%name /= 'TIME') cycle
ltt_com_global%ramper(ir)%ele%control%var(iv)%value = t
enddo
enddo

n = ltt_com_global%n_ramper_loc
call ltt_apply_rampers_to_slave (ele, ltt_com_global%ramper(1:n), err)

! The beginning element is never tracked through. If there is energy ramping and the user is writing out
! p0c or E_tot from the beginning element, the user may be confused since these values will not change.
! So adjust the beginning element's p0c and E_tot to keep users happy.

if (ele%ix_ele == 1) then
ele0 => pointer_to_next_ele(ele, -1)
ele0%value(p0c$) = ele%value(p0c_start$)
ele0%value(E_tot$) = ele%value(E_tot_start$)
endif

! Adjust particle reference energy if needed.

if (bunch%particle(1)%p0c == ele%value(p0c_start$)) return

do ip = 1, size(bunch%particle)
orb => bunch%particle(ip)
if (orb%state /= alive$) cycle
r = orb%p0c / ele%value(p0c_start$)
orb%vec(2) = r * orb%vec(2)
orb%vec(4) = r * orb%vec(4)
orb%vec(6) = r * orb%vec(6) + (orb%p0c - ele%value(p0c_start$)) / ele%value(p0c_start$)
orb%p0c = ele%value(p0c_start$)
enddo
call ltt_track1_bunch_hook (bunch, ele, err, centroid, direction, finished, bunch_track)

end subroutine
94 changes: 94 additions & 0 deletions bsim/modules/lt_tracking_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1256,6 +1256,7 @@ subroutine ltt_run_beam_mode (lttp, ltt_com, ix_start_turn, ix_end_turn, beam)
do i_turn = ix_start_turn+1, ix_end_turn
do ib = 1, size(beam%bunch)
bunch => beam%bunch(ib)
bunch%ix_turn = i_turn
if (i_turn == lttp%ix_turn_record .and. lttp%ix_particle_record > 0) then
bunch%particle(lttp%ix_particle_record)%ix_user = 1
else
Expand Down Expand Up @@ -2881,4 +2882,97 @@ subroutine ltt_apply_rampers_to_slave (slave, ramper, err_flag)

end subroutine ltt_apply_rampers_to_slave

!-------------------------------------------------------------------------------------------
!-------------------------------------------------------------------------------------------
!-------------------------------------------------------------------------------------------
!+
! Subroutine ltt_track1_bunch_hook (bunch, ele, err, centroid, direction, finished, bunch_track)
!
! This routine handles ramper element bookkeeping.
!
! This routine is called by the customized version of track1_bunch_hook that is linked with
! the long_term_tracking program.
!
! Input:
! bunch_start -- Bunch_struct: Starting bunch position.
! ele -- Ele_struct: Element to track through.
! centroid(0:) -- coord_struct, optional: Approximate centroid orbit. Only needed if CSR is on.
! Hint: Calculate this before bunch tracking by tracking a single particle.
! direction -- integer, optional: +1 (default) -> Track forward, -1 -> Track backwards.
!
! Output:
! bunch_end -- bunch_struct: Ending bunch position.
! err -- Logical: Set true if there is an error.
! EG: Too many particles lost for a CSR calc.
! finished -- logical: When set True, the standard track1_bunch code will not be called.
!-

subroutine ltt_track1_bunch_hook (bunch, ele, err, centroid, direction, finished, bunch_track)

type (bunch_struct), target :: bunch
type (ele_struct), target :: ele
type (ele_struct), pointer :: ele0
type (bunch_track_struct), optional :: bunch_track
type (coord_struct), optional :: centroid(0:)
type (coord_struct), pointer :: orb

real(rp) t, r

integer, optional :: direction
integer ip, ir, ie, n, iv

logical err, finished

! Rampers are only applied to the element once per bunch. That is, it is assumed
! that the ramper control function variation is negligible over the time scale of a bunch passage.
! To evaluate multiple times in a bunch passage would, in general, be wrong if using ran() or ran_gauss().

err = .false.
finished = .false.
if (.not. ltt_params_global%ramping_on) return
if (ltt_params_global%ramp_update_each_particle) return

n = ltt_com_global%n_ramper_loc
if (n == 0) return

t = sum(bunch%particle%t, bunch%particle%state == alive$) / &
count(bunch%particle%state == alive$) + 0.5_rp * ele%value(delta_ref_time$) + &
ltt_params_global%ramping_start_time

do ir = 1, ltt_com_global%n_ramper_loc
do iv = 1, size(ltt_com_global%ramper(ir)%ele%control%var)
if (ltt_com_global%ramper(ir)%ele%control%var(iv)%name /= 'TIME') cycle
ltt_com_global%ramper(ir)%ele%control%var(iv)%value = t
enddo
enddo

n = ltt_com_global%n_ramper_loc
call ltt_apply_rampers_to_slave (ele, ltt_com_global%ramper(1:n), err)

! The beginning element is never tracked through. If there is energy ramping and the user is writing out
! p0c or E_tot from the beginning element, the user may be confused since these values will not change.
! So adjust the beginning element's p0c and E_tot to keep users happy.

if (ele%ix_ele == 1) then
ele0 => pointer_to_next_ele(ele, -1)
ele0%value(p0c$) = ele%value(p0c_start$)
ele0%value(E_tot$) = ele%value(E_tot_start$)
endif

! Adjust particle reference energy if needed.

if (bunch%particle(1)%p0c == ele%value(p0c_start$)) return

do ip = 1, size(bunch%particle)
orb => bunch%particle(ip)
if (orb%state /= alive$) cycle
r = orb%p0c / ele%value(p0c_start$)
orb%vec(2) = r * orb%vec(2)
orb%vec(4) = r * orb%vec(4)
orb%vec(6) = r * orb%vec(6) + (orb%p0c - ele%value(p0c_start$)) / ele%value(p0c_start$)
orb%p0c = ele%value(p0c_start$)
enddo

end subroutine ltt_track1_bunch_hook

end module
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/10/28 02:30:40"
character(*), parameter :: tao_version_date = "2023/10/28 16:39:43"
end module

0 comments on commit 4af8674

Please sign in to comment.