/[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.13 - (show annotations) (download)
Tue Apr 28 18:45:22 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint61n, checkpoint61q, checkpoint61o, checkpoint61m, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.12: +15 -15 lines
change macros (EXCH & GLOBAL_SUM/MAX) sufix _R4/_R8 to _RS/_RL
 when applied to _RS/_RL variable
BUG to fix: global_sum of var in common block (SBO.h) is wrong (multi-threaded)

1 C $Header: /u/gcmpack/MITgcm/pkg/sbo/sbo_calc.F,v 1.12 2008/08/11 22:28:06 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 "CG2D.h"
124 #include "SBO.h"
125
126 C !INPUT PARAMETERS: ===================================================
127 C == Routine arguments ==
128 C myTime :: Current time of simulation ( s )
129 C myIter :: Iteration number
130 C myThid :: Number of this instance of SBO_CALC
131 _RL myTime
132 INTEGER myIter, myThid
133
134 #ifdef ALLOW_SBO
135
136 C !LOCAL VARIABLES: ====================================================
137 c external function called by calc_sbo
138 c returns density of sea water
139 _RL sbo_rho
140 _RL rhoK(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
141
142 c internal variables
143 c bi, bj - array indices
144 c I - index over longitude grid points
145 c J - index over latitude grid points
146 c K - index over layers
147 c lat - latitude of grid point (radians)
148 c lat_deg - latitude of grid point (degrees)
149 c lon - longitude of grid point (radians)
150 c radius - radius of bottom of layer (m)
151 c darea - element of surface area (unit radius)
152 c dradius - element of radius (m)
153 c dvolume - element of volume (m**3)
154 c s - salinity at grid point (ppt)
155 c t - temperature at grid point (deg C)
156 c u - eastward velocity at grid point (m/s)
157 c v - northward velocity at grid point (m/s)
158 c density - density at grid point (kg/m**3)
159 c ae - earth s mean radius (m) (PREM value)
160 c grav - earth s mean gravity (m/s**2) (PREM)
161 c sbo_omega - earth s mean angular velocity (rad/s)
162 integer bi, bj, I, J, K, Kn0
163 _RL lat, lat_deg, lon, radius, darea, dradius, dvolume, depth
164 _RL s, t, u, v, density
165 _RL ae, grav, sbo_omega
166 PARAMETER ( ae = 6.3710 _d 6 )
167 PARAMETER ( grav = 9.8156 )
168 PARAMETER ( sbo_omega = 7.292115 _d -5 )
169 CEOP
170
171 c initialize variables to be computed
172 xoamc = 0.0
173 yoamc = 0.0
174 zoamc = 0.0
175 xoamp = 0.0
176 yoamp = 0.0
177 zoamp = 0.0
178 mass = 0.0
179 xcom = 0.0
180 ycom = 0.0
181 zcom = 0.0
182 sbobp = 0.0
183 sboarea = 0.0
184 sboempmrwet = 0.0
185 sboqnetwet = 0.0
186
187 DO bj = myByLo(myThid), myByHi(myThid)
188 DO bi = myBxLo(myThid), myBxHi(myThid)
189 DO J = 1-OLy, sNy+OLy
190 DO I = 1-OLx, sNx+OLx
191 obp(I,J,bi,bj) = 0.0
192 ENDDO
193 ENDDO
194 ENDDO
195 ENDDO
196
197 c loop over all grid points, accumulating mass, com, oam, and obp
198
199 do bj = myByLo(myThid), myByHi(myThid)
200 do bi = myBxLo(myThid), myBxHi(myThid)
201 do K = 0, Nr
202 kn0 = max(K,1)
203
204 CALL FIND_RHO_2D(
205 I 1, sNx, 1, sNy, Kn0,
206 I theta(1-OLx,1-OLy,Kn0,bi,bj),
207 I salt(1-OLx,1-OLy,Kn0,bi,bj),
208 O rhoK,
209 I Kn0, bi, bj, myThid )
210
211 c--
212 do J = 1, sNy
213 do I = 1, sNx
214 if ( _hFacC(i,j,Kn0,bi,bj) .ne. 0. ) then
215
216 c latitude (rad)
217 lat_deg = yC(I,J,bi,bj)
218 lat = yC(I,J,bi,bj) * pi / 180.0
219 c longitude (rad)
220 lon = xC(I,J,bi,bj) * pi / 180.0
221 c unit radius
222 darea = dyF(I,J,bi,bj) * dxF(I,J,bi,bj) / ae / ae
223 & * maskC(I,J,Kn0,bi,bj)
224
225 if ( K .EQ. 0 ) then
226 sboarea = sboarea + darea
227 sboempmrwet = sboempmrwet + empmr(i,j,bi,bj)*darea
228 sboqnetwet = sboqnetwet + qnet(i,j,bi,bj) *darea
229 c K=0 => ssh
230 radius = ae
231 dradius = etaN(I,J,bi,bj) * maskC(I,J,Kn0,bi,bj)
232
233 else
234 c-- K > 0
235
236 c radius to center of cell (m)
237 radius = ae - abs(rC(K))
238 dradius = drF(K) * maskC(I,J,K,bi,bj)
239 c-- end of K-if
240 end if
241
242
243 cph s = salt(I,J,Kn0,bi,bj)
244 cph t = theta(I,J,Kn0,bi,bj)
245 u =(uvel(I,J,Kn0,bi,bj)+uvel(I+1,J,Kn0,bi,bj))/2.
246 v =(vvel(I,J,Kn0,bi,bj)+vvel(I,J+1,Kn0,bi,bj))/2.
247
248 c cell volume (m**3)
249 dvolume = darea * radius**2 * dradius
250
251 c get density
252 depth = ae - radius
253 cph(
254 cph compute density consistent with EOS used by model
255 cph density = sbo_rho(depth,lat_deg,s,t)
256 density = rhoConst + rhoK(I,J)
257 cph)
258
259 c accumulate mass of oceans
260 mass = mass + density * dvolume
261
262 c accumulate center-of-mass of oceans
263 xcom = xcom + density * cos(lat) * cos(lon)
264 & * radius * dvolume
265 ycom = ycom + density * cos(lat) * sin(lon)
266 & * radius * dvolume
267 zcom = zcom + density * sin(lat) *
268 & radius * dvolume
269
270 c accumulate oceanic angular momentum due to currents
271 xoamc = xoamc + ( v*sin(lon)-u*sin(lat)*cos(lon))
272 & * density * radius * dvolume
273 yoamc = yoamc + (-v*cos(lon)-u*sin(lat)*sin(lon))
274 & * density * radius * dvolume
275 zoamc = zoamc + u*cos(lat)
276 & * density * radius * dvolume
277
278 c accumulate oceanic angular momentum due to pressure
279 xoamp = xoamp - sin(lat) * cos(lat) * cos(lon)
280 & * sbo_omega * density * radius**2 * dvolume
281 yoamp = yoamp - sin(lat) * cos(lat) * sin(lon)
282 & * sbo_omega * density * radius**2 * dvolume
283 zoamp = zoamp + cos(lat)**2
284 & * sbo_omega * density * radius**2 * dvolume
285
286 c accumulate ocean-bottom pressure
287 obp(I,J,bi,bj) = obp(I,J,bi,bj) +
288 & grav * density * dradius
289 sbobp = obp(I,J,bi,bj)
290
291 c end if wet
292 endif
293 c end loop over I
294 end do
295 c end loop over J
296 end do
297
298 c end loop over K
299 end do
300 c end loop over bi
301 end do
302 c end loop over bj
303 end do
304
305 c sum all values across model tiles
306 _GLOBAL_SUM_RL( mass , myThid )
307 _GLOBAL_SUM_RL( xcom , myThid )
308 _GLOBAL_SUM_RL( ycom , myThid )
309 _GLOBAL_SUM_RL( zcom , myThid )
310 _GLOBAL_SUM_RL( xoamc , myThid )
311 _GLOBAL_SUM_RL( yoamc , myThid )
312 _GLOBAL_SUM_RL( zoamc , myThid )
313 _GLOBAL_SUM_RL( xoamp , myThid )
314 _GLOBAL_SUM_RL( yoamp , myThid )
315 _GLOBAL_SUM_RL( zoamp , myThid )
316 cph(
317 _GLOBAL_SUM_RL( sbobp, myThid )
318 _GLOBAL_SUM_RL( sboarea, myThid )
319 _GLOBAL_SUM_RL( sboempmrwet, myThid )
320 _GLOBAL_SUM_RL( sboqnetwet, myThid )
321 cph)
322
323 c finish calculating center-of-mass of oceans
324 xcom = xcom / mass
325 ycom = ycom / mass
326 zcom = zcom / mass
327 cph(
328 sbobp = sbobp / sboarea
329 sboempmrwet = sboempmrwet / sboarea
330 sboqnetwet = sboqnetwet / sboarea
331 cph)
332
333 #endif /* ALLOW_SBO */
334
335 return
336 end

  ViewVC Help
Powered by ViewVC 1.1.22