SUBROUTINE GS_DCOD  ( cldt, bufrtn, nhours, iret )
C************************************************************************
C* GS_DCOD								*
C*									*
C* This routine decodes bulletins containing GNSS (Global Navigation	*
C* Satellite System) BUFR messages into NCEP BUFR format.		*
C*									*
C* GS_DCOD ( CLDT, BUFRTA, BUFRTN, NHOURS, IRET )			*
C*									*
C* Input parameters:							*
C*	CLDT		CHAR*		Date-time from command line	*
C*	BUFRTN		CHAR*		NCEP BUFR tables file		*
C*	NHOURS		INTEGER		Max # of hours before run time	*
C*					for creating NCEP BUFR output	*
C*									*
C* Output parameters:							*
C*	IRET		INTEGER		Return code:			*
C*					  0 = normal return		*
C*									*
C**									*
C* Log:									*
C* J. Ator/NCEP		06/15						*
C* J. Ator/NCEP		03/16	Add RSRD and EXPRSRD			*
C* M. Weiss/IMSG        06/21   MAXOUT (200000) --> MAXOUT (199900)     *
C************************************************************************
	INCLUDE		'GEMPRM.PRM'
	INCLUDE		'BRIDGE.PRM'
C*
	CHARACTER*(*)	cldt, bufrtn
C*
C*	Maximum number of descriptors within Section 3 of a
C*	GNSS BUFR message.
C*
	PARAMETER	( MXDSC = 75 )
C*
	PARAMETER	( MXMN = 200 )
C*
	PARAMETER	( MXLV = 1 )
C*
	CHARACTER	bull*(DCMXBF), cbull*(DCMXBF), bfstyp*8,
     +			seqnum*8, buhd*8, cborg*8, bulldt*8, bbb*8,
     +			rundt*12, sysdt*12, subtyp*8, logmsg*200,
     +			cdesc( MXDSC )*6, stsn*20,
     +                  bufrdn*(DCMXLN), bufrbn*(DCMXLN)
C*
	INTEGER		irundt ( 5 ), irptdt ( 5 ), 
     +			ibull ( DCMXBF / 4 )
C*
	LOGICAL		bullok, msgok
C*
	REAL*8		r8in ( MXMN, MXLV ), PKFTBV
C*
	EQUIVALENCE	( cbull (1:4), ibull (1) )
C*
	INCLUDE		'ERMISS.FNC'
C*-----------------------------------------------------------------------
	iret = 0
C
C*      Get the BUFR tables directory from the tables file.  This
C*      directory will be passed to subroutine MTINFO as the location
C*      in which to search for any needed master table files.
C
        CALL FL_PATH ( bufrtn, bufrdn, bufrbn, ierpth )        
C
C*	Open the tables file for the NCEP BUFR (i.e. output) stream.
C
	CALL FL_SOPN ( bufrtn, iubftn, ierspn )
	IF ( ierspn .ne. 0 ) THEN
	  CALL DC_WLOG ( 0, 'FL', ierspn, bufrtn, ierwlg )
	  RETURN
	END IF
C
C*	Open the BUFR messages file.
C
	CALL FL_GLUN ( iubfma, iergln )
	IF ( iergln .ne. 0 ) THEN
	  CALL DC_WLOG ( 0, 'FL', iergln, ' ', ierwlg )
	  RETURN
	END IF
	OPEN ( UNIT = iubfma, FILE = '.dummy/dcgnss',
     +		FORM = 'UNFORMATTED' )
	CALL OPENBF ( iubfma, 'SEC3', iubftn )
C
        CALL MTINFO ( bufrdn, 98, 99 )
C
C*	Open the messages file for the NCEP BUFR (i.e. output) stream.
C
	CALL FL_GLUN ( iubfmn, iergln )
	IF ( iergln .ne. 0 ) THEN
	  CALL DC_WLOG ( 0, 'FL', iergln, ' ', ierwlg )
	  RETURN
	END IF
C
C*	Connect the tables and messages files for the
C*	NCEP BUFR (i.e. output) stream.
C
	CALL OPENBF ( iubfmn, 'NUL', iubftn )
C
C*      Specify that NCEP BUFR (i.e. output) messages are to be encoded
C*	using edition 4, compressed, and up to 200K bytes in size.
C
	CALL CMPMSG ( 'Y' )
	CALL PKVS01 ( 'BEN', 4 )
	CALL MAXOUT ( 199900 )
C
C*	Close the tables file for the NCEP BUFR (i.e. output) stream.
C
	CALL FL_CLOS ( iubftn, iercls )
	IF ( iercls .ne. 0 ) THEN
	  CALL DC_WLOG ( 0, 'FL', iercls, ' ', ierwlg )
	END IF
C
	DO WHILE ( .true. )
C
C*	  Get a new bulletin from the input pipe.
C
	  CALL DC_GBUL ( bull, lenb, ifdtyp, iergbl )
	  IF ( iergbl .ne. 0 ) THEN
C
C*	    A time-out occurred while waiting for a new bulletin
C*	    on the input pipe.  Shut down the decoder and exit.
C
	    CALL DC_WLOG ( 0, 'DC', iergbl, ' ', ierwlg )
	    CALL CLOSBF ( iubfma )
	    CALL CLOSBF ( iubfmn )
	    CALL FL_CLAL ( iercal )
	    RETURN
	  END IF
C
	  bullok = .true.
C
C*	  Decode the header information from this bulletin.
C
	  IF ( ifdtyp .eq. 0 ) THEN
C
C*	    Decode WMO products.
C
	    CALL DC_GHDR ( bull, lenb, seqnum, buhd, cborg,
     +			   bulldt, bbb, ibptr, ierghd )
	    IF ( ierghd .ne. 0 ) THEN
	      CALL DC_WLOG ( 2, 'DC', ierghd, ' ', ierwlg )
	      bullok = .false.
	    ELSE
C
C*	      Start an entry for this bulletin in the decoder log.
C
	      logmsg = '########################################'
	      CALL DC_WLOG ( 2, 'DC', 2, logmsg, ierwlg )
	      logmsg = seqnum // buhd // cborg // bulldt // bbb
	      CALL DC_WLOG ( 2, 'DC', 2, logmsg, ierwlg )
	    END IF
	  ELSE
C
C*	    Do not decode AFOS products.
C
	    bullok = .false.
	  END IF
C
	  IF ( bullok ) THEN
C
C*	    Get the system time.
C
	    itype = 1
	    CALL CSS_GTIM ( itype, sysdt, iergtm )
	    IF ( iergtm .ne. 0 ) THEN
	      CALL DC_WLOG ( 2, 'SS', iergtm, ' ', ierwlg )
	      bullok = .false.
	    END IF
	  END IF
C
	  IF ( bullok ) THEN
C
C*	    If a date-time was entered on the command line, then use it
C*	    as the run date-time.  Otherwise, use the system time as
C*	    the run date-time.
C
	    IF ( cldt .eq. 'SYSTEM' ) THEN
	      rundt = sysdt
	    ELSE
	      CALL TI_STAN ( cldt, sysdt, rundt, ierstn )
	      IF ( ierstn .ne. 0 ) THEN
		CALL DC_WLOG ( 2, 'TI', ierstn, ' ', ierwlg )
		bullok = .false.
	      END IF
	    END IF
	  END IF
C
	  IF ( bullok ) THEN
C
C*	    Convert the run date-time to integer.
C
	    CALL TI_CTOI ( rundt, irundt, iercto )
	    IF ( iercto .ne. 0 ) THEN
	      CALL DC_WLOG  ( 2, 'TI', iercto, ' ', ierwlg )
	      bullok = .false.
	    ELSE
	      nmsg = 0
	    END IF
	  END IF
C
	  DO WHILE ( bullok )
C
C*	    Locate the next BUFR message within the bulletin, and
C*	    store it within an equivalenced integer array.
C
	    ipt1 = INDEX ( bull (ibptr:lenb), 'BUFR' )
	    IF ( ipt1 .eq. 0 ) THEN
	      bullok = .false.
	      IF ( nmsg .eq. 0 ) THEN
		IF ( INDEX ( bull (ibptr:lenb), 'NIL' ) .ne. 0 ) THEN
		  logmsg = 'NIL bulletin'
		  CALL DC_WLOG  ( 2, 'DC', 2, logmsg, ierwlg )
		END IF
	      ELSE
C
C*		Make sure that all BUFR output for this bulletin has
C*		been written to the BUFR output stream before going back
C*		to DC_GBUL and waiting for a new bulletin on the pipe.
C
		CALL UT_WBFR ( iubfmn, 'gnss', 1, ierwbf )
	      END IF
	    ELSE
	      istart = ibptr + ipt1 - 1
	      ibptr = istart + 4
	      cbull = bull ( istart : lenb )
C
	      nmsg = nmsg + 1
	      nrept = 0
	      msgok = .false.
C
C*	      Retrieve the Section 3 descriptors from the message and
C*	      check for the presence of one or more particular values.
C
	      CALL UPDS3 ( ibull, MXDSC, cdesc, ndesc )
	      ii = 1
	      DO WHILE ( ( ii .le. ndesc ) .and. ( .not. msgok ) )
		IF ( cdesc(ii) .eq. '307022' ) THEN
		  msgok = .true.
		ELSE
		  ii = ii + 1
		END IF
	      END DO
C
	      IF ( msgok ) THEN
C
C*		Open the BUFR message for reading.
C
		CALL READERME ( ibull, iubfma, bfstyp, ibfdt, ierrme )
		IF ( ierrme .ne. 0 ) THEN
		  msgok = .false.
		END IF
	      ELSE
		logmsg = 'message does not contain 307022 sequence'
		CALL DC_WLOG ( 2, 'DC', 2, logmsg, ierwlg )
	      END IF
C
	      DO WHILE ( msgok )
C
C*		Get the next report from this BUFR message.
C
		IF ( IREADSB ( iubfma ) .ne. 0 ) THEN
C
C*		  There are no more reports in this message.
C
		  msgok = .false.
C
C*		  Print a count of the number of reports processed.
C
		  WRITE  ( UNIT = logmsg, FMT = '( A, I4, A )' )
     +			'contained ', nrept, ' reports'
		  CALL DC_WLOG  ( 2, 'DC', 2, logmsg, ierwlg )
C
		ELSE
		  nrept = nrept + 1
C
C*		  Get the report date-time.
C
		  CALL UFBINT ( iubfma, r8in, MXMN, MXLV, nlv,
     +				'YEAR MNTH DAYS HOUR MINU' )
C
C*		  Don't create BUFR output for reports that are more
C*		  than NHOURS before or more than 3 hours after the
C*		  run time.
C
		  rptyr = UT_BMRI ( r8in (1,1) )
		  rptmo = UT_BMRI ( r8in (2,1) )
		  rptdy = UT_BMRI ( r8in (3,1) )
		  rpthr = UT_BMRI ( r8in (4,1) )
		  rptmi = UT_BMRI ( r8in (5,1) )
		  IF ( ( ERMISS ( rptyr ) ) .or.
     +		       ( ERMISS ( rptmo ) ) .or.
     +		       ( ERMISS ( rptdy ) ) .or.
     +		       ( ERMISS ( rpthr ) ) .or.
     +		       ( ERMISS ( rptmi ) ) ) THEN
		    iertmk = -1
		  ELSE
		    irptdt (1) = INT ( rptyr )
		    irptdt (2) = INT ( rptmo )
		    irptdt (3) = INT ( rptdy )
		    irptdt (4) = INT ( rpthr )
		    irptdt (5) = INT ( rptmi )
		    CALL DC_TMCK ( 2, irundt, irptdt, nhours, 180,
     +				   iertmk )
		  END IF
C
		  IF ( iertmk .eq. 0 ) THEN
C
		    subtyp = 'NC012004'
C
C*                  Open a BUFR message for output.
C
		    ibfdt = ( irptdt (1) * 1000000 )  +
     +			    ( irptdt (2) * 10000 )  +
     +			    ( irptdt (3) * 100 )  +  irptdt (4)
		    CALL OPENMB ( iubfmn, subtyp, ibfdt )
C
C*		    Get the (long) station name.
C
		    CALL READLC ( iubfma, stsn, 'STSN' )
C
C*		    Get and store the main data sequence.
C
		    CALL UFBSEQ ( iubfma, r8in, MXMN, MXLV, nlv,
     +				  'GBGNSSDA' )
		    CALL UFBSEQ ( iubfmn, r8in, MXMN, 1, nlv2,
     +				  'GBGNSSDA' )
C
C*		    Bulletin header.
C
		    CALL UT_CIBF ( iubfmn, 'SEQNUM', seqnum, 8, ier )
		    CALL UT_CIBF ( iubfmn, 'BUHD', buhd, 8, ier )
		    CALL UT_CIBF ( iubfmn, 'BORG', cborg, 8, ier )
		    CALL UT_CIBF ( iubfmn, 'BULTIM', bulldt, 8, ier )
		    CALL UT_CIBF ( iubfmn, 'BBB', bbb, 8, ier )
C
C*		    Receipt time.
C
		    CALL UT_RIBF ( iubfmn, 'RCTS', FLOAT (0), ier )
		    CALL UT_RIBF ( iubfmn, 'RCYR',
     +				   FLOAT ( irundt (1) ), ier )
		    CALL UT_RIBF ( iubfmn, 'RCMO',
     +				   FLOAT ( irundt (2) ), ier )
		    CALL UT_RIBF ( iubfmn, 'RCDY',
     +				   FLOAT ( irundt (3) ), ier )
		    CALL UT_RIBF ( iubfmn, 'RCHR',
     +				   FLOAT ( irundt (4) ), ier )
		    CALL UT_RIBF ( iubfmn, 'RCMI',
     +				   FLOAT ( irundt (5) ), ier )
C
C*		    Correction indicator.
C
		    IF ( ( IUPBS01 ( ibull, 'USN' ) .gt. 0 ) .or.
     +			    ( bbb(1:1) .eq. 'C' ) ) THEN
		      icorn = 1
		    ELSE
		      icorn = 0
		    END IF
		    CALL UT_RIBF ( iubfmn, 'CORN', FLOAT (icorn), ier )
C
C*		    Restrictions on redistribution.
C
		    IF ( cborg(1:4) .eq. 'KWBC' ) THEN
			rsrd = PKFTBV (9,5)
			CALL UT_RIBF ( iubfmn, 'RSRD', rsrd, ierrbf )
		    END IF
C
C*		    Write the BUFR output to the BUFR output stream.
C
		    CALL UT_WBFR ( iubfmn, 'gnss', 0, ierwbf )
		    CALL WRITLC ( iubfmn, stsn, 'STSN' )
		  END IF
		END IF
	      END DO
            END IF
	  END DO
	END DO
C*
	RETURN
	END