subroutine scale_data (maxim, plot1, save, plot2, plot3) use cesrv_struct use cesrv_interface use quick_plot implicit none type (p1_plot_struct), target :: plot1 type (qp_axis_struct), pointer :: y1 type (p1_plot_struct), optional :: plot2, plot3 type (d2_data_struct), pointer :: data integer n_use real(rp) maxim, old_max, old_min, y_this_min, y_this_max, y_limit logical save, use_plot2, use_plot3 ! init y1 => plot1%y_axis old_min = y1%min old_max = y1%max ! do not rescale without any data. n_use = plot1%n_use use_plot2 = .false. if (present(plot2)) then if (associated(plot2%d1)) then use_plot2 = .true. n_use = n_use + plot2%n_use endif endif use_plot3 = .false. if (present(plot3)) then if (associated(plot3%d1)) then use_plot3 = .true. n_use = n_use + plot3%n_use endif endif if (n_use == 0) then print *, 'SCALE_DATA: CANNOT SCALE WITHOUT ANY DATA.' return endif ! if maxim is negative this does not make any sense if (maxim < 0) then print *, 'ERROR: SCALE NUMBER MUST BE POSITIVE!' return endif ! if plot is limited then temporarily turn this off since we cannot do ! the calculation with it on. if (maxim == 0) then n_use = plot1%n_use y_limit = plot1%y_limit ! save current plot1%y_limit = -1 ! turn off limiting call plotting_data_calc (plot1) y1%max = maxval(abs(plot1%y(1:n_use))) y1%max = max(y1%max, 10e-5) y1%min = minval(abs(plot1%y(1:n_use))) plot1%y_limit = y_limit ! if plot2 is present then scale to the combined plot1 and plot2 data. if (use_plot2) then n_use = plot2%n_use y_limit = plot2%y_limit plot2%y_limit = -1 ! turn off limiting call plotting_data_calc (plot2) plot2%y_limit = y_limit y_this_max = maxval(abs(plot2%y(1:n_use))) y_this_min = minval(abs(plot2%y(1:n_use))) if (plot1%p2%gang_scale) then y1%max = max(y1%max, y_this_max) y1%min = min(y1%min, y_this_min) else call qp_calc_axis_scale (y_this_min, y_this_max, plot2%y_axis) call qp_calc_axis_places (plot2%y_axis) plot2%y_axis%places = max(plot2%y_axis%places, 0) endif endif ! if plot3 is present then scale to the combined plot1 and plot3 data. if (use_plot3) then n_use = plot3%n_use y_limit = plot3%y_limit plot3%y_limit = -1 ! turn off limiting call plotting_data_calc (plot3) plot3%y_limit = y_limit y_this_max = maxval(abs(plot3%y(1:n_use))) y_this_min = minval(abs(plot3%y(1:n_use))) if (plot1%p2%gang_scale) then y1%max = max(y1%max, y_this_max) y1%min = min(y1%min, y_this_min) else call qp_calc_axis_scale (plot3%y_axis%min, y_this_max, plot3%y_axis) call qp_calc_axis_places (plot3%y_axis) plot3%y_axis%places = max(plot3%y_axis%places, 0) endif endif call qp_calc_axis_scale (y1%min, y1%max, y1) else y1%max = maxim if (y1%bounds == 'ZERO_SYMMETRIC') then y1%min = -maxim else y1%min = 0 endif endif if (y1%min == y1%max) then print *, 'SCALE_DATA: AXIS_MIN = AXIS_MAX!' y1%min = old_min y1%max = old_max return endif call qp_calc_axis_places (y1) y1%places = max(y1%places, 0) if (plot1%p2%gang_scale .or. maxim /= 0) then if (use_plot2) call plot_y_axis_min_max_transfer (plot1%y_axis, plot2%y_axis) if (use_plot3) call plot_y_axis_min_max_transfer (plot1%y_axis, plot3%y_axis) endif if (save .and. associated(plot1%p2%d2)) then data => plot1%p2%d2 data%p2 = plot1%p2 data%p2%plot1%p2 => data%p2 data%p2%plot2%p2 => data%p2 data%p2%plot3%p2 => data%p2 endif end subroutine