!........................................................................ ! ! Subroutine : ! ! Description: ! ! Arguments : ! ! Mod/Commons: ! ! Calls : ! ! Author : ! ! Modified : ! !........................................................................ ! ! ! $Log$ ! Revision 1.8 2007/01/30 16:15:14 dcs ! merged with branch_bmad_1. ! ! Revision 1.4 2003/11/10 17:01:54 dcs ! removed lat symmetry ! ! Revision 1.3 2003/09/05 16:36:06 dlr ! if a parasitic crossing point is within a wiggler, model element from ! end to crossing point as old style ! ! Revision 1.2 2003/04/30 17:14:53 cesrulib ! dlr's changes since last import ! ! Revision 1.1.1.1 2002/12/13 19:23:29 cesrulib ! import bmadz ! ! !........................................................................ ! ! if(lat%ele(i)%key == wiggler$)then ! pc%cross(j)%ele%key = drift$ ! pc%cross(j)%ele%tracking_method = bmad_standard$ ! endif SUBROUTINE parasitic_crossing_points (lat, pc) use bmad use bmad_interface use bunchcross_mod implicit none type (lat_struct) lat type (pc_struct) pc type (coord_struct) orb0 real(rp) zlat, zpc, zend integer i, j zend = lat%ele(lat%n_ele_track)%s i=1 zlat =lat%ele(1)%s do j=1, pc%total_pc zpc =pc%cross(j)%ele%s if(zpc <= zend + 0.0009)then do while(zlat < zpc) i=i+1 zlat=lat%ele(i)%s end do pc%cross(j)%ix = i pc%cross(j)%ele = lat%ele(i) call kill_taylor (pc%cross(j)%ele%taylor) pc%cross(j)%ele%value(num_steps$) = 10 pc%cross(j)%ele%s = zpc pc%cross(j)%ele%value(l$) = pc%cross(j)%ele%s - lat%ele(i-1)%s if(lat%ele(i)%key == hybrid$)pc%cross(j)%ele%key = drift$ call make_mat6(pc%cross(j)%ele, lat%param) endif end do return end