Skip to content

Commit

Permalink
Minor Tao bug fix. (#1342)
Browse files Browse the repository at this point in the history
  • Loading branch information
DavidSagan authored Dec 5, 2024
1 parent 7f7a931 commit bd27565
Show file tree
Hide file tree
Showing 6 changed files with 35 additions and 19 deletions.
6 changes: 3 additions & 3 deletions bmad/code/lat_ele_locator.f90
Original file line number Diff line number Diff line change
Expand Up @@ -84,9 +84,9 @@
! loc_str -- character(*): Element names or indexes. May be lower case.
! lat -- lat_struct: Lattice to search through.
! above_ubound_is_err
! -- logical, optional: If the upper bound "e2" on an "e1:e2" range construct
! is above the maximum element index then treat this as an error?
! Default is True. If False, treat e2 as the maximum element index.
! -- logical, optional: Default is True. If the upper bound "e2" on an "e1:e2" range construct
! is an integer and above the maximum element index then treat this as an error?
! If False, treat e2 as the maximum element index.
! ix_dflt_branch -- integer, optional: If present and not -1 then restrict search to specified branch.
! If not present or -1: Search all branches. Exception: For elements specified using
! an integer index (EG: "43"), if ix_dflt_branch is not present or -1 use branch 0.
Expand Down
32 changes: 22 additions & 10 deletions bmad/parsing/bmad_parser_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1371,9 +1371,9 @@ subroutine parser_read_sr_wake (ele, delim, delim_found, err_flag)
type (wake_sr_z_long_struct), pointer :: srz
type (wake_sr_struct), pointer :: wake_sr

real(rp) f
real(rp), allocatable :: table(:,:)
integer i, itrans, ilong, iz, ipt, ix_word, n0, n1, nn, nt
real(rp) f, esum, val
real(rp), allocatable :: table(:,:), gauss(:)
integer i, j, itrans, ilong, iz, ipt, ix_word, n0, n1, nn, nt, ns

logical delim_found, err_flag, err

Expand Down Expand Up @@ -1532,17 +1532,29 @@ subroutine parser_read_sr_wake (ele, delim, delim_found, err_flag)
srz%w = srz%w(nt:1:-1)
srz%smoothing_sigma = c_light * srz%smoothing_sigma
endif
srz%fw = srz%w
call fft_1d(srz%fw, -1)

if (srz%smoothing_sigma /= 0) then
do i = 2, nn+1
f = (i - 1) * pi * srz%smoothing_sigma / (srz%dz * nt)
f = exp(-2 * f**2)
srz%fw(i) = f * srz%fw(i)
srz%fw(nt-i+2) = f * srz%fw(nt-i+2)
ns = nint(3*srz%smoothing_sigma / srz%dz)
allocate (gauss(-ns:ns))
do i = -ns, ns
gauss(i) = exp(-0.5 * i * (srz%dz / srz%smoothing_sigma)**2)
enddo

srz%fw = 0
do i = 1, nt
esum = 0
do j = max(1, i - ns), min(nt, i + ns)
srz%fw(i) = srz%fw(i) + gauss(j-i) * srz%w(j)
esum = esum + gauss(j-i)
enddo
srz%fw(i) = srz%fw(i) / esum
enddo
else
srz%fw = srz%w
endif

call fft_1d(srz%fw, -1)

else
allocate (srz%w(0), srz%fw(0), srz%w_out(0), srz%fbunch(0))
endif
Expand Down
1 change: 1 addition & 0 deletions tao/code/tao_graph_setup_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -505,6 +505,7 @@ subroutine tao_graph_phase_space_setup (plot, graph)
if (.not. associated(ele)) then
call out_io (s_error$, r_name, 'CURVE REFERENCE ELEMENT IS NOT AN ELEMENT THAT IS TRACKED THROUGH: ' // curve%ele_ref_name, &
'FOR CURVE: ' // tao_curve_name(curve))
cycle
endif

select case (curve%component)
Expand Down
9 changes: 6 additions & 3 deletions tao/code/tao_set_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1450,9 +1450,8 @@ subroutine tao_set_curve_cmd (curve_name, component, value_str)
type (tao_curve_array_struct), allocatable :: curve(:)
type (tao_graph_array_struct), allocatable :: graph(:)
type (lat_struct), pointer :: lat
type (ele_struct), pointer :: ele_track

integer i, j, ios, i_uni
integer i, j, ios
integer, allocatable :: ix_ele(:)

character(*) curve_name, component, value_str
Expand Down Expand Up @@ -1484,8 +1483,9 @@ subroutine set_this_curve (this_curve)
type (tao_universe_struct), pointer :: u
type (tao_model_branch_struct), pointer :: model_branch
type (ele_pointer_struct), allocatable :: eles(:)
type (ele_struct), pointer :: ele_track

integer ix, i_branch
integer ix, i_branch, i_uni
logical err, is_int
character(40) name, comp

Expand Down Expand Up @@ -1661,6 +1661,9 @@ subroutine set_this_curve (this_curve)

! Set lattice recalc for a phase_space plot

if (err) return
if (.not. associated(this_graph%p%r)) return ! A template plot is ignored.

if (this_graph%type == 'phase_space') then
i_uni = tao_universe_index(tao_curve_ix_uni(this_curve))
ele_track => tao_curve_ele_ref(this_curve, .true.)
Expand Down
4 changes: 2 additions & 2 deletions tao/doc/pipe-interface.tex
Original file line number Diff line number Diff line change
Expand Up @@ -191,8 +191,8 @@ \section{Plotting Issues}

Normally when \tao is not displaying the plot page when the \vn{-noplot} option is used, \tao will,
to save time, not calculate the points needed for plotting curves. The exception is if
\vn{-external_plotting} is turned on. In this case, to make plot references unambiguous, plot can be
referred to by their index number. The plot index number can be viewed using the \vn{pipe
\vn{-external_plotting} is turned on. In this case, to make plot references unambiguous, a plot can be
referred to by its index number. The plot index number can be viewed using the \vn{pipe
plot_list} command. Template plots can be referenced using the syntax ``\vn{@Tnnn}'' where \vn{nnn}
is the index number. For example, \vn{@T3} referrers to the template plot with index 3. Similarly,
the displayed plots (plots that are associated with plot regions) can be referred to using the
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/12/01 16:51:09"
character(*), parameter :: tao_version_date = "2024/12/02 15:05:24"
end module

0 comments on commit bd27565

Please sign in to comment.