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

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

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


Revision 1.3 - (hide annotations) (download)
Mon Sep 3 20:29:47 2012 UTC (11 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63s, checkpoint64, checkpoint65, checkpoint65b, checkpoint65a
Changes since 1.2: +7 -7 lines
only one space between 'CALL' and S/R name (easier to grep for)

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagstats_others_calc.F,v 1.2 2009/09/03 14:53:32 jmc Exp $
2 jmc 1.1 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 jmc 1.2 #ifndef REAL4_IS_SLOW
85     INTEGER i,j
86     _RS tmp_hFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87     #endif
88 jmc 1.1
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 jmc 1.2 #ifdef REAL4_IS_SLOW
101 jmc 1.3 CALL DIAGSTATS_CALC(
102 jmc 1.1 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 jmc 1.3 I dpphys(1-OLx,1-OLy,kl,bi,bj), arrArea,
108 jmc 1.1 I drLoc, specialVal, exclSpVal, useWeight, myThid )
109 jmc 1.2 #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 jmc 1.3 CALL DIAGSTATS_CALC(
117 jmc 1.2 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 jmc 1.1
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 jmc 1.3 CALL DIAGSTATS_CALC(
220 jmc 1.1 O statArr,
221     I inpArr, frcArr, scaleFact, power, useFract,
222     I regId, regMskVal,
223     I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
224 jmc 1.3 I regMask, aim_landFr(1-OLx,1-OLy,bi,bj),
225     I aim_landFr(1-OLx,1-OLy,bi,bj), arrArea,
226 jmc 1.1 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