source: trunk/LMDZ.TITAN.old/libf/phytitan/gwprofil.F @ 3094

Last change on this file since 3094 was 1530, checked in by emillour, 9 years ago

Venus and Titan GCMs:
Updates in the physics to keep up with updates in LMDZ5 (up to
LMDZ5 trunk, rev 2350) concerning dynamics/physics separation:

  • Adapted makelmdz and makelmdz_fcm script to stop if trying to compile 1d model or newstart or start2archive in parallel.
  • got rid of references to "dimensions.h" in physics. Within physics packages, use nbp_lon (=iim), nbp_lat (=jjmp1) and nbp_lev (=llm) from module mod_grid_phy_lmdz (in phy_common) instead. Only partially done for Titan, because of many hard-coded commons; a necessary first step will be to clean these up (using modules).

EM

File size: 5.7 KB
Line 
1      subroutine gwprofil
2     *         ( nlon, nlev
3     *         , kgwd ,kdx  , ktest
4     *         , kkcrit, kkcrith, kcrit ,  kkenvh, kknu,kknu2
5     *         , paphm1, prho   , pstab , ptfr , pvph , pri , ptau
6     *         , pdmod   , pnu   , psig ,pgamma, pstd, ppic,pval)
7
8C**** *gwprofil*
9C
10C     purpose.
11C     --------
12C
13C**   interface.
14C     ----------
15C          from *gwdrag*
16C
17C        explicit arguments :
18C        --------------------
19C     ==== inputs ===
20C
21C     ==== outputs ===
22C
23C        implicit arguments :   none
24C        --------------------
25C
26C     method:
27C     -------
28C     the stress profile for gravity waves is computed as follows:
29C     it decreases linearly with heights from the ground
30C     to the low-level indicated by kkcrith,
31C     to simulates lee waves or
32C     low-level gravity wave breaking.
33C     above it is constant, except when the waves encounter a critical
34C     level (kcrit) or when they break.
35C     The stress is also uniformly distributed above the level
36C     ntop.                                         
37C
38      use dimphy
39      IMPLICIT NONE
40
41#include "YOMCST.h"
42#include "YOEGWD.h"
43
44C-----------------------------------------------------------------------
45C
46C*       0.1   ARGUMENTS
47C              ---------
48C
49      integer nlon,nlev,kgwd
50      integer kkcrit(nlon),kkcrith(nlon),kcrit(nlon)
51     *       ,kdx(nlon),ktest(nlon)
52     *       ,kkenvh(nlon),kknu(nlon),kknu2(nlon)
53C
54      real paphm1(nlon,nlev+1), pstab(nlon,nlev+1),
55     *     prho  (nlon,nlev+1), pvph (nlon,nlev+1),
56     *     pri   (nlon,nlev+1), ptfr (nlon), ptau(nlon,nlev+1)
57     
58      real pdmod (nlon) , pnu (nlon) , psig(nlon),
59     *     pgamma(nlon) , pstd(nlon) , ppic(nlon), pval(nlon)
60     
61C-----------------------------------------------------------------------
62C
63C*       0.2   local arrays
64C              ------------
65C
66      integer jl,jk
67      real zsqr,zalfa,zriw,zdel,zb,zalpha,zdz2n,zdelp,zdelpt
68
69      real zdz2 (klon,klev) , znorm(klon) , zoro(klon)
70      real ztau (klon,klev+1)
71C
72C-----------------------------------------------------------------------
73C
74C*         1.    INITIALIZATION
75C                --------------
76C
77C      print *,' entree gwprofil'
78 100  CONTINUE
79C
80C
81C*    COMPUTATIONAL CONSTANTS.
82C     ------------- ----------
83C
84      do 400 jl=kidia,kfdia
85      if(ktest(jl).eq.1)then
86      zoro(jl)=psig(jl)*pdmod(jl)/4./pstd(jl)
87      ztau(jl,klev+1)=ptau(jl,klev+1)
88c     print *,jl,ptau(jl,klev+1)
89      ztau(jl,kkcrith(jl))=grahilo*ptau(jl,klev+1)
90      endif
91  400 continue
92 
93C
94      do 430 jk=klev+1,1,-1
95C
96C
97C*         4.1    constant shear stress until top of the
98C                 low-level breaking/trapped layer
99  410 CONTINUE
100C
101      do 411 jl=kidia,kfdia
102      if(ktest(jl).eq.1)then
103           if(jk.gt.kkcrith(jl)) then
104           zdelp=paphm1(jl,jk)-paphm1(jl,klev+1)
105           zdelpt=paphm1(jl,kkcrith(jl))-paphm1(jl,klev+1)
106           ptau(jl,jk)=ztau(jl,klev+1)+zdelp/zdelpt*
107     c                 (ztau(jl,kkcrith(jl))-ztau(jl,klev+1))
108           else                   
109           ptau(jl,jk)=ztau(jl,kkcrith(jl))
110           endif
111       endif
112 411  continue             
113C
114C*         4.15   constant shear stress until the top of the
115C                 low level flow layer.
116 415  continue
117C       
118C
119C*         4.2    wave displacement at next level.
120C
121  420 continue
122C
123  430 continue
124
125C
126C*         4.4    wave richardson number, new wave displacement
127C*                and stress:  breaking evaluation and critical
128C                 level
129C
130                         
131      do 440 jk=klev,1,-1
132
133      do 441 jl=kidia,kfdia
134      if(ktest(jl).eq.1)then
135      znorm(jl)=prho(jl,jk)*sqrt(pstab(jl,jk))*pvph(jl,jk)
136      zdz2(jl,jk)=ptau(jl,jk)/amax1(znorm(jl),gssec)/zoro(jl)
137      endif
138  441 continue
139
140      do 442 jl=kidia,kfdia
141      if(ktest(jl).eq.1)then
142          if(jk.lt.kkcrith(jl)) then
143          if((ptau(jl,jk+1).lt.gtsec).or.(jk.le.kcrit(jl))) then
144             ptau(jl,jk)=0.0
145          else
146               zsqr=sqrt(pri(jl,jk))
147               zalfa=sqrt(pstab(jl,jk)*zdz2(jl,jk))/pvph(jl,jk)
148               zriw=pri(jl,jk)*(1.-zalfa)/(1+zalfa*zsqr)**2
149               if(zriw.lt.grcrit) then
150c                 print *,' breaking!!!',ptau(jl,jk),zsqr
151                  zdel=4./zsqr/grcrit+1./grcrit**2+4./grcrit
152                  zb=1./grcrit+2./zsqr
153                  zalpha=0.5*(-zb+sqrt(zdel))
154                  zdz2n=(pvph(jl,jk)*zalpha)**2/pstab(jl,jk)
155                  ptau(jl,jk)=znorm(jl)*zdz2n*zoro(jl)
156               endif
157               
158               ptau(jl,jk)=amin1(ptau(jl,jk),ptau(jl,jk+1))
159                 
160          endif
161          endif
162      endif
163  442 continue
164  440 continue
165
166C  REORGANISATION OF THE STRESS PROFILE AT LOW LEVEL
167
168      do 530 jl=kidia,kfdia
169      if(ktest(jl).eq.1)then
170         ztau(jl,kkcrith(jl)-1)=ptau(jl,kkcrith(jl)-1)
171         ztau(jl,ntop)=ptau(jl,ntop)
172      endif
173 530  continue     
174
175      do 531 jk=1,klev
176     
177      do 532 jl=kidia,kfdia
178      if(ktest(jl).eq.1)then
179               
180         if(jk.gt.kkcrith(jl)-1)then
181
182          zdelp=paphm1(jl,jk)-paphm1(jl,klev+1    )
183          zdelpt=paphm1(jl,kkcrith(jl)-1)-paphm1(jl,klev+1    )
184          ptau(jl,jk)=ztau(jl,klev+1    ) +
185     .                (ztau(jl,kkcrith(jl)-1)-ztau(jl,klev+1    ) )*
186     .                zdelp/zdelpt
187     
188        endif
189      endif
190           
191 532  continue   
192 
193C  REORGANISATION AT THE MODEL TOP....
194
195      do 533 jl=kidia,kfdia
196      if(ktest(jl).eq.1)then
197
198         if(jk.lt.ntop)then
199
200          zdelp =paphm1(jl,ntop)
201          zdelpt=paphm1(jl,jk)
202          ptau(jl,jk)=ztau(jl,ntop)*zdelpt/zdelp
203c         ptau(jl,jk)=ztau(jl,ntop)               
204
205        endif
206
207      endif
208
209 533  continue
210
211 
212 531  continue       
213
214
215 123   format(i4,1x,20(f6.3,1x))
216
217
218      return
219      end
220
Note: See TracBrowser for help on using the repository browser.