PROGRAM AGRUN
C
      DIMENSION XLOS(3),TIMEIN(1)
C
      OPEN(1,FILE='CAF03340',FORM='FORMATTED',STATUS='OLD')
C
      IUNIT=1
      ID=1
      IYEAR=1990
      IDAY=344
      NTIMES=1
      IRROR=0
C
      DO 10 I=1,50
      TIMEIN(1)=I+1000.
      CALL AGMOD (IUNIT,ID,IYEAR,IDAY,NTIMES,TIMEIN,IRROR,
     +                   XLOS)
      PRINT101,I,TIMEIN(1),IRROR,XLOS,ID
  101 FORMAT(5X,I5,F12.3,I4,3F12.5,I5)
   10 CONTINUE
C
      STOP
      END
C*********************************************************************
C
C     CSCI:  AGMOD     CSC: AGMOD    (LLCSC 51)
C
C     AGMOD    -  Subroutine to call the LLCSCs within AGMOD
C
C     Files:  AFGL VAX780:
C             USR$DSKH:[LCY.SPACAPP.AGMOD] AGMOD.FOR  -  source
C                                          AGMOD.OLB  -  object library
C
C             AFGL CYBER 180 - NOS/VE SIDE:
C               :NVAGL.SPACAPP.LOS.AGMOD              -  source
C                                 .LOSLBR             -  object
C
C     Author: L. K. Harada  -  Space Applications Corp.
C                              1310 Orleans Drive
C                              Sunnyvale, CA  94089
C                              (408)-744-0990
C
C     Current Revision:    00
C
C=====================================================================
C
C     Revision History:
C     -------- -------
C
C     Rev   Date     By    Reason
C     ---   ----     --    ------
C
C      00  14JAN88   LKH   Original
C
C=====================================================================
C
C     Purpose and Usage:
C     -----------------
C        Subroutine AGMOD is the driver for the LOS function. AGMOD
C     calls LLCSCs RAAF, CHECK, EPOLY and CLOS to perform the line of
C     sight calculations assigned to this function. AGMOD sets the
C     ERROR flag to a positive value if a mission event occurred in
C     the TIMEIN time span.
C
C     Limitations:
C     -----------
C        A positive return value for the ERROR flag is the inclusive
C     OR of the mission event codes encountered during the TIMEIN time
C     span. Should the TIMEIN time span cross several segment
C     boundaries, a positive value for ERROR will not indicate which
C     mission events are to be associated with which TIMEIN times.
C
C        This routine is designed to minimized I/O time by calling
C     for a read of the ATAF file (by subroutine RAAF) only once per
C     processing run. If it is desired to calculate lines of sight for
C     a different orbit (i.e., a different ATAF file), it will be
C     necessary to stop and restart the user program which calls
C     AGMOD.
C
C=====================================================================
C
C     Arguments:
C     ---------
C     Name           Type   Use  Description
C     ----           ----   ---  -----------
C     ATAFLU         Intg        ATAF logical unit number
C     ID             Intg        User's instrument identification
C     YEAR           Intg        Requested year
C     DAY            Intg        Requested day
C     NTIMES         Intg   U    Number of times requested by user
C     TIMEIN(NTIMES) Real         Time(s) of interest
C     ERROR          Intg   S    Error return value
C                                 ( + => sum of mission events numbers)
C                                 ( 0 => no errors)
C                                 (-1 => file read error)
C                                 (-2 => Incorrect vehicle ID)
C                                 (-3 => End of file reached
C                                        prematurely)
C                                 (-4 => NUMSEG exceeds MAXSEG)
C                                 (-5 => IORDER exceeds MAXORD)
C                                 (-6 => error in ID)
C                                 (-7 => error in YEAR or DAY)
C                                 (-8 => error in TIMEIN)
C     LOS(3,NTIMES)   Real        Output array storing the instrument's
C                                line(s) of sight in ECI coordinates
C                                 ( LOS(1,I) => x-component at time I )
C                                 ( LOS(2,I) => y-component at time I )
C                                 ( LOS(3,I) => z-component at time I )
C
C=====================================================================
C
C     Common Variables:
C     ------ ---------
C     Name                  Type   Use  Description
C     ----                  ----   ---  -----------
C     LOSCOM                  -     -   Common storage for the ATAF file
C                                       contents  which define the fit
C                                       parameters for the attitude
C                                       solution over each segment
C     MAXORD                PAR         Maximum allowable order of fit
C                                       (MAXORD=10)
C     MAXSEG                PAR         Maximum allowable number of
C                                       segments (MAXSEG=50)
C     UTSTAR                Intg    U   Universal Time at start of data
C     FCDAY                 Intg        Fit coefficient day
C     FCYEAR                Intg        Fit coefficient year
C     NUMSEG                Intg        Number of segments
C     SEGTIM(2,MAXSEG)      Real    U   Segment start and end times
C     MULT(MAXSEG)          Real        Multiplicative constant for
C                                       linear transformation of time
C                                       range
C     ADD(MAXSEG)           Real        Additive constant for linear
C                                       transformation of time range
C     CONFLG(MAXSEG)        Intg    U   Mission event code numbers
C     IORDER(3,MAXSEG)      Intg        Order of the fit for each
C                                       parameter and segment
C     FITRA(MAXORD,MAXSEG)  Real        Coefficients for the right
C                                       ascension for each segment
C     FITDC(MAXORD,MAXSEG)  Real        Coefficients for the declination
C                                       for each segment
C     FITSR(MAXORD,MAXSEG)  Real        Coefficients for the spin rate
C                                       for each segment
C     PHANG(MAXSEG)         Real        Phase angle at start of each
C                                       segment
C
C=====================================================================
C
C
C     Local variables
C     ----- ---------
C     Name       Type     Description
C     ----       ----     -----------
C     FIRST      Log      Logical variable
C     I          Intg     Index variable
C     K          Intg     Index variable
C     N          Intg     Index variable
C     SEGNUM     Intg     Segment number
C     FRSTIM     Real     Variable for segment start time
C     LASTIM     Real     Variable for segment end time
C
C=====================================================================
C
C     Called Routines:
C     ------ --------
C     Name       Location         Purpose
C     ----       --------         -------
C
C     RAAF       AGMOD library    Reads the ATAF and stores the values
C                                 into LOSCOM
C
C     CHECK      AGMOD library    Checks the user`s input parameters
C
C     EPOLY      AGMOD library    Subroutine to evaluate the Chebyshev
C                                 polynomials using the appropriate
C                                 coefficients of the right ascension,
C                                 declination and spin rate.
C
C     CLOS       AGMOD library    Calculates the instrument line(s)
C                                 of sight
C
C=====================================================================
C
C     Inputs/Outputs:
C     --------------
C     None
C
C*********************************************************************
C
      SUBROUTINE AGMOD (ATAFLU, ID, YEAR, DAY, NTIMES, TIMEIN, ERROR,
     +                   LOS)
C
C.....Declaration Section
C
C.....Arguments:
C
      INTEGER         ATAFLU, ID, YEAR, DAY, NTIMES, ERROR
C
      REAL            TIMEIN(NTIMES), LOS(3,NTIMES)
C
C.....Declarations for line of sight common LOSCOM
C
      INTEGER       MAXORD, MAXSEG
      PARAMETER (MAXORD=10)
      PARAMETER (MAXSEG=50)
      INTEGER         FCDAY, FCYEAR, UTSTAR, NUMSEG, CONFLG(MAXSEG),
     +                IORDER(3,MAXSEG)
C
      REAL            SEGTIM(2,MAXSEG), MULT(MAXSEG), ADD(MAXSEG),
     +                FITDC(MAXORD,MAXSEG), FITRA(MAXORD,MAXSEG),
     +                FITSR(MAXORD,MAXSEG), PHANG(MAXSEG)
C
      COMMON  /LOSCOM/ FCDAY, FCYEAR, UTSTAR, NUMSEG, SEGTIM, MULT,
     +                 ADD, CONFLG, IORDER, FITRA, FITDC, FITSR, PHANG
C
C.....Local variables
C
      LOGICAL         FIRST
      INTEGER         I, J, K, N, P, SEGNUM
      SAVE            FIRST
      REAL            FRSTIM, LASTIM
      DATA            FIRST /.TRUE./
C
C.....Executable code section:
C
C.....Initialize local variables
C
      SEGNUM = 0
      FRSTIM = 0.
      LASTIM = 0.
C
C     Subroutine RAAF is called to read in the contents of the Agency
C     Tape Attitude File (ATAF) if the logical variable FIRST is
C     TRUE. A successful read will cause FIRST to be set to FALSE.
C     Subsequent calls to AGMOD will not trigger any further reads
C     of the ATAF
C
      IF (FIRST) THEN
        CALL RAAF (ATAFLU, ERROR)
        IF (ERROR.NE.0) RETURN
        FIRST = .FALSE.
      END IF
C
C     Subroutine CHECK is called to verify the user's input parameters;
C     the year at start of data, the day at start of data, the
C     time(s) and the instrument ID.
C
      CALL CHECK (ID, YEAR, DAY, TIMEIN, NTIMES, ERROR)
      IF (ERROR.NE.0) RETURN
C
C     Subroutine EPOLY is called to evaluate the Chebyshev polynomial
C     fits of right ascension, declination and spin rate the requested
C     time(s) using the fit coefficients in LOSCOM.
C
      CALL EPOLY (TIMEIN, NTIMES, LOS)
C
C     Subroutine CLOS is called to calculate the instrument's line(s)
C     sight
C
      CALL CLOS (ID, TIMEIN, NTIMES, LOS)
C
C     Check for an occurrence of a mission event in the TIMEIN time
C     span. ERROR will be set to a positive value if a mission event
C     occurred in the TIMEIN time span
C
      DO 50 I = 1, NTIMES
         IF (TIMEIN(I).LT. FRSTIM.OR.TIMEIN(I).GT.LASTIM) THEN
   40       SEGNUM = SEGNUM + 1
            FRSTIM = SEGTIM(1,SEGNUM) + REAL(UTSTAR)/1000.0
            LASTIM = SEGTIM(2,SEGNUM) + REAL(UTSTAR)/1000.0
            IF (TIMEIN(I).GE.LASTIM.AND.SEGNUM.LT.NUMSEG) GO TO 40
            IF (CONFLG(SEGNUM).GT.0) THEN
               IF (MOD(ERROR,2*CONFLG(SEGNUM))/CONFLG(SEGNUM).EQ.1) THEN
                  CONTINUE
               ELSE
                  ERROR = ERROR + CONFLG(SEGNUM)
               END IF
            END IF
         END IF
   50 CONTINUE
      RETURN
      END
C*********************************************************************
C
C     CSCI:  AGMOD     CSC: CHECK   (LLCSC 512)
C
C     CHECK    -  Subroutine to check the user's input parameters
C
C     Files:  AFGL VAX780:
C             USR$DSKH:[LCY.SPACAPP.AGMOD] CHECK.FOR  -  source
C                                          AGMOD.OLB  -  object library
C
C             AFGL CYBER 180 - NOS/VE Side:
C               :NVAFGL.SPACAPP.LOS.CHECK             -  source
C                                  .LOSLBR            -  object library
C
C     Author: L. K. Harada  -  Space Applications Corp.
C                              1310 Orleans Drive
C                              Sunnyvale, CA  94089
C                              (408)-744-0990
C
C     Current Revision:    00
C
C=====================================================================
C
C     Revision History:
C     -------- -------
C
C     Rev   Date     By    Reason
C     ---   ----     --    ------
C
C      00  11JAN88   LKH   Original
C
C=====================================================================
C
C     Purpose and Usage:
C     -----------------
C
C        Subroutine CHECK is called by the LLCSC AGMOD compare the
C     requested times, year, day and instrument ID with the valid
C     segment times, year and day in LOSCOM, and the ID parameters in
C     IDCOM respectively. An error flag is set if the instrument ID is
C     invalid or the requested times, year or day are out of range.
C
C     Limitations:
C     -----------
C     None
C
C=====================================================================
C
C     Arguments:
C     ---------
C     Name           Type  Use  Description
C     ----           ----  ---  -----------
C     YEAR           Intg   U   Requested year
C     DAY            Intg   U   Requested day
C     TIMEIN(NTIMES) Real   U   Time(s) of interest
C     NTIMES         Intg   U   Number of times requested by user
C     ID             Intg   U   User's instrument identification
C     ERROR          Intg   S   Error return value
C                                 ( 0 => no errors)
C                                 (-6 => error in ID)
C                                 (-7 => error in YEAR or DAY)
C                                 (-8 => error in TIMEIN)
C
C=====================================================================
C
C     Common Variables:
C     ------ ---------
C     Name                 Type   Use  Description
C     ----                 ----   ---  -----------
C     LOSCOM                 -     -   Common storage for the ATAF file
C                                      contents  which define the fit
C                                      parameters for the attitude
C                                      solution over each segment
C     MAXORD               PAR         Maximum allowable order of fit
C                                      (MAXORD=10)
C     MAXSEG               PAR         Maximum allowable number of
C                                      segments (MAXSEG=50)
C     UTSTAR               Intg    U   Universal Time at start of data
C     FCDAY                Intg    U   Fit coefficient day
C     FCYEAR               Intg    U   Fit coefficient year
C     NUMSEG               Intg    U   Number of segments
C     SEGTIM(2,MAXSEG)     Real    U   Segment start and end times
C     MULT(MAXSEG)         Real        Multiplicative constant for
C                                      linear transformation of time
C                                      range
C     ADD(MAXSEG)          Real        Additive constant for linear
C                                      transformation of time range
C     CONFLG(MAXSEG)       Intg        Mission event code numbers
C     IORDER(3,MAXSEG)     Intg        Order of the fit for each
C                                      parameter and segment
C     FITRA(MAXORD,MAXSEG) Real        Coefficients for the right
C                                      ascension for each segment
C     FITDC(MAXORD,MAXSEG) Real        Coefficients for the declination
C                                      for each segment
C     FITSR(MAXORD,MAXSEG) Real        Coefficients for the spin rate
C                                      for each segment
C     PHANG(MAXSEG)        Real        Phase angle at start of each
C                                      segment
C
C     Name                  Type   Use  Description
C     ----                  ----   ---  -----------
C     IDCOM                  -     -   Common containing instruments'
C                                      azimuth and elevation angles
C     NUMID                 PAR        Number of instrument IDs defined
C                                      (NUMID=40)
C     AZMUTH(NUMID)         Real       Instrument`s azimuth angle
C     ELVATN(NUMID)         Real       Instrument's elevation angle
C
C=====================================================================
C
C
C     Local variables
C     ----- ---------
C     Name       Type     Description
C     ----       ----     -----------
C     I          Intg     Index variable
C     EPS        Real     Added to TIMEIN to prevent machine round
C                         off errors
C
C=====================================================================
C
C     Called Routines:
C     ------ --------
C     None
C
C=====================================================================
C
C     Inputs/Outputs:
C     --------------
C     None
C
C*********************************************************************
C
      SUBROUTINE CHECK (ID, YEAR, DAY, TIMEIN, NTIMES, ERROR)
C
C.....Declaration Section
C
C.....Arguments:
C
      INTEGER         ID, YEAR, DAY, NTIMES, ERROR
C
      REAL            TIMEIN(NTIMES)
C
C.....Declarations for line of sight common LOSCOM
C
      INTEGER         MAXORD, MAXSEG
C
      PARAMETER (MAXORD=10)
      PARAMETER (MAXSEG=50)
C
      INTEGER         FCDAY, FCYEAR, UTSTAR, NUMSEG, CONFLG(MAXSEG),
     +                IORDER(3,MAXSEG)
C
      REAL            SEGTIM(2,MAXSEG), MULT(MAXSEG), ADD(MAXSEG),
     +                FITDC(MAXORD,MAXSEG), FITRA(MAXORD,MAXSEG),
     +                FITSR(MAXORD,MAXSEG), PHANG(MAXSEG)
C
      COMMON  /LOSCOM/ FCDAY, FCYEAR, UTSTAR, NUMSEG, SEGTIM, MULT,
     +                 ADD, CONFLG, IORDER, FITRA, FITDC, FITSR, PHANG
C
C.....Declarations for instrument common IDCOM
C
      INTEGER         NUMID
      PARAMETER       (NUMID=40)
C
      REAL            AZMUTH(NUMID), ELVATN(NUMID)
C
      COMMON  /IDCOM/  AZMUTH, ELVATN
C
C.....Local variables
C
      INTEGER         I
C
      REAL            EPS
C
      DATA            EPS /1.0E-05/
C
C.....Executable code section:
C
C     Check the instrument's ID against the instrument list in
C     IDCOM
C
      ERROR = -6
      DO 10 I = 1, NUMID
         IF (ID.EQ.I) ERROR = 0
   10 CONTINUE
      IF (ERROR.NE.0) RETURN
C
C     Check the input year and day against the fit coefficient year and
C     day, FCYEAR and FCDAY
C
      IF (YEAR.NE.FCYEAR.OR.DAY.NE.FCDAY) THEN
         ERROR = -7
         RETURN
      END IF
C
C     Verify that the time(s) of interest is(are) within the valid time
C     span
C
      DO 20 I = 1,NTIMES
         IF (TIMEIN(I)+EPS.LT.SEGTIM(1,1)+REAL(UTSTAR)/1000.0.OR.
     +    TIMEIN(I)-EPS.GT.SEGTIM(2,NUMSEG)+REAL(UTSTAR)/1000.0) THEN
              ERROR = -8
         ENDIF
   20 CONTINUE
      RETURN
      END
C*********************************************************************
C
C     CSCI:  AGMOD     CSC: CLOS    (LLCSC 514)
C
C     CLOS     -  Subroutine to calculate the instrument's line(s) of
C                 sight
C
C     Files:  AFGL VAX780:
C             USR$DSKH:[LCY.SPACAPP.AGMOD] CLOS.FOR   -  source
C                                          AGMOD.OLB  -  object library
C
C             AFGL CYBER 180 - NOS/VE Side:
C               :NVAFGL.SPACAPP.LOS.CLOS              -  source
C                                  .LOSLBR            -  object library
C
C     Author: L. K. Harada  -  Space Applications Corp.
C                              1310 Orleans Drive
C                              Sunnyvale, CA  94089
C                              (408)-744-0990
C
C     Current Revision:    00
C
C=====================================================================
C
C     Revision History:
C     -------- -------
C
C     Rev   Date     By    Reason
C     ---   ----     --    ------
C
C      00  11JAN88   LKH   Original
C
C=====================================================================
C
C     Purpose and Usage:
C     -----------------
C
C        Subroutine CLOS is called by LLCSC AGMOD to calculate the
C     line(s) of sight of the user's instrument. The spacecraft's
C     x-axis at a calculated phase angle plus the instrument's azimuth
C     angle is represented by VECTX. The spacecraft's y-axis, YSC is
C     determined by the cross product of the spin axis and the space-
C     craft's x-axis, VECTX. Therefore, the general direction cosine
C     matrix, TMTRIX, is a rotation by the instrument's elevation angle,
C     ELVATN, about the spacecraft's y-axis, YSC. The product of TMTRIX
C     and VECTX yields the instrument's line of sight in direction
C     cosines in Earth Centered Inertial (ECI) coordinates.
C
C     Limitations:
C     -----------
C     None
C
C=====================================================================
C
C     Arguments:
C     ---------
C     Name           Type  Use  Description
C     ----           ----  ---  -----------
C     ID             Intg   U   Instrument's ID
C     NTIMES         Intg   U   Number of times requested by user
C     TIMEIN(NTIMES) Real   U   Time(s) of interest
C     LOS(3,NTIMES)  Real   B   Argument array,from subroutine EPOLY,
C                               storing the instrument's right
C                               ascension, declination and spin
C                               rate
C                                 ( LOS(1,I) => right ascension at
C                                               time I)
C                                 ( LOS(2,I) => declination at time I)
C                                 ( LOS(3,I) => spin rate at time I)
C                               On completion of subroutine CLOS, the
C                               array, LOS, stores the instrument's
C                               line(s) of sight in ECI coordinates
C                                 ( LOS(1,I) => x-component at time I)
C                                 ( LOS(2,I) => y-component at time I)
C                                 ( LOS(3,I) => z-component at time I)
C
C=====================================================================
C
C     Common Variables:
C     ------ ---------
C     Name                 Type   Use  Description
C     ----                 ----   ---  -----------
C     LOSCOM                 -     -   Common storage for the ATAF file
C                                      contents  which define the fit
C                                      parameters for the attitude
C                                      solution over each segment
C     MAXORD                PAR        Maximum allowable order of fit
C                                      (MAXORD=10)
C     MAXSEG                PAR        Maximum allowable number of
C                                      segments (MAXSEG=50)
C     UTSTAR               Intg    U   Universal Time at start of data
C     FCDAY                Intg        Fit coefficient day
C     FCYEAR               Intg        Fit coefficient year
C     NUMSEG               Intg        Number of segments
C     SEGTIM(2,MAXSEG)     Real    U   Segment start and end times
C     MULT(MAXSEG)         Real    U   Multiplicative constant for
C                                      linear transformation of time
C                                      range
C     ADD(MAXSEG)          Real    U   Additive constant for linear
C                                      transformation of time range
C     CONFLG(MAXSEG)       Intg        Mission event code numbers
C     IORDER(3,MAXSEG)     Intg        Order of the fit for each
C                                      parameter and segment
C     FITRA(MAXORD,MAXSEG) Real        Coefficients for the right
C                                      ascension for each segment
C     FITDC(MAXORD,MAXSEG) Real        Coefficients for the declination
C                                      for each segment
C     FITSR(MAXORD,MAXSEG) Real        Coefficients for the spin rate
C                                      for each segment
C     PHANG(MAXSEG)        Real    U   Phase angle at start of each
C                                      segment
C
C     Name                 Type   Use  Description
C     ----                 ----   ---  -----------
C     IDCOM                  -     -   Common containing instruments'
C                                      azimuth and elevation angles
C     NUMID                 PAR        Number of instrument IDs defined
C                                      (NUMID=40)
C     AZMUTH(NUMID)        Real    B   Instrument`s azimuth angle
C     ELVATN(NUMID)        Real    B   Instrument's elevation angle
C
C=====================================================================
C
C     Local variables
C     ----- ---------
C     Name       Type     Description
C     ----       ----     -----------
C     I          Intg     Index variable
C     K          Intg     Index variable
C     M          Intg     Index variable
C     N          Intg     Index variable
C     SEGNUM     Intg     Segment number
C     AZ         Real     Instrument's azimuth angle in radians
C     CDEC       Real     Cos(declination)
C     CEL        Real     Cos(elevation)
C     CRA        Real     Cos(right ascension)
C     CSUM       Real     Cos(phase + azimuth)
C     DIFF       Real     1 - cos(elevation)
C     EL         Real     Instrument's elevation angle in radians
C     FRSTIM     Real     Variable for the segment start time
C     LASTIM     Real     Variable for the segment end time
C     OFFTIM     Real     Offset time from start of data
C     PHI        Real     Total phase from start of segment
C     PHASE      Real     Phase from time of zero phase
C     PI         Real     Pi
C     PRDONE     Real     Product of YSC(1), YSC(2) and DIFF
C     PRDTWO     Real     Product of YSC(2), YSC(3) and DIFF
C     PRDTRI     Real     Product of YSC(3), YSC(1) and DIFF
C     SDEC       Real     Sin(declination)
C     SEL        Real     Sin(elevation)
C     SINONE     Real     Product of YSC(1) and SEL
C     SINTWO     Real     Product of YSC(2) and SEL
C     SINTRI     Real     Product of YSC(3) and SEL
C     SOFTIM     Real     Segment offset time
C     SRA        Real     Sin(right ascension)
C     SSUM       Real     Sin(phase + azimuth)
C     SUM        Real     Variable for matrix multiplication
C     TMTRIX(3,3)Real     Transformation matrix representing a rotation
C                         of elevation angle about YSC.
C     VECTX(3)   Real     Matrix representing the spacecraft's
C                         x-axis at a particular phase angle
C     YSC(3)     Real     Spacecraft's Y-axis at the calculated phase
C                         and instrument's azimuth angle
C
C=====================================================================
C
C     Called Routines:
C     ------ --------
C     None
C
C=====================================================================
C
C     Inputs/Outputs:
C     --------------
C     None
C
C*********************************************************************
C
      SUBROUTINE CLOS (ID, TIMEIN, NTIMES, LOS)
C
C.....Declaration Section
C
C.....Arguments:
C
      INTEGER         NTIMES, ID
C
      REAL            TIMEIN(NTIMES), LOS(3,NTIMES)
C
C.....Declarations for line of sight common LOSCOM
C
      INTEGER         MAXORD, MAXSEG
C
      PARAMETER (MAXORD=10)
      PARAMETER (MAXSEG=50)
C
      INTEGER         FCDAY, FCYEAR, UTSTAR, NUMSEG, CONFLG(MAXSEG),
     +                IORDER(3,MAXSEG)
C
      REAL            SEGTIM(2,MAXSEG), MULT(MAXSEG), ADD(MAXSEG),
     +                FITDC(MAXORD,MAXSEG), FITRA(MAXORD,MAXSEG),
     +                FITSR(MAXORD,MAXSEG), PHANG(MAXSEG)
C
      COMMON  /LOSCOM/ FCDAY, FCYEAR, UTSTAR, NUMSEG, SEGTIM, MULT,
     +                 ADD, CONFLG, IORDER, FITRA, FITDC, FITSR, PHANG
C
C.....Declarations for instrument common IDCOM
C
      INTEGER         NUMID
      PARAMETER       (NUMID=40)
C
      REAL            AZMUTH(NUMID), ELVATN(NUMID)
C
      COMMON  /IDCOM/  AZMUTH, ELVATN
C
C.....Local variables
C
      INTEGER         I, K, M, N, SEGNUM
      REAL            FRSTIM, LASTIM, VECTX(3), OFFTIM, SOFTIM, YSC(3),
     +                TMTRIX(3,3), AZ, EL, SSUM, CSUM, SRA, CRA, SDEC,
     +                CDEC, CEL, SEL, DIFF, PRDONE, PRDTWO, PRDTRI,
     +                SINONE, SINTWO, SINTRI, PHI, PHASE, PI, SUM
C
      PARAMETER       (PI = 3.14159265358979)
C
C.....Executable code section:
C
C.....Initialize local variables
C
      SEGNUM = 0
      FRSTIM = 0.0
      LASTIM = 0.0
C
C     Loop over all requested times through NTIMES to compute
C     the phase angle from the time of zero phase. An algorithm
C     is implemented to determine the segment in which a particular
C     time of interest lies by testing the condition that
C     TIMEIN must lie between the local variables FRSTIM and
C     LASTIM.
C
      DO 40 I = 1, NTIMES
         IF (TIMEIN(I).LT.FRSTIM.OR.TIMEIN(I).GT.LASTIM.AND.
     +      SEGNUM.LT.NUMSEG) THEN
   10       SEGNUM = SEGNUM + 1
            FRSTIM = SEGTIM(1,SEGNUM) + REAL(UTSTAR)/1000.0
            LASTIM = SEGTIM(2,SEGNUM) + REAL(UTSTAR)/1000.0
            SOFTIM = -(1.0 + ADD(SEGNUM))/MULT(SEGNUM)
            IF (TIMEIN(I).GE.LASTIM.AND.SEGNUM.LT.NUMSEG) GO TO 10
         END IF
C
C        Bypass segments that FIT was unable to generate fit
C        coefficients
C
         IF (CONFLG(SEGNUM).LT.0) THEN
            CONTINUE
         ELSE
C
C           The total phase angle from the start of the segment is
C           the spin rate at TIMEIN multiply by the difference between
C           TIMEIN and the segment start time, FRSTIME. The product is
C           is added to the phase angle at the start of the segment,
C           PHANG to get the total phase. The phase angle from the time
C           of zero phase is the MOD of PHI by 2*pi.
C
            OFFTIM = TIMEIN(I) - REAL(UTSTAR) / 1000.0
            PHI = LOS(3,I) * PI / 30.0 * (OFFTIM-SOFTIM)
     +           + PHANG(SEGNUM) * PI / 180.0
            PHASE = MOD(PHI,2.0 * PI)
C
C           Set the azimuth and elevation angles that are initialized
C           via internal data statements in BLOCK DATA subprogram BLKDAT.
C
            AZ = AZMUTH(ID) * PI/180.
            EL = ELVATN(ID) * PI/180.
C
C           Set up the matrix, VECTX that represents the spacecraft`s
C           X-axis at a calculated phase angle plus the rotation of the
C           instrument's azimuth angle
C
            SSUM = SIN(PHASE + AZ)
            CSUM = COS(PHASE + AZ)
C
            SRA  = SIN(LOS(1,I) * PI / 180.0)
            CRA  = COS(LOS(1,I) * PI / 180.0)
C
            SDEC = SIN(LOS(2,I) * PI / 180.0)
            CDEC = COS(LOS(2,I) * PI / 180.0)
C
            VECTX(1) = -(SSUM * SDEC * CRA) - (CSUM * SRA)
            VECTX(2) = -(SSUM * SDEC * SRA) + (CRA * CSUM)
            VECTX(3) =  SSUM * CDEC
C
C           Set up the matrix, YSC that represents the spacecraft`s
C           Y-axis at a calculated phase angle plus the rotation of the
C           instrument's azimuth angle
C
            YSC(1) = (CSUM * SDEC * CRA) - (SSUM * SRA)
            YSC(2) = (CSUM * SDEC * SRA) + (CRA * SSUM)
            YSC(3) = - CSUM * CDEC
C
C           The transformation matrix, TMTRIX, represents the general
C           direction cosine matrix of a rotation about the spacecraft's
C           Y-axis by the instrument's elevation angle.
C
            CEL = COS(-EL)
            SEL = SIN(-EL)
C
            DIFF = 1 - COS(-EL)
C
            PRDONE = YSC(1) * YSC(2) * DIFF
            PRDTWO = YSC(2) * YSC(3) * DIFF
            PRDTRI = YSC(3) * YSC(1) * DIFF
C
            SINONE = YSC(1) * SEL
            SINTWO = YSC(2) * SEL
            SINTRI = YSC(3) * SEL
C
            TMTRIX(1,1) = CEL + (YSC(1) * YSC(1) * DIFF)
            TMTRIX(1,2) = PRDONE + SINTRI
            TMTRIX(1,3) = PRDTRI - SINTWO
            TMTRIX(2,1) = PRDONE - SINTRI
            TMTRIX(2,2) = CEL + (YSC(2) * YSC(2) * DIFF)
            TMTRIX(2,3) = PRDTWO + SINONE
            TMTRIX(3,1) = PRDTRI + SINTWO
            TMTRIX(3,2) = PRDTWO - SINONE
            TMTRIX(3,3) = CEL + (YSC(3) * YSC(3) * DIFF)
C
C           Perform matrix multiplication of the transformation matrix,
C           TMTRIX, with the matrix, VECTX. The resultant matrix, LOS, is
C           the line of sight of the instrument.
C
            DO 30 M = 1,3
               SUM = 0.
               DO 20 N = 1,3
                  SUM = SUM + TMTRIX(M,N) * VECTX(N)
   20          CONTINUE
               LOS(M,I) = SUM
   30       CONTINUE
         END IF
   40 CONTINUE
      RETURN
      END
C
C     ..................................................................
C
C        SUBROUTINE CNPS
C
C        PURPOSE
C           COMPUTES THE VALUE OF AN N-TERM EXPANSION IN CHEBYSHEV
C           POLYNOMIALS WITH COEFFICIENT VECTOR C FOR ARGUMENT VALUE X.
C
C        USAGE
C           CALL CNPS(Y,X,C,N)
C
C        DESCRIPTION OF PARAMETERS
C           Y     - RESULT VALUE
C           X     - ARGUMENT VALUE
C           C     - COEFFICIENT VECTOR OF GIVEN EXPANSION
C                   COEFFICIENTS ARE ORDERED FROM LOW TO HIGH
C
C           N     - DIMENSION OF COEFFICIENT VECTOR C
C
C        REMARKS
C           OPERATION IS BYPASSED IN CASE N LESS THAN 1
C
C        SUBROUTINES AND FUNCTION SUBPROGRAMS REQUIRED
C           NONE
C
C        METHOD
C           DEFINITION
C           Y=SUM(C(I)*T(I-1,X), SUMMED OVER I FROM 1 TO N).
C           EVALUATION IS DONE BY MEANS OF BACKWARD RECURSION
C           USING THE RECURRENCE EQUATION FOR CHEBYSHEV POLYNOMIALS
C           T(N+1,X)=2*X*T(N,X)-T(N-1,X).
C
C     ..................................................................
C
      SUBROUTINE CNPS(Y,X,C,N)
C
      DIMENSION C(*)
C
C        TEST OF DIMENSION
      IF(N)1,1,2
    1 RETURN
C
    2 IF(N-2)3,4,4
    3 Y=C(1)
      RETURN
C
C        INITIALIZATION
    4 ARG=X+X
      H1=0.
      H0=0.
C
      DO 5 I=1,N
      K=N-I
      H2=H1
      H1=H0
    5 H0=ARG*H1-H2+C(K+1)
      Y=0.5*(C(1)-H2+H0)
C
      RETURN
      END
C*********************************************************************
C
C     CSCI:  AGMOD     CSC: EPOLY    (LLCSC 513)
C
C     EPOLY    -  Subroutine to evaluate the Chebyshev polynomials
C                 using the appropriate coefficients of the right
C                 ascension, declination and spin rate
C
C     Files:  AFGL VAX780:
C             USR$DSKH:[LCY.SPACAPP.AGMOD] EPOLY.FOR  -  source
C                                          AGMOD.OLB  -  object library
C
C             AFGL CYBER 180 - NOS/VE Side:
C               :NVAFGL.SPACAPP.LOS.EPOLY             -  source
C                                  .LOSLBR            -  object library
C
C     Author: L. K. Harada  -  Space Applications Corp.
C                              1310 Orleans Drive
C                              Sunnyvale, CA  94089
C                              (408)-744-0990
C
C     Current Revision:    00
C
C=====================================================================
C
C     Revision History:
C     -------- -------
C
C     Rev   Date     By    Reason
C     ---   ----     --    ------
C
C      00  11JAN88   LKH   Original
C
C=====================================================================
C
C     Purpose and Usage:
C     -----------------
C
C        Subroutine EPOLY is called by LLCSC AGMOD to evaluate the
C     Chebyshev polynomials using the appropriate coefficients in
C     LOSCOM. EPOLY reduces the argument, TIMEIN, in order that the
C     time of interest is on the interval (-1,1) on which the
C     coefficients were determined. EPOLY calls CNPS from the IBM
C     scientific subroutine library which is resident on the CYBER.
C
C     Limitations:
C     -----------
C     None
C
C=====================================================================
C
C     Arguments:
C     ---------
C     Name           Type  Use  Description
C     ----           ----  ---  -----------
C     TIMEIN(NTIMES) Real   U   Time(s) of interest
C     NTIMES         Intg   U   Number of times requested by user
C     LOS(3,NTIMES)  Real   B   Argument array storing the instru-
C                               ment's right ascension, declination
C                               and spin rate
C                                 ( LOS(1,I) => right ascension at
C                                               time I)
C                                 ( LOS(2,I) => declination at time I)
C                                 ( LOS(3,I) => spin rate at time I)
C
C=====================================================================
C
C     Common Variables:
C     ------ ---------
C     Name                 Type   Use  Description
C     ----                 ----   ---  -----------
C     LOSCOM                 -     -   Common storage for the ATAF file
C                                      contents  which define the fit
C                                      parameters for the attitude
C                                      solution over each segment
C     MAXORD                PAR        Maximum allowable order of fit
C                                      (MAXORD=10)
C     MAXSEG                PAR        Maximum allowable number of
C                                      segments (MAXSEG=50)
C     UTSTAR               Intg    U   Universal Time at start of data
C     FCDAY                Intg        Fit coefficient day
C     FCYEAR               Intg        Fit coefficient year
C     NUMSEG               Intg        Number of segments
C     SEGTIM(2,MAXSEG)     Real    U   Segment start and end times
C     MULT(MAXSEG)         Real    U   Multiplicative constant for
C                                      linear transformation of time
C                                      range
C     ADD(MAXSEG)          Real    U   Additive constant for linear
C                                      transformation of time range
C     CONFLG(MAXSEG)       Intg        Mission event code numbers
C     IORDER(3,MAXSEG)     Intg    U   Order of the fit for each
C                                      parameter and segment
C     FITRA(MAXORD,MAXSEG) Real    U   Coefficients for the right
C                                      ascension for each segment
C     FITDC(MAXORD,MAXSEG) Real    U   Coefficients for the declination
C                                      for each segment
C     FITSR(MAXORD,MAXSEG) Real    U   Coefficients for the spin rate
C                                      for each segment
C     PHANG(MAXSEG)        Real        Phase angle at start of each
C                                      segment
C
C=====================================================================
C
C     Local variables
C     ----- ---------
C     Name         Type     Description
C     ----         ----     -----------
C     I            Intg     Index loop
C     K            Intg     Index loop
C     IORD         Intg     Order of the parameter for a specific
C                           segment
C     PARAM        Intg     Integer variable identifying parameter
C                           ( PARAM=1 => Right ascension )
C                           ( PARAM=2 => Declination )
C                           ( PARAM=3 => Spin rate )
C     SEGNUM       Intg     Segment number
C     COEFF(MAXORD)Real     Coefficients for a specific parameter
C     FRSTIM       Real     Variable for the segment start time
C     LASTIM       Real     Variable for the segment end time
C     OFFTIM       Real     Offset time from start of data
C     POLYVL       Real     Variable representing the value obtained
C                           from CNPS
C     RDCTIM       Real     Value of the reduced TIMEIN
C
C=====================================================================
C
C     Called Routines:
C     ------ --------
C     Name       Location         Purpose
C     ----       --------         -------
C
C     CNPS       AGMOD library    To evaluate the fit coefficients
C
C=====================================================================
C
C     Inputs/Outputs:
C     --------------
C     None
C
C*********************************************************************
C
      SUBROUTINE EPOLY (TIMEIN, NTIMES, LOS)
C
C.....Declaration Section
C
C.....Arguments:
C
      INTEGER         NTIMES
C
      REAL            TIMEIN(NTIMES), LOS(3,NTIMES)
C
C.....Declarations for line of sight common LOSCOM
C
      INTEGER         MAXORD, MAXSEG
C
      PARAMETER (MAXORD=10)
      PARAMETER (MAXSEG=50)
C
      INTEGER         FCDAY, FCYEAR, UTSTAR, NUMSEG, CONFLG(MAXSEG),
     +                IORDER(3,MAXSEG)
C
      REAL            SEGTIM(2,MAXSEG), MULT(MAXSEG), ADD(MAXSEG),
     +                FITDC(MAXORD,MAXSEG), FITRA(MAXORD,MAXSEG),
     +                FITSR(MAXORD,MAXSEG), PHANG(MAXSEG)
C
      COMMON  /LOSCOM/ FCDAY, FCYEAR, UTSTAR, NUMSEG, SEGTIM, MULT,
     +                 ADD, CONFLG, IORDER, FITRA, FITDC, FITSR, PHANG
C
C.....Local variables
C
      INTEGER         I, K, SEGNUM, IORD, PARAM
      REAL            FRSTIM, LASTIM, COEFF(MAXORD), POLYVL, RDCTIM,
     +                OFFTIM
C
C.....Executable code section:
C
C.....Initialize local variables.
C
      SEGNUM = 0
      FRSTIM = 0.
      LASTIM = 0.
C
C     Begin loop through each time of interest to determine the
C     appropriate segment and the proper number of coefficients
C     for a particular parameter.
C
      DO 40 I = 1,NTIMES
         IF (TIMEIN(I).LT.FRSTIM.OR.TIMEIN(I).GT.LASTIM.AND.
     +       SEGNUM.LT.NUMSEG) THEN
   10       SEGNUM = SEGNUM + 1
            FRSTIM = SEGTIM(1,SEGNUM) + REAL(UTSTAR)/1000.0
            LASTIM = SEGTIM(2,SEGNUM) + REAL(UTSTAR)/1000.0
            IF (TIMEIN(I).GE.LASTIM.AND.SEGNUM.LT.NUMSEG) GO TO 10
         END IF
C
C        Begin loop through each parameter. PARAM=1 => Right ascension
C                                           PARAM=2 => Declination
C                                           PARAM=3 => Spin rate
C
         DO 30 PARAM = 1,3
C
C           Bypass segments that FIT was unable to generate fit
C           coefficients.
C
            IF (CONFLG(SEGNUM).LT.0) THEN
                LOS(PARAM, I) = 0.0
                CONTINUE
            ELSE
C
C              Three way selection to select the proper number of
C              coefficients for the given parameter
C
               IORD = IORDER(PARAM, SEGNUM)
               DO 20 K=1,IORD
                  IF (PARAM.EQ.1) THEN
                     COEFF(K) = FITRA(K,SEGNUM)
                  ELSEIF (PARAM.EQ.2) THEN
                     COEFF(K) = FITDC(K,SEGNUM)
                  ELSE
                     COEFF(K) = FITSR(K,SEGNUM)
                  END IF
   20          CONTINUE
C
C              The following assignment calculates the offset time(s)
C              from time at start of data, UTSTAR, and requested
C              time(s), TIMEIN, then reduces the offset time(s) of
C              interest on the interval (-1,1)
C
               OFFTIM = TIMEIN(I) - REAL(UTSTAR)/1000.0
               RDCTIM = OFFTIM * MULT(SEGNUM) + ADD(SEGNUM)
C
C              Call procedure CNPS to evaluate the polynomials for
C              TIMEIN(I)
C
               CALL CNPS(POLYVL,RDCTIM,COEFF,IORD)
C
C              Store the polynomial value, POLYVL, into the appropriate
C              parameter array
C
               LOS(PARAM,I) = POLYVL
            END IF
   30    CONTINUE
   40 CONTINUE
      RETURN
      END
C*********************************************************************
C
C     CSCI:  AGMOD     CSC:  LOSBLK
C
C     LOSBLK    -  Subprogram to initialize values for the instrument's
C                  azimuth and elevation arrays contained in named
C                  commom IDCOM
C
C     Files:  AFGL VAX780:
C             USR$DSKH:[LCY.SPACAPP.AGMOD] LOSBLK.FOR  -  source
C                                          AGMOD.OLB   -  object library
C
C             AFGL CYBER 180 - NOS/VE Side:
C               :NVAFGL.SPACAPP.LOS.LOSBLK             -  source
C                                  .LOSLBR             -  object library
C
C     Author: L. K. Harada  -  Space Applications Corp.
C                              1310 Orleans Drive
C                              Sunnyvale, CA  94089
C                              (408)-744-0990
C
C     Current Revision:    00
C
C=====================================================================
C
C     Revision History:
C     -------- -------
C
C     Rev   Date     By    Reason
C     ---   ----     --    ------
C
C      00  12JAN88   LKH   Original
C
C=====================================================================
C
C     Purpose and Usage:
C     -----------------
C        The block data subprogram initializes values for the
C     instrument's azimuth and elevation angle arrays contained in
C     named common IDCOM.
C
C     Limitations:
C     -----------
C     None
C
C=====================================================================
C
C     Arguments:
C     ---------
C     None
C
C=====================================================================
C
C     Common Variables:
C     ------ ---------
C     Name                  Type   Use  Description
C     ----                  ----   ---  -----------
C     IDCOM                  -      -   Common containing instruments'
C                                       azimuth and elevation angles
C     NUMID                 PAR         Number of instrument IDs defined
C                                       (NUMID=40)
C     AZMUTH(NUMID)         Real    S   Instrument`s azimuth angle
C     ELVATN(NUMID)         Real    S   Instrument's elevation angle
C
C=====================================================================
C
C     Local Variables:
C     ----- ---------
C     None
C
C=====================================================================
C
C     Called Routines:
C     ------ --------
C     None
C
C=====================================================================
C
C     Inputs/Outputs:
C     --------------
C     None
C
C*********************************************************************
C
      BLOCK DATA LOSBLK
C
C.....Declaration Section
C
C.....Declarations for instrument common IDCOM
C
      INTEGER         NUMID
C
      PARAMETER       (NUMID=40)
C
      REAL            AZMUTH(NUMID), ELVATN(NUMID)
C
      COMMON  /IDCOM/  AZMUTH, ELVATN
C
C     Instruments' azimuths and elevations are initialized in DATA
C     statements
C
      DATA AZMUTH /000.000, 090.000, 180.000, 270.000, 000.000,
     +             090.000, 180.000, 270.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000/
C
      DATA ELVATN /000.000, 000.000, 000.000, 000.000, 090.000,
     +             -90.000, 045.000, -45.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000,
     +             000.000, 000.000, 000.000, 000.000, 000.000/
C
      END
C**********************************************************************
C
C     CSCI:  AGMOD     CSC: RAAF    (LLCSC 511)
C
C     CHECK    -  Subroutine to read in the contents of the Agency
C                 Attitude file into the internal common, LOSCOM.
C
C     Files:  AFGL VAX780:
C             USR$DSKH:[LCY.SPACAPP.AGMOD] RAAF.FOR   -  source
C                                          AGMOD.OLB  -  object library
C
C             AFGL.CYBER 180 -NOS/VE Side:
C               :NVAFGL.SPACAPP.LOS.RAAF              -  source
C                                  .LOSLBR            -  object library
C
C     Author: L. K. Harada  -  Space Applications Corp.
C                              1310 Orleans Drive
C                              Sunnyvale, CA  94089
C                              (408)-744-0990
C
C     Current Revision:    00
C
C=====================================================================
C
C     Revision History:
C     -------- -------
C
C     Rev   Date     By    Reason
C     ---   ----     --    ------
C
C      00  18JAN88   LKH   Original
C
C=====================================================================
C
C     Purpose and Usage:
C     -----------------
C
C        Subroutine RAAF is called by the LLCSC AGMOD to read in the
C     contents of the Agency Attitude file into an internal common,
C     LOSCOM.
C
C     Limitations:
C     -----------
C     None
C
C=====================================================================
C
C     Arguments:
C     ---------
C     Name           Type  Use  Description
C     ----           ----  ---  -----------
C     ATAFLU         Intg   U   ATAF logical unit number
C     ERROR          Intg   S   Error return value
C                                 ( 0 => no errors)
C                                 (-1 => file read error)
C                                 (-2 => Incorrect vehicle ID)
C                                 (-3 => End of file reached
C                                        prematurely)
C                                 (-4 => NUMSEG exceeds MAXSEG)
C                                 (-5 => IORDER exceeds MAXORD)
C
C=====================================================================
C
C     Common Variables:
C     ------ ---------
C     Name                 Type   Use  Description
C     ----                 ----   ---  -----------
C     LOSCOM                 -     -   Common storage for the ATAF file
C                                      contents  which define the fit
C                                      parameters for the attitude
C                                      solution over each segment
C     MAXORD                PAR        Maximum allowable order of fit
C                                      (MAXORD=10)
C     MAXSEG                PAR        Maximum allowable number of
C                                      segments (MAXSEG=50)
C     UTSTAR               Intg    S   Universal Time at start of data
C     FCDAY                Intg    S   Fit coefficient day
C     FCYEAR               Intg    S   Fit coefficient year
C     NUMSEG               Intg    S   Number of segments
C     SEGTIM(2,MAXSEG)     Real    S   Segment start and end times
C     MULT(MAXSEG)         Real    S   Multiplicative constant for
C                                      linear transformation of time
C                                      range
C     ADD(MAXSEG)          Real    S   Additive constant for linear
C                                      transformation of time range
C     CONFLG(MAXSEG)       Intg    S   Mission event code numbers
C     IORDER(3,MAXSEG)     Intg    S   Order of the fit for each
C                                      parameter and segment
C     FITRA(MAXORD,MAXSEG) Real    S   Coefficients for the right
C                                      ascension for each segment
C     FITDC(MAXORD,MAXSEG) Real    S   Coefficients for the declination
C                                      for each segment
C     FITSR(MAXORD,MAXSEG) Real    S   Coefficients for the spin rate
C                                      for each segment
C     PHANG(MAXSEG)        Real    S   Phase angle at start of each
C                                      segment
C
C=====================================================================
C
C
C     Local variables
C     ----- ---------
C     Name       Type     Description
C     ----       ----     -----------
C     I          Intg     Index variable
C     N          Intg     Index variable
C     IOS        Intg     Status variable
C     SATID      C*16     Satellite ID read from FCD header
C     VEHID      C*16     CRRES vehicle ID
C
C=====================================================================
C
C     Called Routines:
C     ------ --------
C     None
C
C=====================================================================
C
C     Inputs/Outputs:
C     --------------
C     Name            I/O Medium  Use  Purpose
C     ----            ----------  ---  -------
C
C     Agency Attitude    File      I   Read in contents of ATAF
C     File
C
C*********************************************************************
C
      SUBROUTINE RAAF (ATAFLU, ERROR)
C
C.....Declaration Section
C
C.....Arguments:
C
      INTEGER         ATAFLU, ERROR
C
C.....Declarations for line of sight common LOSCOM
C
      INTEGER         MAXORD, MAXSEG
C
      PARAMETER (MAXORD=10)
      PARAMETER (MAXSEG=50)
C
      INTEGER         FCDAY, FCYEAR, UTSTAR, NUMSEG, CONFLG(MAXSEG),
     +                IORDER(3,MAXSEG)
C
      REAL            SEGTIM(2,MAXSEG), MULT(MAXSEG), ADD(MAXSEG),
     +                FITDC(MAXORD,MAXSEG), FITRA(MAXORD,MAXSEG),
     +                FITSR(MAXORD,MAXSEG), PHANG(MAXSEG)
C
      COMMON  /LOSCOM/ FCDAY, FCYEAR, UTSTAR, NUMSEG, SEGTIM, MULT,
     +                 ADD, CONFLG, IORDER, FITRA, FITDC, FITSR, PHANG
C
C.....Local variables
C
      INTEGER         I, N, IOS
      CHARACTER*16    VEHID, SATID
C
C.....Executable code section:
C
C     Initialize vehicle identification, VEHID
C
      VEHID = 'CRRES P86-1     '
C
C     Read in ATAF FCD header
C
      READ (ATAFLU, '(/,A)', IOSTAT=IOS, ERR=50, END= 60) SATID
C
C     Test to assure ID field in the FCD header corresponds to
C     the actual CRRES vehicle ID
C
      IF (SATID.NE.VEHID) THEN
         ERROR = -2
         RETURN
      END IF
C
      READ (ATAFLU, '(/,I5,/,I5,/,I11)', IOSTAT=IOS, ERR=50,
     +      END= 60) FCYEAR, FCDAY, UTSTAR
C
      READ (ATAFLU, '(/,I5)', IOSTAT=IOS, ERR=50, END=60) NUMSEG
C
C     Test to assure that the number of segments, NUMSEG in the
C     FCD file is less than or equal to the preset maximum number
C     of segments MAXSEG.
C
      IF (NUMSEG.GT.MAXSEG) THEN
         ERROR = -4
         RETURN
      END IF
C
C     Read in FCD file data records
C
      DO 40 I = 1, NUMSEG
         READ (ATAFLU, '(/,F13.4,/,F13.4)', IOSTAT=IOS, ERR=50,
     +        END=60) SEGTIM(1,I), SEGTIM(2,I)
C
         READ (ATAFLU, '(F30.0,/,F30.0,/,I5)', IOSTAT=IOS, ERR=50,
     +        END=60) MULT(I), ADD(I), CONFLG(I)
C
         READ (ATAFLU, '(I5)', IOSTAT=IOS, ERR=50, END=60) IORDER (1,I)
C
C        Test to assure that the order, IORDER for the right
C        ascension in the FCD file is less than or equal to the
C        preset maximum order, MAXORD
C
         IF (IORDER(1,I).GT.MAXORD) THEN
            ERROR = -5
            RETURN
         END IF
         DO 10 N = 1, IORDER(1,I)
            READ (ATAFLU, '(F30.0)', IOSTAT=IOS, ERR=50, END=60)
     +            FITRA(N,I)
   10    CONTINUE
         READ (ATAFLU, '(I5)', IOSTAT=IOS, ERR=50, END=60) IORDER (2,I)
C
C        Test to assure that the order, IORDER for the declination
C        in the FCD file is less than or equal to the preset maximum
C        order, MAXORD
C
         IF (IORDER(2,I).GT.MAXORD) THEN
            ERROR = -5
            RETURN
         END IF
         DO 20 N = 1, IORDER(2,I)
            READ (ATAFLU, '(F30.0)', IOSTAT=IOS, ERR=50, END=60)
     +            FITDC(N,I)
   20    CONTINUE
         READ (ATAFLU,'(I5)', IOSTAT=IOS, ERR=50, END=60) IORDER (3,I)
C
C        Test to assure that the order, IORDER for the spin rate
C        in the FCD file is less than or equal to the preset maximum
C        order, MAXORD
C
         IF (IORDER(3,I).GT.MAXORD) THEN
            ERROR = -5
            RETURN
         END IF
         DO 30 N = 1, IORDER(3,I)
            READ (ATAFLU, '(F30.0)', IOSTAT=IOS, ERR=50, END=60)
     +         FITSR(N,I)
   30    CONTINUE
         READ (ATAFLU,'(F30.0)',IOSTAT=IOS, ERR=50, END=60) PHANG(I)
   40 CONTINUE
      RETURN
C
C     Return in the event that an error occurred during the input
C     process
C
   50 CONTINUE
      ERROR = -1
      RETURN
C
C     Return in the event that end of file is encountered prematurely
C
   60 CONTINUE
      ERROR = -3
      RETURN
      END