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

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

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

revision 1.1 by molod, Tue Apr 27 17:43:40 2004 UTC revision 1.9 by jmc, Tue Mar 27 15:49:37 2012 UTC
# Line 1  Line 1 
1         subroutine do_fizhi(uphy,vphy,thphy,sphy,pephy,  C $Header$
2       .                              ctmt,xxmt,yymt,zetamt,xlmt,khmt,tke,  C $Name$
3       .                xC,yC,  #include "FIZHI_OPTIONS.h"
4       .im1,im2,jm1,jm2,Nrphys,Nsx,Nsy,idim1,idim2,jdim1,jdim2,bi,bj,nchp,         SUBROUTINE DO_FIZHI(myIter,myid,
5       .                                         duphy,dvphy,dthphy,dsphy)       & idim1,idim2,jdim1,jdim2,Nrphin,nSxin,nSyin,im1,im2,jm1,jm2,bi,bj,
6         & turbStart, nchp,nchptot,nchpland,
7         & uphy,vphy,thphy,sphy,pephy,lons,lats,Zsurf,
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         & iras,nlwcld,cldtotlwin,cldraslwin,cldlsplwin,nlwlz,lwlzin,
14         & nswcld,cldtotswin,cldrasswin,cldlspswin,nswlz,swlzin,imstturbsw,
15         & imstturblw,qliqaveswin,qliqavelwin,fccaveswin,fccavelwin,
16         & rainconin,rainlspin,snowfallin,
17         & duphy,dvphy,dthphy,dsphy)
18  c-----------------------------------------------------------------------  c-----------------------------------------------------------------------
19  c Dummy routine to calculate physics increments - here set them to  c Interface routine to calculate physics increments - calls fizhi_driver.
20  c                                  the Held-Suarez forcing terms  c Purpose of this routine is to set up arrays local to fizhi and 'save'
21    c them from one iteration to the next, and act as interface between the
22    c model common blocks (held in fizhi_wrapper) and fizhi_driver.
23    c Copies of variables that are 'shadowed' are made here without shadows
24    c for passing to fizhi_driver.
25    c Note: routine is called from inside a bi-bj loop
26    c
27  c-----------------------------------------------------------------------  c-----------------------------------------------------------------------
28         implicit none        IMPLICIT NONE
29  #include "CPP_OPTIONS.h"  #include "SIZE.h"
30    #include "fizhi_SIZE.h"
31    #include "chronos.h"
32    
33    C Argument list declarations
34          INTEGER myIter,myid,im1,im2,jm1,jm2,idim1,idim2,jdim1,jdim2
35          INTEGER Nrphin,nSxin,nSyin,bi,bj,nchp
36          LOGICAL turbStart
37          INTEGER nchptot(nSxin,nSyin),nchpland(nSxin,nSyin)
38          _RL uphy(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
39          _RL vphy(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
40          _RL thphy(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
41          _RL sphy(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
42          _RL pephy(idim1:idim2,jdim1:jdim2,Nrphin+1,nSxin,nSyin)
43          _RS lons(idim1:idim2,jdim1:jdim2,nSxin,nSyin)
44          _RS lats(idim1:idim2,jdim1:jdim2,nSxin,nSyin)
45          _RS Zsurf(idim1:idim2,jdim1:jdim2,nSxin,nSyin)
46          _RL ctmt(nchp,nSxin,nSyin),xxmt(nchp,nSxin,nSyin)
47          _RL yymt(nchp,nSxin,nSyin)
48          _RL zetamt(nchp,nSxin,nSyin)
49          _RL xlmt(nchp,Nrphin,nSxin,nSyin),khmt(nchp,Nrphin,nSxin,nSyin)
50          _RL tke(nchp,Nrphin,nSxin,nSyin)
51          _RL tgz(im2,jm2,nSxin,nSyin)
52          _RL sst(idim1:idim2,jdim1:jdim2,nSxin,nSyin)
53          _RL sice(idim1:idim2,jdim1:jdim2,nSxin,nSyin)
54          _RL phis_var(im2,jm2,nSxin,nSyin)
55          INTEGER landtype(im2,jm2,nSxin,nSyin)
56          _RL fracland(im2,jm2,nSxin,nSyin),emiss(im2,jm2,10,nSxin,nSyin)
57          _RL albvisdr(im2,jm2,nSxin,nSyin),albvisdf(im2,jm2,nSxin,nSyin)
58          _RL albnirdr(im2,jm2,nSxin,nSyin),albnirdf(im2,jm2,nSxin,nSyin)
59          _RL chfr(nchp,nSxin,nSyin),alai(nchp,nSxin,nSyin)
60          _RL agrn(nchp,nSxin,nSyin)
61          INTEGER ityp(nchp,nSxin,nSyin),igrd(nchp,nSxin,nSyin)
62          _RL chlat(nchp,nSxin,nSyin),chlon(nchp,nSxin,nSyin)
63          _RL tcanopy(nchp,nSxin,nSyin),tdeep(nchp,nSxin,nSyin)
64          _RL ecanopy(nchp,nSxin,nSyin),swetshal(nchp,nSxin,nSyin)
65          _RL swetroot(nchp,nSxin,nSyin),swetdeep(nchp,nSxin,nSyin)
66          _RL snodep(nchp,nSxin,nSyin),capac(nchp,nSxin,nSyin)
67          _RL o3(im2,jm2,Nrphin,nSxin,nSyin)
68          _RL qstr(im2,jm2,Nrphin,nSxin,nSyin)
69          _RL co2,cfc11,cfc12,cfc22,n2o(Nrphin),methane(Nrphin)
70    
71          INTEGER iras(nSxin,nSyin)
72          INTEGER nlwcld(nSxin,nSyin),nlwlz(nSxin,nSyin)
73          INTEGER nswcld(nSxin,nSyin),nswlz(nSxin,nSyin)
74          INTEGER imstturbsw(nSxin,nSyin),imstturblw(nSxin,nSyin)
75          _RL cldtotlwin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
76          _RL cldraslwin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
77          _RL cldlsplwin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
78          _RL lwlzin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
79          _RL cldtotswin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
80          _RL cldrasswin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
81          _RL cldlspswin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
82          _RL swlzin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
83          _RL qliqaveswin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
84          _RL qliqavelwin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
85          _RL fccaveswin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
86          _RL fccavelwin(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
87          _RL rainlspin(idim1:idim2,jdim1:jdim2,nSxin,nSyin)
88          _RL rainconin(idim1:idim2,jdim1:jdim2,nSxin,nSyin)
89          _RL snowfallin(idim1:idim2,jdim1:jdim2,nSxin,nSyin)
90    
91    
92          _RL duphy(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
93          _RL dvphy(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
94          _RL dthphy(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
95          _RL dsphy(idim1:idim2,jdim1:jdim2,Nrphin,nSxin,nSyin)
96    
97    
98    c Local Variables
99          INTEGER ptracer,ntracer
100          PARAMETER (ptracer = 1)
101          PARAMETER (ntracer = 1)
102    
103          _RL xlats(sNx,sNy),xlons(sNx,sNy),sea_ice(sNx,sNy)
104          _RL p(sNx,sNy,nSx,nSy)
105          _RL u(sNx,sNy,Nrphys),v(sNx,sNy,Nrphys),t(sNx,sNy,Nrphys)
106          _RL q(sNx,sNy,Nrphys,ntracer)
107          _RL pl(sNx,sNy,Nrphys,nSx,nSy),pkl(sNx,sNy,Nrphys,nSx,nSy)
108          _RL ple(sNx,sNy,Nrphys+1,nSx,nSy)
109          _RL pkle(sNx,sNy,Nrphys+1,nSx,nSy)
110          _RL dpres(sNx,sNy,Nrphys,nSx,nSy)
111          _RL lwdt(sNx,sNy,Nrphys,nSx,nSy)
112          _RL lwdtclr(sNx,sNy,Nrphys,nSx,nSy)
113          _RL swdt(sNx,sNy,Nrphys,nSx,nSy)
114          _RL swdtclr(sNx,sNy,Nrphys,nSx,nSy)
115          _RL turbu(sNx,sNy,Nrphys,nSx,nSy)
116          _RL turbv(sNx,sNy,Nrphys,nSx,nSy)
117          _RL turbt(sNx,sNy,Nrphys,nSx,nSy)
118          _RL turbq(sNx,sNy,Nrphys,ntracer,nSx,nSy)
119          _RL moistu(sNx,sNy,Nrphys,nSx,nSy)
120          _RL moistv(sNx,sNy,Nrphys,nSx,nSy)
121          _RL moistt(sNx,sNy,Nrphys,nSx,nSy)
122          _RL moistq(sNx,sNy,Nrphys,ntracer,nSx,nSy)
123          _RL radswt(sNx,sNy,nSx,nSy),radswg(sNx,sNy,nSx,nSy)
124          _RL swgclr(sNx,sNy,nSx,nSy)
125          _RL fdirpar(sNx,sNy,nSx,nSy),fdifpar(sNx,sNy,nSx,nSy)
126          _RL osr(sNx,sNy,nSx,nSy),osrclr(sNx,sNy,nSx,nSy)
127          _RL tg0(sNx,sNy,nSx,nSy),radlwg(sNx,sNy,nSx,nSy)
128          _RL lwgclr(sNx,sNy,nSx,nSy),st4(sNx,sNy,nSx,nSy)
129          _RL dst4(sNx,sNy,nSx,nSy),dlwdtg(sNx,sNy,Nrphys,nSx,nSy)
130          _RL qq(sNx,sNy,Nrphys,nSx,nSy)
131          INTEGER i,j,L
132          _RL getcon, kappa, p0kappa, s0, ra
133          _RL cosz(sNx,sNy)
134          _RL cldtot_lw(sNx,sNy,Nrphys)
135          _RL cldras_lw(sNx,sNy,Nrphys)
136          _RL cldlsp_lw(sNx,sNy,Nrphys)
137          _RL lwlz(sNx,sNy,Nrphys)
138          _RL cldtot_sw(sNx,sNy,Nrphys)
139          _RL cldras_sw(sNx,sNy,Nrphys)
140          _RL cldlsp_sw(sNx,sNy,Nrphys)
141          _RL swlz(sNx,sNy,Nrphys)
142          _RL qliqavesw(sNx,sNy,Nrphys)
143          _RL qliqavelw(sNx,sNy,Nrphys)
144          _RL fccavesw(sNx,sNy,Nrphys)
145          _RL fccavelw(sNx,sNy,Nrphys)
146          _RL rainlsp(sNx,sNy)
147          _RL raincon(sNx,sNy)
148          _RL snowfall(sNx,sNy)
149    
150          _RL tempij(sNx,sNy)
151          _RL tempi(2)
152    
153         integer im1,im2,jm1,jm2,idim1,idim2,jdim1,jdim2        _RL kF,sigma_b,ks,ka,deg2rad,pi,atm_po,atm_kappa,termp,kv,kT
154         integer Nrphys,Nsx,Nsy,bi,bj,nchp        _RL term1,term2,thetalim,thetaeq,recip_p0g
155         _RL uphy(im1:im2,jm1:jm2,Nrphys,Nsx,Nsy)  
156         _RL vphy(im1:im2,jm1:jm2,Nrphys,Nsx,Nsy)        LOGICAL alarm
157         _RL thphy(im1:im2,jm1:jm2,Nrphys,Nsx,Nsy)        EXTERNAL alarm
158         _RL sphy(im1:im2,jm1:jm2,Nrphys,Nsx,Nsy)  
159         _RL pephy(im1:im2,jm1:jm2,Nrphys+1,Nsx,Nsy)  C***********************************************************************
        _RL ctmt(nchp,Nsx,Nsy),xxmt(nchp,Nsx,Nsy),yymt(nchp,Nsx,Nsy)  
        _RL zetamt(nchp,Nsx,Nsy)  
        _RL xlmt(nchp,Nrphys,Nsx,Nsy),khmt(nchp,Nrphys,Nsx,Nsy)  
        _RL tke(nchp,Nrphys,Nsx,Nsy)  
        _RL duphy(im1:im2,jm1:jm2,Nrphys,Nsx,Nsy)  
        _RL dvphy(im1:im2,jm1:jm2,Nrphys,Nsx,Nsy)  
        _RL dthphy(im1:im2,jm1:jm2,Nrphys,Nsx,Nsy)  
        _RL dsphy(im1:im2,jm1:jm2,Nrphys,Nsx,Nsy)  
        _RS xC(im1:im2,jm1:jm2,Nsx,Nsy)  
        _RS yC(im1:im2,jm1:jm2,Nsx,Nsy)  
 c  
        integer i,j,L  
        _RL kF,sigma_b,ks,ka,deg2rad,pi,atm_po,atm_kappa,termp,kv,kT  
        _RL term1,term2,thetalim,thetaeq,recip_p0g  
        _RL getcon  
160    
161         kF=1. _d 0/86400. _d 0         kF=1. _d 0/86400. _d 0
162         sigma_b = 0.7 _d 0         sigma_b = 0.7 _d 0
# Line 43  c Line 168  c
168         deg2rad = getcon('DEG2RAD')         deg2rad = getcon('DEG2RAD')
169    
170         do L = 1,Nrphys         do L = 1,Nrphys
171          do j = jdim1,jdim2          do j = jm1,jm2
172          do i = idim1,idim2          do i = im1,im2
173           recip_P0g= 1. _d 0 / pephy(i,j,1,bi,bj)           recip_P0g= 1. _d 0 / pephy(i,j,Nrphys+1,bi,bj)
174  c U  and V terms:  c U  and V terms:
175           termP=0.5 _d 0*((pephy(i,j,L,bi,bj)+pephy(i,j,L+1,bi,bj))           termP=0.5 _d 0*((pephy(i,j,L,bi,bj)+pephy(i,j,L+1,bi,bj))
176       &                   *recip_P0g )       &                   *recip_P0g )
# Line 55  c U  and V terms: Line 180  c U  and V terms:
180    
181  c T terms  c T terms
182  C--   Forcing term(s)  C--   Forcing term(s)
183           term1=60. _d 0*(sin(yC(I,J,bi,bj)*deg2rad)**2)           term1=60. _d 0*(sin(lats(I,J,bi,bj)*deg2rad)**2)
184           termP=0.5 _d 0*( pephy(i,j,L,bi,bj) + pephy(i,j,L+1,bi,bj) )           termP=0.5 _d 0*( pephy(i,j,L,bi,bj) + pephy(i,j,L+1,bi,bj) )
185           term2=10. _d 0*log(termP/atm_po)           term2=10. _d 0*log(termP/atm_po)
186       &            *(cos(yC(I,J,bi,bj)*deg2rad)**2)       &            *(cos(lats(I,J,bi,bj)*deg2rad)**2)
187           thetaLim = 200. _d 0/ ((termP/atm_po)**atm_kappa)           thetaLim = 200. _d 0/ ((termP/atm_po)**atm_kappa)
188           thetaEq=315. _d 0-term1-term2           thetaEq=315. _d 0-term1-term2
189           thetaEq=MAX(thetaLim,thetaEq)           thetaEq=MAX(thetaLim,thetaEq)
190           kT=ka+(ks-ka)           kT=ka+(ks-ka)
191       &     *MAX(0. _d 0,       &     *MAX(0. _d 0,
192       &       (termP*recip_P0g-sigma_b)/(1. _d 0-sigma_b) )       &       (termP*recip_P0g-sigma_b)/(1. _d 0-sigma_b) )
193       &     *COS((yC(I,J,bi,bj)*deg2rad))**4       &     *COS((lats(I,J,bi,bj)*deg2rad))**4
194           if(termP*recip_P0g.gt.0.04)then           if(termP*recip_P0g.gt.0.04)then
195            dthphy(i,j,L,bi,bj)=- kT*( thphy(I,J,L,bi,bj)-thetaEq )            dthphy(i,j,L,bi,bj)=- kT*( thphy(I,J,L,bi,bj)-thetaEq )
196           else           else
# Line 80  C--   Forcing term(s) Line 205  C--   Forcing term(s)
205          enddo          enddo
206         enddo         enddo
207    
208         return        return
209         end        end

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.9

  ViewVC Help
Powered by ViewVC 1.1.22