Skip to content

Commit

Permalink
Fix ltt_track1_preprocess in lt_tracking_mod. (#1354)
Browse files Browse the repository at this point in the history
* Removed openMP use for Tao DE optimization until a fix is in place.
  • Loading branch information
DavidSagan authored Jan 7, 2025
1 parent ec94a40 commit f3c2dc4
Show file tree
Hide file tree
Showing 5 changed files with 10 additions and 13 deletions.
3 changes: 1 addition & 2 deletions bsim/modules/lt_tracking_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3507,12 +3507,11 @@ subroutine ltt_track1_preprocess (start_orb, ele, param, err_flag, finished, rad
! This routine may be called by bmad_parser (via ele_compute_ref_energy_and_time) which is
! before LTT ramping has been setup. To avoid problems, return if setup has not been done.

err_flag = .false.
if (.not. associated(ltt_com_global%tracking_lat%ele)) return

! Recording a particle track?

err_flag = .false.

if (start_orb%ix_user > 0 .and. start_orb%state == alive$) then
iu = lunget()
if (ele%ix_ele <= 1) then
Expand Down
12 changes: 6 additions & 6 deletions tao/code/tao_de_optimizer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ subroutine tao_de_optimizer (abort)
use tao_interface, dummy => tao_de_optimizer
use tao_top10_mod, only: tao_var_write
use opti_de_mod
use opti_de_openmp_mod
!!! use opti_de_openmp_mod # And there is commented out code below.

implicit none

Expand Down Expand Up @@ -62,11 +62,11 @@ function merit_wrapper (var_vec, status, iter_count) result (merit)
write (line, '(a, i0)') 'Differential evolution optimizer, population: ', population
call out_io (s_blank$, r_name, line)

if (s%com%omp_n_threads == 1) then
!!! if (s%com%omp_n_threads == 1) then
merit = opti_de (var_vec, s%global%n_opti_cycles, population, merit_wrapper, var_step, status)
else
merit = opti_de_openmp (var_vec, s%global%n_opti_cycles, population, merit_wrapper, var_step, status)
endif
!!! else
!!! merit = opti_de_openmp (var_vec, s%global%n_opti_cycles, population, merit_wrapper, var_step, status)
!!! endif

print *, 'tao_de_optimizer merit for rank ', merit, s%mpi%rank

Expand Down Expand Up @@ -121,7 +121,7 @@ function merit_wrapper (var_vec, status, iter_count) result (this_merit)
integer, save :: t0(8), t1(8), t_del(8), t_delta

character(80) line, line2, stars
character(20) :: r_name = 'tao_de_optimizer'
character(*), parameter :: r_name = 'tao_de_optimizer'
character(1) char

logical calc_ok
Expand Down
3 changes: 1 addition & 2 deletions tao/code/tao_init_lattice.f90
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ subroutine tao_init_lattice (init_lat_file, err_flag)
type (lat_struct), pointer :: lat
type (lat_struct) parse_lat
type (ele_struct), pointer :: ele1, ele2
type (tao_universe_struct), pointer :: u, u_work
type (tao_universe_struct), pointer :: u
type (branch_struct), pointer :: branch
type (ele_struct), pointer :: ele
type (coord_struct), allocatable :: orbit(:)
Expand Down Expand Up @@ -101,7 +101,6 @@ subroutine tao_init_lattice (init_lat_file, err_flag)
!

allocate (s%u(s%com%n_universes))
nullify (s%com%u_working)

! Read in the lattices

Expand Down
3 changes: 1 addition & 2 deletions tao/code/tao_struct.f90
Original file line number Diff line number Diff line change
Expand Up @@ -391,7 +391,7 @@ module tao_struct
end type

!-----------------------------------------------------------------------
! The data_struct defines the fundamental data structure representing
! The tao_data_struct defines the fundamental data structure representing
! one datum point.
! The universe_struct will hold an array of data_struct structures: u%data(:).
!
Expand Down Expand Up @@ -739,7 +739,6 @@ module tao_struct
type tao_common_struct
type (tao_alias_struct) :: alias(200) = tao_alias_struct()
type (tao_alias_struct) :: key(100) = tao_alias_struct()
type (tao_universe_struct), pointer :: u_working => null() ! Index of working universe.
type (tao_command_file_struct), allocatable :: cmd_file(:)
type (named_number_struct), allocatable :: symbolic_num(:) ! Named numbers
type (tao_plot_region_struct), allocatable :: plot_place_buffer(:) ! Used when %external_plotting is on.
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/20 22:19:05"
character(*), parameter :: tao_version_date = "2024/12/22 21:46:37"
end module

0 comments on commit f3c2dc4

Please sign in to comment.