Skip to content

Commit

Permalink
Fix PTC bombing program due to e_gun being tracked through. Error fla…
Browse files Browse the repository at this point in the history
…gs are set instead. (#1148)

* Fix PTC bombing program due to e_gun being tracked through. Error flags are set instead.
* Fix Tao "set global quiet" command.
  • Loading branch information
DavidSagan authored Aug 16, 2024
1 parent 5e7c5b1 commit a54fe58
Show file tree
Hide file tree
Showing 9 changed files with 87 additions and 61 deletions.
8 changes: 6 additions & 2 deletions bmad/code/combine_consecutive_elements.f90
Original file line number Diff line number Diff line change
Expand Up @@ -53,11 +53,15 @@ subroutine combine_consecutive_elements (lat, error)
cycle
endif
call combine_eles (ele1, ele2, branch, error)
if (error) return
endif

if (ele2%key == marker$ .and. ie < branch%n_ele_track - 1) then
ele2 => branch%ele(ie+2)
if (ele1%name == ele2%name .and. ele1%key == ele2%key) call combine_eles (ele1, ele2, branch, error)
if (ele1%name == ele2%name .and. ele1%key == ele2%key) then
call combine_eles (ele1, ele2, branch, error)
if (error) return
endif
endif

enddo
Expand Down Expand Up @@ -171,7 +175,7 @@ subroutine combine_eles (ele1, ele2, branch, error)
ele1%value(voltage$) = 2 * ele1%value(voltage$)

case (taylor$)
call concat_ele_taylor (ele1%taylor, ele2, ele1%taylor)
call concat_ele_taylor (ele1%taylor, ele2, ele1%taylor, error)

end select

Expand Down
4 changes: 2 additions & 2 deletions bmad/code/make_hybrid_lat.f90
Original file line number Diff line number Diff line change
Expand Up @@ -279,9 +279,9 @@ subroutine make_hybrid_lat (lat_in, lat_out, use_taylor, orb0_arr)

if (do_taylor) then
if (associated(ele_in%taylor(1)%term)) then
call concat_ele_taylor (ele_out%taylor, ele_in, ele_out%taylor)
call concat_ele_taylor (ele_out%taylor, ele_in, ele_out%taylor, err_flag)
else
call taylor_propagate1 (ele_out%taylor, ele_in, b_in%param)
call taylor_propagate1 (ele_out%taylor, ele_in, b_in%param, err_flag)
endif
else
ele_out%mat6 = matmul(ele_in%mat6, ele_out%mat6)
Expand Down
19 changes: 11 additions & 8 deletions bmad/code/transfer_map_calc.f90
Original file line number Diff line number Diff line change
Expand Up @@ -111,19 +111,19 @@ subroutine transfer_map_calc (lat, t_map, err_flag, ix1, ix2, ref_orb, ix_branch

if (i1 < i2) then
do i = i1+1, i2
call add_on_to_map (t_map, branch%ele(i))
call add_on_to_map (t_map, branch%ele(i), err_flag)
if (err_flag) return
enddo

! Circular lattice with i1 > i2: Track through origin.

elseif (branch%param%geometry == closed$) then
do i = i1+1, branch%n_ele_track
call add_on_to_map (t_map, branch%ele(i))
call add_on_to_map (t_map, branch%ele(i), err_flag)
if (err_flag) return
enddo
do i = 1, i2
call add_on_to_map (t_map, branch%ele(i))
call add_on_to_map (t_map, branch%ele(i), err_flag)
if (err_flag) return
enddo

Expand All @@ -133,15 +133,15 @@ subroutine transfer_map_calc (lat, t_map, err_flag, ix1, ix2, ref_orb, ix_branch

if (unit_start_this) then
do i = i2+1, i1
call add_on_to_map (t_map, branch%ele(i))
call add_on_to_map (t_map, branch%ele(i), err_flag)
if (err_flag) return
enddo
call taylor_inverse (t_map, t_map)

else
call taylor_make_unit (a_map)
do i = i2+1, i1
call add_on_to_map (a_map, branch%ele(i))
call add_on_to_map (a_map, branch%ele(i), err_flag)
if (err_flag) return
enddo
call taylor_inverse (a_map, a_map)
Expand All @@ -154,20 +154,23 @@ subroutine transfer_map_calc (lat, t_map, err_flag, ix1, ix2, ref_orb, ix_branch
!--------------------------------------------------------
contains

subroutine add_on_to_map (map, ele)
subroutine add_on_to_map (map, ele, err_flag)

type (taylor_struct) :: map(:)
type (ele_struct) ele
integer i, k
logical err_flag

!

if (logic_option(.false., concat_if_possible) .and. associated(ele%taylor(1)%term)) then
call concat_ele_taylor (map, ele, map)
call concat_ele_taylor (map, ele, map, err_flag)
else
call taylor_propagate1 (map, ele, branch%param, orb0)
call taylor_propagate1 (map, ele, branch%param, err_flag, orb0)
endif

if (err_flag) return

! Check for overflow
! Map term overflow defined by |term| > 10^(20*n) where n = sum(term_exponents)

Expand Down
6 changes: 4 additions & 2 deletions bmad/modules/transfer_map_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -188,6 +188,8 @@ subroutine transfer_this_map (map, branch, s_1, s_2, error_flag, orb, concat_if_
! Init
! Want to get the whole lattice if [s_1, s_2] spans the entire lattice

error_flag = .false.

if (s_1 == branch%ele(0)%s) then
ix_ele = 1
else
Expand Down Expand Up @@ -249,10 +251,10 @@ subroutine transfer_this_map (map, branch, s_1, s_2, error_flag, orb, concat_if_
! Now for the integration step

if (track_entire_ele .and. logic_option(.false., concat_if_possible) .and. associated(ele%taylor(1)%term)) then
call concat_ele_taylor (map, ele, map)
call concat_ele_taylor (map, ele, map, error_flag); if (error_flag) return
call init_coord(orb, map%ref, ele, downstream_end$)
else
call taylor_propagate1 (map, runt, branch%param, orb)
call taylor_propagate1 (map, runt, branch%param, error_flag, orb); if (error_flag) return
call init_coord(orb, map%ref, runt, downstream_end$)
endif

Expand Down
1 change: 1 addition & 0 deletions bmad/ptc/ele_to_fibre.f90
Original file line number Diff line number Diff line change
Expand Up @@ -442,6 +442,7 @@ subroutine ele_to_fibre (ele, ptc_fibre, param, use_offsets, err_flag, integ_ord
call out_io (s_fatal$, r_name, 'CONVERSION TO PTC NOT IMPLEMENTED FOR ELEMENTS OF TYPE ' // trim(key_name(ele%key)), &
'FOR ELEMENT: ' // trim(ele%name))
if (global_com%exit_on_error) call err_exit
return
end select

!------------------------------
Expand Down
33 changes: 24 additions & 9 deletions bmad/ptc/ptc_interface_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2095,7 +2095,7 @@ end subroutine concat_taylor
!------------------------------------------------------------------------
!------------------------------------------------------------------------
!+
! Subroutine concat_ele_taylor (taylor1, ele, taylor3)
! Subroutine concat_ele_taylor (taylor1, ele, taylor3, err_flag)
!
! Routine to concatinate two taylor maps:
! taylor3[x] = ele_taylor(taylor1[x])
Expand All @@ -2105,14 +2105,15 @@ end subroutine concat_taylor
! Also see: concat_taylor
!
! Input:
! taylor1(6) -- Taylor_struct: Taylor map.
! ele -- ele_struct: Element containing a Taylor map.
! taylor1(6) -- Taylor_struct: Taylor map.
! ele -- ele_struct: Element containing a Taylor map.
!
! Output
! taylor3(6) -- Taylor_struct: Concatinated map
! taylor3(6) -- Taylor_struct: Concatinated map
! err_flag -- logical: Set True if there is an error. False otherwise.
!-

Subroutine concat_ele_taylor (taylor1, ele, taylor3)
Subroutine concat_ele_taylor (taylor1, ele, taylor3, err_flag)

use s_tracking, only: mis_fib, alloc, kill, dtiltd, assignment(=), real_8, fibre

Expand All @@ -2127,9 +2128,12 @@ Subroutine concat_ele_taylor (taylor1, ele, taylor3)
real(rp) beta0, beta1, tilt
real(8) x_dp(6)
logical err_flag
character(*), parameter :: r_name = 'concat_ele_taylor'

! Match elements are not implemented in PTC so just use the matrix.

err_flag = .false.

if (ele%key == match$) then
call mat6_to_taylor (ele%vec0, ele%mat6, ele%taylor)
call concat_taylor (taylor1, ele%taylor, taylor3)
Expand All @@ -2154,6 +2158,10 @@ Subroutine concat_ele_taylor (taylor1, ele, taylor3)

param%particle = positron$ ! Actually this does not matter to the calculation
call ele_to_fibre (ele, fib, param, .true., err_flag)
if (err_flag) then
call out_io(s_error$, r_name, 'CANNOT USE ELEMENT WITH PTC: ' // ele_full_name(ele))
return
endif

! Init

Expand Down Expand Up @@ -2410,7 +2418,7 @@ end subroutine real_8_to_taylor
!------------------------------------------------------------------------
!------------------------------------------------------------------------
!+
! Subroutine taylor_propagate1 (bmad_taylor, ele, param, ref_in)
! Subroutine taylor_propagate1 (bmad_taylor, ele, param, err_flag, ref_in)
!
! Subroutine to track (symplectic integration) a taylor map through an element.
! The alternative routine, if ele has a taylor map, is concat_taylor.
Expand All @@ -2427,10 +2435,11 @@ end subroutine real_8_to_taylor
! if the direction of propagation is backwards.
!
! Output:
! bmad_taylor(6) -- Taylor_struct: Map through element
! bmad_taylor(6) -- Taylor_struct: Map through element.
! err_flag -- logical: Set True if there is an error. False otherwise.
!-

subroutine taylor_propagate1 (bmad_taylor, ele, param, ref_in)
subroutine taylor_propagate1 (bmad_taylor, ele, param, err_flag, ref_in)

use s_tracking
use mad_like, only: real_8, fibre, ptc_track => track
Expand All @@ -2448,11 +2457,12 @@ subroutine taylor_propagate1 (bmad_taylor, ele, param, ref_in)

real(rp) beta0, beta1, m2_rel
logical err_flag
character(*), parameter :: r_name = 'taylor_propagate1'

! If the element is a taylor then just concat since this is faster.

if (ele%key == taylor$) then
call concat_ele_taylor (bmad_taylor, ele, bmad_taylor)
call concat_ele_taylor (bmad_taylor, ele, bmad_taylor, err_flag)
return
endif

Expand All @@ -2471,6 +2481,11 @@ subroutine taylor_propagate1 (bmad_taylor, ele, param, ref_in)
! track the map

call ele_to_fibre (ele, ptc_fibre, param, .true., err_flag, ref_in = ref_in)
if (err_flag) then
call out_io(s_error$, r_name, 'CANNOT USE ELEMENT WITH PTC: ' // ele_full_name(ele))
return
endif

call track_probe_x (ptc_tlr, ptc_private%base_state, fibre1 = bmadl%start)

! transfer ptc map back to bmad map
Expand Down
Loading

0 comments on commit a54fe58

Please sign in to comment.