/[MITgcm]/MITgcm/pkg/aim_v23/phy_radiat.F
ViewVC logotype

Contents of /MITgcm/pkg/aim_v23/phy_radiat.F

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


Revision 1.3 - (show annotations) (download)
Thu Jun 24 23:43:11 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57g_pre, checkpoint57s_post, checkpoint58b_post, checkpoint57b_post, checkpoint57g_post, checkpoint56b_post, checkpoint57y_post, checkpoint54d_post, checkpoint54e_post, checkpoint57r_post, checkpoint57d_post, checkpoint57i_post, checkpoint59, checkpoint58, checkpoint55, checkpoint54, checkpoint57, checkpoint56, checkpoint58f_post, checkpoint57n_post, checkpoint58d_post, checkpoint58a_post, checkpoint57z_post, checkpoint54f_post, checkpoint58y_post, checkpoint58t_post, checkpoint55i_post, checkpoint58m_post, checkpoint57l_post, checkpoint57t_post, checkpoint55c_post, checkpoint57v_post, checkpoint57f_post, checkpoint57a_post, checkpoint57h_pre, checkpoint54b_post, checkpoint58w_post, checkpoint57h_post, checkpoint57y_pre, checkpoint55g_post, checkpoint58o_post, checkpoint57c_post, checkpoint58p_post, checkpoint58q_post, checkpoint55d_post, checkpoint58e_post, checkpoint54a_pre, checkpoint55d_pre, checkpoint57c_pre, checkpoint58r_post, checkpoint55j_post, checkpoint54a_post, checkpoint55h_post, checkpoint58n_post, checkpoint57e_post, checkpoint55b_post, checkpoint59e, checkpoint59d, checkpoint59a, checkpoint55f_post, checkpoint59c, checkpoint59b, checkpoint53g_post, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, eckpoint57e_pre, checkpoint58k_post, checkpoint58v_post, checkpoint56a_post, checkpoint58l_post, checkpoint53f_post, checkpoint57h_done, checkpoint57j_post, checkpoint57f_pre, checkpoint58g_post, checkpoint58x_post, checkpoint58h_post, checkpoint56c_post, checkpoint58j_post, checkpoint57a_pre, checkpoint55a_post, checkpoint57o_post, checkpoint57k_post, checkpoint57w_post, checkpoint58i_post, checkpoint57x_post, checkpoint58c_post, checkpoint58u_post, checkpoint58s_post, checkpoint55e_post, checkpoint54c_post
Changes since 1.2: +20 -12 lines
- include stability function into surf.Flux derivative relative to Ts
- calculate clear-sky radiation & surface temp. change
- update diagnostics (snap-shot, timeave & diagnostics)

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/phy_radiat.F,v 1.2 2004/03/11 14:33:19 jmc Exp $
2 C $Name: $
3
4 #include "AIM_OPTIONS.h"
5
6 SUBROUTINE SOL_OZ (SOLC, TYEAR, SLAT, CLAT,
7 O FSOL, OZONE, OZUPP, ZENIT, STRATZ,
8 I bi, bj, myThid)
9
10 C--
11 C-- SUBROUTINE SOL_OZ (SOLC,TYEAR)
12 C--
13 C-- Purpose: Compute the flux of incoming solar radiation
14 C-- and a climatological ozone profile for SW absorption
15 C-- Input: SOLC = solar constant (area averaged)
16 C-- TYEAR = time as fraction of year (0-1, 0 = 1jan.h00)
17 C SLAT = sin(lat)
18 C CLAT = cos(lat)
19 C-- Output: FSOL = flux of incoming solar radiation
20 C-- OZONE = flux absorbed by ozone (lower stratos.)
21 C-- OZUPP = flux absorbed by ozone (upper stratos.)
22 C-- ZENIT = function of solar zenith angle
23 C-- STRATZ = ?
24 C-- Updated common blocks: RADZON
25 C--
26
27 IMPLICIT NONE
28
29 C Resolution parameters
30
31 C-- size for MITgcm & Physics package :
32 #include "AIM_SIZE.h"
33
34 #include "EEPARAMS.h"
35
36 C Constants + functions of sigma and latitude
37 #include "com_physcon.h"
38
39 C Radiation constants
40 #include "com_radcon.h"
41
42 C-- Routine arguments:
43 INTEGER bi, bj, myThid
44 _RL SOLC, TYEAR
45 _RL SLAT(NGP), CLAT(NGP)
46 _RL FSOL(NGP), OZONE(NGP), OZUPP(NGP), ZENIT(NGP), STRATZ(NGP)
47
48 #ifdef ALLOW_AIM
49
50 C-- Local variables:
51 INTEGER J, NZEN
52
53 C- jmc: declare all local variables:
54 _RL ALPHA, CSR1, CSR2, COZ1, COZ2
55 _RL AZEN, RZEN, CZEN, SZEN, AST, FS0, FLAT2
56 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
57
58 C ALPHA = year phase ( 0 - 2pi, 0 = winter solstice = 22dec.h00 )
59 ALPHA = 4. _d 0*ASIN(1. _d 0)*(TYEAR+10. _d 0/365. _d 0)
60
61 CSR1=-0.796 _d 0*COS(ALPHA)
62 CSR2= 0.147 _d 0*COS(2. _d 0*ALPHA)-0.477 _d 0
63 COZ1= 1.0 _d 0 * COS(ALPHA)
64 COZ2= 1.8 _d 0
65 C
66 AZEN=1.0
67 NZEN=2
68
69 RZEN=-COS(ALPHA)*23.45 _d 0*ASIN(1. _d 0)/90. _d 0
70 CZEN=COS(RZEN)
71 SZEN=SIN(RZEN)
72
73 AST=0.025 _d 0
74 FS0=10. _d 0
75 C FS0=16.-8.*COS(ALPHA)
76
77 DO J=1,NGP
78
79 FLAT2 = 1.5 _d 0*SLAT(J)**2 - 0.5 _d 0
80
81 C solar radiation at the top
82 FSOL(J) = SOLC*
83 & MAX( 0. _d 0, 1. _d 0+CSR1*SLAT(J)+CSR2*FLAT2 )
84
85 C ozone depth in upper and lower stratosphere
86 OZUPP(J) = EPSSW*(1.-FLAT2)
87 OZONE(J) = EPSSW*(1.+COZ1*SLAT(J)+COZ2*FLAT2)
88
89 C zenith angle correction to (downward) absorptivity
90 ZENIT(J) = 1. + AZEN*
91 & (1. _d 0-(CLAT(J)*CZEN+SLAT(J)*SZEN))**NZEN
92
93 C ozone absorption in upper and lower stratosphere
94 OZUPP(J)=FSOL(J)*OZUPP(J)*ZENIT(J)
95 OZONE(J)=FSOL(J)*OZONE(J)*ZENIT(J)
96 STRATZ(J)=AST*FSOL(J)*CLAT(J)**3
97 & +MAX( FS0-FSOL(J), 0. _d 0 )
98
99 ENDDO
100
101 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
102
103 #endif /* ALLOW_AIM */
104 RETURN
105 END
106
107
108 SUBROUTINE RADSW (PSA,dpFac,QA,RH,ALB,
109 I FSOL, OZONE, OZUPP, ZENIT, STRATZ,
110 O TAU2, STRATC,
111 O ICLTOP,CLOUDC,FTOP,FSFC,DFABS,
112 I kGrd,bi,bj,myThid)
113 C--
114 C-- SUBROUTINE RADSW (PSA,QA,RH,ALB,
115 C-- & ICLTOP,CLOUDC,FTOP,FSFC,DFABS)
116 C--
117 C-- Purpose: Compute the absorption of shortwave radiation and
118 C-- initialize arrays for longwave-radiation routines
119 C-- Input: PSA = norm. surface pressure [p/p0] (2-dim)
120 C dpFac = cell delta_P fraction (3-dim)
121 C-- QA = specific humidity [g/kg] (3-dim)
122 C-- RH = relative humidity (3-dim)
123 C-- ALB = surface albedo (2-dim)
124 C-- Output: ICLTOP = cloud top level (2-dim)
125 C-- CLOUDC = total cloud cover (2-dim)
126 C-- FTOP = net downw. flux of sw rad. at the atm. top (2-dim)
127 C-- FSFC = net downw. flux of sw rad. at the surface (2-dim)
128 C-- DFABS = flux of sw rad. absorbed by each atm. layer (3-dim)
129 C Input: kGrd = Ground level index (2-dim)
130 C bi,bj = tile index
131 C myThid = Thread number for this instance of the routine
132 C--
133
134 IMPLICIT NONE
135
136 C Resolution parameters
137
138 C-- size for MITgcm & Physics package :
139 #include "AIM_SIZE.h"
140
141 #include "EEPARAMS.h"
142
143 C Constants + functions of sigma and latitude
144
145 #include "com_physcon.h"
146
147 C Radiation parameters
148
149 #include "com_radcon.h"
150
151 C-- Routine arguments:
152 _RL PSA(NGP),dpFac(NGP,NLEV),QA(NGP,NLEV),RH(NGP,NLEV)
153 _RL ALB(NGP,0:3)
154 INTEGER ICLTOP(NGP)
155 _RL CLOUDC(NGP), FTOP(NGP), FSFC(NGP,0:3), DFABS(NGP,NLEV)
156
157 _RL FSOL(NGP), OZONE(NGP), OZUPP(NGP), ZENIT(NGP), STRATZ(NGP)
158 _RL TAU2(NGP,NLEV,NBAND),STRATC(NGP)
159 c _RL FLUX(NGP,4)
160
161 INTEGER kGrd(NGP)
162 INTEGER bi, bj, myThid
163
164 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
165
166 #ifdef ALLOW_AIM
167
168 C-- Local variables:
169 c _RL QCLOUD(NGP), ACLOUD(NGP), PSAZ(NGP),
170 _RL QCLOUD(NGP), ACLOUD(NGP),
171 & ALBTOP(NGP,NLEV), FREFL(NGP,NLEV), FLUX(NGP,2)
172
173 C- jmc: define "FLUX" as a local variable & remove Equivalences:
174 c EQUIVALENCE (ALBTOP(1,1),TAU2(1,1,3))
175 c EQUIVALENCE ( FREFL(1,1),TAU2(1,1,4))
176
177 INTEGER NL1(NGP)
178 INTEGER K, J
179 LOGICAL makeClouds
180
181 C- jmc: declare local variables:
182 _RL FBAND1, FBAND2, RRCL, RQCL, DQACL, QACL3
183 _RL ABS1, DELTAP
184 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
185
186 FBAND2=0.05 _d 0
187 FBAND1=1.-FBAND2
188
189 DO J=1,NGP
190 NL1(J)=kGrd(J)-1
191 ENDDO
192
193 C-- 1. Cloud cover:
194 C defined as a linear fun. of the maximum relative humidity
195 C in all tropospheric layers above PBL:
196 C CLOUDC = 0 for RHmax < RHCL1, = 1 for RHmax > RHCL2.
197 C This value is reduced by a factor (Qbase/QACL) if the
198 C cloud-base absolute humidity Qbase < QACL.
199 C
200 makeClouds = ICLTOP(1) .GE. 0
201 RRCL=1./(RHCL2-RHCL1)
202 RQCL=1./QACL2
203 C
204 DO J=1,NGP
205 CLOUDC(J)=0.
206 QCLOUD(J)=0.
207 ICLTOP(J)=NLEV+1
208 FREFL(J,1)=0.
209 ENDDO
210
211 DO K=1,NLEV
212 DO J=1,NGP
213 ALBTOP(J,K)=0.
214 ENDDO
215 ENDDO
216 C
217 IF ( makeClouds ) THEN
218 C- skipp this part for clear-sky diagnostics
219
220 DQACL=(QACL2-QACL1)/(0.5 _d 0 - SIG(2))
221 DO J=1,NGP
222 ICLTOP(J)= kGrd(J)
223 DO K=NL1(J),2,-1
224 QACL3=MIN(QACL2,QACL1+DQACL*(SIG(K)-SIG(2)))
225 IF (RH(J,K).GT.RHCL1.AND.QA(J,K).GT.QACL1) THEN
226 CLOUDC(J)=MAX(CLOUDC(J),RH(J,K)-RHCL1)
227 IF (QA(J,K).GT.QACL3) ICLTOP(J)=K
228 ENDIF
229 ENDDO
230 ENDDO
231
232 DO J=1,NGP
233 IF (kGrd(J).NE.0)
234 & QCLOUD(J)= MAX( QA(J,kGrd(J)), QA(J,NL1(J)) )
235 CLOUDC(J)=MIN(1. _d 0,CLOUDC(J)*RRCL)
236 IF (CLOUDC(J).GT.0.0) THEN
237 CLOUDC(J)=CLOUDC(J)*MIN(1. _d 0,QCLOUD(J)*RQCL)
238 ALBTOP(J,ICLTOP(J))=ALBCL*CLOUDC(J)
239 ELSE
240 ICLTOP(J)=NLEV+1
241 ENDIF
242 ENDDO
243
244 C- end if makeClouds
245 ENDIF
246
247 C
248 C-- 2. Shortwave transmissivity:
249 C function of layer mass, ozone (in the statosphere),
250 C abs. humidity and cloud cover (in the troposphere)
251
252 DO J=1,NGP
253 c_FM PSAZ(J)=PSA(J)*ZENIT(J)
254 ACLOUD(J)=CLOUDC(J)*(ABSCL1+ABSCL2*QCLOUD(J))
255 ENDDO
256
257 DO J=1,NGP
258 c_FM DELTAP=PSAZ(J)*DSIG(1)
259 DELTAP=ZENIT(J)*DSIG(1)*dpFac(J,1)
260 TAU2(J,1,1)=EXP(-DELTAP*ABSDRY)
261 ENDDO
262 C
263 DO J=1,NGP
264 DO K=2,NL1(J)
265 c_FM ABS1=ABSDRY+ABSAER*SIG(K)**2
266 c_FM DELTAP=PSAZ(J)*DSIG(K)
267 ABS1=ABSDRY+ABSAER*(SIG(K)/PSA(J))**2
268 DELTAP=ZENIT(J)*DSIG(K)*dpFac(J,K)
269 IF (K.EQ.ICLTOP(J)) THEN
270 TAU2(J,K,1)=EXP(-DELTAP*
271 & (ABS1+ABSWV1*QA(J,K)+2.*ACLOUD(J)))
272 ELSE IF (K.GT.ICLTOP(J)) THEN
273 TAU2(J,K,1)=EXP(-DELTAP*
274 & (ABS1+ABSWV1*QA(J,K)+ACLOUD(J)))
275 ELSE
276 TAU2(J,K,1)=EXP(-DELTAP*(ABS1+ABSWV1*QA(J,K)))
277 ENDIF
278 ENDDO
279 ENDDO
280
281 c_FM ABS1=ABSDRY+ABSAER*SIG(NLEV)**2
282 DO J=1,NGP
283 K = kGrd(J)
284 ABS1=ABSDRY+ABSAER*(SIG(K)/PSA(J))**2
285 c_FM DELTAP=PSAZ(J)*DSIG(NLEV)
286 DELTAP=ZENIT(J)*DSIG(K)*dpFac(J,K)
287 TAU2(J,K,1)=EXP(-DELTAP*(ABS1+ABSWV1*QA(J,K)))
288 ENDDO
289
290 DO J=1,NGP
291 DO K=2,kGrd(J)
292 DELTAP=ZENIT(J)*DSIG(K)*dpFac(J,K)
293 TAU2(J,K,2)=EXP(-DELTAP*ABSWV2*QA(J,K))
294 ENDDO
295 ENDDO
296 C
297 C--- 3. Shortwave downward flux
298 C
299 C 3.1 Absorption in the stratosphere
300
301 C 3.1.1 Initialization of fluxes (subtracting
302 C ozone absorption in the upper stratosphere)
303
304 DO J=1,NGP
305 FTOP(J) =FSOL(J)
306 FLUX(J,1)=FSOL(J)*FBAND1-OZUPP(J)
307 FLUX(J,2)=FSOL(J)*FBAND2
308 STRATC(J)=STRATZ(J)*PSA(J)
309 ENDDO
310
311 C 3.1.2 Ozone and dry-air absorption
312 C in the lower (modelled) stratosphere
313
314 DO J=1,NGP
315 DFABS(J,1)=FLUX(J,1)
316 FLUX (J,1)=TAU2(J,1,1)*(FLUX(J,1)-OZONE(J)*PSA(J))
317 DFABS(J,1)=DFABS(J,1)-FLUX(J,1)
318 ENDDO
319
320 C 3.3 Absorption and reflection in the troposphere
321 C
322 DO J=1,NGP
323 DO K=2,kGrd(J)
324 FREFL(J,K)=FLUX(J,1)*ALBTOP(J,K)
325 FLUX (J,1)=FLUX(J,1)-FREFL(J,K)
326 DFABS(J,K)=FLUX(J,1)
327 FLUX (J,1)=TAU2(J,K,1)*FLUX(J,1)
328 DFABS(J,K)=DFABS(J,K)-FLUX(J,1)
329 ENDDO
330 ENDDO
331
332 DO J=1,NGP
333 DO K=2,kGrd(J)
334 DFABS(J,K)=DFABS(J,K)+FLUX(J,2)
335 FLUX (J,2)=TAU2(J,K,2)*FLUX(J,2)
336 DFABS(J,K)=DFABS(J,K)-FLUX(J,2)
337 ENDDO
338 ENDDO
339
340 C
341 C--- 4. Shortwave upward flux
342 C
343 C 4.1 Absorption and reflection at the surface
344 C
345 DO J=1,NGP
346 C for each surface type:
347 FSFC(J,1)=FLUX(J,1)*(1.-ALB(J,1))+FLUX(J,2)
348 FSFC(J,2)=FLUX(J,1)*(1.-ALB(J,2))+FLUX(J,2)
349 FSFC(J,3)=FLUX(J,1)*(1.-ALB(J,3))+FLUX(J,2)
350 C weighted average according to land/sea/sea-ice fraction:
351 FSFC(J,0)=FLUX(J,1)+FLUX(J,2)
352 FLUX(J,1)=FLUX(J,1)*ALB(J,0)
353 FSFC(J,0)=FSFC(J,0)-FLUX(J,1)
354 ENDDO
355 C
356 C 4.2 Absorption of upward flux
357 C
358 DO J=1,NGP
359 DO K=kGrd(J),1,-1
360 DFABS(J,K)=DFABS(J,K)+FLUX(J,1)
361 FLUX (J,1)=TAU2(J,K,1)*FLUX(J,1)
362 DFABS(J,K)=DFABS(J,K)-FLUX(J,1)
363 FLUX (J,1)=FLUX(J,1)+FREFL(J,K)
364 ENDDO
365 ENDDO
366 C
367 C 4.3 Net solar radiation = incoming - outgoing
368 C
369 DO J=1,NGP
370 FTOP(J)=FTOP(J)-FLUX(J,1)
371 ENDDO
372
373 C
374 C--- 5. Initialization of longwave radiation model
375 C
376 C 5.1 Longwave transmissivity:
377 C function of layer mass, abs. humidity and cloud cover.
378
379 DO J=1,NGP
380 ACLOUD(J)=CLOUDC(J)*(ABLCL1+ABLCL2*QCLOUD(J))
381 ENDDO
382
383 DO J=1,NGP
384 c_FM DELTAP=PSA(J)*DSIG(1)
385 DELTAP=DSIG(1)*dpFac(J,1)
386 TAU2(J,1,1)=EXP(-DELTAP*ABLWIN)
387 TAU2(J,1,2)=EXP(-DELTAP*ABLCO2)
388 TAU2(J,1,3)=1.
389 TAU2(J,1,4)=1.
390 ENDDO
391
392 DO K=2,NLEV
393 DO J=1,NGP
394 c_FM DELTAP=PSA(J)*DSIG(K)
395 DELTAP=DSIG(K)*dpFac(J,K)
396 IF ( K.GE.ICLTOP(J).AND.K.NE.kGrd(J) ) THEN
397 TAU2(J,K,1)=EXP(-DELTAP*(ABLWIN+ACLOUD(J)))
398 ELSE
399 TAU2(J,K,1)=EXP(-DELTAP*ABLWIN)
400 ENDIF
401 TAU2(J,K,2)=EXP(-DELTAP*ABLCO2)
402 TAU2(J,K,3)=EXP(-DELTAP*ABLWV1*QA(J,K))
403 TAU2(J,K,4)=EXP(-DELTAP*ABLWV2*QA(J,K))
404 ENDDO
405 ENDDO
406 C
407 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
408 #endif /* ALLOW_AIM */
409
410 RETURN
411 END
412
413
414 SUBROUTINE RADLW (IMODE,TA,TS,ST4S,
415 I OZUPP, STRATC, TAU2,
416 & FLUX, ST4A,
417 & FTOP,FSFC,DFABS,
418 I kGrd,bi,bj,myThid)
419 C--
420 C-- SUBROUTINE RADLW (IMODE,TA,TS,ST4S,
421 C-- & FTOP,FSFC,DFABS)
422 C--
423 C-- Purpose: Compute the absorption of longwave radiation
424 C-- Input: IMODE = index for operation mode
425 C-- -1 : downward flux only
426 C-- 0 : downward + upward flux
427 C-- +1 : upward flux only
428 C-- TA = absolute temperature (3-dim)
429 C-- TS = surface temperature [if IMODE=0,1]
430 C-- ST4S = surface blackbody emission [if IMODE=1]
431 C-- FSFC = FSFC output from RADLW(-1,... ) [if IMODE=1]
432 C-- DFABS = DFABS output from RADLW(-1,... ) [if IMODE=1]
433 C-- Output: ST4S = surface blackbody emission [if IMODE=0]
434 C-- FTOP = outgoing flux of lw rad. at the top [if IMODE=0,1]
435 C-- FSFC = downward flux of lw rad. at the sfc. [if IMODE= -1]
436 C-- net upw. flux of lw rad. at the sfc. [if IMODE=0,1]
437 C-- DFABS = flux of lw rad. absorbed by each atm. layer (3-dim)
438 C Input: kGrd = Ground level index (2-dim)
439 C bi,bj = tile index
440 C myThid = Thread number for this instance of the routine
441 C--
442
443 IMPLICIT NONE
444
445 C Resolution parameters
446
447 C-- size for MITgcm & Physics package :
448 #include "AIM_SIZE.h"
449
450 #include "EEPARAMS.h"
451
452 C Number of radiation bands with tau < 1
453 c INTEGER NBAND
454 c PARAMETER ( NBAND=4 )
455
456 C Constants + functions of sigma and latitude
457 #include "com_physcon.h"
458
459 C Radiation parameters
460 #include "com_radcon.h"
461
462 C-- Routine arguments:
463 INTEGER IMODE
464 _RL TA(NGP,NLEV), TS(NGP), ST4S(NGP)
465 _RL FTOP(NGP), FSFC(NGP), DFABS(NGP,NLEV)
466 _RL OZUPP(NGP), STRATC(NGP)
467 _RL TAU2(NGP,NLEV,NBAND), FLUX(NGP,NBAND), ST4A(NGP,NLEV,2)
468
469 INTEGER kGrd(NGP)
470 INTEGER bi,bj,myThid
471
472 #ifdef ALLOW_AIM
473
474 C-- Local variables:
475 INTEGER K, J, JB
476 c INTEGER J0, Jl, I2
477 INTEGER NL1(NGP)
478
479 C- jmc: declare all local variables:
480 _RL REFSFC, BRAD, EMIS
481 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
482
483 DO J=1,NGP
484 NL1(J)=kGrd(J)-1
485 ENDDO
486
487 REFSFC=1.-EMISFC
488
489 IF (IMODE.EQ.1) GO TO 410
490
491 C--- 1. Blackbody emission from atmospheric full and half levels.
492 C Temperature is interpolated as a linear function of ln sigma.
493 C At the lower boundary, the emission is linearly extrapolated;
494 C at the upper boundary, the atmosphere is assumed isothermal.
495
496 DO K=1,NLEV
497 DO J=1,NGP
498 ST4A(J,K,1)=TA(J,K)*TA(J,K)
499 ST4A(J,K,1)=SBC*ST4A(J,K,1)*ST4A(J,K,1)
500 ENDDO
501 ENDDO
502 C
503 DO K=1,NLEV-1
504 DO J=1,NGP
505 ST4A(J,K,2)=TA(J,K)+WVI(K,2)*(TA(J,K+1)-TA(J,K))
506 ST4A(J,K,2)=ST4A(J,K,2)*ST4A(J,K,2)
507 ST4A(J,K,2)=SBC*ST4A(J,K,2)*ST4A(J,K,2)
508 ENDDO
509 ENDDO
510 C
511 DO J=1,NGP
512 c ST4A(J,NLEV,2)=ST4A(J,NLEV,1)
513 K=kGrd(J)
514 ST4A(J,K,2)=2.*ST4A(J,K,1)-ST4A(J,NL1(J),2)
515 ENDDO
516
517 C--- 2. Initialization
518 C--- (including the stratospheric correction term)
519
520 DO J=1,NGP
521 FTOP(J) = 0.
522 FSFC(J) = STRATC(J)
523 DFABS(J,1)=-STRATC(J)
524 ENDDO
525
526 DO K=2,NLEV
527 DO J=1,NGP
528 DFABS(J,K)=0.
529 ENDDO
530 ENDDO
531
532 C--- 3. Emission ad absorption of longwave downward flux.
533 C Downward emission is an average of the emission from the full level
534 C and the half-level below, weighted according to the transmissivity
535 C of the layer.
536
537 C 3.1 Stratosphere
538
539 K=1
540 DO JB=1,2
541 DO J=1,NGP
542 BRAD=ST4A(J,K,2)+TAU2(J,K,JB)*(ST4A(J,K,1)-ST4A(J,K,2))
543 EMIS=FBAND(NINT(TA(J,K)),JB)*(1.-TAU2(J,K,JB))
544 FLUX(J,JB)=EMIS*BRAD
545 DFABS(J,K)=DFABS(J,K)-FLUX(J,JB)
546 ENDDO
547 ENDDO
548
549 DO JB=3,NBAND
550 DO J=1,NGP
551 FLUX(J,JB)=0.
552 ENDDO
553 ENDDO
554
555 C 3.2 Troposphere
556
557 DO JB=1,NBAND
558 DO J=1,NGP
559 DO K=2,kGrd(J)
560 BRAD=ST4A(J,K,2)+TAU2(J,K,JB)*(ST4A(J,K,1)-ST4A(J,K,2))
561 EMIS=FBAND(NINT(TA(J,K)),JB)*(1.-TAU2(J,K,JB))
562 DFABS(J,K)=DFABS(J,K)+FLUX(J,JB)
563 FLUX(J,JB)=TAU2(J,K,JB)*FLUX(J,JB)+EMIS*BRAD
564 DFABS(J,K)=DFABS(J,K)-FLUX(J,JB)
565 ENDDO
566 ENDDO
567 ENDDO
568
569 DO JB=1,NBAND
570 DO J=1,NGP
571 FSFC(J)=FSFC(J)+EMISFC*FLUX(J,JB)
572 ENDDO
573 ENDDO
574
575 IF (IMODE.EQ.-1) RETURN
576
577 C--- 4. Emission ad absorption of longwave upward flux
578 C Upward emission is an average of the emission from the full level
579 C and the half-level above, weighted according to the transmissivity
580 C of the layer (for the top layer, full-level emission is used).
581 C Surface lw emission in "band 0" goes directly into FTOP.
582
583 C 4.1 Surface
584
585 DO J=1,NGP
586 ST4S(J)=TS(J)*TS(J)
587 ST4S(J)=SBC*ST4S(J)*ST4S(J)
588 ST4S(J)=EMISFC*ST4S(J)
589 ENDDO
590
591 C Entry point for upward-only mode (IMODE=1)
592 410 CONTINUE
593
594 DO J=1,NGP
595 FSFC(J)=ST4S(J)-FSFC(J)
596 FTOP(J)=FTOP(J)+FBAND(NINT(TS(J)),0)*ST4S(J)
597 ENDDO
598
599 DO JB=1,NBAND
600 DO J=1,NGP
601 FLUX(J,JB)=FBAND(NINT(TS(J)),JB)*ST4S(J)
602 & +REFSFC*FLUX(J,JB)
603 ENDDO
604 ENDDO
605
606 C 4.2 Troposphere
607
608 DO JB=1,NBAND
609 DO J=1,NGP
610 DO K=kGrd(J),2,-1
611 BRAD=ST4A(J,K-1,2)+TAU2(J,K,JB)*(ST4A(J,K,1)-ST4A(J,K-1,2))
612 EMIS=FBAND(NINT(TA(J,K)),JB)*(1.-TAU2(J,K,JB))
613 DFABS(J,K)=DFABS(J,K)+FLUX(J,JB)
614 FLUX(J,JB)=TAU2(J,K,JB)*FLUX(J,JB)+EMIS*BRAD
615 DFABS(J,K)=DFABS(J,K)-FLUX(J,JB)
616 ENDDO
617 ENDDO
618 ENDDO
619
620 C 4.3 Stratosphere
621
622 K=1
623 DO JB=1,2
624 DO J=1,NGP
625 EMIS=FBAND(NINT(TA(J,K)),JB)*(1.-TAU2(J,K,JB))
626 DFABS(J,K)=DFABS(J,K)+FLUX(J,JB)
627 FLUX(J,JB)=TAU2(J,K,JB)*FLUX(J,JB)+EMIS*ST4A(J,K,1)
628 DFABS(J,K)=DFABS(J,K)-FLUX(J,JB)
629 ENDDO
630 ENDDO
631
632 C 4.4 Outgoing longwave radiation
633
634 DO JB=1,NBAND
635 DO J=1,NGP
636 FTOP(J)=FTOP(J)+FLUX(J,JB)
637 ENDDO
638 ENDDO
639
640 DO J=1,NGP
641 FTOP(J)=FTOP(J)+OZUPP(J)
642 ENDDO
643
644 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
645 #endif /* ALLOW_AIM */
646
647 RETURN
648 END
649
650
651 SUBROUTINE RADSET( myThid )
652
653 C--
654 C-- SUBROUTINE RADSET
655 C--
656 C-- Purpose: compute energy fractions in LW bands
657 C-- as a function of temperature
658 C-- Initialized common blocks: RADFIX
659
660 IMPLICIT NONE
661
662 C Resolution parameters
663
664 C-- size for MITgcm & Physics package :
665 #include "AIM_SIZE.h"
666
667 #include "EEPARAMS.h"
668
669 C Radiation constants
670 #include "com_radcon.h"
671
672 C-- Routine arguments:
673 INTEGER myThid
674
675 #ifdef ALLOW_AIM
676
677 C-- Local variables:
678 INTEGER JTEMP, JB
679 _RL EPS3
680
681 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
682
683 EPS3=0.95 _d 0
684
685 DO JTEMP=200,320
686 FBAND(JTEMP,0)= EPSLW
687 FBAND(JTEMP,2)= 0.148 _d 0 - 3.0 _d -6 *(JTEMP-247)**2
688 FBAND(JTEMP,3)=(0.375 _d 0 - 5.5 _d -6 *(JTEMP-282)**2)*EPS3
689 FBAND(JTEMP,4)= 0.314 _d 0 + 1.0 _d -5 *(JTEMP-315)**2
690 FBAND(JTEMP,1)= 1. _d 0 -(FBAND(JTEMP,0)+FBAND(JTEMP,2)
691 & +FBAND(JTEMP,3)+FBAND(JTEMP,4))
692 ENDDO
693
694 DO JB=0,NBAND
695 DO JTEMP=lwTemp1,199
696 FBAND(JTEMP,JB)=FBAND(200,JB)
697 ENDDO
698 DO JTEMP=321,lwTemp2
699 FBAND(JTEMP,JB)=FBAND(320,JB)
700 ENDDO
701 ENDDO
702
703 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
704 #endif /* ALLOW_AIM */
705
706 RETURN
707 END

  ViewVC Help
Powered by ViewVC 1.1.22