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

Contents of /MITgcm/pkg/diagnostics/diagstats_others_calc.F

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


Revision 1.4 - (show annotations) (download)
Mon Aug 25 22:13:51 2014 UTC (9 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65c, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.3: +12 -10 lines
update comments/description and argument name following the changes
 in diagstats_calc.F

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagstats_others_calc.F,v 1.3 2012/09/03 20:29:47 jmc Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 C-- File diagstats_others_calc.F: Routines to calculate regional statistics
7 C and dealing with special type of fields
8 C-- o DIAGSTATS_LM_CALC :: for fields on FIZHI-grid (parse(10)='L' or 'M')
9 C-- o DIAGSTATS_G_CALC :: for land-type fields (parse(10)='G')
10
11 CBOP
12 C !ROUTINE: DIAGSTATS_LM_CALC
13 C !INTERFACE:
14 SUBROUTINE DIAGSTATS_LM_CALC(
15 O statArr,
16 I inpArr, frcArr, scaleFact, power, useFract,
17 I useReg, regMskVal,
18 I nStats,sizI1,sizI2,sizJ1,sizJ2, iRun,jRun,
19 I regMask, arrMask, arrArea,
20 I specialVal, exclSpVal,
21 I k,bi,bj, parsFld, myThid )
22
23 C !DESCRIPTION:
24 C Compute statistics for this tile, level, region
25 C using FIZHI level thickness
26
27 C !USES:
28 IMPLICIT NONE
29
30 #include "EEPARAMS.h"
31 #include "SIZE.h"
32 #ifdef ALLOW_FIZHI
33 #include "fizhi_SIZE.h"
34 #include "gridalt_mapping.h"
35 #endif
36
37 C !INPUT/OUTPUT PARAMETERS:
38 C == Routine Arguments ==
39 C statArr :: output statistics array
40 C inpArr :: input field array to process (compute stats & add to statFld)
41 C frcArr :: fraction used for weighted-average diagnostics
42 C scaleFact :: scaling factor
43 C power :: option to fill-in with the field square (power=2)
44 C useFract :: if True, use fraction-weight
45 C useReg :: how to use region-mask: =0 : not used ;
46 C =1 : grid-center location ; =2 : U location ; =3 : V location
47 C regMskVal :: region-mask identificator value
48 C nStats :: size of output statArr
49 C sizI1,sizI2 :: size of inpArr array: 1rst index range (min,max)
50 C sizJ1,sizJ2 :: size of inpArr array: 2nd index range (min,max)
51 C iRun,jRun :: range of 1rst & 2nd index to process
52 C regMask :: regional mask
53 C arrMask :: mask for this input array
54 C arrArea :: Area weighting factor
55 C specialVal :: special value in input array (to exclude if exclSpVal=T)
56 C exclSpVal :: if T, exclude "specialVal" in input array
57 C k,bi,bj :: level and tile indices used for weighting (mask,area ...)
58 C parsFld :: parser field with characteristics of the diagnostics
59 C myThid :: my Thread Id number
60 INTEGER nStats,sizI1,sizI2,sizJ1,sizJ2
61 INTEGER iRun, jRun
62 _RL statArr(0:nStats)
63 _RL inpArr (sizI1:sizI2,sizJ1:sizJ2)
64 _RL frcArr (sizI1:sizI2,sizJ1:sizJ2)
65 _RL scaleFact
66 INTEGER power
67 LOGICAL useFract
68 INTEGER useReg
69 _RS regMskVal
70 _RS regMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71 _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72 _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73 _RL specialVal
74 LOGICAL exclSpVal
75 INTEGER k, bi, bj
76 CHARACTER*16 parsFld
77 INTEGER myThid
78 CEOP
79
80 #ifdef ALLOW_FIZHI
81 C !LOCAL VARIABLES:
82 LOGICAL useWeight
83 INTEGER kl
84 _RL drLoc
85 #ifndef REAL4_IS_SLOW
86 INTEGER i,j
87 _RS tmp_hFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88 #endif
89
90 c IF ( useFIZHI ) THEN
91
92 IF ( parsFld(10:10).EQ.'L' ) THEN
93 kl = 1 + Nrphys - k
94 useWeight = .TRUE.
95 ELSE
96 kl = 1
97 useWeight = .FALSE.
98 ENDIF
99 drLoc = 1. _d 0
100
101 #ifdef REAL4_IS_SLOW
102 CALL DIAGSTATS_CALC(
103 O statArr,
104 I inpArr, frcArr, scaleFact, power, useFract,
105 I useReg, regMskVal,
106 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
107 I regMask, arrMask,
108 I dpphys(1-OLx,1-OLy,kl,bi,bj), arrArea,
109 I drLoc, specialVal, exclSpVal, useWeight, myThid )
110 #else /* REAL4_IS_SLOW */
111 C make local copy of dpphys (RL type) into RS array tmp_hFac
112 DO j=1-OLy,sNy+OLy
113 DO i=1-OLx,sNx+OLx
114 tmp_hFac(i,j) = dpphys(i,j,kl,bi,bj)
115 ENDDO
116 ENDDO
117 CALL DIAGSTATS_CALC(
118 O statArr,
119 I inpArr, frcArr, scaleFact, power, useFract,
120 I useReg, regMskVal,
121 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
122 I regMask, arrMask, tmp_hFac, arrArea,
123 I drLoc, specialVal, exclSpVal, useWeight, myThid )
124 #endif /* REAL4_IS_SLOW */
125
126 c ENDIF
127 #endif /* ALLOW_FIZHI */
128
129 RETURN
130 END
131
132 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
133
134 CBOP
135 C !ROUTINE: DIAGSTATS_G_CALC
136 C !INTERFACE:
137 SUBROUTINE DIAGSTATS_G_CALC(
138 O statArr,
139 I inpArr, frcArr, scaleFact, power, useFract,
140 I useReg, regMskVal,
141 I nStats,sizI1,sizI2,sizJ1,sizJ2, iRun,jRun,
142 I regMask, arrArea,
143 I specialVal, exclSpVal,
144 I k,bi,bj, parsFld, myThid )
145
146 C !DESCRIPTION:
147 C Compute statistics for this tile, level, region
148 C using "ground" (land) type fraction
149
150 C !USES:
151 IMPLICIT NONE
152
153 #include "EEPARAMS.h"
154 #ifdef ALLOW_LAND
155 # include "LAND_SIZE.h"
156 # include "LAND_PARAMS.h"
157 # ifdef ALLOW_AIM
158 # include "AIM_FFIELDS.h"
159 # endif
160 #else
161 # include "SIZE.h"
162 #endif
163
164 C !INPUT/OUTPUT PARAMETERS:
165 C == Routine Arguments ==
166 C statArr :: output statistics array
167 C inpArr :: input field array to process (compute stats & add to statFld)
168 C frcArr :: fraction used for weighted-average diagnostics
169 C scaleFact :: scaling factor
170 C power :: option to fill-in with the field square (power=2)
171 C useFract :: if True, use fraction-weight
172 C useReg :: how to use region-mask: =0 : not used ;
173 C =1 : grid-center location ; =2 : U location ; =3 : V location
174 C regMskVal :: region-mask identificator value
175 C nStats :: size of output statArr
176 C sizI1,sizI2 :: size of inpArr array: 1rst index range (min,max)
177 C sizJ1,sizJ2 :: size of inpArr array: 2nd index range (min,max)
178 C iRun,jRun :: range of 1rst & 2nd index to process
179 C regMask :: regional mask
180 C arrArea :: Area weighting factor
181 C specialVal :: special value in input array (to exclude if exclSpVal=T)
182 C exclSpVal :: if T, exclude "specialVal" in input array
183 C k,bi,bj :: level and tile indices used for weighting (mask,area ...)
184 C parsFld :: parser field with characteristics of the diagnostics
185 C myThid :: my Thread Id number
186 INTEGER nStats,sizI1,sizI2,sizJ1,sizJ2
187 INTEGER iRun, jRun
188 _RL statArr(0:nStats)
189 _RL inpArr (sizI1:sizI2,sizJ1:sizJ2)
190 _RL frcArr (sizI1:sizI2,sizJ1:sizJ2)
191 _RL scaleFact
192 INTEGER power
193 LOGICAL useFract
194 INTEGER useReg
195 _RS regMskVal
196 _RS regMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
197 _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
198 _RL specialVal
199 LOGICAL exclSpVal
200 INTEGER k, bi, bj
201 CHARACTER*16 parsFld
202 INTEGER myThid
203 CEOP
204
205 #ifdef ALLOW_LAND
206 C !LOCAL VARIABLES:
207 LOGICAL useWeight
208 INTEGER kl
209 _RL drLoc
210
211 c IF ( useLand ) THEN
212
213 IF ( parsFld(10:10).EQ.'G' ) THEN
214 kl = MIN(k,land_nLev)
215 drLoc = land_dzF(kl)
216 ELSE
217 drLoc = 1. _d 0
218 ENDIF
219 useWeight = .TRUE.
220
221 CALL DIAGSTATS_CALC(
222 O statArr,
223 I inpArr, frcArr, scaleFact, power, useFract,
224 I useReg, regMskVal,
225 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
226 I regMask, aim_landFr(1-OLx,1-OLy,bi,bj),
227 I aim_landFr(1-OLx,1-OLy,bi,bj), arrArea,
228 I drLoc, specialVal, exclSpVal, useWeight, myThid )
229
230 c ENDIF
231 #endif /* ALLOW_LAND */
232
233 RETURN
234 END

  ViewVC Help
Powered by ViewVC 1.1.22