/[MITgcm]/MITgcm/pkg/sbo/sbo_calc.F
ViewVC logotype

Contents of /MITgcm/pkg/sbo/sbo_calc.F

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


Revision 1.14 - (show annotations) (download)
Sun Jan 3 20:01:36 2010 UTC (14 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62c, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint64, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62b, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f
Changes since 1.13: +226 -220 lines
- sbobp (global mean ocean bottom pressure ?) computation was strange ;
  => change it ; also remove few unused variables.
- should use array "rA" for grid-cell area (instead of dyF*dxF)

1 C $Header: /u/gcmpack/MITgcm/pkg/sbo/sbo_calc.F,v 1.13 2009/04/28 18:45:22 jmc Exp $
2 C $Name: $
3
4 #include "SBO_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: SBO_CALC
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE SBO_CALC( myTime, myIter, myThid )
11
12 C !DESCRIPTION: \bv
13 C /==========================================================\
14 C | SUBROUTINE SBO_CALC |
15 C | o Do SBO diagnostic output. |
16 C |==========================================================|
17 C | NOTE: The following subtleties are ignored for time |
18 C | being but may need revisiting at some point in time. |
19 C | 1) The model is volume-preserving and Boussinesq so |
20 C | quantities like oceanic mass need to be interpreted |
21 C | with some care. |
22 C | 2) The sea surface height variable etaN lags other |
23 C | prognostic variables by half a time step. This lag |
24 C | is ignored in SBO computations. |
25 C | 3) Density is computed using function SBO_RHO which is |
26 C | not exaclty equivalent to the model s FIND_RHO. |
27 C \==========================================================/
28 IMPLICIT NONE
29
30 C=======================================================================
31 C
32 C Written by Richard Gross (Richard.Gross@jpl.nasa.gov)
33 C June 10, 2001: Modified for online computations in MIT GCM UV
34 C by Dimitris Menemenlis (Menemenlis@jpl.nasa.gov)
35 C
36 C Purpose
37 C calc_sbo calculates the core products of the IERS Special Bureau
38 C for the Oceans including oceanic mass, center-of-mass, angular
39 C momentum, and bottom pressure.
40 C
41 C Usage
42 C 1. calc_sbo must be called, and the results saved, at each time step
43 C in order to create a time series of the IERS SBO core products
44 C 2. it is suggested that after the time series have been generated
45 C and before saving the results to a file, time-mean values be
46 C computed and removed from all of the calculated core products
47 C and that the mean values be reported along with the demeaned
48 C time series
49 C
50 C Availability
51 C ftp://euler.jpl.nasa.gov/sbo/software/calc_sbo.f
52 C
53 C Reference
54 C Gross, R. S., F. O. Bryan, Y. Chao, J. O. Dickey, S. L. Marcus,
55 C R. M. Ponte, and R. Tokmakian, The IERS Special Bureau for the
56 C Oceans, in IERS Technical Note on the IERS Global Geophysical
57 C Fluids Center, edited by B. Chao, in press, Observatoire de Paris,
58 C Paris, France, 2000.
59 C
60 C Required inputs
61 C gridded values of horizontal velocity (u,v), temperature,
62 C salinity, and sea surface height along with the latitude,
63 C and longitude of the grid points and the thicknesses of the
64 C vertical layers
65 C
66 C External routines called by calc_sbo
67 C real function rho1(s, t)
68 C returns density of sea water given salinity s and temperature t
69 C (a default version of rho1 has been included with calc_sbo,
70 C however in general this should be replaced by a function that
71 C returns the density of the model ocean so that the same density
72 C as the model s is used to compute the sbo products)
73 C
74 C Assumptions
75 C 1. the input velocity, temperature, salinity, and sea surface
76 C height fields are assumed to be defined on the same grid
77 C 2. the horizontal grid is assumed to be equally spaced in
78 C latitude and longitude
79 C 3. land is flagged in the input quantities by a salinity or
80 C temperature value greater than or equal to 999.99
81 C 4. input quantities are assumed to have the following units:
82 C salinity (s) parts per thousand
83 C temperature (t) degrees centigrade
84 C eastwards velocity (u) centimeters per second
85 C northwards velocity (v) centimeters per second
86 C sea surface height (ssh) meters
87 C latitude of grid point degrees N
88 C longitude of grid point degrees E
89 C thickness of layer meters
90 C 5. input quantities are passed to calc_sbo via common blocks
91 C /ogcm/ and /vgrid/
92 C 6. land is flagged in the output ocean-bottom pressure (obp)
93 C by a value of -999.99
94 C 7. calulated products have the units:
95 C mass of oceans (mass) kilograms (kg)
96 C center-of-mass of oceans (com) meters (m)
97 C oceanic angular momentum (oam) kg-m**2/second
98 C ocean-bottom pressure (obp) Pascals (Newton/m**2)
99 C 8. calculated products are passed out of calc_sbo via common
100 C block /sbo/
101 C 9. the sea surface height layer is assumed to have the same
102 C velocity, temperature, and salinity as the first depth layer
103 C
104 C For questions regarding calc_sbo or the IERS SBO, please contact:
105 C Richard Gross Richard.Gross@jpl.nasa.gov
106 C Jet Propulsion Laboratory ph. +1 818-354-4010
107 C Mail Stop 238-332 fax +1 818-393-6890
108 C 4800 Oak Grove Drive
109 C Pasadena, Ca 91109-8099
110 C USA
111 C
112 C=======================================================================
113 C \ev
114
115 C !USES: ===============================================================
116 C === Global variables ===
117 #include "SIZE.h"
118 #include "EEPARAMS.h"
119 #include "PARAMS.h"
120 #include "GRID.h"
121 #include "DYNVARS.h"
122 #include "FFIELDS.h"
123 #include "SBO.h"
124
125 C !INPUT PARAMETERS: ===================================================
126 C == Routine arguments ==
127 C myTime :: Current time of simulation ( s )
128 C myIter :: Iteration number
129 C myThid :: Number of this instance of SBO_CALC
130 _RL myTime
131 INTEGER myIter, myThid
132
133 #ifdef ALLOW_SBO
134
135 C !LOCAL VARIABLES: ====================================================
136 C external function called by calc_sbo
137 C returns density of sea water
138 _RL rhoK(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
139
140 C internal variables
141 C bi, bj :: array indices
142 C i :: index over longitude grid points
143 C j :: index over latitude grid points
144 C k :: index over layers
145 C lat :: latitude of grid point (radians)
146 C lat_deg :: latitude of grid point (degrees)
147 C lon :: longitude of grid point (radians)
148 C radius :: radius of bottom of layer (m)
149 C darea :: element of surface area (unit radius)
150 C dradius :: element of radius (m)
151 C dvolume :: element of volume (m**3)
152 C s :: salinity at grid point (ppt)
153 C t :: temperature at grid point (deg C)
154 C u :: eastward velocity at grid point (m/s)
155 C v :: northward velocity at grid point (m/s)
156 C density :: density at grid point (kg/m**3)
157 C ae :: earth s mean radius (m) (PREM value)
158 C grav :: earth s mean gravity (m/s**2) (PREM)
159 C sbo_omega :: earth s mean angular velocity (rad/s)
160 integer bi, bj, i, j, k, kn0
161 _RL lat, lat_deg, lon, radius, darea, dradius, dvolume, depth
162 _RL u, v, density
163 _RL ae, grav, sbo_omega
164 PARAMETER ( ae = 6.3710 _d 6 )
165 PARAMETER ( grav = 9.8156 )
166 PARAMETER ( sbo_omega = 7.292115 _d -5 )
167 CEOP
168
169 C initialize variables to be computed
170 xoamc = 0.0
171 yoamc = 0.0
172 zoamc = 0.0
173 xoamp = 0.0
174 yoamp = 0.0
175 zoamp = 0.0
176 mass = 0.0
177 xcom = 0.0
178 ycom = 0.0
179 zcom = 0.0
180 sbobp = 0.0
181 sboarea = 0.0
182 sboempmrwet = 0.0
183 sboqnetwet = 0.0
184
185 DO bj = myByLo(myThid), myByHi(myThid)
186 DO bi = myBxLo(myThid), myBxHi(myThid)
187 DO j = 1-OLy, sNy+OLy
188 DO i = 1-OLx, sNx+OLx
189 obp(i,j,bi,bj) = 0.0
190 ENDDO
191 ENDDO
192 ENDDO
193 ENDDO
194
195 C loop over all grid points, accumulating mass, com, oam, and obp
196
197 DO bj = myByLo(myThid), myByHi(myThid)
198 DO bi = myBxLo(myThid), myBxHi(myThid)
199 DO k = 0, Nr
200 kn0 = max(k,1)
201
202 CALL FIND_RHO_2D(
203 I 1, sNx, 1, sNy, kn0,
204 I theta(1-OLx,1-OLy,kn0,bi,bj),
205 I salt(1-OLx,1-OLy,kn0,bi,bj),
206 O rhoK,
207 I kn0, bi, bj, myThid )
208
209 C--
210 DO j = 1, sNy
211 DO i = 1, sNx
212 IF ( maskC(i,j,kn0,bi,bj) .NE. 0. ) THEN
213
214 C latitude (rad)
215 lat_deg = yC(i,j,bi,bj)
216 lat = yC(i,j,bi,bj) * pi / 180.0
217 C longitude (rad)
218 lon = xC(i,j,bi,bj) * pi / 180.0
219 C unit radius : should be using rA like this:
220 c darea = rA(i,j,bi,bj)*maskC(i,j,kn0,bi,bj) /ae/ae
221 darea = dyF(i,j,bi,bj) * dxF(i,j,bi,bj) / ae / ae
222 & * maskC(i,j,kn0,bi,bj)
223
224 IF ( k .EQ. 0 ) THEN
225 sboarea = sboarea + darea
226 sboempmrwet = sboempmrwet + empmr(i,j,bi,bj)*darea
227 sboqnetwet = sboqnetwet + qnet(i,j,bi,bj) *darea
228 C k=0 => ssh
229 radius = ae
230 dradius = etaN(i,j,bi,bj) * maskC(i,j,kn0,bi,bj)
231
232 ELSE
233 C-- k > 0
234
235 C radius to center of cell (m)
236 radius = ae - ABS(rC(k))
237 dradius = drF(k) * maskC(i,j,k,bi,bj)
238 C-- end of k-if
239 ENDIF
240
241
242 cph s = salt(i,j,kn0,bi,bj)
243 cph t = theta(i,j,kn0,bi,bj)
244 u =(uvel(i,j,kn0,bi,bj)+uvel(i+1,j,kn0,bi,bj))*0.5 _d 0
245 v =(vvel(i,j,kn0,bi,bj)+vvel(i,j+1,kn0,bi,bj))*0.5 _d 0
246
247 C cell volume (m**3)
248 dvolume = darea * radius**2 * dradius
249
250 C get density
251 depth = ae - radius
252 cph(
253 cph compute density consistent with EOS used by model
254 cph density = sbo_rho(depth,lat_deg,s,t)
255 density = rhoConst + rhoK(i,j)
256 cph)
257
258 C accumulate mass of oceans
259 mass = mass + density * dvolume
260
261 C accumulate center-of-mass of oceans
262 xcom = xcom + density * COS(lat) * COS(lon)
263 & * radius * dvolume
264 ycom = ycom + density * COS(lat) * SIN(lon)
265 & * radius * dvolume
266 zcom = zcom + density * SIN(lat)
267 & * radius * dvolume
268
269 C accumulate oceanic angular momentum due to currents
270 xoamc = xoamc + ( v*SIN(lon)-u*SIN(lat)*COS(lon))
271 & * density * radius * dvolume
272 yoamc = yoamc + (-v*COS(lon)-u*SIN(lat)*SIN(lon))
273 & * density * radius * dvolume
274 zoamc = zoamc + u*COS(lat)
275 & * density * radius * dvolume
276
277 C accumulate oceanic angular momentum due to pressure
278 xoamp = xoamp - SIN(lat) * COS(lat) * COS(lon)
279 & * sbo_omega * density * radius*radius * dvolume
280 yoamp = yoamp - SIN(lat) * COS(lat) * SIN(lon)
281 & * sbo_omega * density * radius*radius * dvolume
282 zoamp = zoamp + COS(lat)**2
283 & * sbo_omega * density * radius*radius * dvolume
284
285 C accumulate ocean-bottom pressure
286 obp(i,j,bi,bj) = obp(i,j,bi,bj)
287 & + grav * density * dradius
288
289 C end if wet
290 ENDIF
291 C end loop over i,j
292 ENDDO
293 ENDDO
294
295 C end loop over k
296 ENDDO
297
298 C accumulate for global-mean ocean-bottom pressure
299 DO j = 1, sNy
300 DO i = 1, sNx
301 sbobp = sbobp + obp(i,j,bi,bj)*rA(i,j,bi,bj)
302 ENDDO
303 ENDDO
304
305 C end loop over bi,bj
306 ENDDO
307 ENDDO
308
309 C sum all values across model tiles
310 C- note: GLOBAL_SUM applied to var. in common block <= wrong if Muti-threaded
311 _GLOBAL_SUM_RL( mass , myThid )
312 _GLOBAL_SUM_RL( xcom , myThid )
313 _GLOBAL_SUM_RL( ycom , myThid )
314 _GLOBAL_SUM_RL( zcom , myThid )
315 _GLOBAL_SUM_RL( xoamc , myThid )
316 _GLOBAL_SUM_RL( yoamc , myThid )
317 _GLOBAL_SUM_RL( zoamc , myThid )
318 _GLOBAL_SUM_RL( xoamp , myThid )
319 _GLOBAL_SUM_RL( yoamp , myThid )
320 _GLOBAL_SUM_RL( zoamp , myThid )
321 cph(
322 _GLOBAL_SUM_RL( sbobp, myThid )
323 _GLOBAL_SUM_RL( sboarea, myThid )
324 _GLOBAL_SUM_RL( sboempmrwet, myThid )
325 _GLOBAL_SUM_RL( sboqnetwet, myThid )
326 cph)
327
328 C finish calculating center-of-mass of oceans
329 xcom = xcom / mass
330 ycom = ycom / mass
331 zcom = zcom / mass
332 cph(
333 c sbobp = sbobp / sboarea
334 sbobp = sbobp / globalArea
335 sboempmrwet = sboempmrwet / sboarea
336 sboqnetwet = sboqnetwet / sboarea
337 cph)
338
339 #endif /* ALLOW_SBO */
340
341 RETURN
342 END

  ViewVC Help
Powered by ViewVC 1.1.22