SUBROUTINE SW_DCOD ( cldt, bufrtn, nhours, iret )
C************************************************************************
C* SW_DCOD								*
C*									*
C* This routine decodes bulletins containing snow cover, depth/density  *
C  and/or water equivalent data into NCEP BUFR format.                  *
C*									*
C* SW_DCOD ( CLDT, 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		10/20						*
C* M. Weiss/IMSG        06/21    MAXOUT (200000) --> MAXOUT (199900)    *                                   
C* J. Ator/NCEP         12/21    Use ISETPRM to increase MXMSGL         *
C************************************************************************
	INCLUDE		'GEMPRM.PRM'
	INCLUDE		'BRIDGE.PRM'
        INCLUDE         'BUFR.CMN'
C*
        CHARACTER*(*)   cldt, bufrtn
C*
C*      Maximum number of descriptors within Section 3 of a BUFR snow
C*      CDE message.
C*
        PARAMETER       ( MXDSC = 100 )
C*
	CHARACTER	bull*(DCMXBF), cbull*(DCMXBF),
     +			seqnum*8, buhd*8, cborg*8, bulldt*8, bbb*8,
     +                  rundt*12, sysdt*12, logmsg*200,
     +			bufrdn*(DCMXLN), bufrbn*(DCMXLN),
     +                  bfstyp*8, cdesc( MXDSC )*6, cntry*80,
     +                  lstn*32, wgoslid*16
C*
C*      Maximum number of data values in a snow CDE subset.
C*
        PARAMETER       ( MXMN = 500 )
C*
        REAL*8          r8in ( MXMN )
C*
	INTEGER		irundt (5), irptdt (5), ibull ( DCMXBF / 4 )
C
	LOGICAL		bullok, msgok, gotwigos
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*      Set any configurable BUFRLIB parameters to optimize them for
C*      the needs of this program.  This includes setting any
C*      parameters associated with BUFRLIB features that we won't be
C*      using in this program to artificially low values, which in turn
C*      will prevent the unnecessary allocation of a lot of memory that
C*      will never be used.
C
        CALL ISETPRM ( 'NFILES', 4 )
        CALL ISETPRM ( 'MXMSGL', 3000000 )
        CALL ISETPRM ( 'MAXMEM', 100000 )
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/dcscde',
     +          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
C*      encoded using edition 4 and up to 200K bytes in size.  Also
C*      read in master code and flag table entries for later use
C*      with subroutine GETCFMNG.
C
        CALL PKVS01 ( 'BEN', 4 )
        CALL MAXOUT ( 199900 )
        CALL CODFLG ( 'Y' )

	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
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
              bullok = .true.
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.
            END IF
          END IF
C
	  DO WHILE ( bullok )
C
C*	    Locate the next BUFR message within the bulletin, and store
C*	    it within an equivalenced integer array.
C
	    ipt1 = INDEX ( bull ( ibptr : lenb ), 'BUFR' )
	    IF ( ipt1 .eq. 0 )  THEN
	      bullok = .false.
C
C*            Make sure that all BUFR output for this bulletin
C*            has been written to the BUFR output stream before
C*            going back to DC_GBUL and waiting for a new bulletin
C*            on the input pipe.
C
              CALL UT_WBFR ( iubfmn, 'scde', 1, ierwbf )
            ELSE
              istart = ibptr + ipt1 - 1
              ibptr = istart + 4
              cbull = bull ( istart : lenb )
              msgok = .false.
              msglen = IUPBS01 ( ibull, 'LENM' )
              IF ( ( msglen .gt. lenb ) .or.
     +            ( cbull ( msglen-3 : msglen ) .ne. '7777' ) ) THEN
                logmsg = 'ERROR: corrupt BUFR message'
                CALL DC_WLOG ( 2, 'DC', 2, logmsg, ierwlg )
              ELSE
C
C*	        Retrieve the Section 3 descriptors from the message
C*              to ensure it contains snow CDE data.
C
                CALL UPDS3 ( ibull, MXDSC, cdesc, ndesc )
                ii = 1
                DO WHILE ( ( ii .le. ndesc ) .and. ( .not. msgok ) )
                  IF ( ( cdesc(ii) .eq. '307101' ) .or.
     +                 ( cdesc(ii) .eq. '307103' ) ) THEN
                    msgok = .true.
                  ELSE
                    ii = ii + 1
                  END IF
                END DO
                IF ( .not. msgok ) THEN
                  IF ( ( ndesc .eq. 18 ) .and.
     +                ( cdesc( 1) .eq. '001101' ) .and.
     +                ( cdesc( 3) .eq. '001019' ) .and.
     +                ( cdesc( 7) .eq. '004003' ) .and.
     +                ( cdesc(10) .eq. '005001' ) .and.
     +                ( cdesc(14) .eq. '012101' ) .and.
     +                ( cdesc(16) .eq. '002177' ) .and.
     +                ( cdesc(17) .eq. '020062' ) .and.
     +                ( cdesc(18) .eq. '013013' ) ) THEN
                    msgok = .true.
                  ELSE
                    logmsg = 'message does not follow WMO template:'
                    CALL DC_WLOG ( 2, 'DC', 2, logmsg, ierwlg )
                    DO ii = 1, ndesc
                      WRITE ( logmsg, FMT = '(I6, A, A)' )
     +                  ii, ': ', cdesc(ii)
                      CALL DC_WLOG ( 2, 'DC', 2, logmsg, ierwlg )
                    END DO
                  END IF
                END IF
              END IF
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
              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.
                ELSE
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
                  CALL UFBINT ( iubfma, r8in, MXMN, 1, nlv,
     +                          'YEAR MNTH DAYS HOUR MINU' )
                  rptyr = UT_BMRI ( r8in (1) )
                  rptmo = UT_BMRI ( r8in (2) )
                  rptdy = UT_BMRI ( r8in (3) )
                  rpthr = UT_BMRI ( r8in (4) )
                  rptmi = UT_BMRI ( r8in (5) )
                  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
C*                  Open a BUFR message for output.
C
                    ibfdt = ( irptdt (1) * 1000000 )  +
     +                      ( irptdt (2) * 10000 )  +
     +                      ( irptdt (3) * 100 )  +  irptdt (4)
                    CALL OPENMB ( iubfmn, 'NC000015', ibfdt )
C
C*                  Write the report date/time.
C
                    CALL UFBINT ( iubfmn, r8in, MXMN, 1, nlv,
     +                            'YEAR MNTH DAYS HOUR MINU' )
C
C*                  Read and write the main report data.
C
                    CALL READLC ( iubfma, lstn, 'LSTN' )
                    CALL UFBINT ( iubfma, r8in, MXMN, 1, nlv,
     +                    'STID NSID TOST WGOSIDS WGOSISID WGOSISNM' )
                    CALL UFBINT ( iubfmn, r8in, MXMN, 1, nlv,
     +                    'STID NSID TOST WGOSIDS WGOSISID WGOSISNM' )
                    IF ( ( IBFMS ( r8in (4) ) .eq. 0 ) .or.
     +                   ( IBFMS ( r8in (5) ) .eq. 0 ) .or.
     +                   ( IBFMS ( r8in (6) ) .eq. 0 ) ) THEN
                      gotwigos = .true.
                      CALL READLC ( iubfma, wgoslid, 'WGOSLID' )
                    ELSE
                      gotwigos = .false.
                    END IF
C
                    iercmn = -1
                    IF ( IBFMS ( r8in (1) ) .eq. 0 )
     +                CALL GETCFMNG ( iubfma, 'STID', IDINT( r8in (1) ),
     +                                ' ', -1, cntry, lcntry, iercmn )
                    IF ( iercmn .eq. 0 ) THEN
                      logmsg = 'Country: ' // cntry(1:lcntry) //
     +                         ', Station: ' // lstn
                    ELSE
                      logmsg = 'Country: UNKNOWN' // 
     +                         ', Station: ' // lstn
                    END IF
                    CALL DC_WLOG ( 2, 'DC', 2, logmsg, ierwlg )
C
                    CALL UFBINT ( iubfma, r8in, MXMN, 1, nlv,
     +                    'CLATH CLONH HSMSL TMDB MODM SOGR TOSD ' //
     +                    'SDEN MSWEM SWEMS' )
                    CALL UFBINT ( iubfmn, r8in, MXMN, 1, nlv,
     +                    'CLATH CLONH HSMSL TMDB MODM SOGR TOSD ' //
     +                    'SDEN MSWEM SWEMS' )
C
                    CALL UFBREP ( iubfma, r8in, 1, MXMN, nlv, 'HSALG' )
                    CALL UFBREP ( iubfmn, r8in, 1, nlv, nlv2, 'HSALG' )
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*                  Write the BUFR output to the BUFR output stream.
C
                    CALL UT_WBFR ( iubfmn, 'scde', 0, ierwbf )
C
                    CALL WRITLC ( iubfmn, lstn, 'LSTN' )
                    IF ( gotwigos ) 
     +                CALL WRITLC ( iubfmn, wgoslid, 'WGOSLID' )
                  END IF
C
                END IF
C
              END DO
C
            END IF
C              
          END DO 
C
	END DO
C*
	RETURN
	END