/[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.4 - (hide annotations) (download)
Wed Jul 28 19:54:37 2004 UTC (19 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint58w_post, checkpoint57m_post, checkpoint55c_post, checkpoint54e_post, checkpoint57s_post, checkpoint57k_post, checkpoint55d_pre, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint58r_post, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57y_post, checkpoint57e_post, checkpoint55h_post, checkpoint58n_post, checkpoint58x_post, checkpoint57g_pre, checkpoint55b_post, checkpoint58t_post, checkpoint58h_post, checkpoint56c_post, checkpoint57y_pre, checkpoint55, checkpoint57f_pre, checkpoint57a_post, checkpoint58q_post, checkpoint54f_post, checkpoint55g_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint55f_post, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, eckpoint57e_pre, checkpoint57h_done, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint57f_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint57c_post, checkpoint58y_post, checkpoint55e_post, checkpoint58k_post, checkpoint58v_post, checkpoint55a_post, checkpoint58s_post, checkpoint58p_post, checkpoint57j_post, checkpoint58b_post, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.3: +18 -12 lines
Bug fix to enable to run ebm in single-hemisphere configuration
(e.g. NH or SH only)

1 heimbach 1.4 C $Header: /u/gcmpack/MITgcm/pkg/ebm/ebm_atmosphere.F,v 1.3 2004/05/21 21:45:35 heimbach Exp $
2 heimbach 1.1 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 heimbach 1.3 #ifdef ALLOW_AUTODIFF_TAMC
39     # include "tamc.h"
40     # include "tamc_keys.h"
41     #endif
42 heimbach 1.1
43     C === Routine arguments ===
44     C myThid - Instance number for this innvocation of CALC_FORCING
45     INTEGER myThid
46     INTEGER myIter
47     _RL myTime
48     CEndOfInterface
49    
50     #ifdef ALLOW_EBM
51    
52     C == Local variables ==
53     _RL Dy
54 heimbach 1.2 _RL ReCountX(1-OLy:sNy+OLy,nSy)
55 heimbach 1.1 INTEGER bi, bj
56     INTEGER i, j
57     INTEGER no_so
58 heimbach 1.3 INTEGER iebmkey
59 heimbach 1.1 LOGICAL TOP_LAYER
60    
61     C-- Top layer only
62     cph TOP_LAYER = k .EQ. 1
63    
64     cph IF ( TOP_LAYER ) THEN
65    
66     DO bj=myByLo(myThid),myByHi(myThid)
67     DO bi=myBxLo(myThid),myBxHi(myThid)
68    
69 heimbach 1.3 #ifdef ALLOW_AUTODIFF_TAMC
70     act1 = bi - myBxLo(myThid)
71     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
72     act2 = bj - myByLo(myThid)
73     max2 = myByHi(myThid) - myByLo(myThid) + 1
74     act3 = myThid - 1
75     max3 = nTx*nTy
76     act4 = ikey_dynamics - 1
77     iebmkey = (act1 + 1) + act2*max1
78     & + act3*max1*max2
79     & + act4*max1*max2*max3
80     #endif /* ALLOW_AUTODIFF_TAMC */
81    
82     DO j=1-oLy,sNy+oLy
83     DO i=1-oLx,sNx+oLx
84     S(i,j,bj) = 0.0
85     P2(i,j,bj) = 0.0
86     P4(i,j,bj) = 0.0
87     ENDDO
88 heimbach 1.2 SW(j,bj) = 0.0
89     LW(j,bj) = 0.0
90     Hd(j,bj) = 0.0
91     Fw(j,bj) = 0.0
92     T(j,bj) = 0.0
93     ReCountX(j,bj) = 0.0
94 heimbach 1.1 ENDDO
95    
96     print *, 'SH', TmlS-t_mlt, TtS-t_mlt
97     print *, 'NH', TmlN-t_mlt, TtN-t_mlt
98    
99     C-- account for ice (can absorb heat on an annual averaged basis)
100     C-- Greenland in Northern Hemisphere, Antarctica in Southern
101 heimbach 1.2 DO j = 1,sNy
102     ReCountX(j,bj) = CountX(j,bj)
103 heimbach 1.1 IF (yC(1,j,bi,bj) .LE. -62.0) THEN
104 heimbach 1.2 ReCountX(j,bj) = 90.
105 heimbach 1.1 ELSE IF (yC(1,j,bi,bj) .EQ. 74.0) THEN
106 heimbach 1.2 ReCountX(j,bj) = CountX(j,bj) + 9.0
107 heimbach 1.1 ELSE IF (yC(1,j,bi,bj) .EQ. 70.0) THEN
108 heimbach 1.2 ReCountX(j,bj) = CountX(j,bj) + 8.0
109 heimbach 1.1 ELSE IF (yC(1,j,bi,bj) .EQ. 66.0) THEN
110 heimbach 1.2 ReCountX(j,bj) = CountX(j,bj) + 5.0
111 heimbach 1.1 ELSE IF (yC(1,j,bi,bj) .EQ. 62.0) THEN
112 heimbach 1.2 ReCountX(j,bj) = CountX(j,bj) + 1.0
113 heimbach 1.1 ENDIF
114     ENDDO
115 heimbach 1.3 #ifdef ALLOW_AUTODIFF_TAMC
116     CADJ STORE ReCountX(:,bj) = comlev1_bibj, key=iebmkey, byte=isbyte
117     #endif
118 heimbach 1.1
119     c=====================================================
120     c Fit area-weighed averaged SST north/south of 34
121     c degree to second Legendre polynomial:
122     c=======================================================
123     T_var(1) = SIN(lat(2)*deg2rad) - SIN(lat(1)*deg2rad)
124     T_var(2) = SIN(lat(3)*deg2rad) - SIN(lat(2)*deg2rad)
125     T_var(3) = SIN(lat(2)*deg2rad)**3. - SIN(lat(1)*deg2rad)**3.
126     T_var(4) = SIN(lat(3)*deg2rad)**3. - SIN(lat(2)*deg2rad)**3.
127 heimbach 1.3 #ifdef ALLOW_AUTODIFF_TAMC
128     CADJ STORE T_var(:) = comlev1_bibj, key=iebmkey, byte=isbyte
129     #endif
130 heimbach 1.1
131     c----------------------------------------
132     c Southern hemisphere:
133     c----------------------------------------
134     T2(1) = 2.*(TtS - TmlS)*T_var(1)*T_var(2)/
135     < (T_var(3)*T_var(2) - T_var(4)*T_var(1))
136     T0(1) = TtS - 0.5*T2(1)*((T_var(3)/T_var(1)) - 1.)
137     c----------------------------------------
138     c Northern hemisphere
139     c----------------------------------------
140     T2(2) = 2.*(TtN - TmlN)*T_var(1)*T_var(2)/
141     < (T_var(3)*T_var(2) - T_var(4)*T_var(1))
142     T0(2) = TtN - 0.5*T2(2)*((T_var(3)/T_var(1)) - 1.)
143     c-----------------------------------------
144     c Temperature at 35 N/S
145     c-----------------------------------------
146     DO no_so = 1,2
147     T35(no_so)= T0(no_so) +
148     < T2(no_so)*0.5*
149     < ((3.*SIN(lat(2)*deg2rad)**2. - 1.))
150     ENDDO
151     c-----------------------------------------
152     c Temperature gradient at 35 N/S
153     c-----------------------------------------
154     DO no_so = 1, 2
155     DTDy35(no_so) = 3.*T2(no_so)*
156     < SIN(lat(2)*deg2rad)/rSphere
157     ENDDO
158     c-----------------------------------------------------------
159     c Magnitude of the heat and moisture transport at 35 N/S
160     c-----------------------------------------------------------
161    
162 heimbach 1.3 #ifdef ALLOW_AUTODIFF_TAMC
163     CADJ STORE T35(:) = comlev1_bibj, key=iebmkey, byte=isbyte
164     CADJ STORE DTDy35(:) = comlev1_bibj, key=iebmkey, byte=isbyte
165     #endif
166 heimbach 1.1
167     DO no_so = 1, 2
168 heimbach 1.4 IF ( DTDy35(no_so).NE.0. .AND. T35(no_so).NE.0. ) THEN
169     gamma = -T35(no_so)*beta*Hw*Nw*Nw/
170 heimbach 1.1 < (gravity*f0*DTDy35(no_so))
171 heimbach 1.4 kappa = Hw/(1 + gamma)
172     De = Hw/(0.48 + 1.48*gamma)
173     C = 0.6*gravity*kappa*kappa*Nw/
174 heimbach 1.1 < (Tw*f0*f0)
175 heimbach 1.4 Cs = rho_air*cp*C*
176 heimbach 1.1 < (1/(1/Hw+1/De) - 1/(1/Hw+1/De+1/dz))
177 heimbach 1.4 Cf = htil*2.97e12*C/(T35(no_so)**3)*(
178 heimbach 1.1 < 1/(1/De + (5420*tau /(T35(no_so)**2)))
179 heimbach 1.4 < - 1/(1/De+5420*tau/(T35(no_so)**2)+1/dz))
180     Cl = Cf*lv
181     Hd35(no_so) = 2.*PI*rSphere*COS(lat(2)*deg2rad)
182 heimbach 1.1 < *(Cs + Cl*exp(-5420./T35(no_so)))
183     < *(abs(DTDy35(no_so))**trans_eff)
184 heimbach 1.4 Fw35(no_so) = 2.*PI*rSphere*COS(lat(2)*deg2rad)
185 heimbach 1.1 < *(abs(DTDy35(no_so))**trans_eff)
186     < *Cf*exp(-5420./T35(no_so))
187 heimbach 1.4 ELSE
188     Hd35(no_so) = 0.
189     Fw35(no_so) = 0.
190     ENDIF
191 heimbach 1.1 ENDDO
192 heimbach 1.4 c
193 heimbach 1.1 Fw35(1) = 929944128.
194     Fw35(2) = 678148032.
195 heimbach 1.4 c
196 heimbach 1.1 #ifdef EBM_VERSION_1BASIN
197     c Fw35(2) = 0.7*Fw35(2)
198     #else
199     Hd35(2) = 1.6*Hd35(2)
200     #endif
201     c======================================================
202     c Calculation of latitudinal profiles
203     c======================================================
204     c
205 heimbach 1.2 DO j=1,sNy
206     DO i=1,sNx
207 heimbach 1.3 C sin(lat)
208     S(i,j,bj) = sin(yC(i,j,bi,bj)*deg2rad)
209     C setup Legendre polynomials and derivatives
210     P2(i,j,bj) = 0.5*(3.*S(i,j,bj)**2 - 1.)
211     P4(i,j,bj) = 0.12*(35.*S(i,j,bj)**4 - 30.*S(i,j,bj)**2 + 3.)
212     ENDDO
213     ENDDO
214     #ifdef ALLOW_AUTODIFF_TAMC
215     CADJ STORE S(:,:,bj) = comlev1_bibj, key=iebmkey, byte=isbyte
216     CADJ STORE P2(:,:,bj) = comlev1_bibj, key=iebmkey, byte=isbyte
217     CADJ STORE P4(:,:,bj) = comlev1_bibj, key=iebmkey, byte=isbyte
218     #endif
219     c
220     DO j=1,sNy
221     DO i=1,sNx
222 heimbach 1.1
223     IF (yC(i,j,bi,bj) .LT. 0.) THEN
224     no_so = 1
225     ELSE
226     no_so = 2
227     ENDIF
228     c net shortwave
229 heimbach 1.3 SW(j,bj) = 0.25*Q0*(1 + Q2*P2(i,j,bj))*
230     < (1 - A0 - A2*P2(i,j,bj) - A4*P4(i,j,bj) )
231 heimbach 1.1 c temperature
232 heimbach 1.3 T(j,bj) = T0(no_so) + T2(no_so)*P2(i,j,bj)
233 heimbach 1.1 c net longwave
234 heimbach 1.2 LW(j,bj) = LW0 + LW1*(T(j,bj)-t_mlt)
235 heimbach 1.1 c climate change run, the parameter to change is DLW
236     #ifdef EBM_CLIMATE_CHANGE
237 heimbach 1.2 LW(j,bj) = LW(j,bj) -
238 heimbach 1.1 < (myTime-startTime)*3.215e-8*DLW
239     c < - 6.0
240     c < *75.0*0.0474*
241 heimbach 1.3 c < (-2.62*S(i,j,bj)**8 + 0.73*S(i,j,bj)**7 +
242     c < 4.82*S(i,j,bj)**6 -
243     c < 1.12*S(i,j,bj)**5 - 2.69*S(i,j,bj)**4 + 0.47*S(i,j,bj)**3 +
244     c < 0.51*S(i,j,bj)**2 - 0.05*S(i,j,bj)**1 + 0.17)
245 heimbach 1.1 #endif
246     c fluxes at ocean/atmosphere interface
247     c Heat Flux = -Div(atmospheric heat transport) + SW - LW
248     #ifdef EBM_VERSION_1BASIN
249 heimbach 1.2 Qnet(i,j,bi,bj) = -1.0*( SW(j,bj) - LW(j,bj) -
250 heimbach 1.1 < Hd35(no_so)*(
251 heimbach 1.3 < 0.000728e4 - 0.00678e4*S(i,j,bj) +
252     < 0.0955e4*S(i,j,bj)**2 + 0.0769e4*S(i,j,bj)**3 -
253     < 0.8508e4*S(i,j,bj)**4 - 0.3581e4*S(i,j,bj)**5 +
254     < 2.9240e4*S(i,j,bj)**6 + 0.8311e4*S(i,j,bj)**7 -
255     < 4.9548e4*S(i,j,bj)**8 - 0.8808e4*S(i,j,bj)**9 +
256     < 4.0644e4*S(i,j,bj)**10 +0.3409e4*S(i,j,bj)**11 -
257     < 1.2893e4*S(i,j,bj)**12 )
258 heimbach 1.1 < /(2*PI*rSphere*rSphere*25.0) )
259 heimbach 1.2 c Qnet(i,j,bi,bj) = -1.0*( SW(j,bj) - LW(j,bj) -
260 heimbach 1.3 c < 0.5*Hd35(no_so)*(3.054e1 - 3.763e1*S(i,j,bj) +
261     c < 1.892e2*S(i,j,bj)**2 + 3.041e2*S(i,j,bj)**3 -
262     c < 1.540e3*S(i,j,bj)**4 - 9.586e2*S(i,j,bj)**5 +
263     c < 2.939e3*S(i,j,bj)**6 + 1.219e3*S(i,j,bj)**7 -
264     c < 2.550e3*S(i,j,bj)**8 - 5.396e2*S(i,j,bj)**9 +
265     c < 8.119e2*S(i,j,bj)**10)
266 heimbach 1.1 c < /(2*PI*rSphere*rSphere*22.3) )
267     #else
268 heimbach 1.2 IF (ReCountX(j,bj) .GT. 0.) THEN
269     Qnet(i,j,bi,bj) = (-90./ReCountX(j,bj))*
270     < ( SW(j,bj) - LW(j,bj) -
271 heimbach 1.3 < Hd35(no_so)*(3.054e1 - 3.763e1*S(i,j,bj) +
272     < 1.892e2*S(i,j,bj)**2 + 3.041e2*S(i,j,bj)**3 -
273     < 1.540e3*S(i,j,bj)**4 - 9.586e2*S(i,j,bj)**5 +
274     < 2.939e3*S(i,j,bj)**6 + 1.219e3*S(i,j,bj)**7 -
275     < 2.550e3*S(i,j,bj)**8 - 5.396e2*S(i,j,bj)**9 +
276     < 8.119e2*S(i,j,bj)**10)
277 heimbach 1.1 < /(2*PI*rSphere*rSphere*22.3) )
278     ELSE
279     Qnet(i,j,bi,bj) = 0.
280     ENDIF
281     #endif
282     c Freshwater Flux = Div(atmospheric moisture transport)
283     c--- conversion of E-P from kg/(s m^2) -> m/s -> psu/s: 1e-3*35/delZ(1)
284     #ifdef EBM_VERSION_1BASIN
285     EmPmR(i,j,bi,bj) = -1.e-3*Fw35(no_so)
286 heimbach 1.3 < *(-0.8454e5*S(i,j,bj)**14 + 0.5367e5*S(i,j,bj)**13
287     < +3.3173e5*S(i,j,bj)**12 - 1.8965e5*S(i,j,bj)**11
288     < -5.1701e5*S(i,j,bj)**10
289     < +2.6240e5*S(i,j,bj)**9 + 4.077e5*S(i,j,bj)**8
290     < -1.791e5*S(i,j,bj)**7
291     < -1.7231e5*S(i,j,bj)**6 + 0.6229e5*S(i,j,bj)**5
292     < +0.3824e5*S(i,j,bj)**4
293     < -0.1017e5*S(i,j,bj)**3 - 0.0387e5*S(i,j,bj)**2
294     < +0.00562e5*S(i,j,bj) + 0.0007743e5)
295 heimbach 1.1 < /(2.0*12.0*PI*rSphere*rSphere)
296     c EmPmR(i,j,bi,bj) = 1.e-3*Fw35(no_so)
297 heimbach 1.3 c < *(50.0 + 228.0*S(i,j,bj) -1.593e3*S(i,j,bj)**2
298     c < - 2.127e3*S(i,j,bj)**3 + 7.3e3*S(i,j,bj)**4
299     c < + 5.799e3*S(i,j,bj)**5 - 1.232e4*S(i,j,bj)**6
300     c < - 6.389e3*S(i,j,bj)**7 + 9.123e3*S(i,j,bj)**8
301     c < + 2.495e3*S(i,j,bj)**9 - 2.567e3*S(i,j,bj)**10)
302 heimbach 1.1 c < /(2*PI*rSphere*rSphere*15.0)
303     #else
304     IF (yC(i,j,bi,bj) .LT. -40.) THEN
305     c-- Southern Hemisphere
306     EmPmR(i,j,bi,bj) = -1.e-3*(Fw35(no_so)*
307 heimbach 1.3 < (-6.5 + 35.3 + 71.7*S(i,j,bj)
308     < - 1336.3*S(i,j,bj)**2 - 425.8*S(i,j,bj)**3
309     < + 5434.8*S(i,j,bj)**4 + 707.9*S(i,j,bj)**5
310     < - 6987.7*S(i,j,bj)**6 - 360.4*S(i,j,bj)**7
311     < + 2855.0*S(i,j,bj)**8)
312 heimbach 1.1 < /(2*PI*rSphere*rSphere*18.0))
313     ELSE
314     c-- Atlantic
315     IF (xC(i,j,bi,bj) .GT. 284.
316     < .OR. xC(i,j,bi,bj) .LT. 28.) THEN
317     EmPmR(i,j,bi,bj) = -1.e-3*(Fw35(no_so)*
318 heimbach 1.3 < (-6.5 -2.878 + 3.157e2*S(i,j,bj) -
319     < 2.388e3*S(i,j,bj)**2 - 4.101e3*S(i,j,bj)**3 +
320     < 1.963e4*S(i,j,bj)**4 + 1.534e4*S(i,j,bj)**5 -
321     < 6.556e4*S(i,j,bj)**6 - 2.478e4*S(i,j,bj)**7 +
322     < 1.083e5*S(i,j,bj)**8 + 1.85e4*S(i,j,bj)**9 -
323     < 8.703e4*S(i,j,bj)**10 - 5.276e3*S(i,j,bj)**11 +
324     < 2.703e4*S(i,j,bj)**12)
325 heimbach 1.1 < /(2*PI*rSphere*rSphere*12.0))
326     ELSE
327     c-- Pacific
328     EmPmR(i,j,bi,bj) = -1.e-3*(Fw35(no_so)
329 heimbach 1.3 < *(-6.5 +51.89 + 4.916e2*S(i,j,bj) -
330     < 1.041e3*S(i,j,bj)**2 - 7.546e3*S(i,j,bj)**3 +
331     < 2.335e3*S(i,j,bj)**4 + 3.449e4*S(i,j,bj)**5 +
332     < 6.702e3*S(i,j,bj)**6 - 6.601e4*S(i,j,bj)**7 -
333     < 2.594e4*S(i,j,bj)**8 + 5.652e4*S(i,j,bj)**9 +
334     < 2.738e4*S(i,j,bj)**10 - 1.795e4*S(i,j,bj)**11 -
335     < 9.486e3*S(i,j,bj)**12)
336 heimbach 1.1 < /(2*PI*rSphere*rSphere*12.0))
337     ENDIF
338     ENDIF
339     #endif
340     ENDDO
341     ENDDO
342     ENDDO
343     ENDDO
344 heimbach 1.2
345     _EXCH_XY_R4(Qnet , myThid )
346     _EXCH_XY_R4(EmPmR , myThid )
347    
348 heimbach 1.1
349     C CALL PLOT_FIELD_XYRS( Qnet, 'Qnet' , 1, myThid )
350     C CALL PLOT_FIELD_XYRS( EmPmR, 'EmPmR' , 1, myThid )
351    
352     cph end of IF TOP_LAYER
353     cph ENDIF
354    
355     #endif /* ALLOW_EBM */
356    
357     END
358    
359    
360    
361    
362    

  ViewVC Help
Powered by ViewVC 1.1.22