!___________________________________________________________________________________________________ ! Aleksandar Donev ! PHY201 Solutions to Worksheet ! December, 2000, MSU !___________________________________________________________________________________________________ ! PROGRAM Erf_Plot USE Precision USE Erf_Series, ONLY: error USE Erf_Timing USE SimpleGraphics IMPLICIT NONE ! We are in position to choose whether we want REAL or COMPLEX x: ! Comment one of these out: INTEGER :: i,k,status,n_points ! I/O status REAL(KIND=sp), DIMENSION(:), ALLOCATABLE :: x, elapsed_time ! The timing result--single precision REAL(KIND=wp), PARAMETER :: x_min=0.0,x_max=4.5 ! Range of plot CHARACTER(50), DIMENSION(2) :: title UserInput: DO WRITE(UNIT=*,FMT="(A)",ADVANCE="NO") "Enter: n_points and error: " READ(UNIT=*,FMT=*,IOSTAT=status) n_points,error IF(status==0) EXIT UserInput ! Do not exit until the user enters acceptable numbers END DO UserInput ALLOCATE(x(n_points),elapsed_time(n_points)) DO i=1,n_points x(i)=REAL(i-1,wp)/REAL(n_points-1,wp)*(x_max-x_min)+x_min elapsed_time(i)=TimeErf(REAL(x(i),wp)) ! Remember that TimeErf accepts precision wp WRITE(UNIT=*,FMT="(A,G15.3,A,G15.2,A)") "x=", x(i)," time=",elapsed_time(i), " us" END DO title(1)="Timing benchmark for the function ErfSeries(x)" WRITE(title(2),*) "epsilon=",error,", A. Donev 1/10/00" CALL InitGraphics(file="Erf_Timing.PNG",file_type="PNG", & plot_title=title, & x_label="x",y_label="time (us)") CALL Plot2D(x=x,y=elapsed_time,plot_spec="STR",new_plot=.TRUE.) ! We must convert everything to single precision CALL Plot2D(x=x,y=elapsed_time,plot_spec="L:B",new_plot=.FALSE.) CALL EndGraphics() END PROGRAM Erf_Plot !