home *** CD-ROM | disk | FTP | other *** search
- C*********************************************************************
- C
- C Written by Victor De Pinto
- C Revised Jan. 25, 1982
- C
- SUBROUTINE PLOT ( DAT )
- C
- C This plotting routine makes magnitude and phase plots on any printer.
- C Unity is full scale for both magnitude and phase.
- C
- LOGICAL QFLG, PHAFLG, LOGFLG
- REAL MAG
- INTEGER FIRSTP, LASTP, NTH
- DIMENSION DAT(2,1024)
- 1 WRITE (1,5)
- 5 FORMAT (' --PLOTTER MENU-- Select function:'/
- X ' 1 PLOT REAL PART OF FILE '/
- X ' 2 PLOT MAGNITUDE (LINEAR) '/
- X ' 3 PLOT MAGNITUDE (LOGARITHMIC) '/
- X ' 4 PLOT PHASE (LINEAR) AND MAGNITUDE (LINEAR) '/
- X ' 5 PLOT PHASE (LINEAR) AND MAGNITUDE (LOGARITHMIC) '/
- X ' 6 BACK TO MAIN MENU >> ')
- READ (1,10) MENU
- 10 FORMAT (I2)
- C Setup flags and get dB scale if Logarithmic plot.
- LOGFLG = .FALSE.
- PHAFLG = .FALSE.
- GO TO (35,35,15,20,12,11), MENU
- GO TO 1
- 11 RETURN
- 12 PHAFLG = .TRUE.
- 15 LOGFLG = .TRUE.
- WRITE (1,16)
- 16 FORMAT ('+0 dB is full scale.'/
- X ' Enter bottom scale decibels. >> ')
- READ (1,506) BOTDB
- BOTDB = ABS( BOTDB )
- GO TO 35
- 20 PHAFLG = .TRUE.
- C
- C Tell the computer how many columns the printer has and take off
- C five to allow for printing the data point number.
- 35 WRITE (1,36)
- 36 FORMAT ('+How many columns on a printer line? (80-132) ')
- READ (1,506) WIDTH
- WIDTH = WIDTH - 5.0
- C
- C Get range of points to plot.
- WRITE (1,37)
- 37 FORMAT ('+What is the first point to plot? (0-1023) ')
- READ (1,40) FIRSTP
- 40 FORMAT (I4)
- WRITE (1,45)
- 45 FORMAT ('+What is the last point to plot? (0-1023) ')
- READ (1,40) LASTP
- WRITE (1,50)
- 50 FORMAT ('+Every Nth point is plotted.
- X ENTER N (normally 1): ')
- READ (1,40) NTH
- C
- GO TO (500,200,200,200,200), MENU
- C
- C Magnitude and phase plot.
- C Phase is plotted only if PHAFLG is true.
- C
- C Determine scale factor.
- 200 WRITE (1,220)
- 220 FORMAT (' Enter the full scale magnitude. (This will be
- X determined'/
- X ' automatically if a negative number is entered.) ')
- READ (1,506) FSMAG
- CALL READ (DAT)
- IF ( FSMAG ) 250,250,265
- C Entry was minus, so determine full scale magnitude.
- 250 FSMAG = 0.0
- DO 260 N=1,1024
- T = DAT(1,N)**2 + DAT(2,N)**2
- IF (T .GT. FSMAG) FSMAG = T
- 260 CONTINUE
- FSMAG = SQRT( FSMAG )
- C
- 265 SCALE = 1.0 / FSMAG
- C
- C Do the plot.
- C
- QFLG = .FALSE.
- DO 295 N = FIRSTP,LASTP,NTH
- IF (QFLG) GO TO 295
- C Compute magnitude.
- MAG = SCALE * SQRT( DAT(1,N+1)**2 + DAT(2,N+1)**2 )
- IF ( .NOT. LOGFLG ) GO TO 275
- C Convert to decibels only if log plot.
- C First see if MAG is too small. If so, avoid Log function.
- IF ( MAG .GE. 1E-30 ) GO TO 270
- MAG = -600.0
- GO TO 275
- 270 MAG = ( 20.0 * ALOG10(MAG) + BOTDB ) / BOTDB
- C
- 275 IF ( .NOT. PHAFLG ) GO TO 290
- C Compute normalized phase if phase was chosen.
- TMP1 = DAT(1,N+1)
- TMP2 = DAT(2,N+1)
- IF (TMP1 .NE. 0.0 .OR. TMP2 .NE. 0.0) GO TO 280
- PHASE = 0.0
- GO TO 290
- 280 PHASE = ATAN2 ( TMP2, TMP1 )
- PHASE = 0.5 + PHASE / 6.29
- C
- 290 CALL TTDRAW (N, MAG, PHASE, PHAFLG, WIDTH)
- CALL QCHEK ( QFLG )
- 295 CONTINUE
- WRITE (2,300)
- 300 FORMAT (' '//)
- GO TO 1
- C
- C PLOT THE REAL PARTS OF A FILE.
- C
- 500 WRITE (1,501)
- 501 FORMAT (' This routine adds an offset to the real parts'/
- X ' of a file, then multiplies by a scale factor.'/
- X ' Full scale is 1.0'/
- X ' ENTER OFFSET <CR> SCALE:'/)
- READ (1,506) FSET, SCALE
- 506 FORMAT (F10.0)
- CALL READ (DAT)
- C Do the plot.
- QFLG = .FALSE.
- DO 520 N=FIRSTP,LASTP,NTH
- IF ( QFLG ) GO TO 520
- Y = SCALE * ( DAT(1,N+1) + FSET )
- CALL TTDRAW (N, Y, Y, .FALSE., WIDTH)
- CALL QCHEK ( QFLG )
- 520 CONTINUE
- WRITE (2,300)
- GO TO 1
- END
- C
- C ******************************************************
- C
- SUBROUTINE TTDRAW (NUMBER, MAG, PHASE, PHAFLG, WIDTH)
- C Plots one data point on the system list device.
- C The point number is pointed first, then the plot character(s).
- C WIDTH is the full scale value.
- REAL MAG
- LOGICAL PHAFLG
- INTEGER LINE (132)
- DATA LINE, IPHASE / 132*' ', 1/
- IF (MAG .GE. 0.0 .AND. MAG .LE. 1.0) GO TO 50
- C If MAG is offscale, print 'O' in the fifth position.
- IMAG = 5
- LINE (IMAG) = 'O'
- GO TO 60
- C Compute the column to plot MAG.
- 50 IMAG = WIDTH * MAG + 1.0
- LINE (IMAG) = '*'
- C
- 60 LENGTH = IMAG
- IF ( .NOT. PHAFLG) GO TO 80
- C Plot phase only if PHAFLG is true.
- 70 IPHASE = 0.5 * WIDTH * PHASE + 1.0
- LINE (IPHASE) = 'P'
- IF (IPHASE .GT. IMAG) LENGTH = IPHASE
- C Print the line.
- 80 WRITE (2,85) NUMBER, ( LINE(K), K=1,LENGTH )
- 85 FORMAT (' ', I4, 132A1)
- C Clear the array.
- LINE (IMAG) = ' '
- LINE (IPHASE) = ' '
- RETURN
- END
-