/[MITgcm]/MITgcm/pkg/diagnostics/diagnostics_fill.F
ViewVC logotype

Diff of /MITgcm/pkg/diagnostics/diagnostics_fill.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.7 by jmc, Thu May 19 02:29:38 2005 UTC revision 1.10 by jmc, Sun Jul 10 00:57:18 2005 UTC
# Line 6  C $Name$ Line 6  C $Name$
6  CBOP  CBOP
7  C     !ROUTINE: DIAGNOSTICS_FILL  C     !ROUTINE: DIAGNOSTICS_FILL
8  C     !INTERFACE:  C     !INTERFACE:
9        SUBROUTINE DIAGNOSTICS_FILL (inpfld, chardiag,        SUBROUTINE DIAGNOSTICS_FILL(
10       I                kLev, nLevs, bibjflg, biArg, bjArg, myThid)       I                inpFld, chardiag,
11         I                kLev, nLevs, bibjFlg, biArg, bjArg, myThid )
12    
13  C     !DESCRIPTION:  C     !DESCRIPTION:
14  C***********************************************************************  C***********************************************************************
# Line 26  C     !INPUT PARAMETERS: Line 27  C     !INPUT PARAMETERS:
27  C***********************************************************************  C***********************************************************************
28  C  Arguments Description  C  Arguments Description
29  C  ----------------------  C  ----------------------
30  C     inpfld ..... Field to increment diagnostics array  C     inpFld    :: Field to increment diagnostics array
31  C     chardiag ... Character expression for diag to fill  C     chardiag  :: Character expression for diag to fill
32  C     kLev   ..... Integer flag for vertical levels:  C     kLev      :: Integer flag for vertical levels:
33  C                  > 0 (any integer): WHICH single level to increment in qdiag.  C                  > 0 (any integer): WHICH single level to increment in qdiag.
34  C                  0,-1 to increment "nLevs" levels in qdiag,  C                  0,-1 to increment "nLevs" levels in qdiag,
35  C                  0 : fill-in in the same order as the input array  C                  0 : fill-in in the same order as the input array
36  C                  -1: fill-in in reverse order.  C                  -1: fill-in in reverse order.
37  C     nLevs ...... indicates Number of levels of the input field array  C     nLevs     :: indicates Number of levels of the input field array
38  C                  (whether to fill-in all the levels (kLev<1) or just one (kLev>0))  C                  (whether to fill-in all the levels (kLev<1) or just one (kLev>0))
39  C     bibjflg .... Integer flag to indicate instructions for bi bj loop  C     bibjFlg   :: Integer flag to indicate instructions for bi bj loop
40  C                  0 indicates that the bi-bj loop must be done here  C                  0 indicates that the bi-bj loop must be done here
41  C                  1 indicates that the bi-bj loop is done OUTSIDE  C                  1 indicates that the bi-bj loop is done OUTSIDE
42  C                  2 indicates that the bi-bj loop is done OUTSIDE  C                  2 indicates that the bi-bj loop is done OUTSIDE
# Line 43  C                     AND that we have b Line 44  C                     AND that we have b
44  C                  3 indicates that the bi-bj loop is done OUTSIDE  C                  3 indicates that the bi-bj loop is done OUTSIDE
45  C                     AND that we have been sent a local array  C                     AND that we have been sent a local array
46  C                     AND that the array has no overlap region (interior only)  C                     AND that the array has no overlap region (interior only)
47  C                  NOTE - bibjflg can be NEGATIVE to indicate not to increment counter  C                  NOTE - bibjFlg can be NEGATIVE to indicate not to increment counter
48  C     biArg ...... X-direction tile number - used for bibjflg=1-3  C     biArg     :: X-direction tile number - used for bibjFlg=1-3
49  C     bjArg ...... Y-direction tile number - used for bibjflg=1-3  C     bjArg     :: Y-direction tile number - used for bibjFlg=1-3
50  C     myThid     ::  my thread Id number  C     myThid    ::  my thread Id number
51  C***********************************************************************  C***********************************************************************
52  C                  NOTE: User beware! If a local (1 tile only) array  C                  NOTE: User beware! If a local (1 tile only) array
53  C                        is sent here, bibjflg MUST NOT be set to 0  C                        is sent here, bibjFlg MUST NOT be set to 0
54  C                        or there will be out of bounds problems!  C                        or there will be out of bounds problems!
55  C***********************************************************************  C***********************************************************************
56        _RL inpfld(*)        _RL     inpFld(*)
57        CHARACTER*8 chardiag        CHARACTER*8 chardiag
58        INTEGER kLev, nLevs, bibjflg, biArg, bjArg        INTEGER kLev, nLevs, bibjFlg, biArg, bjArg
59        INTEGER myThid        INTEGER myThid
60  CEOP  CEOP
61    
62  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
63    C     ndId      :: diagnostic Id number (in available diagnostics list)
64  C ===============  C ===============
65        INTEGER m, n, j        INTEGER m, n, j, k, l, bi, bj
66        INTEGER ndiagnum, ipointer, iSp, jSd        INTEGER ndId, ipt, iSp
67  c     INTEGER region2fill(0:nRegions)        INTEGER region2fill(0:nRegions)
68          _RL     scaleFact
69    
70          scaleFact = 1. _d 0
71          IF ( bibjFlg.EQ.0 ) THEN
72            bi = 1
73            bj = 1
74          ELSE
75            bi = biArg
76            bj = bjArg
77          ENDIF
78  C--   2D/3D Diagnostics :  C--   2D/3D Diagnostics :
79  C Run through list of active diagnostics to make sure  C Run through list of active diagnostics to make sure
80  C we are trying to fill a valid diagnostic  C we are trying to fill a valid diagnostic
   
       ndiagnum = 0  
       ipointer = 0  
81        DO n=1,nlists        DO n=1,nlists
82         DO m=1,nActive(n)         DO m=1,nActive(n)
83          IF ( chardiag.EQ.flds(m,n) ) THEN          IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
84           ndiagnum = jdiag(m,n)           ipt = idiag(m,n)
85           IF (ndiag(ndiagnum).GE.0) ipointer = idiag(ndiagnum)           IF ( ndiag(ipt,bi,bj).GE.0 ) THEN
86               ndId = jdiag(m,n)
87    C-    diagnostic is valid & active, do the filling:
88               CALL DIAGNOSTICS_FILL_FIELD(
89         I                inpFld, inpFld, scaleFact, 0,
90         I                ndId, ipt, kLev, nLevs,
91         I                bibjFlg, biArg, bjArg, myThid )
92             ENDIF
93          ENDIF          ENDIF
94         ENDDO         ENDDO
95        ENDDO        ENDDO
96    
 C if we are a valid and an active diagnostic, do the filling:  
       IF ( ipointer.NE.0 ) THEN  
         CALL DIAGNOSTICS_FILL_FIELD( inpfld, ndiagnum, ipointer,  
      I                kLev, nLevs, bibjflg, biArg, bjArg, myThid )  
       ENDIF  
   
97  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
98    C--   Global/Regional Statistics :
99    
100    C Run through list of active statistics-diagnostics to make sure
101    C we are trying to compute & fill a valid diagnostic
102    
103          DO n=1,diagSt_nbLists
104           DO m=1,diagSt_nbActv(n)
105            IF ( chardiag.EQ.diagSt_Flds(m,n) .AND. iSdiag(m,n).GT.0 ) THEN
106             iSp = iSdiag(m,n)
107             IF ( qSdiag(0,0,iSp,bi,bj).GE.0. ) THEN
108               ndId = jSdiag(m,n)
109    C-    Find list of regions to fill:
110               DO j=0,nRegions
111                region2fill(j) = diagSt_region(j,n)
112               ENDDO
113    C-    if this diagnostics appears in several lists (with same freq)
114    C     then add regions from other lists
115               DO l=1,diagSt_nbLists
116                DO k=1,diagSt_nbActv(l)
117                 IF ( iSdiag(k,l).EQ.-iSp ) THEN
118                  DO j=0,nRegions
119                   region2fill(j) = MAX(region2fill(j),diagSt_region(j,l))
120                  ENDDO
121                 ENDIF
122                ENDDO
123               ENDDO
124    C-    diagnostics is valid and Active: Now do the filling
125               CALL DIAGSTATS_FILL(
126         I                inpFld, inpFld, scaleFact, 0,
127         I                ndId, iSp, region2fill, kLev, nLevs,
128         I                bibjFlg, biArg, bjArg, myThid )
129             ENDIF
130            ENDIF
131           ENDDO
132          ENDDO
133    
134        RETURN        RETURN
135        END        END

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.10

  ViewVC Help
Powered by ViewVC 1.1.22