Skip to content

Commit

Permalink
more. (#1315)
Browse files Browse the repository at this point in the history
* Corrected element has_misalign bookkeeping.
  • Loading branch information
DavidSagan authored Nov 21, 2024
1 parent 9d3c7e5 commit 22c21f4
Show file tree
Hide file tree
Showing 12 changed files with 58 additions and 37 deletions.
11 changes: 11 additions & 0 deletions bmad/code/attribute_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -143,18 +143,29 @@ subroutine attribute_bookkeeper (ele, force_bookkeeping)
case (sbend$, rf_bend$)
val(roll_tot$) = val(roll$)
val(ref_tilt_tot$) = val(ref_tilt$)
ele%bookkeeping_state%has_misalign = (val(ref_tilt_tot$) /= 0 .or. val(roll_tot$) /= 0)

case (crystal$, mirror$, multilayer_mirror$)
val(tilt_tot$) = val(tilt$)
val(ref_tilt_tot$) = val(ref_tilt$)
ele%bookkeeping_state%has_misalign = (val(ref_tilt_tot$) /= 0 .or. val(tilt_tot$) /= 0)

case default
val(tilt_tot$) = val(tilt$)
ele%bookkeeping_state%has_misalign = (val(tilt_tot$) /= 0)
end select

val(x_offset_tot$) = val(x_offset$)
val(y_offset_tot$) = val(y_offset$)
val(z_offset_tot$) = val(z_offset$)
val(x_pitch_tot$) = val(x_pitch$)
val(y_pitch_tot$) = val(y_pitch$)

ele%bookkeeping_state%has_misalign = (ele%bookkeeping_state%has_misalign .or. val(x_offset_tot$) /= 0 .or. &
val(y_offset_tot$) /= 0 .or. val(z_offset_tot$) /= 0 .or. &
val(x_pitch_tot$) /= 0 .or. val(y_pitch_tot$) /= 0)
if (ele%key == sad_mult$) ele%bookkeeping_state%has_misalign = (ele%bookkeeping_state%has_misalign .or. &
val(x_offset_mult$) /= 0 .or. val(y_offset_mult$) /= 0)
endif

! Super_lord length change is put in last slave
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ subroutine control_bookkeeper (lat, ele, err_flag)
! If ele is present we only do bookkeeping for this one element and its slaves

if (present(ele)) then
call control_bookkeeper1 (lat, ele, .true., err)
call control_bookkeeper1 (lat, ele, .true., .true., err)
if (present(err_flag)) err_flag = err
return
endif
Expand All @@ -51,12 +51,10 @@ subroutine control_bookkeeper (lat, ele, err_flag)

if (present(err_flag)) err_flag = .false.

if (bmad_com%auto_bookkeeper) then
lat%ele(:)%bookkeeping_state%control = stale$ ! Bookkeeping done on this element yet?
endif

! Bookkkeeping is done from the top level down.
! The top level elements are those lord elements that have no lords on top of them.
! Here only the lord elements are bookkeeped since if there is a super_slave with multiple lords,
! the super_slave must be bookkeeped after all the lords are done.

ie_loop: do ie = lat%n_ele_track+1, lat%n_ele_max
ele2 => lat%ele(ie)
Expand All @@ -66,21 +64,21 @@ subroutine control_bookkeeper (lat, ele, err_flag)
cycle
endif
if (ele2%n_lord > 0) cycle
call control_bookkeeper1 (lat, ele2, .false., err)
call control_bookkeeper1 (lat, ele2, .false., .false., err)
if (err .and. present(err_flag)) err_flag = .true.
enddo ie_loop

! And now bookkeeping for the elements in the tracking lattice

do ib = 0, ubound(lat%branch, 1)
branch => lat%branch(ib)
if (.not. bmad_com%auto_bookkeeper .and. branch%param%bookkeeping_state%control /= stale$ .and. &
if (branch%param%bookkeeping_state%control /= stale$ .and. &
branch%param%bookkeeping_state%attributes /= stale$) cycle

do ie = 0, branch%n_ele_track
ele2 => branch%ele(ie)
if (ele2%bookkeeping_state%control /= stale$ .and. ele2%bookkeeping_state%attributes /= stale$) cycle
call attribute_bookkeeper (ele2)
call control_bookkeeper1 (lat, ele2, .false., .true., err)
ele2%bookkeeping_state%control = ok$
enddo

Expand All @@ -97,22 +95,22 @@ subroutine control_bookkeeper (lat, ele, err_flag)
!--------------------------------------------------------------------------
!--------------------------------------------------------------------------
!+
! Subroutine control_bookkeeper1 (lat, ele, force_bookkeeping, err_flag)
! Subroutine control_bookkeeper1 (lat, ele, force_bookkeeping, bookkeep_tracking_elements, err_flag)
!
! This routine is for control bookkeeping for a single element.
! This subroutine is only to be called from control_bookkeeper and is
! not meant for general use.
!-

recursive subroutine control_bookkeeper1 (lat, ele, force_bookkeeping, err_flag)
recursive subroutine control_bookkeeper1 (lat, ele, force_bookkeeping, bookkeep_tracking_elements, err_flag)

type (lat_struct), target :: lat
type (ele_struct) ele
type (ele_struct), pointer :: slave

integer i

logical call_a_bookkeeper, force_bookkeeping
logical call_a_bookkeeper, force_bookkeeping, bookkeep_tracking_elements
logical err_flag

! Only do bookkeeping on this element if it is stale or bookkeeping is forced by the calling routine.
Expand Down Expand Up @@ -156,7 +154,7 @@ recursive subroutine control_bookkeeper1 (lat, ele, force_bookkeeping, err_flag)
! attribute_bookkeeper must be called again.
! This is true even if the lattice is static since a slave element
! can have its lord's dependent attribute values.
! Example: super_slave will, at this point, have its lord's num_steps value but
! Example: super_slave will, at this point, have its lord's num_steps value but
! num_steps in the slave is different from the lord due to differences in length.

if (call_a_bookkeeper) call attribute_bookkeeper (ele, force_bookkeeping)
Expand All @@ -165,13 +163,14 @@ recursive subroutine control_bookkeeper1 (lat, ele, force_bookkeeping, err_flag)

endif

! Recursively call this routine on the slaves
! Recursively call this routine on the slaves.

do i = 1, ele%n_slave
if (ele%lord_status == control_lord$) cycle
if (err_flag) return
slave => pointer_to_slave (ele, i)
call control_bookkeeper1 (lat, slave, force_bookkeeping, err_flag)
if (.not. bookkeep_tracking_elements .and. slave%lord_status == not_a_lord$) cycle
call control_bookkeeper1 (lat, slave, force_bookkeeping, bookkeep_tracking_elements, err_flag)
enddo

end subroutine control_bookkeeper1
Expand Down
2 changes: 1 addition & 1 deletion bmad/modules/bmad_struct.f90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ module bmad_struct
! IF YOU CHANGE THE LAT_STRUCT OR ANY ASSOCIATED STRUCTURES YOU MUST INCREASE THE VERSION NUMBER !!!
! THIS IS USED BY BMAD_PARSER TO MAKE SURE DIGESTED FILES ARE OK.

integer, parameter :: bmad_inc_version$ = 325
integer, parameter :: bmad_inc_version$ = 326

!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Expand Down
3 changes: 2 additions & 1 deletion bmad/modules/bookkeeper_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -659,7 +659,7 @@ subroutine makeup_super_slave (lat, slave, err_flag)
slave%value(bl_vkick$) = slave%value(bl_vkick$) + lord%value(bl_vkick$)
enddo

if (any(slave%value /= old_value)) call set_ele_status_stale (slave, attribute_group$)
if (any(slave%value /= old_value)) call attribute_bookkeeper (slave, .true.)

return
endif
Expand Down Expand Up @@ -1631,6 +1631,7 @@ subroutine makeup_control_slave (lat, slave, err_flag)
vs(z_offset_tot$) = l_slave_off_tot(3)
endif

slave%bookkeeping_state%has_misalign = .true.
on_an_offset_girder = .true.

cycle
Expand Down
19 changes: 0 additions & 19 deletions bmad/modules/changed_attribute_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -466,25 +466,6 @@ subroutine set_flags_for_changed_real_attribute (ele, attrib, set_dependent)
endif
endif

! Is element misaligned?

select case (ele%key)
case (sbend$)
ele%bookkeeping_state%has_misalign = (ele%value(ref_tilt$) /= 0 .or. &
ele%value(x_offset$) /= 0 .or. ele%value(y_offset$) /= 0 .or. ele%value(z_offset$) /= 0 .or. &
ele%value(roll$) /= 0 .or. ele%value(x_pitch$) /= 0 .or. ele%value(y_pitch$) /= 0)

case (sad_mult$)
ele%bookkeeping_state%has_misalign = (ele%value(x_offset_mult$) /= 0 .or. ele%value(y_offset_mult$) /= 0 .or. &
ele%value(x_offset$) /= 0 .or. ele%value(y_offset$) /= 0 .or. ele%value(z_offset$) /= 0 .or. &
ele%value(tilt$) /= 0 .or. ele%value(x_pitch$) /= 0 .or. ele%value(y_pitch$) /= 0)

case default
ele%bookkeeping_state%has_misalign = &
(ele%value(x_offset$) /= 0 .or. ele%value(y_offset$) /= 0 .or. ele%value(z_offset$) /= 0 .or. &
ele%value(tilt$) /= 0 .or. ele%value(x_pitch$) /= 0 .or. ele%value(y_pitch$) /= 0)
end select

!------------------------------------------------
! By element type

Expand Down
1 change: 1 addition & 0 deletions regression_tests/abs_time_test/abs_time_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ program abs_time_test

!

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

call reallocate_coord (orb1, lat%n_ele_max)
Expand Down
14 changes: 13 additions & 1 deletion regression_tests/bookkeeper_test/bookkeeper_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ program bookkeeper_test
implicit none

type (lat_struct), target :: lat, lat2, lat3
type (ele_struct), pointer :: ele, nele
type (ele_struct), pointer :: ele, nele, slave
type (ele_struct) a_ele
type (ele_pointer_struct), allocatable :: eles(:)
type (coord_struct) orb
Expand Down Expand Up @@ -264,6 +264,18 @@ program bookkeeper_test
call lat_ele_locator ('quad::*', lat, eles, n_loc, err)
write (1, '(a, i4)') '"N_Quad_Loc" ABS 0', n_loc

!

call bmad_parser('pipe_superimpose.bmad', lat)
ele => lat%ele(6)
ele%value(x_offset$) = 0.0123456789012345
call set_flags_for_changed_attribute(ele, ele%value(x_offset$))
call lattice_bookkeeper(lat, err)

slave => lat%ele(2)
write (1, '(a, l1, a)') '"Pipe-superimpose-state" STR "', slave%bookkeeping_state%has_misalign, '"'
write (1, '(a, 2es24.16)') '"Pipe-superimpose-val" REL 1E-14 ', slave%value(x_offset$), slave%value(x_offset_tot$)

close(1)

end program
2 changes: 2 additions & 0 deletions regression_tests/bookkeeper_test/output.correct
Original file line number Diff line number Diff line change
Expand Up @@ -217,3 +217,5 @@
"Aperture-6" STR "Lost_Pos_Y"
"Aperture-7" STR "Lost_Neg_X"
"N_Quad_Loc" ABS 0 9
"Pipe-superimpose-state" STR "T"
"Pipe-superimpose-val" REL 1E-14 1.2345679104328156E-02 1.2345679104328156E-02
11 changes: 11 additions & 0 deletions regression_tests/bookkeeper_test/pipe_superimpose.bmad
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
beginning[beta_a] = 10
beginning[beta_b] = 10
beginning[e_tot] = 100e6
parameter[geometry] = open

p1: pipe, L = 1
q1: quad, L = 0.1, superimpose, ref = p1, k1 = 1

lat: line = (p1)

use, lat
1 change: 1 addition & 0 deletions regression_tests/closed_orbit_test/closed_orbit_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ program co_test

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

bmad_com%auto_bookkeeper = .false.
call bmad_parser ('bmad_L9A18A000-_MOVEREC.lat', lat)

n = lat%n_ele_track
Expand Down
2 changes: 2 additions & 0 deletions regression_tests/ptc_test/ptc_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,8 @@ program ptc_test
!----------------------------------------------------------
! Check information passing between bmad element and associated ptc fibre

bmad_com%auto_bookkeeper = .false.

call bmad_parser ('diff_test.bmad', lat)
call lattice_bookkeeper (lat)
call lat_to_ptc_layout(lat)
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/11/17 23:41:42"
character(*), parameter :: tao_version_date = "2024/11/19 14:45:26"
end module

0 comments on commit 22c21f4

Please sign in to comment.