/[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.1 - (show annotations) (download)
Fri Nov 22 17:17:03 2002 UTC (21 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint51k_post, checkpoint47e_post, checkpoint52l_pre, hrcube4, hrcube5, checkpoint50c_post, checkpoint52d_pre, checkpoint48e_post, checkpoint50c_pre, checkpoint52j_pre, checkpoint51o_pre, checkpoint51l_post, checkpoint48i_post, checkpoint50d_pre, checkpoint52k_post, checkpoint51, checkpoint50, checkpoint52, checkpoint50d_post, checkpoint52f_post, checkpoint50b_pre, checkpoint51f_post, checkpoint48b_post, checkpoint51d_post, checkpoint48c_pre, checkpoint47d_pre, checkpoint51t_post, checkpoint51n_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint51s_post, checkpoint47a_post, checkpoint48d_pre, checkpoint51j_post, checkpoint47i_post, checkpoint52e_pre, checkpoint52e_post, checkpoint51n_pre, checkpoint47d_post, checkpoint48d_post, checkpoint48f_post, checkpoint52b_pre, checkpoint51l_pre, checkpoint48h_post, checkpoint51q_post, checkpoint51b_pre, checkpoint47g_post, checkpoint52b_post, checkpoint52c_post, checkpoint51h_pre, checkpoint48a_post, checkpoint50f_post, checkpoint50a_post, checkpoint50f_pre, checkpoint52f_pre, checkpoint47j_post, branch-exfmods-tag, branchpoint-genmake2, checkpoint51r_post, checkpoint48c_post, checkpoint51i_post, checkpoint51b_post, checkpoint51c_post, checkpoint47b_post, checkpoint52d_post, checkpoint50g_post, checkpoint52a_pre, checkpoint50h_post, checkpoint52i_post, checkpoint50e_pre, checkpoint50i_post, checkpoint51i_pre, checkpoint52h_pre, checkpoint52j_post, checkpoint47f_post, checkpoint50e_post, branch-netcdf, checkpoint51e_post, checkpoint48, checkpoint49, checkpoint51o_post, checkpoint51f_pre, checkpoint47h_post, checkpoint52a_post, checkpoint51g_post, ecco_c52_e35, checkpoint50b_post, checkpoint51m_post, checkpoint51a_post, checkpoint51p_post, checkpoint48g_post, checkpoint51u_post
Branch point for: branch-exfmods-curt, branch-genmake2, branch-nonh, tg2-branch, netcdf-sm0, checkpoint51n_branch
new aim pkg: adapted from Franco Molteni SPEEDY code, ver23

1 C $Header: $
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),ALB(NGP)
153 INTEGER ICLTOP(NGP)
154 _RL CLOUDC(NGP), FTOP(NGP), FSFC(NGP), DFABS(NGP,NLEV)
155
156 _RL FSOL(NGP), OZONE(NGP), OZUPP(NGP), ZENIT(NGP), STRATZ(NGP)
157 _RL TAU2(NGP,NLEV,NBAND),STRATC(NGP)
158 c _RL FLUX(NGP,4)
159
160 INTEGER kGrd(NGP)
161 INTEGER bi, bj, myThid
162
163 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
164
165 #ifdef ALLOW_AIM
166
167 C-- Local variables:
168 c _RL QCLOUD(NGP), ACLOUD(NGP), PSAZ(NGP),
169 _RL QCLOUD(NGP), ACLOUD(NGP),
170 & ALBTOP(NGP,NLEV), FREFL(NGP,NLEV), FLUX(NGP,2)
171
172 C- jmc: define "FLUX" as a local variable & remove Equivalences:
173 c EQUIVALENCE (ALBTOP(1,1),TAU2(1,1,3))
174 c EQUIVALENCE ( FREFL(1,1),TAU2(1,1,4))
175
176 INTEGER NL1(NGP)
177 INTEGER K, J
178
179 C- jmc: declare local variables:
180 _RL FBAND1, FBAND2, RRCL, RQCL, DQACL, QACL3
181 _RL ABS1, DELTAP
182 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
183
184 FBAND2=0.05 _d 0
185 FBAND1=1.-FBAND2
186
187 DO J=1,NGP
188 NL1(J)=kGrd(J)-1
189 ENDDO
190
191 C-- 1. Cloud cover:
192 C defined as a linear fun. of the maximum relative humidity
193 C in all tropospheric layers above PBL:
194 C CLOUDC = 0 for RHmax < RHCL1, = 1 for RHmax > RHCL2.
195 C This value is reduced by a factor (Qbase/QACL) if the
196 C cloud-base absolute humidity Qbase < QACL.
197 C
198
199 RRCL=1./(RHCL2-RHCL1)
200 RQCL=1./QACL2
201 C
202 DO J=1,NGP
203 CLOUDC(J)=0.
204 QCLOUD(J)=0.
205 IF (kGrd(J).NE.0)
206 & QCLOUD(J)= MAX( QA(J,kGrd(J)), QA(J,NL1(J)) )
207 ICLTOP(J)= kGrd(J)
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 DQACL=(QACL2-QACL1)/(0.5 _d 0 - SIG(2))
218 DO J=1,NGP
219 DO K=NL1(J),2,-1
220 QACL3=MIN(QACL2,QACL1+DQACL*(SIG(K)-SIG(2)))
221 IF (RH(J,K).GT.RHCL1.AND.QA(J,K).GT.QACL1) THEN
222 CLOUDC(J)=MAX(CLOUDC(J),RH(J,K)-RHCL1)
223 IF (QA(J,K).GT.QACL3) ICLTOP(J)=K
224 ENDIF
225 ENDDO
226 ENDDO
227
228 DO J=1,NGP
229 CLOUDC(J)=MIN(1. _d 0,CLOUDC(J)*RRCL)
230 IF (CLOUDC(J).GT.0.0) THEN
231 CLOUDC(J)=CLOUDC(J)*MIN(1. _d 0,QCLOUD(J)*RQCL)
232 ALBTOP(J,ICLTOP(J))=ALBCL*CLOUDC(J)
233 ELSE
234 ICLTOP(J)=NLEV+1
235 ENDIF
236 ENDDO
237
238 C
239 C-- 2. Shortwave transmissivity:
240 C function of layer mass, ozone (in the statosphere),
241 C abs. humidity and cloud cover (in the troposphere)
242
243 DO J=1,NGP
244 c_FM PSAZ(J)=PSA(J)*ZENIT(J)
245 ACLOUD(J)=CLOUDC(J)*(ABSCL1+ABSCL2*QCLOUD(J))
246 ENDDO
247
248 DO J=1,NGP
249 c_FM DELTAP=PSAZ(J)*DSIG(1)
250 DELTAP=ZENIT(J)*DSIG(1)*dpFac(J,1)
251 TAU2(J,1,1)=EXP(-DELTAP*ABSDRY)
252 ENDDO
253 C
254 DO J=1,NGP
255 DO K=2,NL1(J)
256 c_FM ABS1=ABSDRY+ABSAER*SIG(K)**2
257 c_FM DELTAP=PSAZ(J)*DSIG(K)
258 ABS1=ABSDRY+ABSAER*(SIG(K)/PSA(J))**2
259 DELTAP=ZENIT(J)*DSIG(K)*dpFac(J,K)
260 IF (K.EQ.ICLTOP(J)) THEN
261 TAU2(J,K,1)=EXP(-DELTAP*
262 & (ABS1+ABSWV1*QA(J,K)+2.*ACLOUD(J)))
263 ELSE IF (K.GT.ICLTOP(J)) THEN
264 TAU2(J,K,1)=EXP(-DELTAP*
265 & (ABS1+ABSWV1*QA(J,K)+ACLOUD(J)))
266 ELSE
267 TAU2(J,K,1)=EXP(-DELTAP*(ABS1+ABSWV1*QA(J,K)))
268 ENDIF
269 ENDDO
270 ENDDO
271
272 c_FM ABS1=ABSDRY+ABSAER*SIG(NLEV)**2
273 DO J=1,NGP
274 K = kGrd(J)
275 ABS1=ABSDRY+ABSAER*(SIG(K)/PSA(J))**2
276 c_FM DELTAP=PSAZ(J)*DSIG(NLEV)
277 DELTAP=ZENIT(J)*DSIG(K)*dpFac(J,K)
278 TAU2(J,K,1)=EXP(-DELTAP*(ABS1+ABSWV1*QA(J,K)))
279 ENDDO
280
281 DO J=1,NGP
282 DO K=2,kGrd(J)
283 DELTAP=ZENIT(J)*DSIG(K)*dpFac(J,K)
284 TAU2(J,K,2)=EXP(-DELTAP*ABSWV2*QA(J,K))
285 ENDDO
286 ENDDO
287 C
288 C--- 3. Shortwave downward flux
289 C
290 C 3.1 Absorption in the stratosphere
291
292 C 3.1.1 Initialization of fluxes (subtracting
293 C ozone absorption in the upper stratosphere)
294
295 DO J=1,NGP
296 FTOP(J) =FSOL(J)
297 FLUX(J,1)=FSOL(J)*FBAND1-OZUPP(J)
298 FLUX(J,2)=FSOL(J)*FBAND2
299 STRATC(J)=STRATZ(J)*PSA(J)
300 ENDDO
301
302 C 3.1.2 Ozone and dry-air absorption
303 C in the lower (modelled) stratosphere
304
305 DO J=1,NGP
306 DFABS(J,1)=FLUX(J,1)
307 FLUX (J,1)=TAU2(J,1,1)*(FLUX(J,1)-OZONE(J)*PSA(J))
308 DFABS(J,1)=DFABS(J,1)-FLUX(J,1)
309 ENDDO
310
311 C 3.3 Absorption and reflection in the troposphere
312 C
313 DO J=1,NGP
314 DO K=2,kGrd(J)
315 FREFL(J,K)=FLUX(J,1)*ALBTOP(J,K)
316 FLUX (J,1)=FLUX(J,1)-FREFL(J,K)
317 DFABS(J,K)=FLUX(J,1)
318 FLUX (J,1)=TAU2(J,K,1)*FLUX(J,1)
319 DFABS(J,K)=DFABS(J,K)-FLUX(J,1)
320 ENDDO
321 ENDDO
322
323 DO J=1,NGP
324 DO K=2,kGrd(J)
325 DFABS(J,K)=DFABS(J,K)+FLUX(J,2)
326 FLUX (J,2)=TAU2(J,K,2)*FLUX(J,2)
327 DFABS(J,K)=DFABS(J,K)-FLUX(J,2)
328 ENDDO
329 ENDDO
330
331 C
332 C--- 4. Shortwave upward flux
333 C
334 C 4.1 Absorption and reflection at the surface
335 C
336 DO J=1,NGP
337 FSFC(J) =FLUX(J,1)+FLUX(J,2)
338 FLUX(J,1)=FLUX(J,1)*ALB(J)
339 FSFC(J) =FSFC(J)-FLUX(J,1)
340 ENDDO
341 C
342 C 4.2 Absorption of upward flux
343 C
344 DO J=1,NGP
345 DO K=kGrd(J),1,-1
346 DFABS(J,K)=DFABS(J,K)+FLUX(J,1)
347 FLUX (J,1)=TAU2(J,K,1)*FLUX(J,1)
348 DFABS(J,K)=DFABS(J,K)-FLUX(J,1)
349 FLUX (J,1)=FLUX(J,1)+FREFL(J,K)
350 ENDDO
351 ENDDO
352 C
353 C 4.3 Net solar radiation = incoming - outgoing
354 C
355 DO J=1,NGP
356 FTOP(J)=FTOP(J)-FLUX(J,1)
357 ENDDO
358
359 C
360 C--- 5. Initialization of longwave radiation model
361 C
362 C 5.1 Longwave transmissivity:
363 C function of layer mass, abs. humidity and cloud cover.
364
365 DO J=1,NGP
366 ACLOUD(J)=CLOUDC(J)*(ABLCL1+ABLCL2*QCLOUD(J))
367 ENDDO
368
369 DO J=1,NGP
370 c_FM DELTAP=PSA(J)*DSIG(1)
371 DELTAP=DSIG(1)*dpFac(J,1)
372 TAU2(J,1,1)=EXP(-DELTAP*ABLWIN)
373 TAU2(J,1,2)=EXP(-DELTAP*ABLCO2)
374 TAU2(J,1,3)=1.
375 TAU2(J,1,4)=1.
376 ENDDO
377
378 DO K=2,NLEV
379 DO J=1,NGP
380 c_FM DELTAP=PSA(J)*DSIG(K)
381 DELTAP=DSIG(K)*dpFac(J,K)
382 IF ( K.GE.ICLTOP(J).AND.K.NE.kGrd(J) ) THEN
383 TAU2(J,K,1)=EXP(-DELTAP*(ABLWIN+ACLOUD(J)))
384 ELSE
385 TAU2(J,K,1)=EXP(-DELTAP*ABLWIN)
386 ENDIF
387 TAU2(J,K,2)=EXP(-DELTAP*ABLCO2)
388 TAU2(J,K,3)=EXP(-DELTAP*ABLWV1*QA(J,K))
389 TAU2(J,K,4)=EXP(-DELTAP*ABLWV2*QA(J,K))
390 ENDDO
391 ENDDO
392 C
393 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
394 #endif /* ALLOW_AIM */
395
396 RETURN
397 END
398
399
400 SUBROUTINE RADLW (IMODE,TA,TS,ST4S,
401 I OZUPP, STRATC, TAU2,
402 & FLUX, ST4A,
403 & FTOP,FSFC,DFABS,
404 I kGrd,bi,bj,myThid)
405 C--
406 C-- SUBROUTINE RADLW (IMODE,TA,TS,ST4S,
407 C-- & FTOP,FSFC,DFABS)
408 C--
409 C-- Purpose: Compute the absorption of longwave radiation
410 C-- Input: IMODE = index for operation mode
411 C-- -1 : downward flux only
412 C-- 0 : downward + upward flux
413 C-- +1 : upward flux only
414 C-- TA = absolute temperature (3-dim)
415 C-- TS = surface temperature [if IMODE=0,1]
416 C-- ST4S = surface blackbody emission [if IMODE=1]
417 C-- FSFC = FSFC output from RADLW(-1,... ) [if IMODE=1]
418 C-- DFABS = DFABS output from RADLW(-1,... ) [if IMODE=1]
419 C-- Output: ST4S = surface blackbody emission [if IMODE=0]
420 C-- FTOP = outgoing flux of lw rad. at the top [if IMODE=0,1]
421 C-- FSFC = downward flux of lw rad. at the sfc. [if IMODE= -1]
422 C-- net upw. flux of lw rad. at the sfc. [if IMODE=0,1]
423 C-- DFABS = flux of lw rad. absorbed by each atm. layer (3-dim)
424 C Input: kGrd = Ground level index (2-dim)
425 C bi,bj = tile index
426 C myThid = Thread number for this instance of the routine
427 C--
428
429 IMPLICIT NONE
430
431 C Resolution parameters
432
433 C-- size for MITgcm & Physics package :
434 #include "AIM_SIZE.h"
435
436 #include "EEPARAMS.h"
437
438 C Number of radiation bands with tau < 1
439 c INTEGER NBAND
440 c PARAMETER ( NBAND=4 )
441
442 C Constants + functions of sigma and latitude
443 #include "com_physcon.h"
444
445 C Radiation parameters
446 #include "com_radcon.h"
447
448 C-- Routine arguments:
449 INTEGER IMODE
450 _RL TA(NGP,NLEV), TS(NGP), ST4S(NGP)
451 _RL FTOP(NGP), FSFC(NGP), DFABS(NGP,NLEV)
452 _RL OZUPP(NGP), STRATC(NGP)
453 _RL TAU2(NGP,NLEV,NBAND), FLUX(NGP,NBAND), ST4A(NGP,NLEV,2)
454
455 INTEGER kGrd(NGP)
456 INTEGER bi,bj,myThid
457
458 #ifdef ALLOW_AIM
459
460 C-- Local variables:
461 INTEGER K, J, JB
462 c INTEGER J0, Jl, I2
463 INTEGER NL1(NGP)
464
465 C- jmc: declare all local variables:
466 _RL REFSFC, BRAD, EMIS
467 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
468
469 DO J=1,NGP
470 NL1(J)=kGrd(J)-1
471 ENDDO
472
473 REFSFC=1.-EMISFC
474
475 IF (IMODE.EQ.1) GO TO 410
476
477 C--- 1. Blackbody emission from atmospheric full and half levels.
478 C Temperature is interpolated as a linear function of ln sigma.
479 C At the lower boundary, the emission is linearly extrapolated;
480 C at the upper boundary, the atmosphere is assumed isothermal.
481
482 DO K=1,NLEV
483 DO J=1,NGP
484 ST4A(J,K,1)=TA(J,K)*TA(J,K)
485 ST4A(J,K,1)=SBC*ST4A(J,K,1)*ST4A(J,K,1)
486 ENDDO
487 ENDDO
488 C
489 DO K=1,NLEV-1
490 DO J=1,NGP
491 ST4A(J,K,2)=TA(J,K)+WVI(K,2)*(TA(J,K+1)-TA(J,K))
492 ST4A(J,K,2)=ST4A(J,K,2)*ST4A(J,K,2)
493 ST4A(J,K,2)=SBC*ST4A(J,K,2)*ST4A(J,K,2)
494 ENDDO
495 ENDDO
496 C
497 DO J=1,NGP
498 c ST4A(J,NLEV,2)=ST4A(J,NLEV,1)
499 K=kGrd(J)
500 ST4A(J,K,2)=2.*ST4A(J,K,1)-ST4A(J,NL1(J),2)
501 ENDDO
502
503 C--- 2. Initialization
504 C--- (including the stratospheric correction term)
505
506 DO J=1,NGP
507 FTOP(J) = 0.
508 FSFC(J) = STRATC(J)
509 DFABS(J,1)=-STRATC(J)
510 ENDDO
511
512 DO K=2,NLEV
513 DO J=1,NGP
514 DFABS(J,K)=0.
515 ENDDO
516 ENDDO
517
518 C--- 3. Emission ad absorption of longwave downward flux.
519 C Downward emission is an average of the emission from the full level
520 C and the half-level below, weighted according to the transmissivity
521 C of the layer.
522
523 C 3.1 Stratosphere
524
525 K=1
526 DO JB=1,2
527 DO J=1,NGP
528 BRAD=ST4A(J,K,2)+TAU2(J,K,JB)*(ST4A(J,K,1)-ST4A(J,K,2))
529 EMIS=FBAND(NINT(TA(J,K)),JB)*(1.-TAU2(J,K,JB))
530 FLUX(J,JB)=EMIS*BRAD
531 DFABS(J,K)=DFABS(J,K)-FLUX(J,JB)
532 ENDDO
533 ENDDO
534
535 DO JB=3,NBAND
536 DO J=1,NGP
537 FLUX(J,JB)=0.
538 ENDDO
539 ENDDO
540
541 C 3.2 Troposphere
542
543 DO JB=1,NBAND
544 DO J=1,NGP
545 DO K=2,kGrd(J)
546 BRAD=ST4A(J,K,2)+TAU2(J,K,JB)*(ST4A(J,K,1)-ST4A(J,K,2))
547 EMIS=FBAND(NINT(TA(J,K)),JB)*(1.-TAU2(J,K,JB))
548 DFABS(J,K)=DFABS(J,K)+FLUX(J,JB)
549 FLUX(J,JB)=TAU2(J,K,JB)*FLUX(J,JB)+EMIS*BRAD
550 DFABS(J,K)=DFABS(J,K)-FLUX(J,JB)
551 ENDDO
552 ENDDO
553 ENDDO
554
555 DO JB=1,NBAND
556 DO J=1,NGP
557 FSFC(J)=FSFC(J)+EMISFC*FLUX(J,JB)
558 ENDDO
559 ENDDO
560
561 IF (IMODE.EQ.-1) RETURN
562
563 C--- 4. Emission ad absorption of longwave upward flux
564 C Upward emission is an average of the emission from the full level
565 C and the half-level above, weighted according to the transmissivity
566 C of the layer (for the top layer, full-level emission is used).
567 C Surface lw emission in "band 0" goes directly into FTOP.
568
569 C 4.1 Surface
570
571 DO J=1,NGP
572 ST4S(J)=TS(J)*TS(J)
573 ST4S(J)=SBC*ST4S(J)*ST4S(J)
574 ENDDO
575
576 C Entry point for upward-only mode (IMODE=1)
577 410 CONTINUE
578
579 DO J=1,NGP
580 ST4S(J)=EMISFC*ST4S(J)
581 FSFC(J)=ST4S(J)-FSFC(J)
582 FTOP(J)=FTOP(J)+FBAND(NINT(TS(J)),0)*ST4S(J)
583 ENDDO
584
585 DO JB=1,NBAND
586 DO J=1,NGP
587 FLUX(J,JB)=FBAND(NINT(TS(J)),JB)*ST4S(J)
588 & +REFSFC*FLUX(J,JB)
589 ENDDO
590 ENDDO
591
592 C 4.2 Troposphere
593
594 DO JB=1,NBAND
595 DO J=1,NGP
596 DO K=kGrd(J),2,-1
597 BRAD=ST4A(J,K-1,2)+TAU2(J,K,JB)*(ST4A(J,K,1)-ST4A(J,K-1,2))
598 EMIS=FBAND(NINT(TA(J,K)),JB)*(1.-TAU2(J,K,JB))
599 DFABS(J,K)=DFABS(J,K)+FLUX(J,JB)
600 FLUX(J,JB)=TAU2(J,K,JB)*FLUX(J,JB)+EMIS*BRAD
601 DFABS(J,K)=DFABS(J,K)-FLUX(J,JB)
602 ENDDO
603 ENDDO
604 ENDDO
605
606 C 4.3 Stratosphere
607
608 K=1
609 DO JB=1,2
610 DO J=1,NGP
611 EMIS=FBAND(NINT(TA(J,K)),JB)*(1.-TAU2(J,K,JB))
612 DFABS(J,K)=DFABS(J,K)+FLUX(J,JB)
613 FLUX(J,JB)=TAU2(J,K,JB)*FLUX(J,JB)+EMIS*ST4A(J,K,1)
614 DFABS(J,K)=DFABS(J,K)-FLUX(J,JB)
615 ENDDO
616 ENDDO
617
618 C 4.4 Outgoing longwave radiation
619
620 DO JB=1,NBAND
621 DO J=1,NGP
622 FTOP(J)=FTOP(J)+FLUX(J,JB)
623 ENDDO
624 ENDDO
625
626 DO J=1,NGP
627 FTOP(J)=FTOP(J)+OZUPP(J)
628 ENDDO
629
630 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
631 #endif /* ALLOW_AIM */
632
633 RETURN
634 END
635
636
637 SUBROUTINE RADSET( myThid )
638
639 C--
640 C-- SUBROUTINE RADSET
641 C--
642 C-- Purpose: compute energy fractions in LW bands
643 C-- as a function of temperature
644 C-- Initialized common blocks: RADFIX
645
646 IMPLICIT NONE
647
648 C Resolution parameters
649
650 C-- size for MITgcm & Physics package :
651 #include "AIM_SIZE.h"
652
653 #include "EEPARAMS.h"
654
655 C Radiation constants
656 #include "com_radcon.h"
657
658 C-- Routine arguments:
659 INTEGER myThid
660
661 #ifdef ALLOW_AIM
662
663 C-- Local variables:
664 INTEGER JTEMP, JB
665 _RL EPS3
666
667 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
668
669 EPS3=0.95 _d 0
670
671 DO JTEMP=200,320
672 FBAND(JTEMP,0)= EPSLW
673 FBAND(JTEMP,2)= 0.148 _d 0 - 3.0 _d -6 *(JTEMP-247)**2
674 FBAND(JTEMP,3)=(0.375 _d 0 - 5.5 _d -6 *(JTEMP-282)**2)*EPS3
675 FBAND(JTEMP,4)= 0.314 _d 0 + 1.0 _d -5 *(JTEMP-315)**2
676 FBAND(JTEMP,1)= 1. _d 0 -(FBAND(JTEMP,0)+FBAND(JTEMP,2)
677 & +FBAND(JTEMP,3)+FBAND(JTEMP,4))
678 ENDDO
679
680 DO JB=0,NBAND
681 DO JTEMP=lwTemp1,199
682 FBAND(JTEMP,JB)=FBAND(200,JB)
683 ENDDO
684 DO JTEMP=321,lwTemp2
685 FBAND(JTEMP,JB)=FBAND(320,JB)
686 ENDDO
687 ENDDO
688
689 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
690 #endif /* ALLOW_AIM */
691
692 RETURN
693 END

  ViewVC Help
Powered by ViewVC 1.1.22