Skip to content

Commit

Permalink
Foil drel_thickness_dx -> dthickness_dx (#904)
Browse files Browse the repository at this point in the history
  • Loading branch information
DavidSagan authored Apr 6, 2024
1 parent 671a324 commit c23b600
Show file tree
Hide file tree
Showing 17 changed files with 461 additions and 180 deletions.
5 changes: 0 additions & 5 deletions bmad/code/attribute_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -446,11 +446,6 @@ subroutine attribute_bookkeeper (ele, force_bookkeeping)

case (foil$)

if (ele%value(thickness$) < 0) then
call out_io(s_error$, r_name, 'FOIL THICKNESS IS LESS THAN ZERO FOR: ' // ele%name)
if (global_com%exit_on_error) call err_exit
endif

call molecular_components(ele%component_name, component)
n = size(component)
if (.not. allocated(ele%foil%material)) allocate(ele%foil%material(n))
Expand Down
10 changes: 10 additions & 0 deletions bmad/code/lat_sanity_check.f90
Original file line number Diff line number Diff line change
Expand Up @@ -601,6 +601,16 @@ subroutine lat_sanity_check (lat, err_flag)
'WHICH DOES NOT HAVE AN ASSOCIATED ATOMIC NUMBER.')
err_flag = .true.
endif

if (ele%value(thickness$) == 0 .and. ele%value(dthickness_dx$) /= 0) then
do i = 1, size(ele%foil%material)
if (ele%foil%material(i)%area_density /= 0) then
call out_io (s_fatal$, r_name, 'ELEMENT: ' // ele_full_name(ele, '@N (&#)') // &
'HAS ZERO THICKNESS, NON-ZERO DTHICKNESS_DX, AND AREA_DENSITY NON-ZERO.')
err_flag = .true.
endif
enddo
endif
endif

! Zero length cavity is verboten
Expand Down
2 changes: 1 addition & 1 deletion bmad/code/type_ele.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1541,7 +1541,7 @@ function is_2nd_column_attribute (ele, attrib_name, ix2_attrib) result (is_2nd_c
'BETA_A1', 'BETA_B1', 'ALPHA_A1', 'ALPHA_B1', 'ETA_X1', 'ETAP_X1', 'X2_EDGE', 'Y2_EDGE', &
'ETA_Y1', 'ETAP_Y1', 'MATRIX', 'X1', 'PX1', 'Y1', 'PY1', 'Z1', 'PZ1', 'Z_CHARGE', &
'C11_MAT1', 'C12_MAT1', 'C21_MAT1', 'C22_MAT1', 'HARMON_MASTER', 'SCATTER', &
'MODE_FLIP1', 'ALPHA_A_STRONG', 'ALPHA_B_STRONG', 'DELTA_REF_TIME', 'DREL_THICKNESS_DX', &
'MODE_FLIP1', 'ALPHA_A_STRONG', 'ALPHA_B_STRONG', 'DELTA_REF_TIME', 'DTHICKNESS_DX', &
'X_KICK', 'Y_KICK', 'Z_KICK', 'E_TOT_START', 'REF_COORDS', 'CRUNCH_CALIB', 'N_SAMPLE', &
'SCATTER_METHOD']

Expand Down
130 changes: 4 additions & 126 deletions bmad/code/write_bmad_lattice_file.f90
Original file line number Diff line number Diff line change
Expand Up @@ -30,20 +30,6 @@ subroutine write_bmad_lattice_file (bmad_file, lat, err, output_form, orbit0)

implicit none

type multipass_region_ele_struct
integer ix_region
logical region_start_pt
logical region_stop_pt
end type

type multipass_region_branch_struct
type (multipass_region_ele_struct), allocatable :: ele(:)
end type

type multipass_region_lat_struct
type (multipass_region_branch_struct), allocatable :: branch(:)
end type

type (multipass_region_lat_struct), target :: mult_lat
type (multipass_region_ele_struct), pointer :: mult_ele(:), m_ele

Expand Down Expand Up @@ -316,7 +302,7 @@ subroutine write_bmad_lattice_file (bmad_file, lat, err, output_form, orbit0)
if (stack(j)%name == '') cycle
if (any(stack(j)%name == physical_const_list%name)) cycle
call find_index(stack(j)%name, str_index, ix, add_to_list = .true., has_been_added = has_been_added)
if (.not. (has_been_added)) cycle ! Avoid duuplicates
if (.not. (has_been_added)) cycle ! Avoid duplicates
write (iu, '(3a)') trim(stack(j)%name), ' = ', re_str(stack(j)%value)
enddo
enddo
Expand Down Expand Up @@ -1149,94 +1135,12 @@ subroutine write_bmad_lattice_file (bmad_file, lat, err, output_form, orbit0)
write (iu, '(a)') '! Lattice lines'
write (iu, '(a)')

! Multipass stuff...

allocate (mult_lat%branch(0:ubound(lat%branch, 1)))
do ib = 0, ubound(lat%branch, 1)
branch => lat%branch(ib)
allocate (mult_lat%branch(ib)%ele(branch%n_ele_max))
mult_lat%branch(ib)%ele(:)%ix_region = 0
mult_lat%branch(ib)%ele(:)%region_start_pt = .false.
mult_lat%branch(ib)%ele(:)%region_stop_pt = .false.
enddo
call multipass_region_info(lat, mult_lat, m_info)

call multipass_all_info (lat, m_info)
! Each 1st pass region is now a valid multipass line.
! Write out this info.

if (size(m_info%lord) /= 0) then

! Go through and mark all 1st pass regions
! In theory the original lattice file could have something like:
! lat: line = (..., m1, m2, ..., m1, -m2, ...)
! where m1 and m2 are multipass lines. The first pass region (m1, m2) looks
! like this is one big region but the later (m1, -m2) signals that this
! is not so.
! We thus go through all the first pass regions and compare them to the
! corresponding higher pass regions. If we find two elements that are contiguous
! in the first pass region but not contiguous in some higher pass region,
! we need to break the first pass region into two.

ix_r = 0
do ib = 0, ubound(lat%branch, 1)
branch => lat%branch(ib)
mult_ele => mult_lat%branch(ib)%ele

in_multi_region = .false.

do ie = 1, branch%n_ele_track
ele => branch%ele(ie)
e_info => m_info%branch(ib)%ele(ie)
ix_pass = e_info%ix_pass

if (ix_pass /= 1) then ! Not a first pass region
if (in_multi_region) mult_ele(ie-1)%region_stop_pt = .true.
in_multi_region = .false.
cycle
endif

! If start of a new region...
if (.not. in_multi_region) then
ix_r = ix_r + 1
mult_ele(ie)%ix_region = ix_r
mult_ele(ie)%region_start_pt = .true.
in_multi_region = .true.
ix_lord = e_info%ix_lord(1)
ix_super = e_info%ix_super(1)
ss1 => m_info%lord(ix_lord)%slave(:,ix_super)
cycle
endif
ix_lord = e_info%ix_lord(1)
ix_super = e_info%ix_super(1)
ss2 => m_info%lord(ix_lord)%slave(:, ix_super)

need_new_region = .false.
if (size(ss1) /= size(ss2)) then
need_new_region = .true.
else
do ix_pass = 2, size(ss1)
if (abs(ss1(ix_pass)%ele%ix_ele - ss2(ix_pass)%ele%ix_ele) == 1) cycle
! not contiguous then need a new region
need_new_region = .true.
exit
enddo
endif

if (need_new_region) then
ix_r = ix_r + 1
mult_ele(ie-1)%region_stop_pt = .true.
mult_ele(ie)%region_start_pt = .true.
endif

ss1 => ss2
mult_ele(ie)%ix_region = ix_r
enddo

enddo

if (in_multi_region) mult_ele(branch%n_ele_track)%region_stop_pt = .true.

! Each 1st pass region is now a valid multipass line.
! Write out this info.

write (iu, '(a)')
write (iu, '(a)') '!-------------------------------------------------------'

Expand Down Expand Up @@ -1279,7 +1183,6 @@ subroutine write_bmad_lattice_file (bmad_file, lat, err, output_form, orbit0)
endif

enddo ! ib branch loop

endif

! Lines for all the branches.
Expand Down Expand Up @@ -1559,31 +1462,6 @@ end subroutine write_if_int_param_changed
!--------------------------------------------------------------------------------
! contains

subroutine add_this_name_to_list (ele, names, an_indexx, n_names, ix_match, has_been_added, named_eles)

type (ele_struct), target :: ele
type (ele_pointer_struct), allocatable :: named_eles(:) ! List of unique element names

integer, allocatable :: an_indexx(:)
integer n_names, ix_match
logical has_been_added
character(40), allocatable :: names(:)

!

if (size(names) < n_names + 1) then
call re_allocate(names, 2*size(names))
call re_allocate(an_indexx, 2*size(names))
call re_allocate_eles(named_eles, 2*size(names), .true.)
endif
call find_index (ele%name, names, an_indexx, n_names, ix_match, add_to_list = .true., has_been_added = has_been_added)
if (has_been_added) named_eles(n_names)%ele => ele

end subroutine add_this_name_to_list

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

subroutine write_if_logic_param_changed (param_now, param_default, param_name)

logical param_now, param_default
Expand Down
12 changes: 10 additions & 2 deletions bmad/code/write_lattice_in_foreign_format.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
! Subroutine write_lattice_in_foreign_format (out_type, out_file_name, lat, ref_orbit, &
! use_matrix_model, include_apertures, dr12_drift_max, ix_start, ix_end, ix_branch, converted_lat, err)
!
! Subroutine to write a Elegant, MAD-8, MAD-X, OPAL, SAD, or XSIF lattice file using the
! Subroutine to write a Elegant, MAD-8, MAD-X, OPAL, SAD, JULIA, or XSIF lattice file using the
! information in a lat_struct. Optionally, only part of the lattice can be generated.
! [XSIF is a variant of MAD8 used by SLAC.]
!
Expand All @@ -29,7 +29,7 @@
! Note: wiggler elements are replaced by a drift-matrix-drift or drift-bend model.
!
! Input:
! out_type -- character(*): Either 'ELEGANT', 'XSIF', 'MAD-8', 'MAD-X', 'SAD', or 'OPAL-T'.
! out_type -- character(*): Either 'ELEGANT', 'XSIF', 'MAD-8', 'MAD-X', 'SAD', or 'OPAL-T', 'JULIA'.
! out_file_name -- character(*): Name of the mad output lattice file.
! lat -- lat_struct: Holds the lattice information.
! ref_orbit(0:) -- coord_struct, allocatable, optional: Referece orbit for sad_mult and patch elements.
Expand Down Expand Up @@ -107,6 +107,14 @@ subroutine write_lattice_in_foreign_format (out_type, out_file_name, lat, ref_or
logical init_needed, mad_out, err_flag, monopole
logical parsing, warn_printed, converted, ptc_exact_model

! Julia translation

if (out_type == 'JULIA') then
call write_lattice_in_julia (out_file_name, lat)
if (present(converted_lat)) converted_lat = lat
return
endif

! SAD translation

if (out_type == 'SAD') then
Expand Down
Loading

0 comments on commit c23b600

Please sign in to comment.