!+ ! Subroutine bmad_create_init_lat (ix_lat, n_ele, s_start, lat_len, start_kinetic_energy, c_err) ! ! First creation routine to call when constructing a lattice from ! the Doocs database. ! ! Input: ! ix_lat -- Integer: Index of lattice to create ! n_ele -- Estimated number of lattice elements. Does not include drifts. ! lat_len -- Real(rp): Lattice length ! start_kinetic_energy ! -- Real(rp): Sarting kinetic energy in eV. ! ! Output: ! c_err -- C_logical: Set True if there is an error. False otherwise. !- subroutine bmad_create_init_lat (ix_lat, n_ele, s_start, lat_len, start_kinetic_energy, c_err) use bmad_common_mod implicit none type (lat_struct), pointer :: lat real(rp) lat_len, start_kinetic_energy, s_start integer n_ele, ix_lat character(24), parameter :: r_name = 'bmad_create_init_lat' logical(c_bool) c_err ! Lattice init c_err = c_logic(.true.) if (lat_status(ix_lat) /= no_init$) then call out_io (s_warn$, r_name, "Multiple initializations of lattice \i0\ attempted!", ix_lat) return end if if (lat_len <= 0 .or. isnan(lat_len)) then call out_io (s_warn$, r_name, 'lat_len input is not positive.') return end if if (start_kinetic_energy < 0 .or. isnan(start_kinetic_energy)) then call out_io (s_warn$, r_name, 'start_kinetic_energy input is not non-negative.') return end if lat => bd_com(ix_lat)%lat call init_lat(lat, 2*n_ele+1) lat%param%particle = electron$ lat%param%geometry = open$ ! Beginning marker element init lat%ele(0)%value(p0c$) = sqrt(start_kinetic_energy**2 + & 2 * start_kinetic_energy * mass_of(lat%param%particle)) lat%ele(0)%value(e_tot$) = start_kinetic_energy + mass_of(lat%param%particle) lat%ele(0)%a%beta = 10 lat%ele(0)%b%beta = 10 lat%ele(0)%s = s_start ! Drift to superimpose on init lat%ele(1)%name = 'drft' lat%ele(1)%key = drift$ lat%ele(1)%value(l$) = lat_len lat%ele(1)%s = lat_len lat%ele(1)%ix_ele = 1 lat%n_ele_track = 1 lat%n_ele_max = 1 bd_com(ix_lat)%status = in_init$ c_err = c_logic(.false.) end subroutine