/[MITgcm]/MITgcm/verification/fizhi-gridalt-hs/code/do_fizhi.F
ViewVC logotype

Annotation of /MITgcm/verification/fizhi-gridalt-hs/code/do_fizhi.F

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


Revision 1.2 - (hide annotations) (download)
Fri Aug 20 13:40:03 2004 UTC (19 years, 8 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint55c_post, checkpoint54e_post, checkpoint55b_post, checkpoint55, checkpoint54f_post, checkpoint55a_post
Changes since 1.1: +557 -42 lines
Check-in of fizhi interface running a Held-Suarez Experiment

1 molod 1.2 C $Header: /u/gcmpack/MITgcm/pkg/fizhi/do_fizhi.F,v 1.36 2004/08/12 15:21:22 molod Exp $
2     C $Name: $
3     #include "FIZHI_OPTIONS.h"
4     subroutine do_fizhi(myid,
5     . idim1,idim2,jdim1,jdim2,Nrphin,Nsxin,Nsyin,im1,im2,jm1,jm2,bi,bj,
6     . nchp,nchptot,nchpland,
7     . uphy,vphy,thphy,sphy,pephy,lons,lats,
8     . ctmt,xxmt,yymt,zetamt,xlmt,khmt,tke,
9     . tgz,sst,sice,phis_var,landtype,fracland,emiss,albnirdr,albnirdf,
10     . albvisdr,albvisdf,ityp,chfr,alai,agrn,igrd,chlat,chlon,
11     . tcanopy,tdeep,ecanopy,swetshal,swetroot,swetdeep,snodep,capac,
12     . o3,qstr,co2,cfc11,cfc12,cfc22,n2o,methane,
13     . duphy,dvphy,dthphy,dsphy)
14 molod 1.1 c-----------------------------------------------------------------------
15 molod 1.2 c Interface routine to calculate physics increments - calls fizhi_driver.
16     c Purpose of this routine is to set up arrays local to fizhi and 'save'
17     c them from one iteration to the next, and act as interface between the
18     c model common blocks (held in fizhi_wrapper) and fizhi_driver.
19     c Copies of variables that are 'shadowed' are made here without shadows
20     c for passing to fizhi_driver.
21     c Note: routine is called from inside a bi-bj loop
22     c
23 molod 1.1 c-----------------------------------------------------------------------
24 molod 1.2 implicit none
25     #include "SIZE.h"
26     #include "fizhi_SIZE.h"
27     #include "chronos.h"
28    
29     C Argument list declarations
30     integer myid,im1,im2,jm1,jm2,idim1,idim2,jdim1,jdim2
31     integer Nrphin,Nsxin,Nsyin,bi,bj,nchp
32     integer nchptot(Nsxin,Nsyin),nchpland(Nsxin,Nsyin)
33     _RL uphy(idim1:idim2,jdim1:jdim2,Nrphin,Nsxin,Nsyin)
34     _RL vphy(idim1:idim2,jdim1:jdim2,Nrphin,Nsxin,Nsyin)
35     _RL thphy(idim1:idim2,jdim1:jdim2,Nrphin,Nsxin,Nsyin)
36     _RL sphy(idim1:idim2,jdim1:jdim2,Nrphin,Nsxin,Nsyin)
37     _RL pephy(idim1:idim2,jdim1:jdim2,Nrphin+1,Nsxin,Nsyin)
38     _RS lons(idim1:idim2,jdim1:jdim2,Nsxin,Nsyin)
39     _RS lats(idim1:idim2,jdim1:jdim2,Nsxin,Nsyin)
40     _RL ctmt(nchp,Nsxin,Nsyin),xxmt(nchp,Nsxin,Nsyin)
41     _RL yymt(nchp,Nsxin,Nsyin)
42     _RL zetamt(nchp,Nsxin,Nsyin)
43     _RL xlmt(nchp,Nrphin,Nsxin,Nsyin),khmt(nchp,Nrphin,Nsxin,Nsyin)
44     _RL tke(nchp,Nrphin,Nsxin,Nsyin)
45     _RL tgz(im2,jm2,Nsxin,Nsyin)
46     _RL sst(idim1:idim2,jdim1:jdim2,Nsxin,Nsyin)
47     _RL sice(idim1:idim2,jdim1:jdim2,Nsxin,Nsyin)
48     _RL phis_var(im2,jm2,Nsxin,Nsyin)
49     integer landtype(im2,jm2,Nsxin,Nsyin)
50     _RL fracland(im2,jm2,Nsxin,Nsyin),emiss(im2,jm2,10,Nsxin,Nsyin)
51     _RL albvisdr(im2,jm2,Nsxin,Nsyin),albvisdf(im2,jm2,Nsxin,Nsyin)
52     _RL albnirdr(im2,jm2,Nsxin,Nsyin),albnirdf(im2,jm2,Nsxin,Nsyin)
53     _RL chfr(nchp,Nsxin,Nsyin),alai(nchp,Nsxin,Nsyin)
54     _RL agrn(nchp,Nsxin,Nsyin)
55     integer ityp(nchp,Nsxin,Nsyin),igrd(nchp,Nsxin,Nsyin)
56     _RL chlat(nchp,Nsxin,Nsyin),chlon(nchp,Nsxin,Nsyin)
57     _RL tcanopy(nchp,Nsxin,Nsyin),tdeep(nchp,Nsxin,Nsyin)
58     _RL ecanopy(nchp,Nsxin,Nsyin),swetshal(nchp,Nsxin,Nsyin)
59     _RL swetroot(nchp,Nsxin,Nsyin),swetdeep(nchp,Nsxin,Nsyin)
60     _RL snodep(nchp,Nsxin,Nsyin),capac(nchp,Nsxin,Nsyin)
61     _RL o3(im2,jm2,Nrphin,Nsxin,Nsyin)
62     _RL qstr(im2,jm2,Nrphin,Nsxin,Nsyin)
63     _RL co2,cfc11,cfc12,cfc22,n2o(Nrphin),methane(Nrphin)
64     _RL duphy(idim1:idim2,jdim1:jdim2,Nrphin,Nsxin,Nsyin)
65     _RL dvphy(idim1:idim2,jdim1:jdim2,Nrphin,Nsxin,Nsyin)
66     _RL dthphy(idim1:idim2,jdim1:jdim2,Nrphin,Nsxin,Nsyin)
67     _RL dsphy(idim1:idim2,jdim1:jdim2,Nrphin,Nsxin,Nsyin)
68    
69    
70     c Local Variables
71     integer ptracer,ntracer
72     parameter (ptracer = 1)
73     parameter (ntracer = 1)
74     integer iras,nlwcld,nlwlz,nswcld,nswlz
75     integer imstturbsw,imstturblw
76    
77     _RL xlats(sNx,sNy),xlons(sNx,sNy),sea_ice(sNx,sNy)
78     _RL p(sNx,sNy,Nsx,Nsy)
79     _RL u(sNx,sNy,Nrphys),v(sNx,sNy,Nrphys),t(sNx,sNy,Nrphys)
80     _RL q(sNx,sNy,Nrphys,ntracer)
81     _RL pl(sNx,sNy,Nrphys,Nsx,Nsy),pkl(sNx,sNy,Nrphys,Nsx,Nsy)
82     _RL ple(sNx,sNy,Nrphys+1,Nsx,Nsy)
83     _RL pkle(sNx,sNy,Nrphys+1,Nsx,Nsy)
84     _RL dpres(sNx,sNy,Nrphys,Nsx,Nsy)
85     _RL lwdt(sNx,sNy,Nrphys,Nsx,Nsy)
86     _RL lwdtclr(sNx,sNy,Nrphys,Nsx,Nsy)
87     _RL swdt(sNx,sNy,Nrphys,Nsx,Nsy)
88     _RL swdtclr(sNx,sNy,Nrphys,Nsx,Nsy)
89     _RL turbu(sNx,sNy,Nrphys,Nsx,Nsy)
90     _RL turbv(sNx,sNy,Nrphys,Nsx,Nsy)
91     _RL turbt(sNx,sNy,Nrphys,Nsx,Nsy)
92     _RL turbq(sNx,sNy,Nrphys,ntracer,Nsx,Nsy)
93     _RL moistu(sNx,sNy,Nrphys,Nsx,Nsy)
94     _RL moistv(sNx,sNy,Nrphys,Nsx,Nsy)
95     _RL moistt(sNx,sNy,Nrphys,Nsx,Nsy)
96     _RL moistq(sNx,sNy,Nrphys,ntracer,Nsx,Nsy)
97     _RL radswt(sNx,sNy,Nsx,Nsy),radswg(sNx,sNy,Nsx,Nsy)
98     _RL swgclr(sNx,sNy,Nsx,Nsy)
99     _RL fdirpar(sNx,sNy,Nsx,Nsy),fdifpar(sNx,sNy,Nsx,Nsy)
100     _RL osr(sNx,sNy,Nsx,Nsy),osrclr(sNx,sNy,Nsx,Nsy)
101     _RL tg0(sNx,sNy,Nsx,Nsy),radlwg(sNx,sNy,Nsx,Nsy)
102     _RL lwgclr(sNx,sNy,Nsx,Nsy),st4(sNx,sNy,Nsx,Nsy)
103     _RL dst4(sNx,sNy,Nsx,Nsy),dlwdtg(sNx,sNy,Nrphys,Nsx,Nsy)
104     _RL rainlsp(sNx,sNy,Nsx,Nsy),raincon(sNx,sNy,Nsx,Nsy)
105     _RL snowfall(sNx,sNy,Nsx,Nsy)
106     _RL cldtot_lw(sNx,sNy,Nrphys,Nsx,Nsy)
107     _RL cldras_lw(sNx,sNy,Nrphys,Nsx,Nsy)
108     _RL cldlsp_lw(sNx,sNy,Nrphys,Nsx,Nsy)
109     _RL lwlz(sNx,sNy,Nrphys,Nsx,Nsy)
110     _RL cldtot_sw(sNx,sNy,Nrphys,Nsx,Nsy)
111     _RL cldras_sw(sNx,sNy,Nrphys,Nsx,Nsy)
112     _RL cldlsp_sw(sNx,sNy,Nrphys,Nsx,Nsy)
113     _RL swlz(sNx,sNy,Nrphys,Nsx,Nsy)
114     _RL qliqavesw(sNx,sNy,Nrphys,Nsx,Nsy)
115     _RL qliqavelw(sNx,sNy,Nrphys,Nsx,Nsy)
116     _RL fccavesw(sNx,sNy,Nrphys,Nsx,Nsy)
117     _RL fccavelw(sNx,sNy,Nrphys,Nsx,Nsy)
118     _RL qq(sNx,sNy,Nrphys,Nsx,Nsy)
119    
120     integer i,j,L
121     _RL getcon, kappa, p0kappa, s0, ra
122     _RL cosz(sNx,sNy)
123    
124     _RL tempij(sNx,sNy)
125    
126     _RL kF,sigma_b,ks,ka,deg2rad,pi,atm_po,atm_kappa,termp,kv,kT
127     _RL term1,term2,thetalim,thetaeq,recip_p0g
128    
129     logical alarm
130     external alarm
131    
132     c save lwdt,lwdtclr,swdt,swdtclr,turbu,turbv,turbt,turbq
133     c save moistu,moistv,moistt,moistq
134     c save radswg,swgclr,fdirpar,fdifpar,osr,osrclr,tg0,radlwg
135     c save st4,dst4,dlwdtg,rainlsp,raincon,snowfall,iras
136     c save nlwcld,cldtot_lw,cldras_lw,cldlsp_lw,nlwlz,lwlz
137     c save nswcld,cldtot_sw,cldras_sw,cldlsp_sw,nswlz,swlz
138     c save imstturbsw,imstturblw,qliqavesw,qliqavelw,fccavesw,fccavelw
139     c save qq
140     c save pl,ple,dpres,pkle,pkl
141    
142     common /saver/ lwdt,lwdtclr,swdt,swdtclr,turbu,turbv,turbt,turbq
143     common /saver/ moistu,moistv,moistt,moistq
144     common /saver/ radswg,swgclr,fdirpar,fdifpar,osr,osrclr,tg0,radlwg
145     common /saver/ st4,dst4,dlwdtg,rainlsp,raincon,snowfall
146     common /saver/ cldtot_lw,cldras_lw,cldlsp_lw,lwlz
147     common /saver/ cldtot_sw,cldras_sw,cldlsp_sw,swlz
148     common /saver/ imstturbsw,imstturblw,qliqavesw,qliqavelw,fccavesw
149     common /saver/ fccavelw
150     common /saver/ qq
151     common /saver/ pl,ple,dpres,pkle,pkl
152     common /saver/ nlwcld,nlwlz
153     common /saver/ nswcld,nswlz
154     common /saver/ iras
155    
156     C***********************************************************************
157     C Unshadow input arrays (and make 'fizhi theta' from true theta)
158     C***********************************************************************
159    
160     if( (nhms.eq.nhms0) .and. (nymd.eq.nymd0) ) then
161     _BEGIN_MASTER(myid)
162     if(myid.eq.1) print *,' Initializing fizhi arrays '
163     _END_MASTER(myid)
164     imstturblw = 0
165     imstturbsw = 0
166     iras = 0
167     nlwcld = 0
168     nlwlz = 0
169     nswcld = 0
170     nswlz = 0
171     do L = 1,Nrphys
172     do j = jm1,jm2
173     do i = im1,im2
174     swlz(i,j,L,bi,bj) = 0.
175     lwlz(i,j,L,bi,bj) = 0.
176     qliqavesw(i,j,L,bi,bj) = 0.
177     qliqavelw(i,j,L,bi,bj) = 0.
178     fccavesw(i,j,L,bi,bj) = 0.
179     fccavelw(i,j,L,bi,bj) = 0.
180     cldtot_sw(i,j,L,bi,bj) = 0.
181     cldras_sw(i,j,L,bi,bj) = 0.
182     cldlsp_sw(i,j,L,bi,bj) = 0.
183     cldtot_lw(i,j,L,bi,bj) = 0.
184     cldras_lw(i,j,L,bi,bj) = 0.
185     cldlsp_lw(i,j,L,bi,bj) = 0.
186     lwdt(i,j,L,bi,bj) = 0.
187     swdt(i,j,L,bi,bj) = 0.
188     turbt(i,j,L,bi,bj) = 0.
189     moistt(i,j,L,bi,bj) = 0.
190     turbq(i,j,L,1,bi,bj) = 0.
191     moistq(i,j,L,1,bi,bj) = 0.
192     turbu(i,j,L,bi,bj) = 0.
193     moistu(i,j,L,bi,bj) = 0.
194     turbv(i,j,L,bi,bj) = 0.
195     moistv(i,j,L,bi,bj) = 0.
196     enddo
197     enddo
198     enddo
199     do j = jm1,jm2
200     do i = im1,im2
201     rainlsp(i,j,bi,bj) = 0.
202     raincon(i,j,bi,bj) = 0.
203     snowfall(i,j,bi,bj) = 0.
204     enddo
205     enddo
206     endif
207    
208     kappa = getcon('KAPPA')
209     p0kappa = 1000.0 ** kappa
210     S0 = getcon('S0')
211    
212     do j = jm1,jm2
213     do i = im1,im2
214     xlats(i,j) = lats(i,j,bi,bj)
215     xlons(i,j) = lons(i,j,bi,bj)
216     enddo
217     enddo
218    
219     call astro ( nymd,nhms, xlats,xlons, im2*jm2, cosz,ra )
220     do j=jm1,jm2
221     do i=im1,im2
222     radswt(i,j,bi,bj) = S0*(1.0/ra**2)*cosz(i,j)
223     enddo
224     enddo
225    
226     if( alarm('moist') .or. alarm('turb') .or.
227     . alarm('radsw') .or. alarm('radlw') ) then
228    
229     C compute pressures - all pressure are converted here to hPa
230     do j = jm1,jm2
231     do i = im1,im2
232     ple(i,j,Nrphys+1,bi,bj) = pephy(i,j,Nrphys+1,bi,bj)/100.
233     pkle(i,j,Nrphys+1,bi,bj)=(pephy(i,j,Nrphys+1,bi,bj)/100.) **kappa
234     p(i,j,bi,bj) = pephy(i,j,Nrphys+1,bi,bj)/100.
235     sea_ice(i,j) = sice(i,j,bi,bj)
236     enddo
237     enddo
238     do L = 1,Nrphys
239     do j = jm1,jm2
240     do i = im1,im2
241     u(i,j,L) = uphy(i,j,L,bi,bj)
242     v(i,j,L) = vphy(i,j,L,bi,bj)
243     t(i,j,L) = thphy(i,j,L,bi,bj)/p0kappa
244     q(i,j,L,1) = sphy(i,j,L,bi,bj)
245     pl(i,j,L,bi,bj) = (pephy(i,j,L,bi,bj)+pephy(i,j,L+1,bi,bj))/200.
246     dpres(i,j,L,bi,bj)=(pephy(i,j,L+1,bi,bj)-pephy(i,j,L,bi,bj))/100.
247     ple(i,j,L,bi,bj) = pephy(i,j,L,bi,bj)/100.
248     if (ple(i,j,L,bi,bj).gt.0.) then
249     pkle(i,j,L,bi,bj) = ple(i,j,L,bi,bj) **kappa
250     else
251     pkle(i,j,L,bi,bj) = 0.
252     endif
253     enddo
254     enddo
255     enddo
256    
257     call pkappa (im2,jm2,Nrphys,ple(1,1,1,bi,bj),pkle(1,1,1,bi,bj),
258     . pkl(1,1,1,bi,bj))
259    
260     if(2.eq.1 )then
261     print *,' In do fizhi, before fizhi driver - bi = ',bi
262     do L = 1,Nrphys+1
263     do j = jm1,jm2
264     do i = im1,im2
265     tempij(i,j) = pephy(i,j,L,bi,bj)
266     enddo
267     enddo
268     c print *,' pephy at level ',l,' ',tempij
269     enddo
270     do L = 1,Nrphys
271     do j = jm1,jm2
272     do i = im1,im2
273     tempij(i,j) = u(i,j,L)
274     enddo
275     enddo
276     c print *,' u at level ',l,' ',tempij
277     enddo
278     do L = 1,Nrphys
279     do j = jm1,jm2
280     do i = im1,im2
281     tempij(i,j) = v(i,j,L)
282     enddo
283     enddo
284     c print *,' v at level ',l,' ',tempij
285     enddo
286     do L = 1,Nrphys
287     do j = jm1,jm2
288     do i = im1,im2
289     tempij(i,j) = t(i,j,L)
290     enddo
291     enddo
292     print *,' t at level ',l,' ',tempij
293     enddo
294     do L = 1,Nrphys
295     do j = jm1,jm2
296     do i = im1,im2
297     tempij(i,j) = q(i,j,L,1)
298     enddo
299     enddo
300     print *,' q at level ',l,' ',tempij
301     enddo
302     do L = 1,Nrphys
303     do j = jm1,jm2
304     do i = im1,im2
305     tempij(i,j) = qstr(i,j,L,bi,bj)
306     enddo
307     enddo
308     print *,' radiation q at level ',l,' ',tempij
309     enddo
310     do L = 1,Nrphys
311     do j = jm1,jm2
312     do i = im1,im2
313     tempij(i,j) = pl(i,j,L,bi,bj)
314     enddo
315     enddo
316     c print *,' pl at level ',l,' ',tempij
317     enddo
318     do L = 1,Nrphys+1
319     do j = jm1,jm2
320     do i = im1,im2
321     tempij(i,j) = ple(i,j,L,bi,bj)
322     enddo
323     enddo
324     c print *,' ple at level ',l,' ',tempij
325     enddo
326     do L = 1,Nrphys
327     do j = jm1,jm2
328     do i = im1,im2
329     tempij(i,j) = pkl(i,j,L,bi,bj)
330     enddo
331     enddo
332     c print *,' pkl at level ',l,' ',tempij
333     enddo
334     do L = 1,Nrphys+1
335     do j = jm1,jm2
336     do i = im1,im2
337     tempij(i,j) = pkle(i,j,L,bi,bj)
338     enddo
339     enddo
340     c print *,' pkle at level ',l,' ',tempij
341     enddo
342     do L = 1,Nrphys
343     do j = jm1,jm2
344     do i = im1,im2
345     tempij(i,j) = dpres(i,j,L,bi,bj)
346     enddo
347     enddo
348     c print *,' dpres at level ',l,' ',tempij
349     enddo
350     do j = jm1,jm2
351     do i = im1,im2
352     tempij(i,j) = tgz(i,j,bi,bj)
353     enddo
354     enddo
355     c print *,' tgz ',tempij
356    
357     print *,' Just before fizhi driver call '
358    
359     endif
360    
361    
362    
363     call fizhi_driver(myid,im2,jm2,Nrphys,bi,bj,ptracer,ntracer,xlats,
364     . xlons,p(1,1,bi,bj),u,v,t,q,pl(1,1,1,bi,bj),ple(1,1,1,bi,bj),
365     . dpres(1,1,1,bi,bj),pkle(1,1,1,bi,bj),pkl(1,1,1,bi,bj),
366     . fracland(1,1,bi,bj),landtype(1,1,bi,bj),radswt(1,1,bi,bj),
367     . phis_var(1,1,bi,bj),tgz(1,1,bi,bj),sea_ice,nchp,chlat(1,bi,bj),
368     . chlon(1,bi,bj),igrd(1,bi,bj),nchptot(bi,bj),nchpland(bi,bj),
369     . chfr(1,bi,bj),ityp(1,bi,bj),tcanopy(1,bi,bj),tdeep(1,bi,bj),
370     . ecanopy(1,bi,bj),swetshal(1,bi,bj),swetroot(1,bi,bj),
371     . swetdeep(1,bi,bj),capac(1,bi,bj),snodep(1,bi,bj),
372     . ctmt(1,bi,bj),xxmt(1,bi,bj),yymt(1,bi,bj),zetamt(1,bi,bj),
373     . xlmt(1,1,bi,bj),khmt(1,1,bi,bj),tke(1,1,bi,bj),
374     . albvisdr(1,1,bi,bj),albvisdf(1,1,bi,bj),albnirdr(1,1,bi,bj),
375     . albnirdf(1,1,bi,bj),emiss(1,1,1,bi,bj),alai(1,bi,bj),
376     . agrn(1,bi,bj),
377     . qstr(1,1,1,bi,bj),o3(1,1,1,bi,bj),
378     . co2,cfc11,cfc12,cfc22,methane,n2o,
379     . lwdt(1,1,1,bi,bj),lwdtclr(1,1,1,bi,bj),swdt(1,1,1,bi,bj),
380     . swdtclr(1,1,1,bi,bj),turbu(1,1,1,bi,bj),turbv(1,1,1,bi,bj),
381     . turbt(1,1,1,bi,bj),turbq(1,1,1,1,bi,bj),moistu(1,1,1,bi,bj),
382     . moistv(1,1,1,bi,bj),moistt(1,1,1,bi,bj),moistq(1,1,1,1,bi,bj),
383     . radswg(1,1,bi,bj),swgclr(1,1,bi,bj),fdirpar(1,1,bi,bj),
384     . fdifpar(1,1,bi,bj),osr(1,1,bi,bj),osrclr(1,1,bi,bj),
385     . tg0(1,1,bi,bj),radlwg(1,1,bi,bj),lwgclr(1,1,bi,bj),
386     . st4(1,1,bi,bj),dst4(1,1,bi,bj),dlwdtg(1,1,1,bi,bj),
387     . rainlsp(1,1,bi,bj),raincon(1,1,bi,bj),snowfall(1,1,bi,bj),iras,
388     . nlwcld,cldtot_lw(1,1,1,bi,bj),cldras_lw(1,1,1,bi,bj),
389     . cldlsp_lw(1,1,1,bi,bj),nlwlz,lwlz(1,1,1,bi,bj),
390     . nswcld,cldtot_sw(1,1,1,bi,bj),cldras_sw(1,1,1,bi,bj),
391     . cldlsp_sw(1,1,1,bi,bj),nswlz,swlz(1,1,1,bi,bj),
392     . imstturbsw,imstturblw,qliqavesw(1,1,1,bi,bj),
393     . qliqavelw(1,1,1,bi,bj),fccavesw(1,1,1,bi,bj),
394     . fccavelw(1,1,1,bi,bj),qq(1,1,1,bi,bj))
395    
396     if(2.eq.1)then
397     print *,' In do fizhi, after fizhi driver - bi = ',bi
398     do L = 1,Nrphys
399     do j = jm1,jm2
400     do i = im1,im2
401     tempij(i,j) = turbu(i,j,L,bi,bj)
402     enddo
403     enddo
404     c print *,' turbu at level ',l,' ',tempij
405     enddo
406     do L = 1,Nrphys
407     do j = jm1,jm2
408     do i = im1,im2
409     tempij(i,j) = turbv(i,j,L,bi,bj)
410     enddo
411     enddo
412     c print *,' turbv at level ',l,' ',tempij
413     enddo
414     do L = 1,Nrphys
415     do j = jm1,jm2
416     do i = im1,im2
417     tempij(i,j) = turbt(i,j,L,bi,bj)*p0kappa/p(i,j,bi,bj)
418     enddo
419     enddo
420     print *,' turbt at level ',l,' ',tempij
421     enddo
422     do L = 1,Nrphys
423     do j = jm1,jm2
424     do i = im1,im2
425     tempij(i,j) = turbq(i,j,L,1,bi,bj)/p(i,j,bi,bj)
426     enddo
427     enddo
428     c print *,' turbq at level ',l,' ',tempij
429     enddo
430     do L = 1,Nrphys
431     do j = jm1,jm2
432     do i = im1,im2
433     tempij(i,j) = moistu(i,j,L,bi,bj)
434     enddo
435     enddo
436     c print *,' moistu at level ',l,' ',tempij
437     enddo
438     do L = 1,Nrphys
439     do j = jm1,jm2
440     do i = im1,im2
441     tempij(i,j) = moistv(i,j,L,bi,bj)
442     enddo
443     enddo
444     c print *,' moistv at level ',l,' ',tempij
445     enddo
446     do L = 1,Nrphys
447     do j = jm1,jm2
448     do i = im1,im2
449     tempij(i,j) = moistt(i,j,L,bi,bj)*p0kappa/p(i,j,bi,bj)
450     enddo
451     enddo
452     print *,' moistt at level ',l,' ',tempij
453     enddo
454     do L = 1,Nrphys
455     do j = jm1,jm2
456     do i = im1,im2
457     tempij(i,j) = moistq(i,j,L,1,bi,bj)/p(i,j,bi,bj)
458     enddo
459     enddo
460     c print *,' moistq at level ',l,' ',tempij
461     enddo
462     do L = 1,Nrphys
463     do j = jm1,jm2
464     do i = im1,im2
465     tempij(i,j) = swdt(i,j,L,bi,bj)*radswt(i,j,bi,bj) *p0kappa /
466     . p(i,j,bi,bj)
467     enddo
468     enddo
469     print *,' swdt at level ',l,' ',tempij
470     enddo
471     do L = 1,Nrphys
472     do j = jm1,jm2
473     do i = im1,im2
474     tempij(i,j) = lwdt(i,j,L,bi,bj)
475     enddo
476     enddo
477     print *,' lwdt alone at level ',l,' ',tempij
478     enddo
479     do L = 1,Nrphys
480     do j = jm1,jm2
481     do i = im1,im2
482     tempij(i,j) = (lwdt(i,j,L,bi,bj)+
483     . dlwdtg(i,j,L,bi,bj)*(tgz(i,j,bi,bj)-tg0(i,j,bi,bj)))
484     . *p0kappa/p(i,j,bi,bj)
485     enddo
486     enddo
487     print *,' net lwdt at level ',l,' ',tempij
488     enddo
489     endif
490    
491     do L = 1,Nrphys
492     do j = jm1,jm2
493     do i = im1,im2
494     duphy(i,j,L,bi,bj) = moistu(i,j,L,bi,bj) + turbu(i,j,L,bi,bj)
495     dvphy(i,j,L,bi,bj) = moistv(i,j,L,bi,bj) + turbv(i,j,L,bi,bj)
496     dthphy(i,j,L,bi,bj) = ((moistt(i,j,L,bi,bj)+turbt(i,j,L,bi,bj)+
497     . lwdt(i,j,L,bi,bj) +
498     . dlwdtg(i,j,L,bi,bj) * (tgz(i,j,bi,bj)-tg0(i,j,bi,bj)) +
499     . swdt(i,j,L,bi,bj)*radswt(i,j,bi,bj) )*p0kappa ) / p(i,j,bi,bj)
500     dsphy(i,j,L,bi,bj) = (moistq(i,j,L,1,bi,bj)+turbq(i,j,L,1,bi,bj))
501     . /p(i,j,bi,bj)
502     enddo
503     enddo
504     enddo
505    
506     if(2.eq.1 )then
507     print *,' In do fizhi, computed fizhi tendencies ',bi
508     do L = 1,Nrphys
509     do j = jm1,jm2
510     do i = im1,im2
511     tempij(i,j) = duphy(i,j,L,bi,bj)
512     enddo
513     enddo
514     c print *,' duphy at level ',l,' ',tempij
515     enddo
516     do L = 1,Nrphys
517     do j = jm1,jm2
518     do i = im1,im2
519     tempij(i,j) = dvphy(i,j,L,bi,bj)
520     enddo
521     enddo
522     c print *,' dvphy at level ',l,' ',tempij
523     enddo
524     do L = 1,Nrphys
525     do j = jm1,jm2
526     do i = im1,im2
527     tempij(i,j) = dthphy(i,j,L,bi,bj)
528     enddo
529     enddo
530     print *,' dthphy at level ',l,' ',tempij
531     enddo
532     do L = 1,Nrphys
533     do j = jm1,jm2
534     do i = im1,im2
535     tempij(i,j) = dsphy(i,j,L,bi,bj)
536     enddo
537     enddo
538     print *,' dsphy at level ',l,' ',tempij
539     enddo
540     endif
541    
542     endif
543    
544     call fizhi_step_diag(myid,p,uphy,vphy,thphy,sphy,qq,pkl,dpres,
545     . radswt,radswg,swgclr,osr,osrclr,st4,dst4,tgz,tg0,radlwg,lwgclr,
546     . turbu,turbv,turbt,turbq,moistu,moistv,moistt,moistq,
547     . lwdt,swdt,lwdtclr,swdtclr,dlwdtg,
548     . im1,im2,jm1,jm2,Nrphys,Nsx,Nsy,bi,bj,ntracer)
549 molod 1.1
550    
551     kF=1. _d 0/86400. _d 0
552     sigma_b = 0.7 _d 0
553     ka=1. _d 0/(40. _d 0*86400. _d 0)
554     ks=1. _d 0/(4. _d 0 *86400. _d 0)
555     pi = getcon('PI')
556     atm_kappa = getcon('KAPPA')
557     atm_po = getcon('ATMPOPA')
558     deg2rad = getcon('DEG2RAD')
559    
560     do L = 1,Nrphys
561 molod 1.2 do j = jm1,jm2
562     do i = im1,im2
563     recip_P0g= 1. _d 0 / pephy(i,j,Nrphys+1,bi,bj)
564 molod 1.1 c U and V terms:
565     termP=0.5 _d 0*((pephy(i,j,L,bi,bj)+pephy(i,j,L+1,bi,bj))
566     & *recip_P0g )
567     kV=kF*MAX( 0. _d 0, (termP-sigma_b)/(1. _d 0-sigma_b) )
568     duphy(i,j,L,bi,bj)= -kV*uphy(i,j,L,bi,bj)
569     dvphy(i,j,L,bi,bj)= -kV*vphy(i,j,L,bi,bj)
570 molod 1.2
571 molod 1.1 c T terms
572     C-- Forcing term(s)
573 molod 1.2 term1=60. _d 0*(sin(lats(I,J,bi,bj)*deg2rad)**2)
574 molod 1.1 termP=0.5 _d 0*( pephy(i,j,L,bi,bj) + pephy(i,j,L+1,bi,bj) )
575     term2=10. _d 0*log(termP/atm_po)
576 molod 1.2 & *(cos(lats(I,J,bi,bj)*deg2rad)**2)
577 molod 1.1 thetaLim = 200. _d 0/ ((termP/atm_po)**atm_kappa)
578     thetaEq=315. _d 0-term1-term2
579     thetaEq=MAX(thetaLim,thetaEq)
580     kT=ka+(ks-ka)
581     & *MAX(0. _d 0,
582     & (termP*recip_P0g-sigma_b)/(1. _d 0-sigma_b) )
583 molod 1.2 & *COS((lats(I,J,bi,bj)*deg2rad))**4
584 molod 1.1 if(termP*recip_P0g.gt.0.04)then
585     dthphy(i,j,L,bi,bj)=- kT*( thphy(I,J,L,bi,bj)-thetaEq )
586 molod 1.2 else
587 molod 1.1 dthphy(i,j,L,bi,bj)=0.
588     endif
589    
590     c S terms (hs runs dry - no moisture)
591     C-- Forcing term(s)
592     dsphy(i,j,L,bi,bj)=0.
593 molod 1.2
594 molod 1.1 enddo
595     enddo
596     enddo
597    
598 molod 1.2 return
599     end

  ViewVC Help
Powered by ViewVC 1.1.22