!+ ! Subroutine PLOT_WAVE (u) ! ! Subroutine to stuff the appropriate data in arrays for PLOT_GRAPH to read !- subroutine plot_wave (u) use cesrv_struct use cesrv_interface use quick_plot implicit none type (universe_struct), target :: u type (qp_axis_struct), pointer :: y_axis integer ix, i, n_use, nl real(rp) :: x_win_pix = 700 real(rp) :: x1_marg = 60, y1_marg = 30 real(rp) :: x2_marg = 200 character(100) path, basename character(70) lines(20) character(1) wave_plane y_axis => u%wave%p2%plot1%y_axis wave_plane = name$%plane(u%wave%p2%plot1%d1%plane) call qp_set_margin (x1_marg, 20.0_rp, y1_marg, 20.0_rp, 'POINTS') call qp_set_page_border (0.0_rp, 0.0_rp, 0.0_rp, 40.0_rp, 'POINTS') call qp_set_axis ('X', 0.0_rp, 150.0_rp, 15, 0) call qp_set_box (1, 4, 1, 4) call qp_set_axis('Y', -y_axis%max, y_axis%max, y_axis%major_div, y_axis%places) n_use = u%wave%p2%plot1%n_use call qp_draw_graph (u%wave%p2%x(1:n_use), u%wave%p2%plot1%y(1:n_use), 'Index', wave_plane, & trim(u%wave%p2%plot1%title) // ' ' // u%wave%p2%plot1%title_suffix) call qp_draw_rectangle (1.0_rp*u%wave%ix_a1, 1.0_rp*u%wave%ix_a2, -0.9_rp*y_axis%max, 0.9_rp*y_axis%max) call qp_draw_rectangle (1.0_rp*u%wave%ix_b1, 1.0_rp*u%wave%ix_b2, -0.9_rp*y_axis%max, 0.9_rp*y_axis%max) call qp_set_box (1, 3, 1, 4) call qp_draw_graph (u%wave%p2%x(1:n_use), u%wave%p2%plot2%y(1:n_use), 'Index', 'delta', 'Residual to Fit of Region A') call qp_draw_rectangle (1.0_rp*u%wave%ix_a1, 1.0_rp*u%wave%ix_a2, -0.4_rp*y_axis%max, 0.4_rp*y_axis%max) call qp_set_box (1, 2, 1, 4) call qp_draw_graph (u%wave%p2%x(1:n_use), u%wave%p2%plot3%y(1:n_use), 'Index', 'delta', 'Residual to Fit of Region B') call qp_draw_rectangle (1.0_rp*u%wave%ix_b1, 1.0_rp*u%wave%ix_b2, -0.4_rp*y_axis%max, 0.4_rp*y_axis%max) ! Info at bottom of page. Right side. call qp_set_box (1, 1, 1, 4) lines(1) = u%wave%p2%d2%date lines(2) = logic%lattice ix = splitfilename (u%wave%p2%d2%file_name, path, basename) lines(3) = path lines(4) = 'Dat: ' // basename if (plot_type_has(plot_ref$, u%wave%p2%base) .or. plot_type_has(plot_ref$, u%wave%p2%plot_data)) then ix = splitfilename (u%wave%p2%d2%ref_file_name, path, basename) lines(5) = 'Ref: ' // basename else lines(5) = 'Ref: NONE' endif write (lines(6), '(a, i7)') 'CESR Set:', u%wave%p2%d2%csr_set lines(7) = ' ' write (lines(8), '(a, 2i4)') 'IX_A1, IX_A2:', u%wave%ix_a1, u%wave%ix_a2 write (lines(9), '(a, 2i4)') 'IX_B1, IX_B2:', u%wave%ix_b1, u%wave%ix_b2 call qp_draw_text_legend (lines(1:9), 0.55_rp, 0.95_rp, '%GRAPH') ! Info at bottom of page. Left side. select case (u%wave%wave_what) case ('ORBIT', 'ETA', 'AC_ETA') ! orbit wave analysis write (lines(1), '(a, f8.3)') 'A Region Sig/A:', u%wave%rms_a write (lines(2), '(a, f8.3)') 'B Region Sig/A:', u%wave%rms_b write (lines(3), '(2(a, f8.3, 5x))') & 'Kick Sig_K/K:', u%wave%rms_k, 'Sig_phi:', u%wave%rms_phi lines(4) = ' ' lines(5) = 'Kick: delta_' // wave_plane // & ''' * sqrt(beta) [urad * sqrt(m)]' lines(6) = 'After Det# Kick phi_' // wave_plane do i = 1, min(u%wave%n_cross, 10) write (lines(i+6), '(i11, f10.2, 1f10.3)') u%wave%ix_cross(i), & u%wave%kick(i), u%wave%phi_kick(i) enddo call qp_draw_text_legend(lines(1:u%wave%n_cross+6), -0.05_rp, 0.95_rp, '%GRAPH') case ('PHASE') ! phase wave anlysis write (lines(1), '(a, f8.3)') 'A Region Sig/A:', u%wave%rms_a write (lines(2), '(a, f8.3)') 'B Region Sig/A:', u%wave%rms_b write (lines(3), '(a, f8.3)') ' chi_a:', u%wave%chi_a write (lines(4), '(2(a, f8.3, 5x))') & 'Kick Sig_K/K:', u%wave%rms_k, 'Sig_phi:', u%wave%rms_phi lines(5) = ' ' write (lines(6), '(a, f10.4, a)') 'Kick:', u%wave%kick(1), & ' ! delta_k*l*beta [dimensionless]' lines(7) = 'After Det# phi_' // wave_plane do i = 1, min(u%wave%n_cross, 10) write (lines(i+7), '(i11, 2f10.3)') u%wave%ix_cross(i), u%wave%phi_kick(i) enddo call qp_draw_text_legend(lines(1:u%wave%n_cross+7), -0.05_rp, 0.95_rp, '%GRAPH') ! cbar wave analysis case ('CBAR') write (lines(1), '(2(a, f8.3, 4x))') 'A Region: Sig_s/A_s:', u%wave%rms_sa, 'Sig_r/A_r:', u%wave%rms_ra write (lines(2), '(2(a, f8.3, 4x))') 'B Region: Sig_s/A_s:', u%wave%rms_sb, 'Sig_r/A_r:', u%wave%rms_rb write (lines(3), '(a, f9.4, 4x, a, f8.3)') 'Kick |Ks| =', 2*u%wave%amp_sba, 'Sig_Ks/Ks:', u%wave%rms_ks write (lines(4), '(a, f9.4, 4x, a, f8.3)') 'Kick |Kr| =', 2*u%wave%amp_rba, 'Sig_Kr/Kr:', u%wave%rms_kr write (lines(5), '(3(a, f8.3, 4x))') 'Chi_a:', u%wave%chi_a, 'Sig_phi+:', u%wave%rms_sphi, ' Sig_phi-:', u%wave%rms_rphi lines(6) = ' ' lines(7) = 'After Det# kick phi_+ phi_- phi_a phi_b' do i = 1, min(u%wave%n_cross, 10) write (lines(i+7), '(i11, f10.4, 4f8.3, 2f10.3)') u%wave%ix_cross(i), & u%wave%kick(i), u%wave%phi_s(i), u%wave%phi_r(i), & (u%wave%phi_s(i)+u%wave%phi_r(i))/2, (u%wave%phi_s(i)-u%wave%phi_r(i))/2 enddo call qp_draw_text_legend(lines(1:u%wave%n_cross+7), -0.05_rp, 0.95_rp, '%GRAPH') end select end subroutine