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

Last change on this file since 695 was 101, checked in by slebonnois, 14 years ago

SL: modifications pour arriver a compiler le gcm VENUS !
Ca marche !
A noter: modifs de makelmdz

File size: 5.8 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 "dimensions.h"
42#include "paramet.h"
43
44#include "YOMCST.h"
45#include "YOEGWD.h"
46
47C-----------------------------------------------------------------------
48C
49C*       0.1   ARGUMENTS
50C              ---------
51C
52      integer nlon,nlev,kgwd
53      integer kkcrit(nlon),kkcrith(nlon),kcrit(nlon)
54     *       ,kdx(nlon),ktest(nlon)
55     *       ,kkenvh(nlon),kknu(nlon),kknu2(nlon)
56C
57      real paphm1(nlon,nlev+1), pstab(nlon,nlev+1),
58     *     prho  (nlon,nlev+1), pvph (nlon,nlev+1),
59     *     pri   (nlon,nlev+1), ptfr (nlon), ptau(nlon,nlev+1)
60     
61      real pdmod (nlon) , pnu (nlon) , psig(nlon),
62     *     pgamma(nlon) , pstd(nlon) , ppic(nlon), pval(nlon)
63     
64C-----------------------------------------------------------------------
65C
66C*       0.2   local arrays
67C              ------------
68C
69      integer jl,jk
70      real zsqr,zalfa,zriw,zdel,zb,zalpha,zdz2n,zdelp,zdelpt
71
72      real zdz2 (klon,klev) , znorm(klon) , zoro(klon)
73      real ztau (klon,klev+1)
74C
75C-----------------------------------------------------------------------
76C
77C*         1.    INITIALIZATION
78C                --------------
79C
80C      print *,' entree gwprofil'
81 100  CONTINUE
82C
83C
84C*    COMPUTATIONAL CONSTANTS.
85C     ------------- ----------
86C
87      do 400 jl=kidia,kfdia
88      if(ktest(jl).eq.1)then
89      zoro(jl)=psig(jl)*pdmod(jl)/4./pstd(jl)
90      ztau(jl,klev+1)=ptau(jl,klev+1)
91c     print *,jl,ptau(jl,klev+1)
92      ztau(jl,kkcrith(jl))=grahilo*ptau(jl,klev+1)
93      endif
94  400 continue
95 
96C
97      do 430 jk=klev+1,1,-1
98C
99C
100C*         4.1    constant shear stress until top of the
101C                 low-level breaking/trapped layer
102  410 CONTINUE
103C
104      do 411 jl=kidia,kfdia
105      if(ktest(jl).eq.1)then
106           if(jk.gt.kkcrith(jl)) then
107           zdelp=paphm1(jl,jk)-paphm1(jl,klev+1)
108           zdelpt=paphm1(jl,kkcrith(jl))-paphm1(jl,klev+1)
109           ptau(jl,jk)=ztau(jl,klev+1)+zdelp/zdelpt*
110     c                 (ztau(jl,kkcrith(jl))-ztau(jl,klev+1))
111           else                   
112           ptau(jl,jk)=ztau(jl,kkcrith(jl))
113           endif
114       endif
115 411  continue             
116C
117C*         4.15   constant shear stress until the top of the
118C                 low level flow layer.
119 415  continue
120C       
121C
122C*         4.2    wave displacement at next level.
123C
124  420 continue
125C
126  430 continue
127
128C
129C*         4.4    wave richardson number, new wave displacement
130C*                and stress:  breaking evaluation and critical
131C                 level
132C
133                         
134      do 440 jk=klev,1,-1
135
136      do 441 jl=kidia,kfdia
137      if(ktest(jl).eq.1)then
138      znorm(jl)=prho(jl,jk)*sqrt(pstab(jl,jk))*pvph(jl,jk)
139      zdz2(jl,jk)=ptau(jl,jk)/amax1(znorm(jl),gssec)/zoro(jl)
140      endif
141  441 continue
142
143      do 442 jl=kidia,kfdia
144      if(ktest(jl).eq.1)then
145          if(jk.lt.kkcrith(jl)) then
146          if((ptau(jl,jk+1).lt.gtsec).or.(jk.le.kcrit(jl))) then
147             ptau(jl,jk)=0.0
148          else
149               zsqr=sqrt(pri(jl,jk))
150               zalfa=sqrt(pstab(jl,jk)*zdz2(jl,jk))/pvph(jl,jk)
151               zriw=pri(jl,jk)*(1.-zalfa)/(1+zalfa*zsqr)**2
152               if(zriw.lt.grcrit) then
153C                 print *,' breaking!!!',ptau(jl,jk)
154                  zdel=4./zsqr/grcrit+1./grcrit**2+4./grcrit
155                  zb=1./grcrit+2./zsqr
156                  zalpha=0.5*(-zb+sqrt(zdel))
157                  zdz2n=(pvph(jl,jk)*zalpha)**2/pstab(jl,jk)
158                  ptau(jl,jk)=znorm(jl)*zdz2n*zoro(jl)
159               endif
160               
161               ptau(jl,jk)=amin1(ptau(jl,jk),ptau(jl,jk+1))
162                 
163          endif
164          endif
165      endif
166  442 continue
167  440 continue
168
169C  REORGANISATION OF THE STRESS PROFILE AT LOW LEVEL
170
171      do 530 jl=kidia,kfdia
172      if(ktest(jl).eq.1)then
173         ztau(jl,kkcrith(jl)-1)=ptau(jl,kkcrith(jl)-1)
174         ztau(jl,ntop)=ptau(jl,ntop)
175      endif
176 530  continue     
177
178      do 531 jk=1,klev
179     
180      do 532 jl=kidia,kfdia
181      if(ktest(jl).eq.1)then
182               
183         if(jk.gt.kkcrith(jl)-1)then
184
185          zdelp=paphm1(jl,jk)-paphm1(jl,klev+1    )
186          zdelpt=paphm1(jl,kkcrith(jl)-1)-paphm1(jl,klev+1    )
187          ptau(jl,jk)=ztau(jl,klev+1    ) +
188     .                (ztau(jl,kkcrith(jl)-1)-ztau(jl,klev+1    ) )*
189     .                zdelp/zdelpt
190     
191        endif
192      endif
193           
194 532  continue   
195 
196C  REORGANISATION AT THE MODEL TOP....
197
198      do 533 jl=kidia,kfdia
199      if(ktest(jl).eq.1)then
200
201         if(jk.lt.ntop)then
202
203          zdelp =paphm1(jl,ntop)
204          zdelpt=paphm1(jl,jk)
205          ptau(jl,jk)=ztau(jl,ntop)*zdelpt/zdelp
206c         ptau(jl,jk)=ztau(jl,ntop)               
207
208        endif
209
210      endif
211
212 533  continue
213
214 
215 531  continue       
216
217
218 123   format(i4,1x,20(f6.3,1x))
219
220
221      return
222      end
223
Note: See TracBrowser for help on using the repository browser.