Skip to content

Commit

Permalink
Tao version update. (bmad-sim#1375)
Browse files Browse the repository at this point in the history
* Fix match element on a girder.

* Tao version update.
  • Loading branch information
DavidSagan authored Jan 26, 2025
1 parent f218301 commit 3aeb0e6
Show file tree
Hide file tree
Showing 10 changed files with 53 additions and 25 deletions.
18 changes: 17 additions & 1 deletion bmad/code/attribute_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -132,7 +132,23 @@ subroutine attribute_bookkeeper (ele, force_bookkeeping)
do i = 1, size(ele%wake%lr%mode)
lr => ele%wake%lr%mode(i)
if (lr%freq_in < 0) lr%freq = ele%value(rf_frequency$)
if (lr%q /= real_garbage$) lr%damp = pi * lr%freq / lr%q

! Old style lattice files set Q and not damp.
if (lr%q /= real_garbage$) then
if (lr%q == 0) then
call out_io (s_error$, r_name, 'Q factor for LR wake mode is zero which does not make sense!', &
'For element: ' // ele%name)
else
lr%damp = pi * lr%freq / lr%q
endif
endif

if (lr%damp == 0) then
lr%q = 1d100
else
lr%q = pi * lr%freq / lr%damp
endif

enddo
endif

Expand Down
2 changes: 1 addition & 1 deletion bmad/code/set_on_off.f90
Original file line number Diff line number Diff line change
Expand Up @@ -136,7 +136,7 @@ subroutine set_on_off (key, lat, switch, orb, use_ref_orb, ix_branch, saved_valu
call set_value_of(a_ptr, false$)

case default
call out_io (s_abort$, r_name, 'BAD SWITCH: \i\ ', switch)
call out_io (s_abort$, r_name, 'BAD SWITCH: \i0\ ', switch)
if (global_com%exit_on_error) call err_exit
end select

Expand Down
1 change: 1 addition & 0 deletions bmad/low_level/control_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ subroutine control_bookkeeper (lat, ele, err_flag)
ele2 => branch%ele(ie)
if (ele2%bookkeeping_state%control /= stale$ .and. ele2%bookkeeping_state%attributes /= stale$) cycle
call control_bookkeeper1 (lat, ele2, .false., .true., err)
if (err) err_flag = .true.
ele2%bookkeeping_state%control = ok$
enddo

Expand Down
17 changes: 10 additions & 7 deletions bmad/modules/bookkeeper_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -286,11 +286,13 @@ recursive subroutine group_change_this (ele, attrib_name, ctl, dir, this_lord, t
'CONTROLS SUPER_LORD: ' // ele%name, &
'AND LORD_PAD1 IS NOW NEGATIVE: \f8.3\ ', r_array = [a_ptr%r])
err_flag = .true.
return
elseif (attrib_name == 'LORD_PAD2') then
call out_io (s_error$, r_name, 'GROUP ELEMENT: ' // lord%name, &
'CONTROLS SUPER_LORD: ' // ele%name, &
'AND LORD_PAD2 IS NOW NEGATIVE: \f8.3\ ', r_array = [a_ptr%r])
err_flag = .true.
return
endif
endif

Expand Down Expand Up @@ -726,7 +728,8 @@ subroutine makeup_super_slave (lat, slave, err_flag)
call out_io (s_abort$, r_name, &
'SUPERPOSITION OF ELEMENTS WITH WAKES NOT YET IMPLEMENTED!', &
'SUPER_LORD: ' // lord%name)
if (global_com%exit_on_error) call err_exit
err_flag = .true.
return
endif

! Physically, the lord length cannot be less than the slave length.
Expand Down Expand Up @@ -1585,7 +1588,8 @@ subroutine makeup_control_slave (lat, slave, err_flag)
if (lord%lord_status == multipass_lord$) cycle
if (lord%key == group$) cycle

if (lord%key == girder$ .and. has_orientation_attributes(slave)) then
if (lord%key == girder$) then
if (.not. has_orientation_attributes(slave)) cycle ! Example: Match element does not have orientation.
v => lord%value
vs => slave%value

Expand Down Expand Up @@ -1638,11 +1642,10 @@ subroutine makeup_control_slave (lat, slave, err_flag)
endif

if (lord%key /= overlay$) then
call out_io (s_abort$, r_name, 'THE LORD IS NOT AN OVERLAY \i\ ', ix_slave)
call type_ele (slave, .true., 0, .false., 0)
if (global_com%exit_on_error) call err_exit
endif

call out_io (s_abort$, r_name, 'THE LORD IS NOT AN OVERLAY: ', lord%name)
err_flag = .true.
return
endif

! overlay lord

Expand Down
19 changes: 13 additions & 6 deletions bmad/output/write_bmad_lattice_file.f90
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ subroutine write_bmad_lattice_file (bmad_file, lat, err, output_form, orbit0)
type (lat_ele_order_struct) order
type (material_struct), pointer :: material

real(rp) s0, x_lim, y_lim, val, x, y, z, fid
real(rp) s0, x_lim, y_lim, val, x, y, z, fid, f

character(*) bmad_file
character(4000) line
Expand Down Expand Up @@ -706,9 +706,9 @@ subroutine write_bmad_lattice_file (bmad_file, lat, err, output_form, orbit0)
', ' // re_str(lrm%damp) // ', ' // re_str(lrm%phi) // ', ' // int_str(lrm%m)

if (lrm%polarized) then
line = trim(line) // ', unpolarized'
else
line = trim(line) // ', ' // re_str(lrm%angle)
else
line = trim(line) // ', unpolarized'
endif

if (lrm%b_sin == 0 .and. lrm%b_cos == 0 .and. lrm%a_sin == 0 .and. lrm%a_cos == 0) then
Expand Down Expand Up @@ -760,15 +760,22 @@ subroutine write_bmad_lattice_file (bmad_file, lat, err, output_form, orbit0)
ix = index(line, '@,')
if (ix /= 0) line = line(1:ix-1) // '{' //line(ix+2:)
name = trim(ele%name) // '.sr_z_long'
f = 1
if (srz%time_based) f = 1.0_rp / c_light
line = trim(line) // ', z_long = {time_based = ' // logic_str(srz%time_based) // ', position_dependence = ' // &
trim(sr_transverse_position_dep_name(srz%position_dependence)) // ', smoothing_sigma = ' // re_str(srz%smoothing_sigma) // &
trim(sr_transverse_position_dep_name(srz%position_dependence)) // ', smoothing_sigma = ' // re_str(f*srz%smoothing_sigma) // &
', w = {call::' // trim(name) // '}'

iu2 = lunget()
open (iu2, file = trim(path) // '/' // trim(name))
do i = 1, size(srz%w)
n = size(srz%w)
do i = 1, n
z = -srz%z0 + (i-1) * srz%dz
write (iu2, '(es16.8, es20.12, a)') z, srz%w(i), ','
if (srz%time_based) then
write (iu2, '(es16.8, es20.12, a)') f*z, srz%w(n+1-i), ','
else
write (iu2, '(es16.8, es20.12, a)') z, srz%w(i), ','
endif
enddo
close(iu2)
line = trim(line) // '}'
Expand Down
3 changes: 2 additions & 1 deletion bmad/parsing/bmad_parser_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4541,7 +4541,8 @@ subroutine parser_add_lords (lord_lat, n_ele_max, plat, lat, check_lat)

enddo main_loop

call control_bookkeeper (lat)
call control_bookkeeper (lat, err_flag = err_flag)
if (err_flag) call parser_error('CONTROL BOOKKEEPING FAILED.')

!-------------------------------------------------------------------------
contains
Expand Down
2 changes: 1 addition & 1 deletion regression_tests/multipass_test/lat.bmad
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ CAVITY2: Lcavity, grid_field = call::cavity2.grid_field.h5, L = 0.568, RF_FREQUE

superimpose, element = DRI01, ref = slave_drift_0_1, offset = 2.25
superimpose, element = Q01, ref = slave_drift_0_2, offset = 0
superimpose, element = CAVITY2, ref = slave_drift_0_4, offset = 0.142
superimpose, element = CAVITY2, ref = slave_drift_0_4, offset = 0.141999999999999

!-------------------------------------------------------
! Lattice lines
Expand Down
8 changes: 4 additions & 4 deletions regression_tests/wake_test/wake_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ program wake_test
use beam_mod
use bmad

type (lat_struct), target :: lat
type (lat_struct), target :: lat, lat0
type (ele_struct), pointer :: ele, ele_z1, ele_p1, ele_p2
type (wake_sr_mode_struct), pointer :: w
type (coord_struct) :: orb0
Expand Down Expand Up @@ -35,9 +35,9 @@ program wake_test
call err_exit
endif

call bmad_parser (lat_file, lat)
!call write_bmad_lattice_file('lat2.bmad', lat)
!call bmad_parser('lat2.bmad', lat)
call bmad_parser (lat_file, lat0)
call write_bmad_lattice_file('lat2.bmad', lat0)
call bmad_parser('lat2.bmad', lat)

call ran_seed_put(123456)

Expand Down
6 changes: 3 additions & 3 deletions tao/doc/command-list.tex
Original file line number Diff line number Diff line change
Expand Up @@ -589,12 +589,12 @@ \section{pipe}\index{commands!pipe}
Note to programmers: For debugging, the \vn{show internal -pipe} command will show the \vn{c_real}
and \vn{c_integer} arrays.

List of possible \vn{<what_to_print>} choices:
Possible \vn{<subcommand>} choices are:
\begin{example}
beam, beam_init, branch1, bunch_comb, bunch_params, bunch1, bmad_com,
building_wall_list, building_wall_graph, building_wall_point,
building_wall_section, constraints, da_params, da_aperture, data,
data_d2_create, data_d2_destroy, data_d_array, data_d1_array,
building_wall_section, constraints, da_params, da_aperture,
data, data_d2_create, data_d2_destroy, data_d_array, data_d1_array,
data_d2, data_d2_array, data_set_design_value, data_parameter,
datum_create, datum_has_ele, derivative, ele:ac_kicker, ele:cartesian_map,
ele:chamber_wall, ele:control_var, ele:cylindrical_map, ele:elec_multipoles,
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 = "2025/01/22 22:35:54"
character(*), parameter :: tao_version_date = "2025/01/25 20:41:09"
end module

0 comments on commit 3aeb0e6

Please sign in to comment.