! ! In the calling program define the structure by: ! RECORD / PC_STRUCT /PC ! ! Example values ! ! PC.CROSS(n).Z z-coordinate of n'th parasitic crossing ! PC.BEAM_BEAM(m,n) logical: true if beam bunch m has close ! encounter with beam bunch n ! PC.CROSS(n).ORBIT orbit of beam at n ! PC.CROSS(n).ELE.X.BETA ! PC.CROSS(n).ELE.X.SIGMA ! PC.CROSS(n).DNUV vertical long range tune shift at n ! PC.CROSS(n).DNUV_X vertical long range tune shift at n (horiz sep only) ! PC.CROSS(n).DNUV_Y vertical long range tune shift at n (vert sep only) ! PC.CROSS(n).IX parasitic crossing n is in lat element ix ! PC.CROSS(n).MAT6(6,6) matrix to propogate from end of element ix ! PC.TOTAL_PC number of parasitic crossings ! PC.POSBUNCH_ELEBUNCH(p,q,r) parsitic crossing where bunch p positron and ! bunch q electron miss ,rth time (r=1,2) !- ! Structure definitions module bunchcross_mod use bmad use bmadz_mod type pc_cross_struct real(rp) dnuv, dnuh, dnuv_x, dnuh_x, dnuv_y, dnuh_y, b_param, distance_to_bpm type (ele_struct) ele type (coord_struct) orbit integer ix character*16 bpm end type type pc_struct type (pc_cross_struct) cross(100)!cross(1000) integer posbunch_elebunch(100,100,2) !posbunch_elebunch(100,100,2) integer total_pc ! number of parasitic crossings logical beam_beam(100,100) !beam_beam(100,1000) logical Pos_beam_beam(100,100) !Pos_beam_beam(100,1000) logical Ele_beam_beam(100,100) !Ele_beam_beam(100,1000) end type contains !........................................................................ ! ! Subroutine : TRACK_TO_PC (CO, PARAM, PC) ! ! Description: Subroutine to track from end of element that includes ! parasitic crossing to crossing point ! ! Arguments : ! Input: PC ! CO(:) closed orbit at end of each lat element ! Output: ! PC -- PC_STRUCT: pc.cross(j).orbit orbit at parasitic ! crossing point ! ! Mod/Commons: ! ! Calls : ! ! Author : ! ! Modified : ! !........................................................................ ! ! ! $Log$ ! Revision 1.7 2007/01/30 16:15:14 dcs ! merged with branch_bmad_1. ! ! Revision 1.3 2004/08/26 21:54:01 dlr ! error message if element name in constraint file is not in lat ! ! Revision 1.2 2003/08/12 01:46:04 mjf7 ! Fixed some parameter inconsistencies and added four more subroutines to modules. - mjf ! ! Revision 1.2 2003/04/30 17:14:56 cesrulib ! dlr's changes since last import ! ! Revision 1.1.1.1 2002/12/13 19:23:30 cesrulib ! import bmadz ! ! !........................................................................ ! subroutine track_to_pc(co, param, PC, lat) implicit none type (lat_struct) lat type (lat_param_struct) param type (coord_struct), allocatable :: co(:) type (pc_struct) pc integer i,j integer iy_before, iy_after, k real(rp) xafter, xbefore ! do j=1,pc%total_pc i=pc%cross(j)%ix call track1 (co(i-1), pc%cross(j)%ele, param, pc%cross(j)%orbit) k=i xbefore=99. xafter = 99. do while (index(lat%ele(k)%name,'DET') == 0) if(k==0)exit k=k-1 ! print '(a16,2i10,5x,a16)','before', i,k, lat%ele(k)%name end do iy_before = k xbefore = pc%cross(j)%ele%s-lat%ele(k)%s k=i do while (index(lat%ele(k)%name,'DET') == 0) k=k+1 ! print '(a16,2i10,5x,a16)','after', i,k, lat%ele(k)%name end do iy_after = k xafter = lat%ele(k)%s-pc%cross(j)%ele%s ! print '(a,2f12.4)','xafter,xbefore', xafter, xbefore if(xafter > xbefore)then pc%cross(j)%distance_to_bpm = xbefore pc%cross(j)%bpm = lat%ele(iy_before)%name else pc%cross(j)%distance_to_bpm = xafter pc%cross(j)%bpm = lat%ele(iy_after)%name endif ! pause enddo return end subroutine track_to_pc !........................................................................ ! ! Subroutine : TWISS_TO_PC ( LAT, global, PC) ! ! Description: Subroutine to propagate twiss parameters from end of element ! that includes parasitic crossing to crossing point and compute ! beam size ! ! Arguments : ! Input: LAT, GLOBAL ! ! Output: ! PC -- PC_STRUCT: pc.cross(j).ele twiss at parasitic crossing point ! pc.cross(j).sigma beam size at parasitic crossing ! ! Mod/Commons: ! ! Calls : ! ! Author : ! ! Modified : ! !........................................................................ ! ! ! $Log$ ! Revision 1.7 2007/01/30 16:15:14 dcs ! merged with branch_bmad_1. ! ! Revision 1.3 2004/08/26 21:54:01 dlr ! error message if element name in constraint file is not in lat ! ! Revision 1.2 2003/08/12 01:46:04 mjf7 ! Fixed some parameter inconsistencies and added four more subroutines to modules. - mjf ! ! Revision 1.2 2003/04/30 17:14:56 cesrulib ! dlr's changes since last import ! ! Revision 1.1.1.1 2002/12/13 19:23:30 cesrulib ! import bmadz ! ! !........................................................................ ! subroutine twiss_to_pc(lat, global, PC) implicit none type (lat_struct) lat type (pc_struct) pc type (global_struct) global real(rp) betax, etax integer i,j ! do j=1,pc%total_pc i=pc%cross(j)%ix call twiss_propagate1 (lat%ele(i-1), pc%cross(j)%ele) betax = pc%cross(j)%ele%a%beta etax = pc%cross(j)%ele%a%eta pc%cross(j)%ele%a%sigma = sqrt(max(0.0, & global%wig%x_emit*betax + (global%wig%sige_e*etax)**2)) enddo return end subroutine twiss_to_pc end module bunchcross_mod