SUBROUTINE LS_SEC3( lszrpt, lsfrpt, ipt, iret )
C************************************************************************
C* LS_SEC3							        *
C*								        *
C* This subroutine calls the routines to decode the groups in section 3 *
C* of the WMO FM12 report.  This section begins with the 333 group.     *
C* The number of groups in the section will vary.                       *
C*								        *
C* LS_SEC3  ( LSZRPT, LSFRPT, IPT, IRET )   			        *
C*							                *
C* Input parameters:						        *
C*      LSZRPT          INTEGER         Report length                   *
C*      LSFRPT          CHARACTER       Report array                    *
C*	LSEC3           INTEGER         Length of section 3 in report   *
C*      ISEC3           INTEGER         Pointer to start of section 3   *
C*	RIVALS(IRNCL0)  REAL		Number of section 1 cloud layers*
C*								        *
C* Input and Output parameters:                                         *
C*	IPT             INTEGER         Pointer to groups in report     *
C*								        *
C* Output parameters:						        *
C*	IRET		INTEGER		Return code		        *
C*				   	 0 = normal return 	        *
C*                                       1 = problems                   *
C* 								        *
C**								        *
C* Log:								        *
C* R. Hollern/NCEP       4/96                                           *
C* R. Hollern/NCEP       1/98   Changed interface, cleaned up code      *
C* A. Hardy/GSC          1/98   Reordered calling sequence, added GEMINC*
C* R. Hollern/NCEP       1/00   Modified for new interface variable sets*
C* R. Hollern/NCEP       4/00   Changed iparam value for 911ff group    *
C* C. Caruso Magee/NCEP  4/07   Break out of do while loop if a second  *
C*                              field is found of type which was        *
C*                              already decoded (may indicate bad       *
C*                              spacing or missing section delimeter).  *
C* C. Caruso Magee/NCEP 4/07    Print log msg if repeat field found.    *
C************************************************************************
        INCLUDE          'GEMPRM.PRM'
        INCLUDE          'lscmn.cmn'
C*
        CHARACTER*(*)   lsfrpt
C*
        INTEGER  jflg(11)
C------------------------------------------------------------------------
        iret = 0
        lvl = 0
C
C*      Determine where to store section 3 cloud data in interface 
C*      arrays.
C
        xly = rivals ( irnclo ) 
C
        IF ( xly .gt. 0.0 .and. xly .lt. 4.0 ) THEN
            lvl = xly + .5
          ELSE
            lvl = 0
        END IF
C
C*      A group should only appear once in a section.  This array will
C*      be used to flag those groups that are decoded in the section.
C
        DO i = 1,11
            jflg ( i ) = 0
        END DO
C
        iend = isec3 + lsec3 - 1
C
        DO WHILE ( ipt .lt. iend )
C
            ipt = ipt + 1
C
            IF ( lsfrpt ( ipt:ipt+1 ) .eq. ' 1' ) THEN
              IF ( jflg ( 1 ) .eq. 0 ) THEN
C
C*              Decode the maximum temperature group.
C             
                ipt = ipt + 2
                iparam = 5
                CALL  LS_TEMP ( lsfrpt, iparam, ipt, jret )
                jflg ( 1 ) = 1
              ELSE
                logmsg = "repeat field 1 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:35), ier)
                ipt = iend
              END IF
            ELSE IF ( lsfrpt ( ipt:ipt+1 ) .eq. ' 2' ) THEN
              IF ( jflg ( 2 ) .eq. 0 ) THEN
C
C*              Decode the minimum temperature group.
C             
                ipt = ipt + 2
                iparam = 6
                CALL  LS_TEMP ( lsfrpt, iparam, ipt, jret )
                jflg ( 2 ) = 1
              ELSE
                logmsg = "repeat field 2 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:35), ier)
                ipt = iend
              END IF
            ELSE IF ( lsfrpt ( ipt:ipt+1 ) .eq. ' 3' ) THEN
              IF ( jflg ( 11 ) .eq. 0 ) THEN
C
C*              Decode the state of the ground without snow 
C*              or measurable ice cover.
C             
                ipt = ipt + 2
                CALL  LS_SGRD ( lsfrpt, ipt, jret )
                jflg ( 11 ) = 1
              ELSE
                logmsg = "repeat field 3 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:35), ier)
                ipt = iend
              END IF
            ELSE IF ( lsfrpt ( ipt:ipt+1 ) .eq. ' 4' ) THEN
              IF ( jflg ( 10 ) .eq. 0 ) THEN
C
C*              Decode the total depth of snow group and
C*              state of the ground.
C             
                ipt = ipt + 2
                CALL  LS_TSNW ( lsfrpt, ipt, jret )
                jflg ( 10 ) = 1
              ELSE
                logmsg = "repeat field 4 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:35), ier)
                ipt = iend
              END IF
            ELSE IF ( lsfrpt ( ipt:ipt+2 ) .eq. ' 55' ) THEN
C
C*              Skip 5-group and the supplementary group which
C*              follows.  Do this to avoid problems.
C             
                ipt = ipt + 8
            ELSE IF ( ( lsfrpt ( ipt:ipt+2 ) .eq. ' 58' .or.
     +                  lsfrpt ( ipt:ipt+2 ) .eq. ' 59' ) ) THEN
              IF ( jflg ( 3 ) .eq. 0 ) THEN
C
C*              Decode the 24 hour pressure change group.
C             
                ipt = ipt + 2
                CALL  LS_PR24 ( lsfrpt, ipt, jret )
                jflg ( 3 ) = 1
              ELSE
                logmsg = "repeat field 58 or 59 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:40), ier)
                ipt = iend
              END IF
            ELSE IF ( lsfrpt ( ipt:ipt+1 ) .eq. ' 6' ) THEN
              IF ( jflg ( 4 ) .eq. 0 ) THEN
C
C*              Decode the precipitation group.
C             
                ipt = ipt + 2
                iparam = 0
                CALL  LS_PREC ( lsfrpt, iparam, ipt, jret )
                jflg ( 4 ) = 1
              ELSE
                logmsg = "repeat field 6 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:35), ier)
                ipt = iend
              END IF
            ELSE IF ( lsfrpt ( ipt:ipt+1 ) .eq. ' 7' ) THEN
              IF ( jflg ( 5 ) .eq. 0 ) THEN
C
C*              Decode the 24-hour precipitation group.
C             
                ipt = ipt + 2
                iparam = 1
                CALL  LS_PREC ( lsfrpt, iparam, ipt, jret )
                jflg ( 5 ) = 1
              ELSE
                logmsg = "repeat field 7 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:35), ier)
                ipt = iend
              END IF
            ELSE IF ( lsfrpt ( ipt:ipt+5 ) .eq. ' 80000' ) THEN
C
C*              Don't decode the additional data in regional code form.
C             
                RETURN
            ELSE IF ( lsfrpt ( ipt:ipt+1 ) .eq. ' 8' ) THEN
C
C*              Decode the cloud groups.
C             
                ipt = ipt + 2
                lvl = lvl + 1
                IF ( lvl .lt. 8 ) THEN
                    CALL  LS_CLD3 ( lsfrpt, lvl, ipt, jret )
                ELSE
                    ipt = ipt + 3
                END IF
            ELSE IF ( lsfrpt ( ipt:ipt+3 ) .eq. ' 904' ) THEN
C
C*              Set xm907g to -1.0, so that if a supplementary wind
C*              group follows the 904ff group, the period for the
C*              group will be set to missing.
C
                xm907g = -1.0
C
C*              This group is not currently decoded.
C             
                ipt = ipt + 3
            ELSE IF ( lsfrpt ( ipt:ipt+3 ) .eq. ' 907' ) THEN
C
C*              Decode the time duration of phenomenom group.
C             
                ipt = ipt + 4
                CALL  LS_TDUR ( lsfrpt, ipt, jret )
            ELSE IF ( lsfrpt ( ipt:ipt+3 ) .eq. ' 910' ) THEN
              IF ( jflg ( 6 ) .eq. 0 ) THEN
C
C*              Decode the wind gust from 910ff group.
C             
                ipt = ipt + 4
                iparam = 1   
                CALL  LS_WSPD ( lsfrpt, iparam, ipt, jret )
                jflg ( 6 ) = 1
              ELSE
                logmsg = "repeat field 910 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:35), ier)
                ipt = iend
              END IF
            ELSE IF ( lsfrpt (ipt:ipt+3) .eq. ' 911' ) THEN
              IF ( jflg ( 8 ) .eq. 0 ) THEN
C
C*              Decode the wind gust from 911ff group.
C             
                ipt = ipt + 4
                iparam = 3
                CALL  LS_WSPD ( lsfrpt, iparam, ipt, jret )
                jflg ( 8 ) = 1
              ELSE
                logmsg = "repeat field 911 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:35), ier)
                ipt = iend
              END IF
            ELSE IF ( lsfrpt ( ipt:ipt+3 ) .eq. ' 912' ) THEN
              IF ( jflg ( 7 ) .eq. 0 ) THEN
C
C*              Decode the wind gust from 912ff group.
C             
                ipt = ipt + 4
                iparam = 2
                CALL  LS_WSPD ( lsfrpt, iparam, ipt, jret )
                jflg ( 7 ) = 1
              ELSE
                logmsg = "repeat field 912 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:35), ier)
                ipt = iend
              END IF
            ELSE IF ( lsfrpt ( ipt:ipt+3 ) .eq. ' 931' ) THEN
              IF ( jflg ( 9 ) .eq. 0 ) THEN
C
C*              Decode the amount of the freshly fallen snow.
C             
                ipt = ipt + 4
                CALL  LS_FSNW ( lsfrpt, ipt, jret )
                jflg (9) = 1
              ELSE
                logmsg = "repeat field 931 found in Sec. 3"
                CALL DC_WLOG (2, 'DC', 2, logmsg(1:35), ier)
                ipt = iend
              END IF
            END IF
        END DO
C*
	RETURN
        END