c

C**** SUBROUTINE GXRSET is called from GREX3, group 19,section 1, and
C     is entered only when the logical RESET is set to 'T' in the
C     SATELLITE.
C     In this example, the time interval is reset so as to ensure that
C     the rate of change of the total amount of a selected "field-value"
C     is neither too large nor too small in a single time step. If out-
C     -of-limits values are encountered, a return is made to the
C     beginning of the time step, and the  calculation is repeated with
C     a more appropriate interval.
C     Its use is illustrated in core-library case 109
C
      SUBROUTINE GXRSET
      INCLUDE 'farray'
      INCLUDE 'grdear'
      INCLUDE 'satear'
      INCLUDE 'grdloc'
      INCLUDE 'satgrd'
      COMMON /NAMFN/NAMFUN,NAMSUB
      CHARACTER*6 NAMFUN,NAMSUB
      COMMON/GENR/RGSP1(8),RECDT,RGSP10(11)
      LOGICAL FIRST
      SAVE FLDLST,FIRST,DTLST
      DATA FIRST/.TRUE./
c
      NAMSUB='GXRSET'
c............................................. sum the field values
      FLDNEW=0.0
      DO 10 IZZ=1,NZ
        CALL FN81(SUM,ANYZ(ISG10,IZZ))
        FLDNEW=FLDNEW+SUM
   10 CONTINUE
      FLDNEW=FLDNEW/FLOAT(NX*NY*NZ)
      IF(ISTEP.EQ.1.AND.FIRST) THEN
        FLDLST=FLDNEW
        DTLST=DT
        FIRST=.FALSE.
      ENDIF
      AFLDN=ABS(FLDNEW)
      AFLDL=ABS(FLDLST)
      IF(ISTEP.GT.1.AND.(AFLDN-AFLDL.LT.RSG10.OR.
     1                   AFLDN-AFLDL.GT.RSG11))  THEN
c.............................................. modify time step
        DT=DTLST*RSG11*RSG12/ABS(AFLDN-AFLDL+TINY)
        WRITE(LUPR1,*)'GXRSET requires time-step repetition'
        CALL WRIT1I('istep   ',istep-1)
        CALL WRIT3R('time    ',tim,'old DT  ',dtlst,'new DT  ',dt)
        CALL WRIT2R('fldlst  ',fldlst,'fldnew  ',fldnew)
        DTLST=DT
c....................................... read in the start-of-step values
        CALL storea(2)
      ELSE
c....................................... dump the end-of-step values
        FLDLST=FLDNEW
        CALL storea(1)
      ENDIF
      NAMSUB='gxrset'
      END
c