SUBROUTINE GETPT(INDEX) C----------------------------------------------------------------------- C This is a modification of subroutine GTMOD in VISPLOT. C C GTMOD: C T.J.Pearson 1979 FEB 18 C Modified for VAX version 1979 JULY 5 C Modified to allow comments 1981 February 9 C Modified to copy input comments to an output file 1982 September 22 C C GETPT: Adapted for ELLIPSE.F to read data points consisting of C separations and position angles from binary star observations. C 28 Sept 1989 J.T.Armstrong C 25 Apr 1991 JTA Modified to read error ellipse parameters C C Read one card from unit 'INDATA'. C The first card contains the star name, the FK5 number, the period, C and the orbital sense ('R' or 'r' is retrograde; otherwise prograde). C Each subsequent card consists of: C ROBS(mas) Separation between stars, in arcsec C THETAOBS(deg) Position angle of line between stars, in deg C measured east from north C DRA(mas) Uncertainty in separation along axis of error ellipse C most closely corresponding to RA C DDEC(mas) As with DRA, but along axis corresponding to Dec C PHI_ERR(deg) Position angle (deg) of "RA" axis of error ellipse, E of N C TSTRING Date in YYMMDD format C UT(sec) UT sec C Copy comments following a '!' character to unit 'PR' C Ignore blank lines. C C Returns the number of records read as INDEX. C----------------------------------------------------------------------- IMPLICIT UNDEFINED (A-Z) INCLUDE 'PARAMETR.INC' INCLUDE 'ELLIPSE.INC' REAL*8 PERIOD, ROBS8, THETAOBS8, DRA8, DDEC8, PHIERR8, UT8 INTEGER*4 I, INDEX, L, J INTEGER*2 CARD(80), BLANK, EXCL CHARACTER*80 CSTR C DATA BLANK/' '/ DATA EXCL/'!'/ C INDEX = 1 C TRIM OFF TRAILING BLANKS: 5 READ(INDATA, '(80A1)', END=50) CARD WRITE(PR,'(80A1)') CARD IF(CARD(1).EQ.EXCL) GO TO 5 L = 80 DO WHILE (CARD(L).EQ.BLANK) L = L-1 IF (L.EQ.0) GO TO 5 END DO I = 1 C READ STARNAME, FK5, PERIOD, SENSE OF ORBIT IF (INDEX.EQ.1) THEN CALL SKIPBL(CARD,L,I) CALL CTOSTR(CARD,L,I,STARNAME) CALL SKIPBL(CARD,L,I) CALL CTOI2 (CARD,L,I,FK5) CALL SKIPBL(CARD,L,I) CALL CTOR2 (CARD,L,I,PERIOD) CALL SKIPBL(CARD,L,I) CALL CTOSTR(CARD,L,I,ORBSENSE) IF(ORBSENSE(1:1).EQ.'R'.OR.ORBSENSE(1:1).EQ.'r') THEN SENSE = -1 ! RETROGRADE ORBIT ELSE SENSE = 1 ! PROGRADE ORBIT END IF ELSE C READ FOUR PARAMETERS CALL SKIPBL(CARD,L,I) CALL CTOR2(CARD,L,I,ROBS8) ROBS(INDEX-1) = ROBS8 CALL SKIPBL(CARD,L,I) CALL CTOR2(CARD,L,I,THETAOBS8) IF (THETAOBS8.LT.0.) THETAOBS8 = THETAOBS8 + 360. IF (THETAOBS8.GT.360. ) THETAOBS8 = THETAOBS8 - 360. THETAOBS(INDEX-1) = THETAOBS8 CALL SKIPBL(CARD,L,I) CALL CTOR2(CARD,L,I,DRA8) DRA(INDEX-1) = DRA8 CALL SKIPBL(CARD,L,I) CALL CTOR2(CARD,L,I,DDEC8) DDEC(INDEX-1) = DDEC8 CALL SKIPBL(CARD,L,I) CALL CTOR2(CARD,L,I,PHIERR8) PHI_ERR(INDEX-1) = PHIERR8 C READ DATE STRING CALL SKIPBL(CARD,L,I) CALL CTOSTR(CARD,L,I,CSTR) TSTRING(INDEX-1) = CSTR(1:6) CALL SKIPBL(CARD,L,I) C READ THE U.T AND/OR ANY COMMENTS AT THE END OF THE LINE UT(INDEX-1) = 0. 30 CALL SKIPBL(CARD,L,I) IF (I.GT.L) GO TO 40 IF (CARD(I).EQ.BLANK) GO TO 40 IF (CARD(I).EQ.EXCL) THEN IF (PR.GT.0) WRITE (PR,'1X,(80A1)') (CARD(J),J=I,L) GO TO 40 END IF CALL CTOR2(CARD,L,I,UT8) UT(INDEX-1) = UT8 D WRITE(OUTC,'(A,F8.1)') ' GETPT: UT(sec) = ',UT(INDEX-1) GO TO 30 END IF 40 CONTINUE INDEX = INDEX + 1 GO TO 5 C INQUIRE(UNIT=INDATA,NAME=DATAFILE) C CALL ERROR('Invalid model format: file '//DATAFILE) 50 RETURN END C