/[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.4 - (hide annotations) (download)
Tue Feb 5 15:31:19 2008 UTC (16 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59o, checkpoint59n, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q
Changes since 1.3: +3 -3 lines
minor modifications for many diagnostics:
- modify "available_diagnostics.log" and diagnostics summary (write mate number)
- use wider (integer) format (generally, use I6) to write diagnostics number
- rename numdiags --> numDiags (to differentiate from mdiag)

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

  ViewVC Help
Powered by ViewVC 1.1.22