Skip to content

Commit

Permalink
Minor mod. (#1013)
Browse files Browse the repository at this point in the history
* auto_bookkeeper now deprecated.
  • Loading branch information
DavidSagan committed Jun 22, 2024
1 parent 7da7f46 commit 5881fd3
Show file tree
Hide file tree
Showing 21 changed files with 539 additions and 151 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -73,6 +73,7 @@ bsim/**/doc/*.pdf
regression_tests/*/output.now
regression_tests/*/lat.bmad
regression_tests/*/r
regression_tests/*/rr
regression_tests/*/rt
regression_tests/*/m
regression_tests/bbu_test/bunch_vec.txt
Expand Down
4 changes: 2 additions & 2 deletions bmad/code/attribute_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -93,9 +93,9 @@ subroutine attribute_bookkeeper (ele, force_bookkeeping)
if (ele%bookkeeping_state%attributes /= stale$) return

if (.false. .and. bp_com%parser_name == '') then ! If not parsing should not be here
call out_io (s_error$, r_name, &
call out_io (s_warn$, r_name, &
'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!', &
'!!!!! Setting bmad_com%auto_bookkeeper = .false. will, in the near future, be mandated for all !!!!!', &
'!!!!! Using intelligent bookkeeping will, in the near future, be mandated for all !!!!!', &
'!!!!! Bmad programs that modify lattice parameters. !!!!!', &
'!!!!! See the "Intelligent Bookkeeping" section in the Bmad manual. !!!!!', &
'!!!!! Contact the maintainer of this program with this information. !!!!!', &
Expand Down
27 changes: 26 additions & 1 deletion bmad/code/chrom_tune.f90
Original file line number Diff line number Diff line change
Expand Up @@ -110,6 +110,7 @@ subroutine chrom_tune(lat, delta_e, target_x, target_y, err_tol, err_flag)

if (status < 0) then
call out_io (s_error$, r_name, 'SINGULAR MATRIX ENCOUNTERED!')
call this_bookkeeping()
return
endif

Expand All @@ -127,16 +128,34 @@ subroutine chrom_tune(lat, delta_e, target_x, target_y, err_tol, err_flag)
else
lat%ele(ix_y_sex(:))%value(k2$) = sex_y_value(:) * (1 + k2_vec(2))
endif
call this_bookkeeping()
return
endif
enddo

call out_io (s_error$, r_name, 'CANNOT ADJUST SEXTUPOLES TO GET DESIRED CHROMATICITIES!')
err_flag = .true.

!------------------------------------------------------
!-------------------------------------------------------
contains

subroutine this_bookkeeping()

do i = 1, size(ix_x_sex)
ele => lat%ele(ix_x_sex(i))
call set_flags_for_changed_attribute(ele, ele%value(k2$))
enddo

do i = 1, size(ix_y_sex)
ele => lat%ele(ix_y_sex(i))
call set_flags_for_changed_attribute(ele, ele%value(k2$))
enddo

end subroutine this_bookkeeping

!------------------------------------------------------
! contains

subroutine chrom_func (a_try, y_fit, dy_da, status)

real(rp), intent(in) :: a_try(:)
Expand All @@ -161,7 +180,9 @@ subroutine chrom_func (a_try, y_fit, dy_da, status)
lat%ele(ix_y_sex(:))%value(k2$) = sex_y_value(:) * (1 + a_try(2))
endif

call this_bookkeeping()
call chrom_calc(lat, delta_e, chrom_x0, chrom_y0)

y_fit = [chrom_x0, chrom_y0]

if (all_x_zero) then
Expand All @@ -176,7 +197,9 @@ subroutine chrom_func (a_try, y_fit, dy_da, status)
lat%ele(ix_y_sex(:))%value(k2$) = sex_y_value(:) * (1 + a_try(2))
endif

call this_bookkeeping()
call chrom_calc(lat, delta_e, chrom_x, chrom_y)

dy_da(1,1) = (chrom_x - chrom_x0) / delta
dy_da(2,1) = (chrom_y - chrom_y0) / delta

Expand All @@ -192,7 +215,9 @@ subroutine chrom_func (a_try, y_fit, dy_da, status)
lat%ele(ix_y_sex(:))%value(k2$) = sex_y_value(:) * (1 + a_try(2) + delta)
endif

call this_bookkeeping()
call chrom_calc(lat, delta_e, chrom_x, chrom_y)

dy_da(1,2) = (chrom_x - chrom_x0) / delta
dy_da(2,2) = (chrom_y - chrom_y0) / delta

Expand Down
10 changes: 8 additions & 2 deletions bmad/code/lat_compute_reference_energy.f90
Original file line number Diff line number Diff line change
Expand Up @@ -69,8 +69,10 @@ subroutine lat_compute_ref_energy_and_time (lat, err_flag)
if (begin_ele%value(inherit_from_fork$) == real_garbage$) then ! Happens first time this routine is called from bmad_parser.
begin_ele%value(inherit_from_fork$) = false$
if (associated(fork_ele)) then
if (begin_ele%ref_species == fork_ele%ref_species .or. begin_ele%ref_species == not_set$) &
begin_ele%value(inherit_from_fork$) = true$
if (begin_ele%ref_species == fork_ele%ref_species .or. begin_ele%ref_species == not_set$) then
begin_ele%value(inherit_from_fork$) = true$
begin_ele%old_value(inherit_from_fork$) = true$
endif
endif
endif

Expand Down Expand Up @@ -138,6 +140,10 @@ subroutine lat_compute_ref_energy_and_time (lat, err_flag)
begin_ele%value(ref_time_start$) = begin_ele%ref_time
endif

begin_ele%old_value(e_tot$) = begin_ele%value(e_tot$)
begin_ele%old_value(e_tot_start$) = begin_ele%value(e_tot_start$)
begin_ele%old_value(p0c$) = begin_ele%value(p0c$)
begin_ele%old_value(p0c_start$) = begin_ele%value(p0c_start$)
begin_ele%bookkeeping_state%ref_energy = ok$

!
Expand Down
12 changes: 12 additions & 0 deletions bmad/code/lattice_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ subroutine lattice_bookkeeper (lat, err_flag)

use bookkeeper_mod, dummy => lattice_bookkeeper
use precision_constants, only: e_muon ! PTC
use bmad_parser_struct, only: bp_com

implicit none

Expand Down Expand Up @@ -60,6 +61,17 @@ subroutine lattice_bookkeeper (lat, err_flag)
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), dval)

if (any(dval /= 0) .and. bp_com%parser_name == '') then ! If not parsing then error
call out_io (s_warn$, r_name, &
'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!', &
'!!!!! Using intelligent bookkeeping will, in the near future, be mandated for all !!!!!', &
'!!!!! Bmad programs that modify lattice parameters. !!!!!', &
'!!!!! See the "Intelligent Bookkeeping" section in the Bmad manual. !!!!!', &
'!!!!! Contact the maintainer of this program with this information. !!!!!', &
'!!!!! This program will run now but in the future this will change. !!!!!', &
'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!')
endif
enddo
enddo
endif
Expand Down
12 changes: 10 additions & 2 deletions bmad/code/set_z_tune.f90
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ subroutine set_z_tune (branch, z_tune, ok, print_err)
integer i, j, k, ix, is, status
integer :: loop_max = 10

logical found_control, err_flag
logical found_control, err_flag, auto_saved

! common

Expand All @@ -58,6 +58,7 @@ subroutine set_z_tune (branch, z_tune, ok, print_err)

! Error detec and init.

auto_saved = bmad_com%auto_bookkeeper
Qz_rel_tol = 1d-5
Qz_abs_tol = 1d-7

Expand Down Expand Up @@ -140,6 +141,7 @@ subroutine set_z_tune (branch, z_tune, ok, print_err)
' 1) ON, AND', &
' 2) HAVE A FINETE RF_FREQUENCY!', &
' THE Z TUNE WILL NOT BE SET.')
bmad_com%auto_bookkeeper = auto_saved
return
endif

Expand All @@ -152,6 +154,7 @@ subroutine set_z_tune (branch, z_tune, ok, print_err)
if (branch%z%tune == 0) then
call out_io (s_error$, r_name, 'CALCULATED Z TUNE IS ZERO. CANNOT SET THE TUNE.')
if (global_com%exit_on_error) call err_exit
bmad_com%auto_bookkeeper = auto_saved
return
endif

Expand Down Expand Up @@ -182,7 +185,10 @@ subroutine set_z_tune (branch, z_tune, ok, print_err)
! now set cavity voltage to get the correct tune

do k = 1, loop_max
if (abs(dz_tune) < Qz_abs_tol) return
if (abs(dz_tune) < Qz_abs_tol) then
bmad_com%auto_bookkeeper = auto_saved
return
endif

if (dz_tune * dz_tune0 < 0) exit ! Have bracketed solution

Expand All @@ -202,6 +208,7 @@ subroutine set_z_tune (branch, z_tune, ok, print_err)
if (global_com%exit_on_error) call err_exit
endif
branch%z%stable = .false.
bmad_com%auto_bookkeeper = auto_saved
return
endif
enddo
Expand All @@ -211,6 +218,7 @@ subroutine set_z_tune (branch, z_tune, ok, print_err)
coef = super_zbrent (dz_tune_func, min(coef0, coef), max(coef0, coef), Qz_rel_tol, Qz_abs_tol, status)
dz_tune = dz_tune_func(coef, status)
branch%z%stable = .true.
bmad_com%auto_bookkeeper = auto_saved

!-------------------------------------------------------------------------------------
contains
Expand Down
1 change: 1 addition & 0 deletions bmad/modules/bookkeeper_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1908,6 +1908,7 @@ subroutine attributes_need_bookkeeping (ele, dval)
select case (ele%key)
case (overlay$, group$, hybrid$)
ele%bookkeeping_state%attributes = ok$
if (present(dval)) dval = 0
return
end select

Expand Down
17 changes: 15 additions & 2 deletions regression_tests/bend_test/bend_test.bmad
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,23 @@ beginning[alpha_a] = 0
beginning[alpha_b] = 0
beginning[etap_x] = 0.001

b: rbend, l_rectangle = 2.0, angle = -0.1, fiducial_pt = entrance_end, e2 = -0
b1: rbend, l_rectangle = 2.0, angle = -0.1, e1 = -0.01, e2 = 0.02, fiducial_pt = none
b2: rbend, l_rectangle = 2.0, angle = -0.1, e1 = -0.01, e2 = 0.02, fiducial_pt = entrance_end
b3: rbend, l_rectangle = 2.0, angle = -0.1, e1 = -0.01, e2 = 0.02, fiducial_pt = center
b4: rbend, l_rectangle = 2.0, angle = -0.1, e1 = -0.01, e2 = 0.02, fiducial_pt = exit_end

ln: line = (b)
ln: line = (b1, b2, b3, b4)
use, ln

no_digested


end_file

!------------------------


&params
dg = 0.01
dangle = 0.1
/
38 changes: 29 additions & 9 deletions regression_tests/bend_test/bend_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,23 +8,42 @@ program bend_test
type (ele_struct), pointer :: ele
type (ele_struct) ele0

real(rp) dparam(5), pa(4), f
integer ie, ip, iz, ix_param(5), np
real(rp) dparam(3), vals(4), f, dg, dangle
integer ie, ip, iz, ix_param(3), np, nargs
character(40) str
character(200) lat_file

namelist / params / dg, dangle

!

lat_file = 'bend_test.bmad'
nargs = command_argument_count()
if (nargs > 0) then
call get_command_argument(1, lat_file)
endif

!

open (1, file = 'output.now', recl = 200)

bmad_com%auto_bookkeeper = .false.
call bmad_parser('bend_test.bmad', lat)
call bmad_parser(lat_file, lat)

open (2, file = lat_file)
read (2, nml = params)
close (2)

!

f = lat%ele(0)%value(p0c$) / c_light
dparam = [0.01_rp, 0.1_rp, 0.1_rp * f, 0.1_rp, 0.1_rp]
ix_param = [g$, angle$, b_field$, l$, l_rectangle$]
dparam = [dg, dangle, dg * f]
ix_param = [g$, angle$, b_field$]


do ie = 1, lat%n_ele_track
ele0 = lat%ele(ie)
if (ie > 1) write (1, *)

do ip = 1, size(ix_param)
ele => lat%ele(ie)
Expand All @@ -33,12 +52,13 @@ program bend_test
ele%value(np) = ele%value(np) + dparam(ip)
call set_flags_for_changed_attribute(ele, ele%value(np))
call lattice_bookkeeper(lat)
str = '"' // int_str(ie) // '-' // trim(ele%name) // '-' // trim(attribute_name(ele, np))

pa(1:3) = [ele%value(ix_param(1)), ele%value(ix_param(2)), ele%value(ix_param(3)) / f]
write (1, '(a, i0, 3a, 4f16.10)') '"', ie, '-', trim(attribute_name(ele, np)), ':g-ang-field" ABS 1E-10', pa(1:3)
vals(1:3) = [ele%value(g$), ele%value(angle$), ele%value(b_field$) / f]
write (1, '(2a, 4f16.10)') trim(str), ' g-ang-field" ABS 1E-10', vals(1:3)

pa = [ele%value(ix_param(4)), ele%value(ix_param(5)), ele%value(e1$), ele%value(e2$)]
write (1, '(a, i0, 3a, 4f16.10)') '"', ie, '-', trim(attribute_name(ele, np)), ':l-lr-e1/2" ABS 1E-10', pa
vals = [ele%value(l$), ele%value(l_rectangle$), ele%value(e1$), ele%value(e2$)]
write (1, '(2a, 4f16.10)') trim(str), ' l-lr-e1/2" ABS 1E-10', vals
enddo
enddo

Expand Down
47 changes: 27 additions & 20 deletions regression_tests/bend_test/output.correct
Original file line number Diff line number Diff line change
@@ -1,20 +1,27 @@
"1-p1-G" ABS 1E-10 0.0100000000 0.0200013336 -0.0100000000
"1-p2-G" ABS 1E-10 2.0001333573 2.0000000000 0.0000000000 0.0200013336
"1-p1-ANGLE" ABS 1E-10 0.0499167083 0.0998334166 -0.0499167083
"1-p2-ANGLE" ABS 1E-10 2.0000000000 1.9966794182 0.0000000000 0.1000000000
"1-p1-B_FIELD" ABS 1E-10 -0.1000000000 -0.2013579208 0.1000000000
"1-p2-B_FIELD" ABS 1E-10 2.0135792079 2.0000000000 0.0000000000 -0.2013579208
"1-p1-L" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000
"1-p2-L" ABS 1E-10 2.1000000000 2.1000000000 0.0000000000 0.0000000000
"1-p1-L_RECTANGLE" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000
"1-p2-L_RECTANGLE" ABS 1E-10 2.1000000000 2.1000000000 0.0000000000 0.0000000000
"2-p1-NOISE" ABS 1E-10 0.0100000000 0.0000000000 0.0000000000
"2-p2-NOISE" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000 0.0000000000
"2-p1-!NULL" ABS 1E-10 0.0000000000 0.1000000000 0.0000000000
"2-p2-!NULL" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000 0.0000000000
"2-p1-!NULL" ABS 1E-10 0.0000000000 0.0000000000 0.1000000000
"2-p2-!NULL" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000 0.0000000000
"2-p1-L" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000
"2-p2-L" ABS 1E-10 0.1000000000 0.0000000000 0.0000000000 0.0000000000
"2-p1-X_DISPERSION_ERR" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000
"2-p2-X_DISPERSION_ERR" ABS 1E-10 0.0000000000 0.1000000000 0.0000000000 0.0000000000
"1-B1-G g-ang-field" ABS 1E-10 -0.0899583385 -0.0899958321 0.0899583385
"1-B1-G l-lr-e1/2" ABS 1E-10 1.0004167882 1.0000792130 -0.0600000000 -0.0300000000
"1-B1-ANGLE g-ang-field" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000
"1-B1-ANGLE l-lr-e1/2" ABS 1E-10 1.0004167882 1.0004167882 -0.0600000000 -0.0300000000
"1-B1-B_FIELD g-ang-field" ABS 1E-10 -0.1099583385 -0.1100041679 0.1099583385
"1-B1-B_FIELD l-lr-e1/2" ABS 1E-10 1.0004167882 0.9999124495 -0.0600000000 -0.0300000000

"2-B2-G g-ang-field" ABS 1E-10 -0.0399167083 -0.0798465124 0.0399167083
"2-B2-G l-lr-e1/2" ABS 1E-10 2.0003280761 1.9982032498 -0.0100000000 -0.0598465124
"2-B2-ANGLE g-ang-field" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000
"2-B2-ANGLE l-lr-e1/2" ABS 1E-10 1.9997998065 1.9997998065 -0.0100000000 0.0200000000
"2-B2-B_FIELD g-ang-field" ABS 1E-10 -0.0599167083 -0.1199652011 0.0599167083
"2-B2-B_FIELD l-lr-e1/2" ABS 1E-10 2.0021994607 1.9974004232 -0.0100000000 -0.0999652011

"3-B3-G g-ang-field" ABS 1E-10 -0.0899583385 -0.0899780267 0.0899583385
"3-B3-G l-lr-e1/2" ABS 1E-10 1.0002188584 0.9998814835 -0.0550050486 -0.0249729781
"3-B3-ANGLE g-ang-field" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000
"3-B3-ANGLE l-lr-e1/2" ABS 1E-10 0.9999874957 0.9999874957 -0.0600000000 0.0200000000
"3-B3-B_FIELD g-ang-field" ABS 1E-10 -0.1099583385 -0.1099980130 0.1099583385
"3-B3-B_FIELD l-lr-e1/2" ABS 1E-10 1.0003608132 0.9998565591 -0.0650227503 -0.0349752627

"4-B4-G g-ang-field" ABS 1E-10 -0.0399167083 -0.0799545201 0.0399167083
"4-B4-G l-lr-e1/2" ABS 1E-10 2.0030339039 2.0009004450 -0.0899545201 0.0200000000
"4-B4-ANGLE g-ang-field" ABS 1E-10 0.0000000000 0.0000000000 0.0000000000
"4-B4-ANGLE l-lr-e1/2" ABS 1E-10 2.0001000868 2.0001000868 -0.0100000000 0.0200000000
"4-B4-B_FIELD g-ang-field" ABS 1E-10 -0.0599167083 -0.1202008094 0.0599167083
"4-B4-B_FIELD l-lr-e1/2" ABS 1E-10 2.0061317242 2.0013043692 -0.1302008094 0.0200000000
1 change: 1 addition & 0 deletions regression_tests/bookkeeper_test/bookkeeper_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,7 @@ program bookkeeper_test

!-----------------------------------------

bmad_com%auto_bookkeeper = .false.
call bmad_parser('ramper.bmad', lat)

call lat_ele_locator ('ramper::*', lat, ramper, n, err)
Expand Down
1 change: 1 addition & 0 deletions regression_tests/cesr_test/cesr_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ program twiss_track_test

open (2, file = 'output.now', recl = 200)

bmad_com%auto_bookkeeper = .false.
lat_file = "bmad_L9A18A000-_MOVEREC.lat"
call bmad_parser (lat_file, lat2)
call write_digested_bmad_file ('digested.file', lat2)
Expand Down
Loading

0 comments on commit 5881fd3

Please sign in to comment.