Skip to content

Commit

Permalink
Correct girder bookkeeping.
Browse files Browse the repository at this point in the history
  • Loading branch information
DavidSagan committed Aug 7, 2024
1 parent b0e60d5 commit 5dfb4cf
Show file tree
Hide file tree
Showing 9 changed files with 209 additions and 94 deletions.
4 changes: 2 additions & 2 deletions bmad/code/attribute_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -711,7 +711,7 @@ subroutine attribute_bookkeeper (ele, force_bookkeeping)
val(l_rectangle$) = sinc(val(angle$)) * val(l$)
end select

if (ele_value_has_changed(ele, [g$], [1e-10_rp], .false.)) then
if (ele_value_has_changed(ele, [g$, rho$], [1e-10_rp, 1e-10_rp], .false.)) then
call set_ele_status_stale (ele, floor_position_group$)
endif
endif
Expand Down Expand Up @@ -759,7 +759,7 @@ subroutine attribute_bookkeeper (ele, force_bookkeeping)
val(l_rectangle$) = sinc(val(angle$)) * val(l$)
end select

if (ele_value_has_changed(ele, [g$], [1e-10_rp], .false.)) then
if (ele_value_has_changed(ele, [g$, rho$], [1e-10_rp, 1e-10_rp], .false.)) then
call set_ele_status_stale (ele, floor_position_group$)
endif

Expand Down
18 changes: 11 additions & 7 deletions bmad/doc/elements.tex
Original file line number Diff line number Diff line change
Expand Up @@ -2547,8 +2547,9 @@ \section{Girder}
Girder supporting three elements labeled \vn{A}, \vn{B}, and \vn{C}. $\calO_A$ is the reference
frame at the upstream end of element \vn{A} (\sref{s:ref.construct}), $\calO_C$ is the reference
frame at the downstream end of element \vn{C}, and $\calO_G$ is the default \vn{origin} reference
frame of the girder. $r_{CA}$ is the vector from $\calO_A$ to $\calO_C$. The length \vn{l} of the
girder is the difference in $s$ between points $\calO_C$ and $\calO_A$.
frame of the girder if the \vn{origin_ele} parameter is not set. $\bfr_{CA}$ is the vector from
$\calO_A$ to $\calO_C$. The length \vn{l} of the girder is set to be the difference in $s$ between
points $\calO_C$ and $\calO_A$.
}
\label{f:girder}
\end{figure}
Expand Down Expand Up @@ -2657,7 +2658,11 @@ \section{Girder}
to \vn{center} results in the reference frame being the frame of the surface (cf.~\fig{f:surface}).

To specify that the global coordinates (\sref{s:global}) are to be used for a girder set
\vn{origin_ele} to \vn{global_coordinates}. Typically this is the same as using the \vn{beginning}
\vn{origin_ele} to
\begin{example}
global_coordinates
\end{example}
Typically this is the same as using the \vn{beginning}
element (\sref{s:begin.ele}) as the \vn{origin_ele} except when the \vn{beginning} element is offset
or reoriented (\sref{s:beginning}).

Expand All @@ -2667,10 +2672,9 @@ \section{Girder}
\vn{A} as shown in the figure. Let $\calO_C$ be the downstream end of the last element in the list
of supported elements. In this example this is the downstream end of element \vn{C}. The origin of
the \vn{girder}'s reference frame, marked $\calO_G$ in the figure, will be half way along the vector
$r_{CA}$ from the origin of $\calO_A$ to the origin of $\calO_B$. The orientation of $\calO_G$ is
constructed by rotating the $\calO_A$ coordinate system along an axis in $\calO_A$'s $x$-$y$ plane
such that $\calO_A$'s $z$ axis ends up parallel with $r_{CA}$. In the example above, the rotation
axis will be along $\calO_A$'s $y$-axis.
$r_{CA}$ from the origin of $\calO_A$ to the origin of $\calO_B$. The orientation of $\calO_G$ is
constructed by rotating the $\calO_A$ coordinates about an axis perpendicular to the $z$-axis of
$\calO_A$ and $\bfr_{CA}$ such that the $z$-axis of $\calO_G$ is parallel with $r_{CA}$.

Once the \vn{origin} reference frame is established, the reference frame of the girder can be offset
from the \vn{origin} frame using the parameters
Expand Down
164 changes: 114 additions & 50 deletions bmad/geometry/ele_geometry.f90
Original file line number Diff line number Diff line change
Expand Up @@ -39,14 +39,13 @@ recursive subroutine ele_geometry (floor_start, ele, floor_end, len_scale, ignor
implicit none

type (ele_struct), target :: ele
type (ele_struct), pointer :: ele0, ele00, slave0, slave1, ele2, this_ele, lord
type (ele_struct), pointer :: ele0, ele00, slave0, slave1, ele2, this_ele, slave
type (floor_position_struct), optional, target :: floor_end
type (floor_position_struct) :: floor_start, this_floor, old_floor, floor0
type (floor_position_struct), pointer :: floor
type (ele_pointer_struct), allocatable :: eles(:)
type (ele_pointer_struct), allocatable, target :: chain_ele(:)
type (lat_param_struct) param
type (lat_struct), pointer :: lat

real(rp), optional :: len_scale
real(rp) knl(0:n_pole_maxx), tilt(0:n_pole_maxx), dtheta
Expand All @@ -55,7 +54,7 @@ recursive subroutine ele_geometry (floor_start, ele, floor_end, len_scale, ignor
real(rp) theta, phi, psi, tlt, dz(3), z0(3), z_cross(3), eps, signif(6)
real(rp) :: w_mat(3,3), w_mat_inv(3,3), s_mat(3,3), r_vec(3), t_mat(3,3)

integer i, k, ie, key, n_loc, ix_pass, n_links, ix_pole_max, ib_to, ix, iv(6)
integer i, j, k, n, ie, key, n_loc, ix_pass, n_links, ix_pole_max, ib_to, ix, iv(6)

logical err, doit, finished, has_multipole_rot_tilt, ele_floor_geometry_calc
logical, optional :: ignore_patch_err
Expand Down Expand Up @@ -144,16 +143,60 @@ recursive subroutine ele_geometry (floor_start, ele, floor_end, len_scale, ignor
else ! Must have a reference element
if (ele%component_name == '') then ! Must be a floor_shift element
ele0 => pointer_to_next_ele(ele, -1)

else
call lat_ele_locator (ele%component_name, ele%branch%lat, eles, n_loc, err)
if (n_loc /= 1) then

! If multiple matches but one match is a slave of ele (which must be a girder), this is OK.
if (n_loc == 0) then
call out_io (s_fatal$, r_name, 'ORIGIN_ELE NAME: ' // ele%component_name, &
'FOR ELEMENT: ' // ele%name, &
'DOES NOT MATCH ANY ELEMENT!')
if (global_com%exit_on_error) call err_exit
return
endif

if (n_loc > 0) then
n = 0
do i = 1, n_loc
do j = 1, ele%n_slave
slave => pointer_to_slave(ele, j)
if (.not. (ele_loc(eles(i)%ele) == ele_loc(slave))) cycle
select case (n)
case (0); n = j
case default; n = -1 ! Mark that there are multiple slave element matches
end select
enddo
enddo
if (n > 0) then
n_loc = 1
eles(1)%ele => pointer_to_slave(ele, n)
endif
if (n_loc > 1) then
call out_io (s_fatal$, r_name, 'ORIGIN_ELE: ' // ele%component_name, &
'FOR ELEMENT: ' // ele%name, &
'IS NOT UNIQUE!')
if (global_com%exit_on_error) call err_exit
return
endif
endif

if (ele%lord_status == multipass_lord$ .or. ele%key == ramper$) then
call out_io (s_fatal$, r_name, 'ORIGIN_ELE: ' // ele%component_name, &
'FOR ELEMENT: ' // ele%name, &
'IS NOT UNIQUE!')
'IS A MULTIPASS_LORD OR RAMPER WHICH DOES NOT HAVE A UNIQUE POSITION')
if (global_com%exit_on_error) call err_exit
return
endif

if (ele%n_slave > 1 .and. (ele%key == overlay$ .or. ele%key == group$)) then
call out_io (s_fatal$, r_name, 'ORIGIN_ELE: ' // ele%component_name, &
'FOR ELEMENT: ' // ele%name, &
'IS AN OVERLAY OR GROUP ELEMENT WHICH HAS MORE THAN ONE SLAVE SO THERE IS NO UNIQUE POSITION')
if (global_com%exit_on_error) call err_exit
return
endif

ele0 => eles(1)%ele
endif

Expand Down Expand Up @@ -237,6 +280,7 @@ recursive subroutine ele_geometry (floor_start, ele, floor_end, len_scale, ignor
call update_floor_angles(floor, floor0)
endif

call end_bookkeeping(ele, old_floor, floor)
return
endif ! Fiducial, girder, floor_shift

Expand Down Expand Up @@ -474,67 +518,87 @@ recursive subroutine ele_geometry (floor_start, ele, floor_end, len_scale, ignor

floor%w = w_mat
call update_floor_angles(floor, floor0)
call end_bookkeeping(ele, old_floor, floor)

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

subroutine end_bookkeeping(ele, old_floor, floor)

! End bookkeeping
type (ele_struct), target :: ele
type (floor_position_struct) old_floor, floor
type (ele_struct), pointer :: lord, slave, ele2
type (lat_struct), pointer :: lat
type (ele_pointer_struct), allocatable, target :: chain_ele(:)

integer k, ib_to, ix, ix_pass, n_links, ie

! End bookkeeping. Only set ele%bookkeeping_state if computing
! ele%floor (ele_floor_geometry_calc = T) and element is associated with a lattice...

eps = bmad_com%significant_length
if (ele_floor_geometry_calc .and. (any(abs(floor%r - old_floor%r) > eps) .or. &
if (ele_floor_geometry_calc .and. associated(ele%branch) .and. (any(abs(floor%r - old_floor%r) > eps) .or. &
abs(floor%theta - old_floor%theta) > eps .or. abs(floor%phi - old_floor%phi) > eps .or. &
abs(floor%psi - old_floor%psi) > eps)) then

! If element is associated with a lattice...
lat => ele%branch%lat

if (associated(ele%branch)) then
lat => ele%branch%lat
! If there is a girder element then *_tot attributes need to be recomputed.
do k = 1, ele%n_lord
lord => pointer_to_lord(ele, k)
if (lord%lord_status == girder_lord$) ele%bookkeeping_state%control = stale$
enddo

! If there is a girder element then *_tot attributes need to be recomputed.
do k = 1, ele%n_lord
lord => pointer_to_lord(ele, k)
if (lord%lord_status == girder_lord$) ele%bookkeeping_state%control = stale$
if (ele%key == girder$) then
do k = 1, ele%n_slave
slave => pointer_to_slave(ele, k)
slave%bookkeeping_state%control = stale$
lat%branch(slave%ix_branch)%param%bookkeeping_state%control = stale$
enddo
endif

! Fork target branch only needs to be recomputed if target branch index is greater than present branch.
if (ele%key == fork$ .or. ele%key == photon_fork$) then
ib_to = nint(ele%value(ix_to_branch$))
if (ib_to > ele%ix_branch) then
ix = nint(ele%value(ix_to_element$))
lat%branch(ib_to)%ele(ix)%bookkeeping_state%floor_position = stale$
lat%branch(ib_to)%param%bookkeeping_state%floor_position = stale$
endif
endif

call multipass_chain(ele, ix_pass, n_links, chain_ele, use_super_lord = .true.)
if (ix_pass > 0) then
do k = ix_pass+1, n_links
this_ele => chain_ele(k)%ele
this_ele%bookkeeping_state%floor_position = stale$
lat%branch(this_ele%ix_branch)%param%bookkeeping_state%floor_position = stale$
if (this_ele%lord_status == super_lord$) then
do ie = 1, this_ele%n_slave
ele2 => pointer_to_slave(this_ele, ie)
ele2%bookkeeping_state%floor_position = stale$
enddo
endif
enddo
! Fork target branch only needs to be recomputed if target branch index is greater than present branch.
if (ele%key == fork$ .or. ele%key == photon_fork$) then
ib_to = nint(ele%value(ix_to_branch$))
if (ib_to > ele%ix_branch) then
ix = nint(ele%value(ix_to_element$))
lat%branch(ib_to)%ele(ix)%bookkeeping_state%floor_position = stale$
lat%branch(ib_to)%param%bookkeeping_state%floor_position = stale$
endif
endif

if (ele%slave_status == super_slave$) then
do k = 1, ele%n_lord
lord => pointer_to_lord(ele, k)
if (lord%lord_status /= super_lord$) exit
lord%bookkeeping_state%floor_position = stale$
if (lord%slave_status == multipass_slave$) then
lord => pointer_to_lord(lord, 1) ! multipass lord
lord%bookkeeping_state%floor_position = stale$
endif
enddo
call multipass_chain(ele, ix_pass, n_links, chain_ele, use_super_lord = .true.)
if (ix_pass > 0) then
do k = ix_pass+1, n_links
this_ele => chain_ele(k)%ele
this_ele%bookkeeping_state%floor_position = stale$
lat%branch(this_ele%ix_branch)%param%bookkeeping_state%floor_position = stale$
if (this_ele%lord_status == super_lord$) then
do ie = 1, this_ele%n_slave
ele2 => pointer_to_slave(this_ele, ie)
ele2%bookkeeping_state%floor_position = stale$
enddo
endif
enddo
endif

elseif (ele%slave_status == multipass_slave$) then
lord => pointer_to_lord(ele, 1)
if (ele%slave_status == super_slave$) then
do k = 1, ele%n_lord
lord => pointer_to_lord(ele, k)
if (lord%lord_status /= super_lord$) exit
lord%bookkeeping_state%floor_position = stale$
endif
if (lord%slave_status == multipass_slave$) then
lord => pointer_to_lord(lord, 1) ! multipass lord
lord%bookkeeping_state%floor_position = stale$
endif
enddo

elseif (ele%slave_status == multipass_slave$) then
lord => pointer_to_lord(ele, 1)
lord%bookkeeping_state%floor_position = stale$
endif
endif

end subroutine end_bookkeeping

end subroutine ele_geometry
26 changes: 19 additions & 7 deletions bmad/output/type_ele.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1506,24 +1506,36 @@ subroutine type_ele (ele, type_zero_attrib, type_mat6, type_taylor, twiss_out, t
nl=nl+1; write (li(nl), '(a)') ' X Y Z Theta Phi Psi'
nl=nl+1; write (li(nl), '(a, 6f12.5, 3x, a)') 'Reference', floor2%r, floor2%theta, floor2%phi, floor2%psi, '! Position without misalignments'
nl=nl+1; write (li(nl), '(a, 6f12.5, 3x, a)') 'Actual ', floor%r, floor%theta, floor%phi, floor%psi, '! Position with offset/pitch/tilt misalignments'

case (girder$)
floor = ele_geometry_with_misalignments (ele)
nl=nl+1; li(nl) = ''
nl=nl+1; li(nl) = 'Global Floor Coords at Reference Point:'
nl=nl+1; write (li(nl), '(a)') ' X Y Z Theta Phi Psi'
nl=nl+1; write (li(nl), '(a, 6f12.5, 3x, a)') 'Reference', ele%floor%r, ele%floor%theta, ele%floor%phi, ele%floor%psi, '! Position without misalignments'
nl=nl+1; write (li(nl), '(a, 6f12.5, 3x, a)') 'Actual ', floor%r, floor%theta, floor%phi, floor%psi, '! Position with offset/pitch/tilt misalignments'
end select

!

floor = ele_geometry_with_misalignments (ele)
select case (ele%key)
case (girder$)
case default
floor = ele_geometry_with_misalignments (ele)

nl=nl+1; li(nl) = ''
nl=nl+1; li(nl) = 'Global Floor Coords at End of Element:'
nl=nl+1; write (li(nl), '(a)') ' X Y Z Theta Phi Psi'
nl=nl+1; write (li(nl), '(a, 6f12.5, 3x, a)') 'Reference', ele%floor%r, ele%floor%theta, ele%floor%phi, ele%floor%psi, '! Position without misalignments'
nl=nl+1; write (li(nl), '(a, 6f12.5, 3x, a)') 'Actual ', floor%r, floor%theta, floor%phi, floor%psi, '! Position with offset/pitch/tilt misalignments'
nl=nl+1; li(nl) = ''
nl=nl+1; li(nl) = 'Global Floor Coords at End of Element:'
nl=nl+1; write (li(nl), '(a)') ' X Y Z Theta Phi Psi'
nl=nl+1; write (li(nl), '(a, 6f12.5, 3x, a)') 'Reference', ele%floor%r, ele%floor%theta, ele%floor%phi, ele%floor%psi, '! Position without misalignments'
nl=nl+1; write (li(nl), '(a, 6f12.5, 3x, a)') 'Actual ', floor%r, floor%theta, floor%phi, floor%psi, '! Position with offset/pitch/tilt misalignments'
end select

!

if (associated(ele0) .and. (ele%ix_ele /= 0 .or. branch%param%geometry == closed$)) then
f0 = ele0%floor
nl=nl+1; write (li(nl), '(a, 6f12.5, 3x, a)') 'delta Ref', floor%r-f0%r, floor%theta-f0%theta, floor%phi-f0%phi, floor%psi-f0%psi, &
'! Delta with respect to last element'
'! Delta of reference with respect to last element'
endif
endif
endif
Expand Down
30 changes: 28 additions & 2 deletions regression_tests/girder_test/girder_test.bmad
Original file line number Diff line number Diff line change
Expand Up @@ -11,15 +11,41 @@ q3: quadrupole, l = 1, tilt = 0.6, x_offset = 0.4, x_pitch = 0.5, tilt = 3.3, y_
b: sbend, l = 1, angle = 0.1, ref_tilt = 0.2
d: drift, l = 1

g1: girder = {q1, q2}, tilt = 0.4, x_offset = 0.2, x_pitch = 0.3, tilt = 1.3, y_offset = 0.2, y_pitch = 0.3
g1: girder = {q1, q2}, tilt = 0.4, x_offset = 0.2, x_pitch = 0.3, tilt = 1.3, y_offset = 0.2, y_pitch = 0.3, origin_ele = q1
g2: girder = {g1, q3}, tilt = 0.5, x_offset = 0.3, x_pitch = 0.4, tilt = 3.3, y_offset = 1.2, y_pitch = 0.01

m_line: line[multipass] = (b, q1, q2, q3, b)
g_line: line = (m_line, m_line)

m:marker, superimpose, ref = q1

use, g_line
!


dd: drift, L = 0.5

bb: sbend, L = 0.5, g = 1, e1 = 0.1, dg = 0.001, roll = 0.001, x_offset = 0.002,
y_offset = 0.003, x_pitch = 0.004, y_pitch = 0.005, ref_tilt = 0.006

qq: quadrupole, L = 0.6, tilt = 0.0013, x_offset = 0.0023,
y_offset = 0.0033, x_pitch = 0.0043, y_pitch = 0.0053

gg: girder = {bb, qq}, tilt = 0.0017, x_offset = 0.0027,
y_offset = 0.0037, x_pitch = 0.0047, y_pitch = 0.0057,
dx_origin = 0.0015, dy_origin = 0.0025, dz_origin = 0.0035,
dtheta_origin = 0.0045, dphi_origin = 0.0055, dpsi_origin = 0.0065

g1_line: line = (dd, bb, qq)
g1_line[beta_a] = 10.0
g1_line[beta_b] = 10.0
g1_line[e_tot] = 10e6
g1_line[geometry] = open

!

use, g_line, g1_line




! superimpose including overlapping superimpose
Expand Down
3 changes: 2 additions & 1 deletion regression_tests/girder_test/girder_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,11 +11,12 @@ program girder_test
implicit none

type (lat_struct), target :: lat
type (branch_struct), pointer :: branch
type (ele_struct), pointer :: girder, slave, slave2, slave3
type (floor_position_struct), pointer :: floor

real(rp) w_mat(3,3), w_mat_inv(3,3), mat3(3,3)
integer i, ig, j, k, nargs
integer i, ib, ig, j, k, nargs

character(40) fmt
character(100) lat_file
Expand Down
Loading

0 comments on commit 5dfb4cf

Please sign in to comment.