program radiation_map use pointer_lattice, pum1 => lat use ptc_layout_mod, dum1 => dp use taylor_mod, dum2 => dp implicit none type (lat_struct), target :: lat type (taylor_struct) tlr(6) real(rp) m6(6,6), mm6(6,6), vec0(6), vv0(6) type (universal_taylor) ut character(100) lat_file, str type(layout), pointer:: atf,atf2,atf_t,atf2_t,als real(dp) prec,closed_orbit(6),mat(6,6),a(6,6),ai(6,6),del,error(6),emi(3),sij(3) real(dp) sigmas(6,6),sig_inf(6,6),sigmas_tracked(6,6),m(6,6),kick_stoch(3) real(dp) energy,deltap,xij ,x(6),t,lam,k1 complex(dp) mc(6,6) type(internal_state),target :: state,sta(2) logical(lp) :: mis=.false. type(c_damap) one_turn_map, Id,a0,mrad,mrad_e_ij,a_cs type(real_8) y(6) type(c_normal_form) normal_form type(c_taylor) phase(4) integer expo(6),pos,no character*48 command_gino,fmd,fmd1 integer i,map_order,j,mf,k,cas,nn type(probe) xs0,xs01,xs02 type(probe_8) ray type(probe_8) xs,xe,xsrad_e_ij !!!!!!!!!!!!!!!!!!!!! type(fibre), pointer :: p,f1,p1, fib1, fib2 type(integration_node), pointer :: ti TYPE(tree_element_zhe) T_zhe1(3), T_zhe2(3), T_zhe3(3) type(probe_zhe) xs0_zhe,xs0_zhe1,xs0_zhe2 type(internal_state_zhe) state_zhe logical matrix c_verbose=.false. prec=1.d-10 ! for printing del=0.d0 use_info=.true. lat_file = 'lat.bmad' if (command_argument_count() > 0) call get_command_argument(1, lat_file) call bmad_parser (lat_file, lat) call set_on_off(rfcavity$, lat, off$) call lat_to_ptc_layout (lat) als=>lat%branch(0)%ptc%m_t_layout use_quaternion=.true. state=nocavity0+spin0 !write(6,*) "no " !read(5,*) no no=ptc_com%taylor_order_ptc ! call init(state,no,0) call alloc(xs) call alloc(phase) call alloc(normal_form) call alloc(one_turn_map, Id) closed_orbit=0 xs0=closed_orbit call find_orbit_x(als,closed_orbit(1:6),STATE,1.e-8_dp,fibre1=1) !write(6,format6) closed_orbit xs0=closed_orbit id =1 xs=id + xs0 call propagate(als, xs, state, fibre1=1) one_turn_map=xs call c_normal(one_turn_map,normal_form,dospin=.true.,phase=phase(1:3), nu_spin=phase(4)) write(6,*) " Transverse tunes------------------------------------------- " call print(phase(1:2)) write(6,*) " Longitudinal time slip " call print(phase(3)) write(6,*) " Spin tune " call print(phase(4)) expo=0 do i=1,2 Write(6,*) " tunes and chromaticities in plane ",i do j=0,no-1 expo(ndpt_bmad+5)=j write(6,*) j,real(phase(i).sub.expo) enddo enddo Write(6,*) " phase slip and chromaticitic phase slip in plane ",i do j=0,no-1 expo(ndpt_bmad+5)=j write(6,*) j,real(phase(3).sub.expo) enddo Write(6,*) " tune and chromaticities for the spin " do j=0,no expo(ndpt_bmad+5)=j write(6,*) j,real(phase(4).sub.expo) enddo 1000 call ptc_end(graphics_maybe=1,flat_file=.false.) contains end program radiation_map