/[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.2 - (show annotations) (download)
Thu Sep 3 14:53:32 2009 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.1: +21 -5 lines
fix argument type problem when REAL4_IS_SLOW is undef

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagstats_others_calc.F,v 1.1 2006/01/23 22:31:11 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 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 #ifndef REAL4_IS_SLOW
85 INTEGER i,j
86 _RS tmp_hFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87 #endif
88
89 c IF ( useFIZHI ) THEN
90
91 IF ( parsFld(10:10).EQ.'L' ) THEN
92 kl = 1 + Nrphys - k
93 useWeight = .TRUE.
94 ELSE
95 kl = 1
96 useWeight = .FALSE.
97 ENDIF
98 drLoc = 1. _d 0
99
100 #ifdef REAL4_IS_SLOW
101 CALL DIAGSTATS_CALC(
102 O statArr,
103 I inpArr, frcArr, scaleFact, power, useFract,
104 I regId, regMskVal,
105 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
106 I regMask, arrMask,
107 I dpphys(1-Olx,1-Oly,kl,bi,bj), arrArea,
108 I drLoc, specialVal, exclSpVal, useWeight, myThid )
109 #else /* REAL4_IS_SLOW */
110 C make local copy of dpphys (RL type) into RS array tmp_hFac
111 DO j=1-OLy,sNy+OLy
112 DO i=1-OLx,sNx+OLx
113 tmp_hFac(i,j) = dpphys(i,j,kl,bi,bj)
114 ENDDO
115 ENDDO
116 CALL DIAGSTATS_CALC(
117 O statArr,
118 I inpArr, frcArr, scaleFact, power, useFract,
119 I regId, regMskVal,
120 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
121 I regMask, arrMask, tmp_hFac, arrArea,
122 I drLoc, specialVal, exclSpVal, useWeight, myThid )
123 #endif /* REAL4_IS_SLOW */
124
125 c ENDIF
126 #endif /* ALLOW_FIZHI */
127
128 RETURN
129 END
130
131 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
132
133 CBOP
134 C !ROUTINE: DIAGSTATS_G_CALC
135 C !INTERFACE:
136 SUBROUTINE DIAGSTATS_G_CALC(
137 O statArr,
138 I inpArr, frcArr, scaleFact, power, useFract,
139 I regId, regMskVal,
140 I nStats,sizI1,sizI2,sizJ1,sizJ2, iRun,jRun,
141 I regMask, arrArea,
142 I specialVal, exclSpVal,
143 I k,bi,bj, parsFld, myThid )
144
145 C !DESCRIPTION:
146 C Compute statistics for this tile, level, region
147 C using "ground" (land) type fraction
148
149 C !USES:
150 IMPLICIT NONE
151
152 #include "EEPARAMS.h"
153 #ifdef ALLOW_LAND
154 # include "LAND_SIZE.h"
155 # include "LAND_PARAMS.h"
156 # ifdef ALLOW_AIM
157 # include "AIM_FFIELDS.h"
158 # endif
159 #else
160 # include "SIZE.h"
161 #endif
162
163 C !INPUT/OUTPUT PARAMETERS:
164 C == Routine Arguments ==
165 C statArr :: output statistics array
166 C inpArr :: input field array to process (compute stats & add to statFld)
167 C frcArr :: fraction used for weighted-average diagnostics
168 C scaleFact :: scaling factor
169 C power :: option to fill-in with the field square (power=2)
170 C useFract :: if True, use fraction-weight
171 C regId :: region number Id
172 C regMskVal :: region-mask identificator value
173 C nStats :: size of output statArr
174 C sizI1,sizI2 :: size of inpArr array: 1rst index range (min,max)
175 C sizJ1,sizJ2 :: size of inpArr array: 2nd index range (min,max)
176 C iRun,jRun :: range of 1rst & 2nd index to process
177 C regMask :: regional mask
178 C arrArea :: Area weighting factor
179 C specialVal :: special value in input array (to exclude if exclSpVal=T)
180 C exclSpVal :: if T, exclude "specialVal" in input array
181 C k,bi,bj :: level and tile indices used for weighting (mask,area ...)
182 C parsFld :: parser field with characteristics of the diagnostics
183 C myThid :: my Thread Id number
184 INTEGER nStats,sizI1,sizI2,sizJ1,sizJ2
185 INTEGER iRun, jRun
186 _RL statArr(0:nStats)
187 _RL inpArr (sizI1:sizI2,sizJ1:sizJ2)
188 _RL frcArr (sizI1:sizI2,sizJ1:sizJ2)
189 _RL scaleFact
190 INTEGER power
191 LOGICAL useFract
192 INTEGER regId
193 _RS regMskVal
194 _RS regMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
195 _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
196 _RL specialVal
197 LOGICAL exclSpVal
198 INTEGER k, bi, bj
199 CHARACTER*16 parsFld
200 INTEGER myThid
201 CEOP
202
203 #ifdef ALLOW_LAND
204 C !LOCAL VARIABLES:
205 LOGICAL useWeight
206 INTEGER kl
207 _RL drLoc
208
209 c IF ( useLand ) THEN
210
211 IF ( parsFld(10:10).EQ.'G' ) THEN
212 kl = MIN(k,land_nLev)
213 drLoc = land_dzF(kl)
214 ELSE
215 drLoc = 1. _d 0
216 ENDIF
217 useWeight = .TRUE.
218
219 CALL DIAGSTATS_CALC(
220 O statArr,
221 I inpArr, frcArr, scaleFact, power, useFract,
222 I regId, regMskVal,
223 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
224 I regMask, aim_landFr(1-Olx,1-Oly,bi,bj),
225 I aim_landFr(1-Olx,1-Oly,bi,bj), arrArea,
226 I drLoc, specialVal, exclSpVal, useWeight, myThid )
227
228 c ENDIF
229 #endif /* ALLOW_LAND */
230
231 RETURN
232 END

  ViewVC Help
Powered by ViewVC 1.1.22