!+ ! Subroutine bmad_create_finalize (ix_lat, c_err) ! ! Cleanup for the lattice creation. ! ! Input: ! ix_lat -- Integer: Index of lattice being created. ! ! Output: ! c_err -- C_logical: Set True if there is an error. False otherwise. !- subroutine bmad_create_finalize (ix_lat, c_err) use bmad_common_mod use bookkeeper_mod implicit none type (lat_struct), pointer :: lat type (ele_struct), pointer :: ele real(rp) mat6(6,6), mat_inv(6,6) integer i, itw, ix_lat character(24), parameter :: r_name = 'bmad_create_finalize' logical(c_bool) c_err, c_err2 ! c_err = c_logic(.true.) if (lat_status(ix_lat) /= in_init$) then call out_io (s_warn$, r_name, "Multiple initializations of lattice \i0\ attempted!", ix_lat) return end if bd_com(ix_lat)%status = init_done$ lat => bd_com(ix_lat)%lat call bmad_lattice_bookkeeper(ix_lat, c_err2) if (f_logic(c_err2)) return call reallocate_coord(bd_com(ix_lat)%orb, lat%n_ele_max) call init_coord (bd_com(ix_lat)%orb(0), ele = lat%ele(0), element_end = downstream_end$, particle = lat%param%particle) ! Compute twiss ! For sbend elements b_field_tot is stored in ele%value(scratch1$) and angle in %value(scratch2$). do itw = 1, lat%n_ele_track ele => lat%ele(itw) if (ele%key == sbend$) then ele%value(angle$) = ele%value(scratch2$) ele%value(g$) = ele%value(angle$) / ele%value(l$) ele%value(b_field$) = ele%value(g$) * ele%value(p0c$) / c_light ele%value(b_field_err$) = ele%value(scratch1$) - ele%value(b_field$) call set_flags_for_changed_attribute (ele, ele%value(b_field$)) endif enddo ! Twiss do itw = 1, lat%n_ele_track ele => lat%ele(itw) if (ele%logic) then call mat_make_unit(mat6) do i = 1, itw mat6 = matmul(lat%ele(i)%mat6, mat6) enddo call mat_inverse(mat6, lat%ele(0)%mat6) call twiss_propagate1(ele, lat%ele(0)) call set_flags_for_changed_attribute(lat%ele(0)) call mat_make_unit(lat%ele(0)%mat6) endif enddo call bmad_lattice_bookkeeper(ix_lat, c_err2) if (f_logic(c_err2)) return lat%ele(0)%a%eta = 0 lat%ele(0)%b%eta = 0 lat%ele(0)%x%eta = 0 lat%ele(0)%y%eta = 0 lat%ele(0)%z%eta = 0 lat%ele(0)%a%etap = 0 lat%ele(0)%b%etap = 0 lat%ele(0)%x%etap = 0 lat%ele(0)%y%etap = 0 lat%ele(0)%a%phi = 0 lat%ele(0)%b%phi = 0 c_err = c_logic(.false.) end subroutine