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

Annotation of /MITgcm/pkg/diagnostics/diagstats_fill.F

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


Revision 1.1 - (hide annotations) (download)
Fri May 20 07:28:51 2005 UTC (19 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57k_post, checkpoint57i_post, checkpoint57j_post
Add new capability: compute & write Global/Regional & per level statistics

1 jmc 1.1 C $Header: $
2     C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: DIAGSTATS_FILL
8     C !INTERFACE:
9     SUBROUTINE DIAGSTATS_FILL( inpFld, ndId, kInQSd, region2fill,
10     I kLev, nLevs, bibjflg, biArg, bjArg, myThid )
11    
12     C !DESCRIPTION:
13     C***********************************************************************
14     C compute statistics over 1 tile
15     C and increment the diagnostics array
16     C***********************************************************************
17     C !USES:
18     IMPLICIT NONE
19    
20     C == Global variables ===
21     #include "EEPARAMS.h"
22     #include "SIZE.h"
23     #include "DIAGNOSTICS_SIZE.h"
24     #include "DIAGNOSTICS.h"
25    
26     C !INPUT PARAMETERS:
27     C***********************************************************************
28     C Arguments Description
29     C ----------------------
30     C inpFld ..... Field to increment diagnostics array
31     C ndId ... Diagnostics Id Number (in available diag list) of diag to process
32     C kInQSd ... Pointer to the slot in qSdiag to fill
33     C region2fill array, indicates whether to compute statistics over region
34     C "j" (if region2fill(j)=1) or not (if region2fill(j)=0)
35     C kLev ..... Integer flag for vertical levels:
36     C > 0 (any integer): WHICH single level to increment in qSdiag.
37     C 0,-1 to increment "nLevs" levels in qSdiag,
38     C 0 : fill-in in the same order as the input array
39     C -1: fill-in in reverse order.
40     C nLevs ...... indicates Number of levels of the input field array
41     C (whether to fill-in all the levels (kLev<1) or just one (kLev>0))
42     C bibjflg .... Integer flag to indicate instructions for bi bj loop
43     C 0 indicates that the bi-bj loop must be done here
44     C 1 indicates that the bi-bj loop is done OUTSIDE
45     C 2 indicates that the bi-bj loop is done OUTSIDE
46     C AND that we have been sent a local array (with overlap regions)
47     C 3 indicates that the bi-bj loop is done OUTSIDE
48     C AND that we have been sent a local array
49     C AND that the array has no overlap region (interior only)
50     C NOTE - bibjflg can be NEGATIVE to indicate not to increment counter
51     C biArg ...... X-direction tile number - used for bibjflg=1-3
52     C bjArg ...... Y-direction tile number - used for bibjflg=1-3
53     C myThid :: my thread Id number
54     C***********************************************************************
55     C NOTE: User beware! If a local (1 tile only) array
56     C is sent here, bibjflg MUST NOT be set to 0
57     C or there will be out of bounds problems!
58     C***********************************************************************
59     _RL inpFld(*)
60     INTEGER ndId, kInQSd
61     INTEGER region2fill(0:nRegions)
62     INTEGER kLev, nLevs, bibjflg, biArg, bjArg
63     INTEGER myThid
64     CEOP
65    
66     C !LOCAL VARIABLES:
67     C ===============
68     c INTEGER m, n
69     INTEGER sizI1,sizI2,sizJ1,sizJ2
70     INTEGER sizTx,sizTy
71     INTEGER iRun, jRun, k, bi, bj
72     INTEGER kFirst, kLast
73     INTEGER kd, kd0, ksgn, kStore
74     CHARACTER*8 parms1
75     CHARACTER*(MAX_LEN_MBUF) msgBuf
76     INTEGER km, km0
77    
78     C If-sequence to see if we are a valid and an active diagnostic
79     c IF ( ndId.NE.0 .AND. kInQSd.NE.0 ) THEN
80    
81     C- select range for 1rst & 2nd indices to accumulate
82     C depending on variable location on C-grid,
83     parms1 = gdiag(ndId)(1:8)
84     IF ( parms1(2:2).EQ.'Z' ) THEN
85     iRun = sNx+1
86     jRun = sNy+1
87     c ELSEIF ( parms1(2:2).EQ.'U' ) THEN
88     c iRun = sNx+1
89     c jRun = sNy
90     c ELSEIF ( parms1(2:2).EQ.'V' ) THEN
91     c iRun = sNx
92     c jRun = sNy+1
93     ELSE
94     iRun = sNx
95     jRun = sNy
96     ENDIF
97    
98     C- Dimension of the input array:
99     IF (ABS(bibjflg).EQ.3) THEN
100     sizI1 = 1
101     sizI2 = sNx
102     sizJ1 = 1
103     sizJ2 = sNy
104     iRun = sNx
105     jRun = sNy
106     ELSE
107     sizI1 = 1-OLx
108     sizI2 = sNx+OLx
109     sizJ1 = 1-OLy
110     sizJ2 = sNy+OLy
111     ENDIF
112     IF (ABS(bibjflg).GE.2) THEN
113     sizTx = 1
114     sizTy = 1
115     ELSE
116     sizTx = nSx
117     sizTy = nSy
118     ENDIF
119     C- Which part of inpFld to add : k = 3rd index,
120     C and do the loop >> do k=kFirst,kLast <<
121     IF (kLev.LE.0) THEN
122     kFirst = 1
123     kLast = nLevs
124     ELSEIF ( nLevs.EQ.1 ) THEN
125     kFirst = 1
126     kLast = 1
127     ELSEIF ( kLev.LE.nLevs ) THEN
128     kFirst = kLev
129     kLast = kLev
130     ELSE
131     STOP 'ABNORMAL END in DIAGSTATS_FILL: kLev > nLevs > 0'
132     ENDIF
133     C- Which part of qSdiag to update: kd = 3rd index,
134     C and do the loop >> do k=kFirst,kLast ; kd = kd0 + k*ksgn <<
135     C 1rst try this: for the mask: km = km0 + k*ksgn so that kd= km + kInQSd - 1
136     IF ( kLev.EQ.-1 ) THEN
137     ksgn = -1
138     kd0 = kInQSd + nLevs
139     km0 = 1 + nLevs
140     ELSEIF ( kLev.EQ.0 ) THEN
141     ksgn = 1
142     kd0 = kInQSd - 1
143     km0 = 0
144     ELSE
145     ksgn = 0
146     kd0 = kInQSd + kLev - 1
147     km0 = kLev
148     ENDIF
149    
150     C- Check for consistency with Nb of levels reserved in storage array
151     kStore = kd0 + MAX(ksgn*kFirst,ksgn*kLast) - kInQSd + 1
152     IF ( kStore.GT.kdiag(ndId) ) THEN
153     _BEGIN_MASTER(myThid)
154     WRITE(msgBuf,'(2A,I3,A)') 'DIAGSTATS_FILL: ',
155     & 'exceed Nb of levels(=',kdiag(ndId),' ) reserved '
156     CALL PRINT_ERROR( msgBuf , myThid )
157     WRITE(msgBuf,'(2A,I4,2A)') 'DIAGSTATS_FILL: ',
158     & 'for Diagnostics #', ndId, ' : ', cdiag(ndId)
159     CALL PRINT_ERROR( msgBuf , myThid )
160     WRITE(msgBuf,'(2A,2I4,I3)') 'calling DIAGSTATS_FILL ',
161     I 'with kLev,nLevs,bibjFlg=', kLev,nLevs,bibjFlg
162     CALL PRINT_ERROR( msgBuf , myThid )
163     WRITE(msgBuf,'(2A,I6,A)') 'DIAGSTATS_FILL: ',
164     I '==> trying to store up to ', kStore, ' levels'
165     CALL PRINT_ERROR( msgBuf , myThid )
166     STOP 'ABNORMAL END: S/R DIAGSTATS_FILL'
167     _END_MASTER(myThid)
168     ENDIF
169    
170     IF ( bibjflg.EQ.0 ) THEN
171    
172     DO bj=myByLo(myThid), myByHi(myThid)
173     DO bi=myBxLo(myThid), myBxHi(myThid)
174     DO k = kFirst,kLast
175     kd = kd0 + ksgn*k
176     km = km0 + ksgn*k
177     CALL DIAGSTATS_LOCAL(
178     U qSdiag(0,0,kd,bi,bj),
179     I inpFld,
180     I sizI1,sizI2,sizJ1,sizJ2,nLevs,sizTx,sizTy,
181     I iRun,jRun,k,bi,bj,
182     I km, bi, bj, region2fill,
183     I ndId, gdiag(ndId), myThid )
184     ENDDO
185     ENDDO
186     ENDDO
187     ELSE
188     bi = MIN(biArg,sizTx)
189     bj = MIN(bjArg,sizTy)
190     DO k = kFirst,kLast
191     kd = kd0 + ksgn*k
192     km = km0 + ksgn*k
193     CALL DIAGSTATS_LOCAL(
194     U qSdiag(0,0,kd,biArg,bjArg),
195     I inpFld,
196     I sizI1,sizI2,sizJ1,sizJ2,nLevs,sizTx,sizTy,
197     I iRun,jRun,k,bi,bj,
198     I km, biArg, bjArg, region2fill,
199     I ndId, gdiag(ndId), myThid )
200     ENDDO
201     ENDIF
202    
203     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
204     c ELSE
205    
206     c ENDIF
207    
208     RETURN
209     END

  ViewVC Help
Powered by ViewVC 1.1.22