module bmadz_mod use bmadz_struct use bookkeeper_mod contains !---------------------------------------------------------------------------- !---------------------------------------------------------------------------- !---------------------------------------------------------------------------- !+ ! Subroutine transfer_lat_taylors (lat_in, lat_out, type_out, transfered_all) ! ! Note: This routine is depracated. DO NOT USE. ! ! Subroutine to transfer the taylor maps from the elements of one lattice to ! the elements of another. The elements are matched between the lattices so ! that the appropriate element in lattice_out will get the correct Taylor map ! even if the order of the elements is different in the 2 lattices. ! ! Note: The transfered Taylor map will be truncated to bmad_com%taylor_order. ! Note: If the taylor_order of an element in lattice_in is less than ! bmad_com%taylor_order then it will not be used. ! ! Modules needed: ! use bmad ! ! Input: ! lat_in -- lat_struct: Input lattice with Taylor maps. ! type_out -- Logical: If True then print a message for each Taylor map ! transfered. ! ! Output: ! lat_out -- lat_struct: lattice to receive the Taylor maps. ! transfered_all ! -- Logical, optional: Set True if a Taylor map is found ! for all elements in lattice_out that need one. False otherwise. !- subroutine transfer_lat_taylors (lat_in, lat_out, type_out, transfered_all) implicit none type (lat_struct), target, intent(in) :: lat_in type (lat_struct), target, intent(inout) :: lat_out type (ele_struct), pointer :: ele_in, ele_out integer i, j integer n_in, ix_in(ubound(lat_in%ele, 1)) logical, intent(in) :: type_out logical, optional :: transfered_all character(25) :: r_name = 'transfer_lat_taylors' ! check global parameters if (present(transfered_all)) transfered_all = .true. if (lat_in%ele(0)%value(E_tot$) /= lat_out%ele(0)%value(E_tot$)) then if (type_out) then call out_io (s_warn$, r_name, & 'THE LATTICE ENERGIES ARE DIFFERENT. TAYLOR MAPS NOT TRANSFERED.') endif if (present(transfered_all)) transfered_all = .false. return endif ! Find the taylor series in the first lattice. n_in = 0 do i = 1, lat_in%n_ele_max if (associated(lat_in%ele(i)%taylor(1)%term)) then if (bmad_com%taylor_order > lat_in%input_taylor_order) cycle n_in = n_in + 1 ix_in(n_in) = i endif enddo ! Go through lattice_out and match elements. ! If we have a match transfer the Taylor map. ! Call attribute_bookkeeper before transfering the taylor map to make sure ! the ele_out%value(:) arry is correct. out_loop: do i = 1, lat_out%n_ele_max ele_out => lat_out%ele(i) do j = 1, n_in ele_in => lat_in%ele(ix_in(j)) if (equivalent_taylor_attributes (ele_in, ele_out)) then if (type_out) call out_io (s_info$, r_name, & ' Reusing Taylor from: ' // trim(ele_in%name) // ' to: ' // ele_out%name) call attribute_bookkeeper (ele_out) call transfer_ele_taylor (ele_in, ele_out, bmad_com%taylor_order) cycle out_loop endif enddo if (ele_out%tracking_method == taylor$ .or. & ele_out%mat6_calc_method == taylor$ .and. type_out) then call out_io (s_warn$, r_name, ' NO TAYLOR FOR: ' // ele_out%name) if (present(transfered_all)) transfered_all = .false. endif enddo out_loop end subroutine transfer_lat_taylors end module