Skip to content

Commit

Permalink
Merge pull request #514 from bmad-sim/devel/step14
Browse files Browse the repository at this point in the history
Devel/step14
  • Loading branch information
DavidSagan committed Sep 27, 2023
2 parents 73a75e6 + 1f6ab5c commit 5e64091
Show file tree
Hide file tree
Showing 9 changed files with 73 additions and 835 deletions.
1 change: 1 addition & 0 deletions bmad/code/attribute_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,7 @@ subroutine attribute_bookkeeper (ele, force_bookkeeping)
if (ele%bookkeeping_state%attributes /= stale$ .and. .not. logic_option(.false., force_bookkeeping)) return

else
call attributes_need_bookkeeping(ele)
if (ele%bookkeeping_state%attributes /= stale$ .and. .not. logic_option(.false., force_bookkeeping)) return

if (ele%lord_status /= not_a_lord$) then
Expand Down
3 changes: 2 additions & 1 deletion bmad/code/lattice_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ subroutine lattice_bookkeeper (lat, err_flag)
type (branch_struct), pointer :: branch
type (bookkeeping_state_struct), pointer :: stat

real(rp) dval(num_ele_attrib$)
integer i, j

logical, optional :: err_flag
Expand All @@ -58,7 +59,7 @@ subroutine lattice_bookkeeper (lat, err_flag)
branch => lat%branch(i)
do j = 0, branch%n_ele_max
call set_ele_status_stale (branch%ele(j), all_groups$, .false.)
call attributes_need_bookkeeping(branch%ele(j))
call attributes_need_bookkeeping(branch%ele(j), dval)
enddo
enddo
endif
Expand Down
25 changes: 14 additions & 11 deletions bmad/modules/bmad_struct.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1035,18 +1035,21 @@ module bmad_struct
type bunch_struct
type (coord_struct), allocatable :: particle(:)
integer, allocatable :: ix_z(:) ! bunch%ix_z(1) is index of head particle, etc.
real(rp) :: charge_tot = 0 ! Total charge in a bunch (Coul).
real(rp) :: charge_live = 0 ! Charge of live particles (Coul).
real(rp) :: z_center = 0 ! Longitudinal center of bunch (m). Note: Generally, z_center of
! bunch #1 is 0 and z_center of the other bunches is negative.
real(rp) :: t_center = 0 ! Center of bunch creation time relative to head bunch.
real(rp) :: t0 = real_garbage$ ! Used by track1_bunch_space_charge for tracking so particles have constant t.
integer :: ix_ele = 0 ! Nominal element bunch is at. But, EG, dead particles can be someplace else.
integer :: ix_bunch = 0 ! Bunch index. Head bunch = 1, etc.
integer :: ix_turn = 0 ! Turn index for long term tracking. ix_turn = 0 before end of first turn, etc.
real(rp) :: charge_tot = 0 ! Total charge in a bunch (Coul).
real(rp) :: charge_live = 0 ! Charge of live particles (Coul).
real(rp) :: z_center = 0 ! Longitudinal center of bunch (m). Note: Generally, z_center of
! bunch #1 is 0 and z_center of the other bunches is negative.
real(rp) :: t_center = 0 ! Center of bunch creation time relative to head bunch.
real(rp) :: t0 = real_garbage$ ! Used by track1_bunch_space_charge for tracking so particles have constant t.
logical :: drift_between_t_and_s = .false.
! Drift (ignore any fields) instead of tracking to speed up the calculation?
! This can only be done under certain circumstances.
integer :: ix_ele = 0 ! Nominal element bunch is at. But, EG, dead particles can be someplace else.
integer :: ix_bunch = 0 ! Bunch index. Head bunch = 1, etc.
integer :: ix_turn = 0 ! Turn index for long term tracking. ix_turn = 0 before end of first turn, etc.
integer :: n_live = 0
integer :: n_good = 0 ! Number of accepted steps when using adaptive step size control.
integer :: n_bad = 0 ! Number of rejected steps when using adaptive step size control.
integer :: n_good = 0 ! Number of accepted steps when using adaptive step size control.
integer :: n_bad = 0 ! Number of rejected steps when using adaptive step size control.
end type

type beam_struct
Expand Down
40 changes: 33 additions & 7 deletions bmad/modules/bookkeeper_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1901,16 +1901,42 @@ subroutine attributes_need_bookkeeping (ele, dval)
enddo
endif

if (associated(ele%cartesian_map)) then
do i = 1, size(ele%cartesian_map)
ele%value(check_sum$) = ele%value(check_sum$) + ele%cartesian_map(i)%field_scale
enddo
endif

if (associated(ele%cylindrical_map)) then
do i = 1, size(ele%cylindrical_map)
ele%value(check_sum$) = ele%value(check_sum$) + ele%cylindrical_map(i)%field_scale
enddo
endif

if (associated(ele%gen_grad_map)) then
do i = 1, size(ele%gen_grad_map)
ele%value(check_sum$) = ele%value(check_sum$) + ele%gen_grad_map(i)%field_scale
enddo
endif

if (associated(ele%grid_field)) then
do i = 1, size(ele%grid_field)
ele%value(check_sum$) = ele%value(check_sum$) + ele%grid_field(i)%field_scale
enddo
endif

!

dv = abs(ele%value - ele%old_value)
dv(x1_limit$:y2_limit$) = 0 ! Limit changes do not need bookkeeping
if (present(dval)) dval = dv
if (present(dval)) then
dv = abs(ele%value - ele%old_value)
dv(x1_limit$:y2_limit$) = 0 ! Limit changes do not need bookkeeping
dval = dv

if (all(dv == 0) .and. ele%key /= capillary$) then
ele%bookkeeping_state%attributes = ok$
else
ele%bookkeeping_state%attributes = stale$
if (all(dv == 0) .and. ele%key /= capillary$) then
ele%bookkeeping_state%attributes = ok$
else
ele%bookkeeping_state%attributes = stale$
endif
endif

end subroutine attributes_need_bookkeeping
Expand Down
22 changes: 22 additions & 0 deletions bmad/space_charge/space_charge_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -416,6 +416,17 @@ subroutine track_bunch_to_s (bunch, s, branch)

!

if (bunch%drift_between_t_and_s) then
do i = 1, size(bunch%particle)
p => bunch%particle(i)
if (p%state /= alive$) cycle
call drift_particle_to_s(p, s, branch)
enddo
return
endif

!

s_end = branch%ele(branch%n_ele_track)%s
s_begin = branch%ele(0)%s

Expand Down Expand Up @@ -474,6 +485,17 @@ subroutine track_bunch_to_t (bunch, t_target, branch)
integer i, status
real(rp) ds, t_target, dt, dt2, s1, s_end, s_target, s_begin

!

if (bunch%drift_between_t_and_s) then
do i = 1, size(bunch%particle)
p0 => bunch%particle(i)
if (p0%state /= alive$) cycle
call drift_particle_to_t(p0, t_target, branch)
enddo
return
endif

! Convert bunch to s-based coordinates

s_begin = branch%ele(0)%s
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/23 01:45:26"
character(*), parameter :: tao_version_date = "2023/09/26 22:48:47"
end module
Loading

0 comments on commit 5e64091

Please sign in to comment.