D Demonstration – the SPEED Program

 D.1 Fortran source
 D.2 Input file

The following pages contain a listing of the Fortran source for a program called SPEED, plus a sample input file. It produces a plot similar to the one from XYPLOT (Appendix C). The SPEED program demonstrates three different compromises between plotting speed and quality of result. The source and a suitable data file (which is the same format as for XYPLOT) are distributed with the SNX software: in the directory NCAR_DIR on VAX/VMS and in the archive /star/starlink/lib/snx/examples/snx-examples.tar on UNIX.

On VAX/VMS, this program may be compiled, linked and run using the command sequence

  $ FORTRAN NCAR_DIR:SPEED
  $ LINK SPEED, NCAR_DIR:SNX_LINK/OPT, STAR_LINK/OPT
  $ RUN SPEED

On UNIX, this program may already be installed in directory /star/bin/examples/snx. If it has been deinstalled and removed to save space, you can copy the entire source directory to a scratch dircetory, and with the SYSTEM environment variable set appropriately, build and run it thus:

  % setenv SYSTEM alpha_OSF/1
  % ./mk speed
  %./speed

The program will prompt “Filename?" (respond NCAR_DIR:SPEED.DAT on VAX/VMS and /star/starlink/lib/snx/speed.dat on UNIX) and “Workstation?" (give the SGS workstation name). The prompt:

      Precision/font?  H=h/w, S=GKS, N=NCAR, E=exit

will then appear. The three font options are as follows:

D.1 Fortran source

        PROGRAM SPEED
  
  *+
  *
  *  Demonstration of different plotting style/speed
  *  tradeoffs in NCAR/SGS/GKS
  *
  *  P T Wallace   Starlink   10 June 1987
  *  P C T Rees    Starlink   19 May 1992
  *     Replaced FLUSH calls with PLOTIT calls.
  *
  *+
  
        IMPLICIT NONE
  
        INTEGER NPMAX
        PARAMETER (NPMAX=10000)
        INTEGER N,NP,IPREC,NCOUNT
        REAL RNULL1,TICK
        CHARACTER FNAME*80,GLAB*80,XLAB*80,YLAB*80,K*1
        REAL X(NPMAX),Y(NPMAX)
        LOGICAL PLOTED,NTBAD
  
  
  
  *  Open input file
        PRINT *,’Filename?’
        READ (*,’(Q,A)’) N,FNAME
        OPEN (UNIT=1,STATUS=’OLD’,FILE=FNAME(:N),READONLY)
  
  *  Read label text
        READ (1,’(A)’,END=9000) GLAB
        READ (1,’(A)’,END=9000) XLAB
        READ (1,’(A)’,END=9000) YLAB
  
  *  Read x,y data
        DO NP=1,NPMAX
           READ (1,*,END=100) X(NP),Y(NP)
        END DO
        NP = NPMAX+1
  
  *  Adjust number of points
   100  CONTINUE
        NP = NP-1
  
  *  Check enough data
        IF (NP.LT.2) GO TO 9000
  
  *  Prepare to plot the graph
        CALL snx_AGOP
        CALL AGGETF(’NULL/1.’,RNULL1)
        PLOTED = .FALSE.
  
  *  Select character precision and font
   200  CONTINUE
        PRINT *,’Precision/font?  H=h/w, S=GKS, N=NCAR, E=exit’
        READ (*,’(A)’) K
        NTBAD = .FALSE.
        IF (K.EQ.’H’.OR.K.EQ.’h’) THEN
  
  *     Hardware characters - fast but tacky
           CALL AGPWRT(0.0,0.0,’ ’,0,0,0,-100)
           IPREC = 0
           NCOUNT = 1
           TICK = 1.0
  
        ELSE IF (K.EQ.’S’.OR.K.EQ.’s’) THEN
  
  *     GKS software characters - reasonably fast and attractive
           CALL AGPWRT(0.0,0.0,’ ’,0,0,0,-100)
           IPREC = 2
           NCOUNT = 6
           TICK = RNULL1
  
        ELSE IF (K.EQ.’N’.OR.K.EQ.’n’) THEN
  
  *     PWRITX characters - fancy but slow
           CALL AGPWRT(0.0,0.0,’ ’,0,0,0,100)
           IPREC = 2
           NCOUNT = 6
           TICK = RNULL1
  
        ELSE IF (K.EQ.’E’.OR.K.EQ.’e’) THEN
  
  *     Exit requested - wrap up
           CALL sgs_CLOSE
           GO TO 9999
  
        ELSE
  
  *     Unrecognised command
           NTBAD = .TRUE.
           PRINT *,’?’
  
        END IF
  
  *  Repeat prompt if problems
        IF (NTBAD) GO TO 200
  
  *  Clear the zone if necessary
        IF (PLOTED) CALL sgs_CLRZ
  
  *  Setup for plotting:
  *
  *  SGS/GKS text precision
        CALL sgs_SPREC(IPREC)
  
  *  Density of tick marks and numeric labels
        CALL AGSETI(’LEFT/MAJOR/COUNT.’,NCOUNT)
        CALL AGSETI(’RIGHT/MAJOR/COUNT.’,NCOUNT)
        CALL AGSETI(’BOTTOM/MAJOR/COUNT.’,NCOUNT)
        CALL AGSETI(’TOP/MAJOR/COUNT.’,NCOUNT)
        CALL AGSETF(’LEFT/MINOR/SPACING.’,TICK)
        CALL AGSETF(’RIGHT/MINOR/SPACING.’,TICK)
        CALL AGSETF(’BOTTOM/MINOR/SPACING.’,TICK)
        CALL AGSETF(’TOP/MINOR/SPACING.’,TICK)
  
  *  Plot the graph
        CALL snx_EZRXY(X,Y,NP,XLAB,YLAB,GLAB)
        CALL PLOTIT(0,0,2)
        CALL sgs_FLUSH
  
        PLOTED = .TRUE.
  
  *  Next plot
        GO TO 200
  
  *  Exits
   9000 CONTINUE
        PRINT *,’Insufficient data!’
  
   9999 CONTINUE
  
        END

D.2 Input file

The beginning of the file which is supplied for use with the SPEED program is given below. It is the same format as for the XYPLOT program, but note that the three label records should not contain PWRITX function codes as these will not work when the “S" or “H" options are used.

  Simulated Stellar Spectrum
  Wavelength
  Flux
     5000.000       6.738085
     5004.000       8.849804
     5008.000       9.914771
     5012.000       9.484353
     5016.000       9.981673
     5020.000       11.45505
     5024.000       8.954852
     5028.000       11.32500
               :
               :
               :
               :