SUBROUTINE HY_DCOD  ( cldt, hydrfl, bufrtb, nhours, iret )
C************************************************************************
C* HY_DCOD								*
C*									*
C* This routine decodes HYDRO data files from FSL into BUFR format.	*
C*									*
C* HY_DCOD ( CLDT, HYDRFL, BUFRTB, NHOURS, IRET )			*
C*									*
C* Input parameters:							*
C*	CLDT		CHAR*		Date-time from command line	*
C*	HYDRFL		CHAR*		HYDRO data file from FSL	*
C*	BUFRTB		CHAR*		BUFR tables file		*
C*	NHOURS		INTEGER		Max # of hours before run time	*
C*					for creating BUFR output	*
C*									*
C* Output parameters:							*
C*	IRET		INTEGER		Return code:			*
C*					  0 = normal return		*
C*									*
C**									*
C* Log:									*
C* C. Caruso Magee/NCEP 11/04   Modify for HYDRO data.                  *
C* C. Caruso Magee/NCEP 04/05   Replace SPFH with REHU.                 *
C* M. Weiss /NCEP       03/24   Use new decod_ut library routines,      *
C*                              to clean up and simplify logic          *
C* M. Weiss /NCEP       04/24   Removed  INCLUDE    'ERMISS.FNC'        * 
C************************************************************************
	INCLUDE	   'GEMPRM.PRM'
	INCLUDE	   'BRIDGE.PRM'
	INCLUDE	   'hycmn.cmn'
C*
	CHARACTER*(*)	cldt, hydrfl, bufrtb
C*
	CHARACTER  hydrdn*(DCMXLN), hydrbn*(DCMXLN), stnm(MXSTNS)*10,
     +		   acid(MXSTNS)*8, crpttm(MXSTNS)*9, cstrtm*9,
     +		   qcd(MXSTNS,NVAR)*1, vcname(NVAR)*7, rimnem(NRIMN)*8,
     +		   cimnem(NCIMN)*8, cmsobn*18, cprovdr(MXSTNS)*20
C*
	REAL	   slat ( MXSTNS ), slon ( MXSTNS ), selv (MXSTNS),
     +		   obs ( MXSTNS, NVAR ) 

        REAL*8     r8date (5)
C*
	INTEGER	   irundt (5), irptdt (5), wmoid (MXSTNS),
     +		   iqca ( MXSTNS, NVAR ), iqcr ( MXSTNS, NVAR ) 

C*	The following variable code names define, in accordance
C*	with the MADIS table files "static/hydrotbl.txt" and
C*	"static/hydrovcn.txt", the variables that will be read
C*	from the HYDRO data file.

	DATA	 vcname / 'PCP5M  ', 'PCP1H  ', 'PCP3H  ', 'PCP6H  ',
     +		          'PCP12H ', 'PCP24H ', 'RIVFLO ', 'RIVSTG '/
C*-----------------------------------------------------------------------
	iret = 0

C*	Extract the basename from the HYDRO data file and write it to
C*	the decoder log.

	CALL FL_PATH ( hydrfl, hydrdn, hydrbn, ierpth )
	logmsg = 'HYDRO filename:  ' // hydrbn
	CALL DC_WLOG ( 0, 'DC', 2, logmsg, ierwlg )

C*	Save the HYDRO data file basename in a separate variable
C*	for later use.

	cmsobn = hydrbn(1:18)

C*	The MADIS (Meteorological Assimilation Data Ingest System)
C*	software from FSL will be used to read the HYDRO data file.
C*	Initialize this software.

	CALL MINIT ( 'HYDRO', 'FSL', .false., ierfin )
	IF ( ierfin .ne. 0 ) THEN
	  CALL UT_EMSG ( 0, 'MINIT', ierfin )
	  RETURN
	END IF

C*	Using the HYDRO data file basename, comput the 
C*	MADIS date-time.

	READ ( UNIT = hydrbn, FMT = '( I4.4, 2I2.2, 1X, 2I2.2 )',
     +         IOSTAT = ier ) ifyear, ifmnth, ifdays, ifhour, ifminu
	IF ( ier .ne. 0 ) THEN
	  CALL UT_EMSG ( 0, 'READ', ier )
	  RETURN
	END IF
	CALL MCHRTIM ( ifyear, ifmnth, ifdays, ifhour, ifminu,
     +	               cstrtm, ierfct )
	IF ( ierfct .ne. 0 ) THEN
	  CALL UT_EMSG ( 0, 'MCHRTIM', ierfct )
	  RETURN
	END IF

C*	Retrieve all of the stations for which there is data in the
C*	HYDRO data file.

	CALL MHYDROSTA ( cstrtm, nstns, stnm, wmoid, slat, slon, selv,
     +                   crpttm, cprovdr, ierfst )
	IF ( ierfst .ne. 0 ) THEN
	  IF ( ierfst .eq. 1006 ) THEN
	    logmsg = 'contained no reports'
	    CALL DC_WLOG ( 0, 'DC', 2, logmsg, ierwlg )
	  ELSE
	    CALL UT_EMSG ( 0, 'MHYDROSTA', ierfst )
	  END IF
	  RETURN
	END IF

C*	Now, retrieve the data for these stations.

	DO ii = 1, NVAR
	  CALL MGETHYDRO ( cstrtm, vcname ( ii ), itmp, nnmsg,
     +	                   obs ( 1, ii ), qcd ( 1, ii ),
     +	                   iqca ( 1, ii ), iqcr ( 1, ii ), ierfgs )
	  IF ( ( ierfgs .ne. 0 ) .and. ( ierfgs .ne. 1006 ) ) THEN
	    CALL UT_EMSG ( 0, 'MGETACARS', ierfgs )
	    RETURN
	  END IF
	END DO

C*	Set the pointers for the interface arrays.

	CALL HY_IFSP ( rimnem, cimnem, ierfsp )
	IF ( ierfsp .ne. 0 ) RETURN

C*	Open the BUFR tables file.

	CALL FL_SOPN ( bufrtb, iunbft, ierspn )
	IF ( ierspn .ne. 0 ) THEN
	  CALL DC_WLOG ( 0, 'FL', ierspn, bufrtb, ierwlg )
	  RETURN
	END IF

C*	Open the BUFR output file.

	CALL FL_GLUN ( iunbfo, iergln )
	IF ( iergln .ne. 0 ) THEN
	  CALL DC_WLOG ( 0, 'FL', iergln, ' ', ierwlg )
	  RETURN
	END IF

C*	Connect the BUFR tables and output files to the BUFR interface.

	CALL OPENBF ( iunbfo, 'NUL', iunbft )

C*	Close the BUFR tables file.

	CALL FL_CLOS ( iunbft, iercls )
	IF ( iercls .ne. 0 ) THEN
	  CALL DC_WLOG ( 0, 'FL', iercls, ' ', ierwlg )
	END IF

C*      Get the run date-time.

        CALL UT_GET_RUNDT ( cldt, irundt, iergrd )
        IF ( iergrd .ne. 0 ) RETURN

C*	Write the number of reports to the decoder log.

	WRITE ( UNIT = logmsg, FMT = '( A, I6, A )' )
     +		'contained ', nstns, ' reports'
	CALL DC_WLOG ( 0, 'DC', 2, logmsg, ierwlg )

C*	Loop on each report.

	DO ii = 1, nstns

C*    	  Start an entry for this report in the decoder log.

	  logmsg = '--------------------'
	  CALL DC_WLOG ( 3, 'DC', 2, logmsg, ierwlg )

C*	  Initialize the interface values arrays.

	  CALL HY_IFIV ( ierfiv )

C*	  Compute and store the date-time.

	  CALL MINTTIM ( crpttm ( ii ), ifyear, ifmnth, ifdays,
     +	                 ifhour, ifminu, ierftm )
	  IF ( ierftm .ne. 0 ) THEN
	    CALL UT_EMSG ( 2, 'MINTTIM', ierftm )
  	  ELSE
	    rivals ( iryear ) = FLOAT ( 1900 + ifyear )
	    rivals ( irmnth ) = FLOAT ( ifmnth )
	    rivals ( irdays ) = FLOAT ( ifdays )
	    rivals ( irhour ) = FLOAT ( ifhour )
	    rivals ( irminu ) = FLOAT ( ifminu )
            r8date (1) = rivals ( iryear )
            r8date (2) = rivals ( irmnth )
            r8date (3) = rivals ( irdays )
            r8date (4) = rivals ( irhour )
            r8date (5) = rivals ( irminu )
	  END IF

C*	  Station and provider IDs.

	  civals ( ichyid ) = stnm ( ii )(1:8)
	  civals ( icprvid ) = cprovdr ( ii )(1:10)

C*     	  Latitude, longitude, and elevation.

	  rivals ( irslat ) = slat ( ii )
	  rivals ( irslon ) = slon ( ii )
	  rivals ( irselv ) = selv ( ii )

C*	  River flow and river stage.                                  

          rivals (irrflo) = UT_MDRI ( obs ( ii, 7 ) )
          rivals (irrstg) = UT_MDRI ( obs ( ii, 8 ) )

C*	  5-min precip (and associated QC values).

	  CALL UT_MDQI ( ii, 1, obs, qcd, iqca, iqcr, MXSTNS,
     +	               rivals ( irpcp5m ), civals ( icpcp5qd ),
     +	               rivals ( irpcp5qa ), rivals ( irpcp5qr ), ierf )

C*	  1-hr precip (and associated QC values).

	  CALL UT_MDQI ( ii, 2, obs, qcd, iqca, iqcr, MXSTNS,
     +	               rivals ( irpcp1h ), civals ( icpcp1qd ),
     +	               rivals ( irpcp1qa ), rivals ( irpcp1qr ), ierf )

C*	  3-hr precip (and associated QC values).

	  CALL UT_MDQI ( ii, 3, obs, qcd, iqca, iqcr, MXSTNS,
     +	               rivals ( irpcp3h ), civals ( icpcp3qd ),
     +	               rivals ( irpcp3qa ), rivals ( irpcp3qr ), ierf )

C*	  6-hr precip (and associated QC values).

	  CALL UT_MDQI ( ii, 4, obs, qcd, iqca, iqcr, MXSTNS,
     +	               rivals ( irpcp6h ), civals ( icpcp6qd ),
     +	               rivals ( irpcp6qa ), rivals ( irpcp6qr ), ierf )

C*	  12-hr precip (and associated QC values).

	  CALL UT_MDQI ( ii, 5, obs, qcd, iqca, iqcr, MXSTNS,
     +	              rivals ( irpcp12h ), civals ( icpcp12qd ),
     +	              rivals ( irpcp12qa ), rivals ( irpcp12qr ), ierf )

C*	  24-hr precip (and associated QC values).

	  CALL UT_MDQI ( ii, 6, obs, qcd, iqca, iqcr, MXSTNS,
     +	              rivals ( irpcp24h ), civals ( icpcp24qd ),
     +	              rivals ( irpcp24qa ), rivals ( irpcp24qr ), ierf )

C*	  Write the interface output to the decoder log.

	  CALL HY_IFPT ( 3, rimnem, cimnem, ierfpt )

C*	  Don't create BUFR output for reports that are more than
C*	  NHOURS before or more than 3 hours after the run time.

          CALL UT_CHECK_BUFRRPTDT ( 2, irundt, r8date(1), r8date(2),
     +                              r8date(3), r8date(4), r8date(5),
     +                              nhours, 180, irptdt, iercrt )
          IF ( iercrt .ne. 0 ) CYCLE

C*	  Convert interface-format data for this report
C*	  into BUFR output and then write the BUFR output
C*	  to the BUFR output stream.

	  CALL HY_BUFR ( iunbfo, irundt, cmsobn, ierbfr )
	END DO

C*	Make sure that all BUFR output has been written before exiting. 

	CALL UT_WBFR ( iunbfo, 'hydro', 1, ierwbf )

	CALL CLOSBF ( iunbfo )
	CALL FL_CLAL ( iercal )
C*
	RETURN
	END