/[MITgcm]/MITgcm/pkg/ebm/ebm_atmosphere.F
ViewVC logotype

Annotation of /MITgcm/pkg/ebm/ebm_atmosphere.F

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


Revision 1.1 - (hide annotations) (download)
Fri May 14 21:10:34 2004 UTC (20 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint53b_post
Commiting new energy balance model to repository
o package is pkg/ebm
o verif. is verification/global_ocean_ebm
o references are in ebm_driver.F
Will need long integration testing.

1 heimbach 1.1 C $Header: $
2     C $Name: $
3    
4     #include "EBM_OPTIONS.h"
5    
6     SUBROUTINE EBM_ATMOSPHERE ( myTime, myiter, myThid )
7    
8     C |==========================================================|
9     C | S/R CALCULATE FORCING FROM ENERGY AND MOISTURE |
10     C | BALANCE ATMOSPHERE |
11     C |==========================================================|
12     C References:
13     C * X. Wang, P. Stone and J. Marotzke, 1999:
14     C Global thermohaline circulation. Part I:
15     C Sensitivity to atmospheric moisture transport.
16     C J. Climate 12(1), 71-82
17     C * X. Wang, P. Stone and J. Marotzke, 1999:
18     C Global thermohaline circulation. Part II:
19     C Sensitivity with interactive transport.
20     C J. Climate 12(1), 83-91
21     C * M. Nakamura, P. Stone and J. Marotzke, 1994:
22     C Destabilization of the thermohaline circulation
23     C by atmospheric eddy transports.
24     C J. Climate 7(12), 1870-1882
25    
26     IMPLICIT NONE
27    
28     C === Global variables ===
29     #include "SIZE.h"
30     #include "EEPARAMS.h"
31     #include "PARAMS.h"
32     #include "FFIELDS.h"
33     #include "DYNVARS.h"
34     #include "GRID.h"
35     #ifdef ALLOW_EBM
36     # include "EBM.h"
37     #endif
38    
39     C === Routine arguments ===
40     C myThid - Instance number for this innvocation of CALC_FORCING
41     INTEGER myThid
42     INTEGER myIter
43     _RL myTime
44     CEndOfInterface
45    
46     #ifdef ALLOW_EBM
47    
48     C == Local variables ==
49     _RL Dy
50     _RL ReCountX(1-OLy:sNy+OLy)
51     INTEGER bi, bj
52     INTEGER i, j
53     INTEGER no_so
54     LOGICAL TOP_LAYER
55    
56     C-- Top layer only
57     cph TOP_LAYER = k .EQ. 1
58    
59     cph IF ( TOP_LAYER ) THEN
60    
61     DO bj=myByLo(myThid),myByHi(myThid)
62     DO bi=myBxLo(myThid),myBxHi(myThid)
63    
64     DO j=1-OLy,sNy+OLy
65     S(j) = 0.0
66     P2(j) = 0.0
67     P4(j) = 0.0
68     SW(j) = 0.0
69     LW(j) = 0.0
70     Hd(j) = 0.0
71     Fw(j) = 0.0
72     T(j) = 0.0
73     ReCountX(j) = 0.0
74     ENDDO
75    
76     print *, 'SH', TmlS-t_mlt, TtS-t_mlt
77     print *, 'NH', TmlN-t_mlt, TtN-t_mlt
78    
79     C-- account for ice (can absorb heat on an annual averaged basis)
80     C-- Greenland in Northern Hemisphere, Antarctica in Southern
81     DO j = 1-OLy,sNy+OLy
82     ReCountX(j) = CountX(j)
83     IF (yC(1,j,bi,bj) .LE. -62.0) THEN
84     ReCountX(j) = 90.
85     ELSE IF (yC(1,j,bi,bj) .EQ. 74.0) THEN
86     ReCountX(j) = CountX(j) + 9.0
87     ELSE IF (yC(1,j,bi,bj) .EQ. 70.0) THEN
88     ReCountX(j) = CountX(j) + 8.0
89     ELSE IF (yC(1,j,bi,bj) .EQ. 66.0) THEN
90     ReCountX(j) = CountX(j) + 5.0
91     ELSE IF (yC(1,j,bi,bj) .EQ. 62.0) THEN
92     ReCountX(j) = CountX(j) + 1.0
93     ENDIF
94     ENDDO
95    
96    
97     c=====================================================
98     c Fit area-weighed averaged SST north/south of 34
99     c degree to second Legendre polynomial:
100     c=======================================================
101     T_var(1) = SIN(lat(2)*deg2rad) - SIN(lat(1)*deg2rad)
102     T_var(2) = SIN(lat(3)*deg2rad) - SIN(lat(2)*deg2rad)
103     T_var(3) = SIN(lat(2)*deg2rad)**3. - SIN(lat(1)*deg2rad)**3.
104     T_var(4) = SIN(lat(3)*deg2rad)**3. - SIN(lat(2)*deg2rad)**3.
105    
106     c----------------------------------------
107     c Southern hemisphere:
108     c----------------------------------------
109     T2(1) = 2.*(TtS - TmlS)*T_var(1)*T_var(2)/
110     < (T_var(3)*T_var(2) - T_var(4)*T_var(1))
111     T0(1) = TtS - 0.5*T2(1)*((T_var(3)/T_var(1)) - 1.)
112     c----------------------------------------
113     c Northern hemisphere
114     c----------------------------------------
115     T2(2) = 2.*(TtN - TmlN)*T_var(1)*T_var(2)/
116     < (T_var(3)*T_var(2) - T_var(4)*T_var(1))
117     T0(2) = TtN - 0.5*T2(2)*((T_var(3)/T_var(1)) - 1.)
118     c-----------------------------------------
119     c Temperature at 35 N/S
120     c-----------------------------------------
121     DO no_so = 1,2
122     T35(no_so)= T0(no_so) +
123     < T2(no_so)*0.5*
124     < ((3.*SIN(lat(2)*deg2rad)**2. - 1.))
125     ENDDO
126     c-----------------------------------------
127     c Temperature gradient at 35 N/S
128     c-----------------------------------------
129     DO no_so = 1, 2
130     DTDy35(no_so) = 3.*T2(no_so)*
131     < SIN(lat(2)*deg2rad)/rSphere
132     ENDDO
133     c-----------------------------------------------------------
134     c Magnitude of the heat and moisture transport at 35 N/S
135     c-----------------------------------------------------------
136    
137    
138     DO no_so = 1, 2
139     gamma = -T35(no_so)*beta*Hw*Nw*Nw/
140     < (gravity*f0*DTDy35(no_so))
141     kappa = Hw/(1 + gamma)
142     De = Hw/(0.48 + 1.48*gamma)
143     C = 0.6*gravity*kappa*kappa*Nw/
144     < (Tw*f0*f0)
145     Cs = rho_air*cp*C*
146     < (1/(1/Hw+1/De) - 1/(1/Hw+1/De+1/dz))
147     Cf = htil*2.97e12*C/(T35(no_so)**3)*(
148     < 1/(1/De + (5420*tau /(T35(no_so)**2)))
149     < - 1/(1/De+5420*tau/(T35(no_so)**2)+1/dz))
150     Cl = Cf*lv
151     Hd35(no_so) = 2.*PI*rSphere*COS(lat(2)*deg2rad)
152     < *(Cs + Cl*exp(-5420./T35(no_so)))
153     < *(abs(DTDy35(no_so))**trans_eff)
154     Fw35(no_so) = 2.*PI*rSphere*COS(lat(2)*deg2rad)
155     < *(abs(DTDy35(no_so))**trans_eff)
156     < *Cf*exp(-5420./T35(no_so))
157     c write(0,*) no_so, Hd35(no_so), Fw35(no_so)
158     ENDDO
159     Fw35(1) = 929944128.
160     Fw35(2) = 678148032.
161     #ifdef EBM_VERSION_1BASIN
162     c Fw35(2) = 0.7*Fw35(2)
163     #else
164     Hd35(2) = 1.6*Hd35(2)
165     #endif
166     c======================================================
167     c Calculation of latitudinal profiles
168     c======================================================
169     c
170     DO j=1-OLy,sNy+OLy
171     DO i=1-Olx,sNx+Olx
172    
173     IF (yC(i,j,bi,bj) .LT. 0.) THEN
174     no_so = 1
175     ELSE
176     no_so = 2
177     ENDIF
178     C sin(lat)
179     S(j) = sin(yC(i,j,bi,bj)*deg2rad)
180     C setup Legendre polynomials and derivatives
181     P2(j) = 0.5*(3.*S(j)**2 - 1.)
182     P4(j) = 0.12*(35.*S(j)**4 - 30.*S(j)**2 + 3.)
183     c net shortwave
184     SW(j) = 0.25*Q0*(1 + Q2*P2(j))*
185     < (1 - A0 - A2*P2(j) - A4*P4(j) )
186     c temperature
187     T(j) = T0(no_so) + T2(no_so)*P2(j)
188     c net longwave
189     LW(j) = LW0 + LW1*(T(j)-t_mlt)
190     c climate change run, the parameter to change is DLW
191     #ifdef EBM_CLIMATE_CHANGE
192     LW(j) = LW(j) -
193     < (myTime-startTime)*3.215e-8*DLW
194     c < - 6.0
195     c < *75.0*0.0474*
196     c < (-2.62*S(j)**8 + 0.73*S(j)**7 +
197     c < 4.82*S(j)**6 -
198     c < 1.12*S(j)**5 - 2.69*S(j)**4 + 0.47*S(j)**3 +
199     c < 0.51*S(j)**2 - 0.05*S(j)**1 + 0.17)
200     #endif
201     c fluxes at ocean/atmosphere interface
202     c Heat Flux = -Div(atmospheric heat transport) + SW - LW
203     #ifdef EBM_VERSION_1BASIN
204     Qnet(i,j,bi,bj) = -1.0*( SW(j) - LW(j) -
205     < Hd35(no_so)*(
206     < 0.000728e4 - 0.00678e4*S(j) +
207     < 0.0955e4*S(j)**2 + 0.0769e4*S(j)**3 -
208     < 0.8508e4*S(j)**4 - 0.3581e4*S(j)**5 +
209     < 2.9240e4*S(j)**6 + 0.8311e4*S(j)**7 -
210     < 4.9548e4*S(j)**8 - 0.8808e4*S(j)**9 +
211     < 4.0644e4*S(j)**10 +0.3409e4*S(j)**11 -
212     < 1.2893e4*S(j)**12 )
213     < /(2*PI*rSphere*rSphere*25.0) )
214     c Qnet(i,j,bi,bj) = -1.0*( SW(j) - LW(j) -
215     c < 0.5*Hd35(no_so)*(3.054e1 - 3.763e1*S(j) +
216     c < 1.892e2*S(j)**2 + 3.041e2*S(j)**3 -
217     c < 1.540e3*S(j)**4 - 9.586e2*S(j)**5 +
218     c < 2.939e3*S(j)**6 + 1.219e3*S(j)**7 -
219     c < 2.550e3*S(j)**8 - 5.396e2*S(j)**9 +
220     c < 8.119e2*S(j)**10)
221     c < /(2*PI*rSphere*rSphere*22.3) )
222     #else
223     IF (ReCountX(j) .GT. 0.) THEN
224     Qnet(i,j,bi,bj) = (-90./ReCountX(j))*
225     < ( SW(j) - LW(j) -
226     < Hd35(no_so)*(3.054e1 - 3.763e1*S(j) +
227     < 1.892e2*S(j)**2 + 3.041e2*S(j)**3 -
228     < 1.540e3*S(j)**4 - 9.586e2*S(j)**5 +
229     < 2.939e3*S(j)**6 + 1.219e3*S(j)**7 -
230     < 2.550e3*S(j)**8 - 5.396e2*S(j)**9 +
231     < 8.119e2*S(j)**10)
232     < /(2*PI*rSphere*rSphere*22.3) )
233     ELSE
234     Qnet(i,j,bi,bj) = 0.
235     ENDIF
236     #endif
237     c Freshwater Flux = Div(atmospheric moisture transport)
238     c--- conversion of E-P from kg/(s m^2) -> m/s -> psu/s: 1e-3*35/delZ(1)
239     #ifdef EBM_VERSION_1BASIN
240     EmPmR(i,j,bi,bj) = -1.e-3*Fw35(no_so)
241     < *(-0.8454e5*S(j)**14 + 0.5367e5*S(j)**13
242     < +3.3173e5*S(j)**12 - 1.8965e5*S(j)**11 - 5.1701e5*S(j)**10
243     < +2.6240e5*S(j)**9 + 4.077e5*S(j)**8 - 1.791e5*S(j)**7
244     < -1.7231e5*S(j)**6 + 0.6229e5*S(j)**5 + 0.3824e5*S(j)**4
245     < -0.1017e5*S(j)**3 - 0.0387e5*S(j)**2
246     < +0.00562e5*S(j) + 0.0007743e5)
247     < /(2.0*12.0*PI*rSphere*rSphere)
248     c EmPmR(i,j,bi,bj) = 1.e-3*Fw35(no_so)
249     c < *(50.0 + 228.0*S(j) -1.593e3*S(j)**2
250     c < - 2.127e3*S(j)**3 + 7.3e3*S(j)**4
251     c < + 5.799e3*S(j)**5 - 1.232e4*S(j)**6
252     c < - 6.389e3*S(j)**7 + 9.123e3*S(j)**8
253     c < + 2.495e3*S(j)**9 - 2.567e3*S(j)**10)
254     c < /(2*PI*rSphere*rSphere*15.0)
255     #else
256     IF (yC(i,j,bi,bj) .LT. -40.) THEN
257     c-- Southern Hemisphere
258     EmPmR(i,j,bi,bj) = -1.e-3*(Fw35(no_so)*
259     < (-6.5 + 35.3 + 71.7*S(j)
260     < - 1336.3*S(j)**2 - 425.8*S(j)**3
261     < + 5434.8*S(j)**4 + 707.9*S(j)**5
262     < - 6987.7*S(j)**6 - 360.4*S(j)**7
263     < + 2855.0*S(j)**8)
264     < /(2*PI*rSphere*rSphere*18.0))
265     ELSE
266     c-- Atlantic
267     IF (xC(i,j,bi,bj) .GT. 284.
268     < .OR. xC(i,j,bi,bj) .LT. 28.) THEN
269     EmPmR(i,j,bi,bj) = -1.e-3*(Fw35(no_so)*
270     < (-6.5 -2.878 + 3.157e2*S(j) -
271     < 2.388e3*S(j)**2 - 4.101e3*S(j)**3 +
272     < 1.963e4*S(j)**4 + 1.534e4*S(j)**5 -
273     < 6.556e4*S(j)**6 - 2.478e4*S(j)**7 +
274     < 1.083e5*S(j)**8 + 1.85e4*S(j)**9 -
275     < 8.703e4*S(j)**10 - 5.276e3*S(j)**11 +
276     < 2.703e4*S(j)**12)
277     < /(2*PI*rSphere*rSphere*12.0))
278     ELSE
279     c-- Pacific
280     EmPmR(i,j,bi,bj) = -1.e-3*(Fw35(no_so)
281     < *(-6.5 +51.89 + 4.916e2*S(j) -
282     < 1.041e3*S(j)**2 - 7.546e3*S(j)**3 +
283     < 2.335e3*S(j)**4 + 3.449e4*S(j)**5 +
284     < 6.702e3*S(j)**6 - 6.601e4*S(j)**7 -
285     < 2.594e4*S(j)**8 + 5.652e4*S(j)**9 +
286     < 2.738e4*S(j)**10 - 1.795e4*S(j)**11 -
287     < 9.486e3*S(j)**12)
288     < /(2*PI*rSphere*rSphere*12.0))
289     ENDIF
290     ENDIF
291     #endif
292     ENDDO
293     ENDDO
294     ENDDO
295     ENDDO
296    
297     C CALL PLOT_FIELD_XYRS( Qnet, 'Qnet' , 1, myThid )
298     C CALL PLOT_FIELD_XYRS( EmPmR, 'EmPmR' , 1, myThid )
299    
300     cph end of IF TOP_LAYER
301     cph ENDIF
302    
303     #endif /* ALLOW_EBM */
304    
305     END
306    
307    
308    
309    
310    

  ViewVC Help
Powered by ViewVC 1.1.22