/[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.1 - (show annotations) (download)
Mon Jan 23 22:31:11 2006 UTC (18 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint60, checkpoint61, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58f_post, checkpoint58d_post, checkpoint58c_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint58p_post, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint58b_post, checkpoint58m_post
- split diagstats_local.F file in 3 ;
- compute statistics for each selected region.

1 C $Header: $
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 regId, 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 regId :: region number Id
46 C regMskVal :: region-mask identificator value
47 C nStats :: size of output statArr
48 C sizI1,sizI2 :: size of inpArr array: 1rst index range (min,max)
49 C sizJ1,sizJ2 :: size of inpArr array: 2nd index range (min,max)
50 C iRun,jRun :: range of 1rst & 2nd index to process
51 C regMask :: regional mask
52 C arrMask :: mask for this input array
53 C arrArea :: Area weighting factor
54 C specialVal :: special value in input array (to exclude if exclSpVal=T)
55 C exclSpVal :: if T, exclude "specialVal" in input array
56 C k,bi,bj :: level and tile indices used for weighting (mask,area ...)
57 C parsFld :: parser field with characteristics of the diagnostics
58 C myThid :: my Thread Id number
59 INTEGER nStats,sizI1,sizI2,sizJ1,sizJ2
60 INTEGER iRun, jRun
61 _RL statArr(0:nStats)
62 _RL inpArr (sizI1:sizI2,sizJ1:sizJ2)
63 _RL frcArr (sizI1:sizI2,sizJ1:sizJ2)
64 _RL scaleFact
65 INTEGER power
66 LOGICAL useFract
67 INTEGER regId
68 _RS regMskVal
69 _RS regMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70 _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71 _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72 _RL specialVal
73 LOGICAL exclSpVal
74 INTEGER k, bi, bj
75 CHARACTER*16 parsFld
76 INTEGER myThid
77 CEOP
78
79 #ifdef ALLOW_FIZHI
80 C !LOCAL VARIABLES:
81 LOGICAL useWeight
82 INTEGER kl
83 _RL drLoc
84
85 c IF ( useFIZHI ) THEN
86
87 IF ( parsFld(10:10).EQ.'L' ) THEN
88 kl = 1 + Nrphys - k
89 useWeight = .TRUE.
90 ELSE
91 kl = 1
92 useWeight = .FALSE.
93 ENDIF
94 drLoc = 1. _d 0
95
96 C- jmc: here we have a Problem if RL & RS are not the same:
97 C since dpphys is RL but argument is RS. leave it like this for now
98 C and will change it once the Regions are fully implemented.
99
100 CALL DIAGSTATS_CALC(
101 O statArr,
102 I inpArr, frcArr, scaleFact, power, useFract,
103 I regId, regMskVal,
104 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
105 I regMask, arrMask,
106 I dpphys(1-Olx,1-Oly,kl,bi,bj), arrArea,
107 I drLoc, specialVal, exclSpVal, useWeight, myThid )
108
109 c ENDIF
110 #endif /* ALLOW_FIZHI */
111
112 RETURN
113 END
114
115 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
116
117 CBOP
118 C !ROUTINE: DIAGSTATS_G_CALC
119 C !INTERFACE:
120 SUBROUTINE DIAGSTATS_G_CALC(
121 O statArr,
122 I inpArr, frcArr, scaleFact, power, useFract,
123 I regId, regMskVal,
124 I nStats,sizI1,sizI2,sizJ1,sizJ2, iRun,jRun,
125 I regMask, arrArea,
126 I specialVal, exclSpVal,
127 I k,bi,bj, parsFld, myThid )
128
129 C !DESCRIPTION:
130 C Compute statistics for this tile, level, region
131 C using "ground" (land) type fraction
132
133 C !USES:
134 IMPLICIT NONE
135
136 #include "EEPARAMS.h"
137 #ifdef ALLOW_LAND
138 # include "LAND_SIZE.h"
139 # include "LAND_PARAMS.h"
140 # ifdef ALLOW_AIM
141 # include "AIM_FFIELDS.h"
142 # endif
143 #else
144 # include "SIZE.h"
145 #endif
146
147 C !INPUT/OUTPUT PARAMETERS:
148 C == Routine Arguments ==
149 C statArr :: output statistics array
150 C inpArr :: input field array to process (compute stats & add to statFld)
151 C frcArr :: fraction used for weighted-average diagnostics
152 C scaleFact :: scaling factor
153 C power :: option to fill-in with the field square (power=2)
154 C useFract :: if True, use fraction-weight
155 C regId :: region number Id
156 C regMskVal :: region-mask identificator value
157 C nStats :: size of output statArr
158 C sizI1,sizI2 :: size of inpArr array: 1rst index range (min,max)
159 C sizJ1,sizJ2 :: size of inpArr array: 2nd index range (min,max)
160 C iRun,jRun :: range of 1rst & 2nd index to process
161 C regMask :: regional mask
162 C arrArea :: Area weighting factor
163 C specialVal :: special value in input array (to exclude if exclSpVal=T)
164 C exclSpVal :: if T, exclude "specialVal" in input array
165 C k,bi,bj :: level and tile indices used for weighting (mask,area ...)
166 C parsFld :: parser field with characteristics of the diagnostics
167 C myThid :: my Thread Id number
168 INTEGER nStats,sizI1,sizI2,sizJ1,sizJ2
169 INTEGER iRun, jRun
170 _RL statArr(0:nStats)
171 _RL inpArr (sizI1:sizI2,sizJ1:sizJ2)
172 _RL frcArr (sizI1:sizI2,sizJ1:sizJ2)
173 _RL scaleFact
174 INTEGER power
175 LOGICAL useFract
176 INTEGER regId
177 _RS regMskVal
178 _RS regMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
179 _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
180 _RL specialVal
181 LOGICAL exclSpVal
182 INTEGER k, bi, bj
183 CHARACTER*16 parsFld
184 INTEGER myThid
185 CEOP
186
187 #ifdef ALLOW_LAND
188 C !LOCAL VARIABLES:
189 LOGICAL useWeight
190 INTEGER kl
191 _RL drLoc
192
193 c IF ( useLand ) THEN
194
195 IF ( parsFld(10:10).EQ.'G' ) THEN
196 kl = MIN(k,land_nLev)
197 drLoc = land_dzF(kl)
198 ELSE
199 drLoc = 1. _d 0
200 ENDIF
201 useWeight = .TRUE.
202
203 CALL DIAGSTATS_CALC(
204 O statArr,
205 I inpArr, frcArr, scaleFact, power, useFract,
206 I regId, regMskVal,
207 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
208 I regMask, aim_landFr(1-Olx,1-Oly,bi,bj),
209 I aim_landFr(1-Olx,1-Oly,bi,bj), arrArea,
210 I drLoc, specialVal, exclSpVal, useWeight, myThid )
211
212 c ENDIF
213 #endif /* ALLOW_LAND */
214
215 RETURN
216 END

  ViewVC Help
Powered by ViewVC 1.1.22