subroutine plot_raw (u) use cesrv_struct use cesrv_interface use quick_plot implicit none type (universe_struct) u type (raw_struct) raw1, raw2 real(rp) x1_marg / 60 /, y1_marg / 30 / character ans logical plot2 ! if (logic%last_read == phase_data$ .or. logic%last_read == ac_eta_data$) then raw1 = u%raw_phase_x raw2 = u%raw_phase_y plot2 = .true. else raw1 = u%raw_orbit plot2 = .false. endif ! call qp_set_margin (x1_marg, x1_marg, y1_marg, y1_marg, 'POINTS') ! margins call qp_set_page_border (0.0_rp, 0.0_rp, 0.0_rp, 50.0_rp, 'POINTS') call qp_clear_page call qp_set_axis ('X', 0.0_rp, 120.0_rp, 10, 0) call qp_set_axis('Y', raw1%y_axis%min, raw1%y_axis%max, & raw1%y_axis%major_div, raw1%y_axis%places) ! plot call plot1_raw (raw1, 2) if (plot2) call plot1_raw (raw2, 1) ! type out if needed call get_input_string (' Type raw numbers? ', ans) if (ans == 'Y' .or. ans == 'y') then call type1_raw (raw1, raw2, plot2) endif return !---------------------------------------------------------------- contains subroutine plot1_raw (raw, iplot) type (raw_struct) raw integer iplot, i, j real(rp) x, ymin, ymax, f ! f = raw%y_scale call qp_set_box (1, iplot, 1, 2) call qp_draw_graph ((/0.0_rp/), (/0.0_rp/), 'Index', raw%y_axis%label, raw%title) do i = 0, 120 x = i ymin = minval(raw%det(i)%amp) / f ymax = maxval(raw%det(i)%amp) / f call qp_draw_symbol (x, sum(raw%det(i)%amp(1:4)/4)/f, type = square_sym$) call qp_draw_line (x, x, ymin, ymax) do j = 1, 4 call qp_draw_symbol (x, raw%det(i)%amp(j)/f, type = plus_sym$) enddo enddo end subroutine !---------------------------------------------------------------- ! contains subroutine type1_raw (raw1, raw2, plot2) type (raw_struct) raw1, raw2 integer i, j character(100) line, line2 real(rp) f logical plot2 ! line2 = '' f = raw1%y_scale if (f /= 1) write (line2, '(a, i0)') 'Amplitudes scaled by: ', nint(f) if (plot2) then line = 'Index Ave_x Amp1_x Amp2_x Amp3_x Amp4_x | Ave_y Amp1_y Amp2_y Amp3_y Amp4_y Sys' else line = 'Index Average Amp1 Amp2 Amp3 Amp4 Sys' endif print * if (line2 /= '') print '(a)', trim(line2) print '(a)', trim(line) do i = lbound(raw1%det, 1), ubound(raw1%det, 1) if (plot2) then print '(i5, 10i8, i5)', i, & nint(sum(raw1%det(i)%amp)/(4*f)), (nint(raw1%det(i)%amp(j)/f), j = 1, 4), & nint(sum(raw2%det(i)%amp)/(4*f)), (nint(raw2%det(i)%amp(j)/f), j = 1, 4), & raw1%det(i)%system_id else print '(i5, 5i8, i5)', i, nint(sum(raw1%det(i)%amp)/(4*f)), & (nint(raw1%det(i)%amp(j)/f), j = 1, 4), raw1%det(i)%system_id endif enddo print '(a)', trim(line) if (line2 /= '') print '(a)', trim(line2) end subroutine end subroutine