source: trunk/LMDZ.VENUS/libf/phyvenus/gwprofil.F @ 2203

Last change on this file since 2203 was 2047, checked in by slebonnois, 6 years ago

SL: VENUS, ajout des modifs apportees par Thomas Navarro pour la parametrisation des ondes de gravite orographiques

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