Skip to content

Commit

Permalink
Make ele%space_charge_method differentially settable by different mul…
Browse files Browse the repository at this point in the history
…tipass slaves.
  • Loading branch information
DavidSagan committed Nov 26, 2024
1 parent 60afa0c commit 3af4777
Show file tree
Hide file tree
Showing 9 changed files with 135 additions and 61 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -80,6 +80,7 @@ regression_tests/hdf5_test/grid_field.h5
regression_tests/hdf5_test/bunch.ascii
regression_tests/multipass_test/lat1.bmad
regression_tests/multipass_test/lat2.bmad
regression_tests/multipass_test/cavity2.grid_field.h5
regression_tests/parse_test/c2.bmad
regression_tests/parse_test/com2.bmad
regression_tests/parse_test/g1.grid_field.h5
Expand Down
2 changes: 1 addition & 1 deletion bmad/modules/bookkeeper_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -481,7 +481,7 @@ subroutine makeup_multipass_slave (lat, slave, err_flag)
slave%symplectify = lord%symplectify
slave%is_on = lord%is_on
slave%csr_method = lord%csr_method
slave%space_charge_method = lord%space_charge_method
!! slave%space_charge_method = lord%space_charge_method

! Handled by set_flags_for_changed_attribute

Expand Down
15 changes: 13 additions & 2 deletions bmad/modules/changed_attribute_bookkeeper.f90
Original file line number Diff line number Diff line change
Expand Up @@ -102,11 +102,11 @@ end subroutine set_flags_for_changed_all_attribute
subroutine set_flags_for_changed_integer_attribute (ele, attrib, set_dependent)

type (ele_struct), target :: ele
type (ele_struct), pointer :: slave
type (ele_struct), pointer :: slave, lord

integer, target :: attrib
integer, pointer :: a_ptr
integer i
integer i, ix_pass

real(rp) dummy

Expand Down Expand Up @@ -157,6 +157,17 @@ subroutine set_flags_for_changed_integer_attribute (ele, attrib, set_dependent)
enddo
endif

!-------------------------------------------------------------------

if (ele%slave_status == multipass_slave$) then
lord => pointer_to_multipass_lord(ele, ix_pass)
if (ix_pass == 1) then
if (associated(a_ptr, ele%space_charge_method)) then
lord%space_charge_method = ele%space_charge_method
endif
endif
endif

end subroutine set_flags_for_changed_integer_attribute

!----------------------------------------------------------------------------
Expand Down
18 changes: 14 additions & 4 deletions bmad/output/write_bmad_lattice_file.f90
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,8 @@ subroutine write_bmad_lattice_file (bmad_file, lat, err, output_form, orbit0)
type (coord_struct), optional :: orbit0
type (ele_attribute_struct) attrib
type (branch_struct), pointer :: branch, branch2
type (ele_struct), pointer :: ele, super, slave, lord, lord2, s1, s2, multi_lord, slave2, ele2, ele_dflt, ele0, girder
type (ele_struct), pointer :: ele, super, slave, lord, lord2, s1, s2, multi_lord
type (ele_struct), pointer :: slave1, slave2, ele2, ele_dflt, ele0, girder
type (ele_struct), target :: ele_default(n_key$), this_ele
type (ele_pointer_struct), allocatable :: named_eles(:) ! List of unique element names
type (ele_attribute_struct) info
Expand Down Expand Up @@ -1308,11 +1309,20 @@ subroutine write_bmad_lattice_file (bmad_file, lat, err, output_form, orbit0)
if (ele%slave_status == super_slave$) cycle

if (ele%key == lcavity$ .or. ele%key == rfcavity$) then
if (ele%value(phi0_multipass$) == 0) cycle
if (.not. have_expand_lattice_line) call write_expand_lat_header
write (iu, '(3a)') trim(ele%name), '[phi0_multipass] = ', re_str(ele%value(phi0_multipass$))
if (ele%value(phi0_multipass$) /= 0) then
if (.not. have_expand_lattice_line) call write_expand_lat_header
write (iu, '(3a)') trim(ele%name), '[phi0_multipass] = ', re_str(ele%value(phi0_multipass$))
endif
endif

if (ele%slave_status == multipass_slave$) then
multi_lord => pointer_to_multipass_lord (ele, ix_pass)
slave1 => pointer_to_slave(multi_lord, 1)
if (ele%space_charge_method /= slave1%space_charge_method) then
if (.not. have_expand_lattice_line) call write_expand_lat_header
write (iu, '(3a)') trim(ele%name), '[space_charge_method] = ', space_charge_method_name(ele%space_charge_method)
endif
endif
enddo

! If there are lattice elements with duplicate names but differing parameters then
Expand Down
12 changes: 7 additions & 5 deletions bmad/parsing/parser_set_attribute.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2063,6 +2063,13 @@ subroutine parser_set_attribute (how, ele, delim, delim_found, err_flag, pele, c
call get_switch (attrib_word, scatter_method_name(1:), ix, err_flag, ele, delim, delim_found); if (err_flag) return
ele%value(scatter_method$) = ix

case ('SPACE_CHARGE_METHOD')
call get_switch (attrib_word, space_charge_method_name(1:), switch, err_flag, ele, delim, delim_found)
if (err_flag) return
ele%space_charge_method = switch
! With multipass, space_charge_method needs bookkeeping since this param can be set individually in the slaves.
if (bp_com%parser_name == 'bmad_parser2') call set_flags_for_changed_attribute(ele, ele%space_charge_method)

case ('SPATIAL_DISTRIBUTION')
call get_switch (attrib_word, distribution_name(1:), ix, err_flag, ele, delim, delim_found); if (err_flag) return
ele%value(spatial_distribution$) = ix
Expand Down Expand Up @@ -2126,11 +2133,6 @@ subroutine parser_set_attribute (how, ele, delim, delim_found, err_flag, pele, c
endif
ele%tracking_method = switch

case ('SPACE_CHARGE_METHOD')
call get_switch (attrib_word, space_charge_method_name(1:), switch, err_flag, ele, delim, delim_found)
if (err_flag) return
ele%space_charge_method = switch

case ('VELOCITY_DISTRIBUTION')
call get_switch (attrib_word, distribution_name(1:), ix, err_flag, ele, delim, delim_found); if (err_flag) return
ele%value(velocity_distribution$) = ix
Expand Down
84 changes: 45 additions & 39 deletions regression_tests/multipass_test/lat.bmad
Original file line number Diff line number Diff line change
@@ -1,43 +1,49 @@
parameter[geometry] = Open

parameter[p0c] =9.9999986944E8
parameter[particle] = Positron
parameter[absolute_time_tracking] = F
beginning[s] = 3

beginning[beta_a] = 10
beginning[beta_b] = 10


parameter[p0c] = 9.99999869440028E8
parameter[particle] = Positron

beginning[beta_a] = 10
beginning[beta_b] = 10


!-------------------------------------------------------

slave_drift_0_1: drift, l = 1.5
slave_drift_0_2: drift, l = 1
slave_drift_0_3: drift, l = 3.5
slave_drift_0_4: drift, l = 0.284
slave_drift_0_6: drift, l = 0.284
MM: Marker
DRI01: Pipe, L = 6, space_charge_method = Slice
Q01: Quadrupole, L = 1, tracking_method = Runge_Kutta, space_charge_method = FFT_3D, A2 = 1
CAVITY2: Lcavity, grid_field = call::cavity2.grid_field.h5, L = 0.568, RF_FREQUENCY = 1.3E9,
DS_STEP = 0.568, mat6_calc_method = Tracking, tracking_method = Runge_Kutta,
space_charge_method = Slice, field_calc = FieldMap

!-------------------------------------------------------
! Overlays, groups, rampers, and superimpose

superimpose, element = DRI01, ref = slave_drift_0_1, offset = 2.25
superimpose, element = Q01, ref = slave_drift_0_2, offset = 0
superimpose, element = CAVITY2, ref = slave_drift_0_4, offset = 0.141999999999999

!-------------------------------------------------------

A: DRIFT, L = 1
MA: PATCH

! Lattice lines


!-------------------------------------------------------
! Overlays, groups, etc.

B: SBEND, L = 0.1, REF_TILT = 0.1, G = 31.415926536, N_REF_PASS = 1
A2: DRIFT, L = 2, N_REF_PASS = 1
FID: FIDUCIAL, DX_ORIGIN = 1, DTHETA_ORIGIN = 0.01, origin_ele = MA
PF: PATCH, TILT = -6.4599543167E-30, FLEXIBLE = T, X_PITCH = -1.9997892306E-14, &
Y_PITCH = -8.8817844391E-16, X_OFFSET = 6.487865977E-16, &
Y_OFFSET = -3.9187172163E-16, Z_OFFSET = 1


multi_line_01: line[multipass] = ( slave_drift_0_1, slave_drift_0_2, slave_drift_0_3, slave_drift_0_4,
MM, slave_drift_0_6)

ERLRECOVERY: line = ( multi_line_01, multi_line_01)

use, ERLRECOVERY

!-------------------------------------------------------

multi_line_01: line[multipass] = ( A, B, A2, B)

B1: line = ( A, MA)

B2: line = ( multi_line_01, FID, PF, multi_line_01)

B2[geometry] = Open
B2[particle] = Positron
B2[p0c] = 9.9999986944E8
B2[s] = 2
B2[ref_time] = 1E-9

B2[beta_a] = 10
B2[beta_b] = 10

use, B1, B2

expand_lattice

Q01\2[space_charge_method] = Slice
CAVITY2\2[space_charge_method] = FFT_3D
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,14 @@ mm: marker, superimpose, ref = cavity2
mline: line[multipass] = (dri01, null_d, cavity2)
erlrecovery: line = (mline, mline)

q01[space_charge_method] = fft_3d
cavity2[space_charge_method] = fft_3d
dri01[space_charge_method] = fft_3d

use, erlrecovery

expand_lattice

dri01[space_charge_method] = slice
q01\2[space_charge_method] = slice
cavity2\1[space_charge_method] = slice
23 changes: 18 additions & 5 deletions regression_tests/multipass_test/multipass_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,14 +4,28 @@ program multipass_test

implicit none

type (lat_struct), target :: lat
type (ele_struct), pointer :: ele
type (lat_struct), target :: lat, lat2
type (ele_struct), pointer :: ele, ele2

! Init
call bmad_parser ('multipass_and_superimpose.bmad', lat)
integer ie

!

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

! Space_charge_method test

call bmad_parser ('multipass_and_superimpose.bmad', lat)
call write_bmad_lattice_file ('lat.bmad', lat)
call bmad_parser ('lat.bmad', lat2)

do ie = 1, lat%n_ele_max
ele => lat%ele(ie)
write (1, '(a, i0, 3a, 2x, a)') '"scm-', ie, trim(ele%name), '" STR ', &
quote(space_charge_method_name(ele%space_charge_method)), &
quote(space_charge_method_name(lat2%ele(ie)%space_charge_method))
enddo

! Forking with a branch element

call bmad_parser ('branch_fork.bmad', lat)
Expand Down Expand Up @@ -55,7 +69,6 @@ program multipass_test
write (1, '(a, 3f12.6)') '"P-7FR" ABS 0', ele%floor%r
write (1, '(a, 3f12.6)') '"P-7FA" ABS 0', ele%floor%theta, ele%floor%phi, ele%floor%psi


! And close

close (1)
Expand Down
33 changes: 28 additions & 5 deletions regression_tests/multipass_test/output.correct
Original file line number Diff line number Diff line change
@@ -1,21 +1,44 @@
"scm-1DRI01\1#1" STR "Slice" "Slice"
"scm-2DRI01\1\Q01\1" STR "FFT_3D" "FFT_3D"
"scm-3DRI01\1#2" STR "Slice" "Slice"
"scm-4CAVITY2\1#1" STR "Slice" "Slice"
"scm-5MM\1" STR "Off" "Off"
"scm-6CAVITY2\1#2" STR "Slice" "Slice"
"scm-7DRI01\2#1" STR "Slice" "Slice"
"scm-8DRI01\2\Q01\2" STR "Slice" "Slice"
"scm-9DRI01\2#2" STR "Slice" "Slice"
"scm-10CAVITY2\2#1" STR "FFT_3D" "FFT_3D"
"scm-11MM\2" STR "Off" "Off"
"scm-12CAVITY2\2#2" STR "FFT_3D" "FFT_3D"
"scm-13END" STR "Off" "Off"
"scm-14DRI01\1" STR "Slice" "Slice"
"scm-15Q01\1" STR "FFT_3D" "FFT_3D"
"scm-16DRI01\2" STR "Slice" "Slice"
"scm-17Q01\2" STR "Slice" "Slice"
"scm-18CAVITY2\1" STR "Slice" "Slice"
"scm-19CAVITY2\2" STR "FFT_3D" "FFT_3D"
"scm-20MM" STR "Off" "Off"
"scm-21DRI01" STR "Slice" "Slice"
"scm-22Q01" STR "FFT_3D" "FFT_3D"
"scm-23CAVITY2" STR "Slice" "Slice"
"BF-01" STR "FORK2"
"BF-02" ABS 0 0 4
"BF-03" REL 1e-12 100.0000
"MS-01" STR "DRI01\1#1"
"MS-02" STR "DRI01\Q01\1"
"MS-02" STR "DRI01\1\Q01\1"
"MS-03" STR "DRI01\1#2"
"MS-04" STR "CAVITY2\1#1"
"MS-05" STR "MM\1"
"MS-06" STR "CAVITY2\1#2"
"MS-07" STR "DRI01\2#1"
"MS-08" STR "DRI01\Q01\2"
"MS-08" STR "DRI01\2\Q01\2"
"MS-09" STR "DRI01\2#2"
"MS-10" STR "CAVITY2\2#1"
"MS-11" STR "MM\2"
"MS-12" STR "CAVITY2\2#2"
"MS-13" STR "END"
"P-0S" ABS 0 2.000000
"P-0T" ABS 0 1.000000E-09
"P-6MI" ABS 0 1.000000 0.000000 0.000000
"P-7FR" ABS 0 1.020000 0.000000 2.999900
"P-7FA" ABS 0 0.010000 0.000000 0.000000
"P-6MI" ABS 0 1.000000 -0.000000 -0.000000
"P-7FR" ABS 0 1.020000 -0.000000 2.999900
"P-7FA" ABS 0 0.010000 -0.000000 0.000000

0 comments on commit 3af4777

Please sign in to comment.