Skip to content

Commit

Permalink
Fix setting of super_slave and multipass_slave attribute elements. (#…
Browse files Browse the repository at this point in the history
  • Loading branch information
DavidSagan authored Aug 4, 2024
1 parent f9674aa commit b0e60d5
Show file tree
Hide file tree
Showing 13 changed files with 80 additions and 54 deletions.
6 changes: 3 additions & 3 deletions bmad/code/set_ele_attribute.f90
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,8 @@
! set_string -- character(*): Attribute and value for set.
! err_print_flag -- logical, optional: If present and False then suppress printing
! of an error message if attribute is, for example, not free.
! set_lords -- logical, optional: Default False. If True, set the super_lord(s) or multipass_lord
! if the element is a super_slave or multipass_slave.
! set_lords -- logical, optional: Default False. If True, set the super_lord(s)
! if the element is a super_slave.
!
! Output:
! ele -- ele_struct: Element with attribute set.
Expand Down Expand Up @@ -94,7 +94,7 @@ subroutine set_ele_attribute (ele, set_string, err_flag, err_print_flag, set_lor

current_file%full_name = ''

if (ele%slave_status == super_slave$ .or. ele%slave_status == multipass_slave$) then
if (logic_option(.false., set_lords) .and. ele%slave_status == super_slave$) then
do i = 1, ele%n_lord
lord => pointer_to_lord(ele, i)
if (lord%slave_status == multipass_slave$) lord => pointer_to_lord(ele, 1)
Expand Down
13 changes: 13 additions & 0 deletions bmad/doc/superimpose-and-multipass.tex
Original file line number Diff line number Diff line change
Expand Up @@ -525,6 +525,19 @@ \subsection{Multipass Fundamentals}
cavity back to itself needs to be properly adjusted to get the desired phase advance. See the discussion
in section~\sref{s:rf.time}.

``Intrinsic'' attributes are attributes that must, to make sense physically, be the same for all
slaves of a given multipass lord. The element length is one such example. The following
non-intrinsic attributes can be set in a multipass slave and will not affect the corresponding
attributes in the lord or the other slaves of the lord:
\begin{example}
csr_ds_step num_steps
csr_method ptc_integration_type
ds_step spin_tracking_method
field_calc space_charge_method
integrator_order tracking_method
mat6_calc_method
\end{example}

Multiple elements of the same name in a multipass line are considered
physically distinct. Example:
\begin{example}
Expand Down
6 changes: 3 additions & 3 deletions bmad/modules/attribute_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3113,12 +3113,12 @@ function check_this_attribute_free (ele, attrib_name, lat, err_print_flag, excep

if (ele%slave_status == multipass_slave$) then
select case (a_name)
case ('CSR_METHOD', 'SPACE_CHARGE_METHOD', 'DESCRIP', 'ALIAS', 'TYPE'); return
case ('CSR_METHOD', 'SPACE_CHARGE_METHOD', 'DESCRIP', 'ALIAS', 'TYPE', 'TRACKING_METHOD', &
'MAT6_CALC_METHOD', 'SPIN_TRACKING_METHOD', 'FIELD_CALC', 'PHI0_MULTIPASS', 'PTC_INTEGRATION_TYPE', &
'INTEGRATOR_ORDER', 'DS_STEP', 'CSR_DS_STEP', 'NUM_STEPS'); return
end select

select case (ele%key)
case (lcavity$, rfcavity$)
if (ix_attrib == phi0_multipass$) return
case (patch$)
lord => pointer_to_lord(ele, 1)
end select
Expand Down
20 changes: 10 additions & 10 deletions bmad/modules/changed_attribute_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -129,32 +129,32 @@ subroutine set_flags_for_changed_integer_attribute (ele, attrib, set_dependent)

! Set independent stuff in multipass lord

if (ele%lord_status == multipass_lord$) then

if (ele%lord_status == multipass_lord$) then
do i = 1, ele%n_slave
slave => pointer_to_slave(ele, i)

if (associated(a_ptr, ele%aperture_at)) then
slave%aperture_at = a_ptr
elseif (associated(a_ptr, ele%ptc_integration_type)) then
slave%ptc_integration_type = a_ptr
elseif (associated(a_ptr, ele%aperture_type)) then
ele%aperture_type = a_ptr
slave%aperture_type = a_ptr
elseif (associated(a_ptr, ele%mat6_calc_method)) then
ele%mat6_calc_method = a_ptr
slave%mat6_calc_method = a_ptr
elseif (associated(a_ptr, ele%tracking_method)) then
ele%tracking_method = a_ptr
slave%tracking_method = a_ptr
elseif (associated(a_ptr, ele%spin_tracking_method)) then
ele%spin_tracking_method = a_ptr
slave%spin_tracking_method = a_ptr
elseif (associated(a_ptr, ele%field_calc)) then
ele%field_calc = a_ptr
slave%field_calc = a_ptr
elseif (associated(a_ptr, ele%csr_method)) then
ele%csr_method = a_ptr
slave%csr_method = a_ptr
elseif (associated(a_ptr, ele%space_charge_method)) then
ele%space_charge_method = a_ptr
slave%space_charge_method = a_ptr
else
exit
endif
enddo

endif

end subroutine set_flags_for_changed_integer_attribute
Expand Down
2 changes: 1 addition & 1 deletion tao/code/tao_change_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -346,7 +346,7 @@ subroutine tao_change_ele (ele_name, attrib_name, num_str, update, err_flag)

delta = m_ptr(i)%r - old_value(i)

call tao_set_flags_for_changed_attribute(u, e_name, eles(i)%ele, m_ptr(i)%r, who = a_name)
call tao_set_flags_for_changed_attribute(u, e_name, eles(i)%ele, m_ptr(i), who = a_name)

max_val = max(abs(old_value(i)), abs(m_ptr(i)%r), abs(d_ptr(1)%r))
str = real_num_fortran_format(max_val, 14, 2)
Expand Down
7 changes: 3 additions & 4 deletions tao/code/tao_command.f90
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ subroutine tao_command (command_line, err_flag, err_is_fatal)
'output ']

logical quit_tao, err, err_is_fatal, silent, gang, abort, err_flag, ok
logical include_wall, update, exact, include_this, lord_set, listing, found
logical include_wall, update, exact, include_this, listing, found

! blank line => nothing to do

Expand Down Expand Up @@ -650,7 +650,6 @@ subroutine tao_command (command_line, err_flag, err_is_fatal)

case ('set')
update = .false.
lord_set = .true.
set_word = ''
branch_str = ''
mask = ''
Expand All @@ -669,7 +668,7 @@ subroutine tao_command (command_line, err_flag, err_is_fatal)
case ('-listing')
listing = .true.
case ('-lord_no_set')
lord_set = .false.
call out_io (s_warn$, r_name, 'Note: The "-lord_no_set" no longer exists. This set will be ignored.')
case ('-branch')
call tao_next_word(cmd_line, branch_str)
case ('-mask')
Expand Down Expand Up @@ -788,7 +787,7 @@ subroutine tao_command (command_line, err_flag, err_is_fatal)
case ('dynamic_aperture')
call tao_set_dynamic_aperture_cmd (cmd_word(1), cmd_word(3))
case ('element')
call tao_set_elements_cmd (cmd_word(1), cmd_word(2), cmd_word(4), update, lord_set)
call tao_set_elements_cmd (cmd_word(1), cmd_word(2), cmd_word(4), update)
case ('floor_plan')
call tao_set_drawing_cmd (s%plot_page%floor_plan, cmd_word(1), cmd_word(3))
case ('geodesic_lm')
Expand Down
14 changes: 8 additions & 6 deletions tao/code/tao_graph_setup_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1257,10 +1257,11 @@ subroutine tao_curve_data_setup (plot, graph, curve)
type (ele_struct), pointer :: ele, ele1, ele2, slave
type (branch_struct), pointer :: branch
type (tao_curve_array_struct), allocatable :: curves(:)
type (all_pointer_struct) var_ptr

real(rp) f, eps, gs, l_tot, s0, s1, x_max, x_min, val, val0, dx, limit, len_branch
real(rp), allocatable :: value_arr(:), x_arr(:), y_arr(:)
real(rp), pointer :: var_ptr


integer ii, k, m, n, n_dat, n2_dat, ib, ie, jj, iv, ic
integer ix, ir, jg, i, j, ix_this, ix_uni, ix1, ix2, n_curve_pts, ix_slave
Expand Down Expand Up @@ -1405,6 +1406,7 @@ subroutine tao_curve_data_setup (plot, graph, curve)
call re_allocate (curve%y_symb, n_curve_pts)
call re_allocate (curve%x_line, n_curve_pts)
call re_allocate (curve%y_line, n_curve_pts)
var_ptr = all_pointer_struct()

if (plot%x_axis_type == 'lat') then

Expand All @@ -1429,26 +1431,26 @@ subroutine tao_curve_data_setup (plot, graph, curve)
call tao_set_curve_invalid (curve, 'BAD VARIABLE CONSTRUCT IN CURVE%DATA_TYPE_X: ' // curve%data_type_x)
return
endif
var_ptr => scratch%attribs(1)%r
var_ptr%r => scratch%attribs(1)%r

else ! x_axis_type == 'var'
call tao_find_var (err, curve%data_type_x, v_array = scratch%var_array)
if (err .or. size(scratch%var_array) /= 1) then
call tao_set_curve_invalid (curve, 'BAD VARIABLE CONSTRUCT IN CURVE%DATA_TYPE_X: ' // curve%data_type_x)
return
endif
var_ptr => scratch%var_array(1)%v%model_value
var_ptr%r => scratch%var_array(1)%v%model_value
endif

! Get datum values as a function of the variable

val0 = var_ptr
val0 = var_ptr%r

j = 0
do i = 1, n_curve_pts
val = graph%x%eval_min + (graph%x%eval_max - graph%x%eval_min) * (i - 1.0_rp) / (n_curve_pts - 1)
if (plot%x_axis_type == 'lat')then
var_ptr = val
var_ptr%r = val
call tao_set_flags_for_changed_attribute (u, name(1:ix1-1), scratch%eles(1)%ele, var_ptr)
s%u(ix_uni)%calc%lattice = .true.
else
Expand Down Expand Up @@ -1483,7 +1485,7 @@ subroutine tao_curve_data_setup (plot, graph, curve)
! Reset

if (plot%x_axis_type == 'lat')then
var_ptr = val0
var_ptr%r = val0
call tao_set_flags_for_changed_attribute (u, name(1:ix1-1), scratch%eles(1)%ele, var_ptr)
s%u(ix_uni)%calc%lattice = .true.
else
Expand Down
2 changes: 1 addition & 1 deletion tao/code/tao_interface.f90
Original file line number Diff line number Diff line change
Expand Up @@ -709,7 +709,7 @@ subroutine tao_set_flags_for_changed_attribute (u, ele_name, ele_ptr, val_ptr, w
implicit none
type (tao_universe_struct), target :: u
type (ele_struct), pointer, optional :: ele_ptr
real(rp), pointer, optional :: val_ptr
type (all_pointer_struct), optional :: val_ptr
character(*) ele_name
character(*), optional :: who
end subroutine
Expand Down
7 changes: 4 additions & 3 deletions tao/code/tao_set_flags_for_changed_attribute.f90
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,8 @@
! ele_name -- character(*): Associated "element" of the changed parameter.
! ele_ptr -- ele_struct, pointer, optional: Pointer to the element.
! May be null, for example, if ele_name = "PARTICLE_START".
! val_ptr -- real(rp):, pointer, optional: Pointer to the attribute that was changed.
! val_ptr -- all_pointer_struct: optional: Pointer to the attribute that was changed.
! Must be present if ele_ptr is present.
! who -- character(*), optional: Name of changed attribute. Only used with PARTICLE_START.
!-

Expand All @@ -23,8 +24,8 @@ subroutine tao_set_flags_for_changed_attribute (u, ele_name, ele_ptr, val_ptr, w
type (tao_universe_struct), target :: u
type (ele_struct), pointer, optional :: ele_ptr
type (lat_struct), pointer :: lat
type (all_pointer_struct), optional :: val_ptr

real(rp), pointer, optional :: val_ptr
integer ib, ie, n_loc, ix_branch
logical err

Expand Down Expand Up @@ -57,7 +58,7 @@ subroutine tao_set_flags_for_changed_attribute (u, ele_name, ele_ptr, val_ptr, w
else
if (ele_ptr%ix_ele <= u%model_branch(ix_branch)%beam%ix_track_start) &
u%model_branch(ix_branch)%beam%init_starting_distribution = .true.
if (present(val_ptr)) call set_flags_for_changed_attribute (ele_ptr, val_ptr)
call set_flags_for_changed_attribute (ele_ptr, val_ptr)
endif
endif
endif
Expand Down
41 changes: 31 additions & 10 deletions tao/code/tao_set_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2956,7 +2956,7 @@ end subroutine tao_set_universe_cmd
!-----------------------------------------------------------------------------
!------------------------------------------------------------------------------
!+
! Subroutine tao_set_elements_cmd (ele_list, attribute, value, update, lord_set)
! Subroutine tao_set_elements_cmd (ele_list, attribute, value, update)
!
! Sets element parameters.
!
Expand All @@ -2966,13 +2966,14 @@ end subroutine tao_set_universe_cmd
! value -- Character(*): Value to set.
!-

subroutine tao_set_elements_cmd (ele_list, attribute, value, update, lord_set)
subroutine tao_set_elements_cmd (ele_list, attribute, value, update)

use attribute_mod, only: attribute_type

implicit none

type (ele_pointer_struct), allocatable :: eles(:), v_eles(:)
type (ele_struct), pointer :: ele, lord
type (tao_universe_struct), pointer :: u
type (all_pointer_struct) a_ptr
type (tao_lattice_struct), pointer :: tao_lat
Expand All @@ -2989,6 +2990,8 @@ subroutine tao_set_elements_cmd (ele_list, attribute, value, update, lord_set)

! Find elements

lord_set = .true.

call tao_locate_all_elements (ele_list, eles, err)
if (err) return
if (size(eles) == 0) then
Expand All @@ -3003,12 +3006,17 @@ subroutine tao_set_elements_cmd (ele_list, attribute, value, update, lord_set)
! And set_ele_attribute cannot handle the situation where there is an array of set values.
! How to handle this depends upon what type of attribute it is.

! Another complication is that something like:
! set ele A:B k1 = 0.1
! Here if there are super slave elements in the range A:B we want to set the lord.
! Exception: phi0_multipass.

! If a real attribute then use tao_evaluate_expression to evaluate.
! If attribute_type returns invalid_name$ then assume attribute is a controller variable which are always real.

if (attribute_type(upcase(attribute)) == is_real$ .or. attribute_type(upcase(attribute)) == invalid_name$) then
! Important to use "size(eles)" as 2nd arg instead of "0" since if value is something like "ran()" then
! want a an array of set_val values with each value different.
! want an array of set_val values with each value different.
call tao_evaluate_expression (value, size(eles), .false., set_val, err)
if (err) return

Expand All @@ -3020,21 +3028,32 @@ subroutine tao_set_elements_cmd (ele_list, attribute, value, update, lord_set)

n_set = 0
do i = 1, size(eles)
call pointer_to_attribute(eles(i)%ele, attribute, .true., a_ptr, err, err_print_flag = .false.)
ele => eles(i)%ele

call pointer_to_attribute(ele, attribute, .true., a_ptr, err, err_print_flag = .false.)
if (err) cycle
if (.not. associated(a_ptr%r)) then
call out_io (s_error$, r_name, 'STRANGE ERROR: PLEASE CONTACT HELP.')
return
endif

call set_ele_real_attribute (eles(i)%ele, attribute, set_val(i), err, .false.)
if (.not. err) n_set = n_set + 1
call tao_set_flags_for_changed_attribute (s%u(eles(i)%id), eles(i)%ele%name, eles(i)%ele, a_ptr%r)
if (ele%slave_status == super_slave$) then
do j = 1, ele%n_lord
lord => pointer_to_lord(ele, j)
call set_ele_real_attribute (lord, attribute, set_val(i), err, .false.)
if (.not. err) n_set = n_set + 1
call tao_set_flags_for_changed_attribute (s%u(eles(i)%id), lord%name, lord, a_ptr)
enddo
else
call set_ele_real_attribute (ele, attribute, set_val(i), err, .false.)
if (.not. err) n_set = n_set + 1
call tao_set_flags_for_changed_attribute (s%u(eles(i)%id), ele%name, ele, a_ptr)
endif
enddo

if (n_set == 0) then
i = size(eles)
call set_ele_real_attribute (eles(i)%ele, attribute, set_val(i), err, .true.)
call set_ele_real_attribute (ele, attribute, set_val(i), err, .true.)
call out_io (s_error$, r_name, 'NOTHING SET.')
endif

Expand All @@ -3047,10 +3066,11 @@ subroutine tao_set_elements_cmd (ele_list, attribute, value, update, lord_set)
call tao_var_check(eles, attribute, update)

return
endif

! If there is a "ele::" construct in the value string...

elseif (index(value, 'ele::') /= 0) then
if (index(value, 'ele::') /= 0) then

val_str = value
u => tao_pointer_to_universe(val_str)
Expand Down Expand Up @@ -3108,7 +3128,8 @@ subroutine tao_set_elements_cmd (ele_list, attribute, value, update, lord_set)
do i = 1, size(eles)
u => s%u(eles(i)%id)
call set_ele_attribute (eles(i)%ele, trim(attribute) // '=' // trim(val_str), err, .false., lord_set)
call tao_set_flags_for_changed_attribute (u, eles(i)%ele%name, eles(i)%ele)
call pointer_to_attribute(eles(i)%ele, attribute, .true., a_ptr, err)
call tao_set_flags_for_changed_attribute (u, eles(i)%ele%name, eles(i)%ele, a_ptr)
if (.not. err) n_set = n_set + 1
enddo

Expand Down
12 changes: 1 addition & 11 deletions tao/doc/command-list.tex
Original file line number Diff line number Diff line change
Expand Up @@ -1261,22 +1261,12 @@ \subsection{set element}

Format:
\begin{example}
set \{-update\} \{-lord_no_set\} element <element_list> <attribute> = <value>
set \{-update\} element <element_list> <attribute> = <value>
\end{example}

The \vn{set element} command sets the attributes of an element. Use the \vn{show element}
command to view the attributes of an element.

The \vn{-lord_no_set} switch, if present, will prevent the set of the corresponding attribute in a
\vn{super_lord} or \vn{multipass_lord} of a slave element that appears in \vn{element_list}. For
example:
\begin{example}
set ele -lord quad::A:B field_calc = True
\end{example}
In this example the element list is all quadrupole in the region between elements \vn{A} and \vn{B}
in the lattice. The presence of the \vn{-lord_no_set} switch means that any \vn{super_slave} or
\vn{multipass_slave} quadrupole in that region will be ignored.

The \vn{-update} switch, if present, suppresses \tao from printing error messages if a ``variable
slave value mismatch'' is detected (\sref{s:var.mismatch}). Independent of whether \vn{-update} is
present or not, \tao will fix the mismatch using the changed value to set all of the slave values.
Expand Down
2 changes: 1 addition & 1 deletion tao/doc/cover-page.tex
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

\begin{flushright}
\large
Revision: July 18, 2024 \\
Revision: August 4, 2024 \\
\end{flushright}

\vfill
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 = "2024/08/02 23:02:22"
character(*), parameter :: tao_version_date = "2024/08/04 00:48:43"
end module

0 comments on commit b0e60d5

Please sign in to comment.