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

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

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


Revision 1.5 - (hide annotations) (download)
Thu Oct 2 14:42:17 2003 UTC (20 years, 8 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint51f_post, checkpoint51j_post, checkpoint51h_pre, checkpoint51i_pre, checkpoint51g_post
Changes since 1.4: +1 -1 lines
Added CPP style comments to #endif ALLOW_
 #endif ALLOW_  -> #endif /* ALLOW_ */

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

  ViewVC Help
Powered by ViewVC 1.1.22