source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3dpar/sponge_mod_p.F90 @ 227

Last change on this file since 227 was 227, checked in by milmd, 10 years ago

Last LMDZ version (1315) with OpenMP directives and other stuff

File size: 5.4 KB
Line 
1module sponge_mod_p
2
3implicit none
4
5
6! sponge parameters (set/read via conf_gcm.F)
7logical,save :: callsponge  ! do we use a sponge on upper layers
8integer,save :: mode_sponge ! sponge mode
9integer,save :: nsponge ! number of sponge layers
10real,save :: tetasponge  ! sponge time scale (s) at topmost layer
11
12
13contains
14
15      subroutine sponge_p(ucov,vcov,h,ps,dt,mode)
16
17! Sponge routine: Quench ucov, vcov and potential temperature near the
18!                 top of the model
19! Depending on 'mode' relaxation of variables is towards:
20! mode = 0 : h -> h_mean , ucov -> 0 , vcov -> 0
21! mode = 1 : h -> h_mean , ucov -> ucov_mean , vcov -> 0
22! mode >= 2 : h -> h_mean , ucov -> ucov_mean , vcov -> vcov_mean
23! Number of layer over which sponge is applied is 'nsponge' (read from def file)
24! Time scale for quenching at top level is given by 'tetasponge' (read from
25! def file) and doubles as level indexes decrease.
26! Quenching is modeled as: A(t)=Am+A0exp(-lambda*t)
27! where Am is the zonal average of the field (or zero), and lambda the inverse
28! of the characteristic quenching/relaxation time scale
29! Thus, assuming Am to be time-independent, field at time t+dt is given by:
30! A(t+dt)=A(t)-(A(t)-Am)*(1-exp(-lambda*dt))
31
32      USE Write_Field_p
33      use parallel_lmdz, only: pole_sud,pole_nord,jj_begin,jj_end,OMP_CHUNK
34      implicit none
35#include "dimensions.h"
36#include "paramet.h"
37#include "comdissip.h"
38#include "comvert.h"
39#include "comgeom2.h"
40#include "iniprint.h"
41
42! Arguments:
43!------------
44      real,intent(inout) :: ucov(iip1,jjp1,llm) ! covariant zonal wind
45      real,intent(inout) :: vcov(iip1,jjm,llm) ! covariant meridional wind
46      real,intent(inout) :: h(iip1,jjp1,llm) ! potential temperature
47!      real,intent(in) :: pext(iip1,jjp1) ! extensive pressure
48      real,intent(in) :: ps(iip1,jjp1) ! surface pressure (Pa)
49      real,intent(in) :: dt   ! time step
50      integer,intent(in) :: mode  ! sponge mode
51
52!   Local:
53!   ------
54
55      real,save :: sig_s(llm) !sigma au milieu des couches
56      REAL vm,um,hm,ptot(jjp1)
57      real,save :: cst(llm)
58      real :: pext(iip1,jjp1) ! extensive pressure
59
60      INTEGER l,i,j
61      integer :: jjb,jje
62      integer,save :: l0 ! layer down to which sponge is applied
63
64      real ssum
65
66      real zkm
67      logical,save :: firstcall=.true.
68
69
70
71      if (firstcall) then
72!$OMP BARRIER
73!$OMP MASTER
74       ! build approximative sigma levels at midlayer
75        do l=1,llm
76          sig_s(l)=((ap(l)+ap(l+1))/preff+bp(l)+bp(l+1))/2.
77        enddo
78
79        l0=llm-nsponge+1
80 
81        write(lunout,*)
82        write(lunout,*)'sponge mode',mode
83        write(lunout,*)'nsponge tetasponge ',nsponge,tetasponge
84        write(lunout,*)'Coeffs for the sponge layer'
85        write(lunout,*)'Z (km)         tau             cst'
86        do l=llm,l0,-1
87          ! double time scale with every level, starting from the top
88          cst(l)=1.-exp(-dt/(tetasponge*2**(llm-l)))
89        enddo
90
91        do l=l0,llm
92           zkm=-scaleheight*log(sig_s(l))
93           print*,zkm,tetasponge*2**(llm-l),cst(l)
94        enddo
95        PRINT*
96
97        firstcall=.false.
98!$OMP END MASTER
99!$OMP BARRIER
100      endif ! of if (firstcall)
101
102!-----------------------------------------------------------------------
103!   compute sponge relaxation:
104!   -------------------------
105      jjb=jj_begin
106      jje=jj_end+1 ! +1 because vcov(j) computations require pext(j+1) & ptot(j+1)
107      IF (pole_sud)  jje=jj_end-1+1
108!$OMP MASTER
109      pext(1:iip1,jjb:jje)=ps(1:iip1,jjb:jje)*aire(1:iip1,jjb:jje)
110      do j=jjb,jje
111         ptot(j)=sum(pext(1:iim,j))
112      enddo
113!$OMP END MASTER
114!$OMP BARRIER
115
116
117!   potential temperature
118      jjb=jj_begin
119      jje=jj_end
120!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)   
121      do l=l0,llm
122         do j=jjb,jje
123            ! compute zonal average
124            hm=0.
125            do i=1,iim
126               hm=hm+h(i,j,l)*pext(i,j)
127            enddo
128            hm=hm/ptot(j)
129            ! update h()
130            do i=1,iim
131               h(i,j,l)=h(i,j,l)-cst(l)*(h(i,j,l)-hm)
132            enddo
133            h(iip1,j,l)=h(1,j,l)
134         enddo
135      enddo
136!$OMP END DO NOWAIT
137
138!   zonal wind
139      jjb=jj_begin
140      jje=jj_end
141      IF (pole_nord) jjb=jj_begin+1
142      IF (pole_sud)  jje=jj_end-1
143!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)   
144      do l=l0,llm
145         do j=jjb,jje
146            um=0.
147            if(mode.ge.1) then ! compute zonal average
148               do i=1,iim
149                  um=um+0.5*ucov(i,j,l)*(pext(i,j)+pext(i+1,j))/cu(i,j)
150               enddo
151               um=um/ptot(j)
152            endif
153            ! update ucov()
154            do i=1,iim
155               ucov(i,j,l)=ucov(i,j,l)-cst(l)*(ucov(i,j,l)-um*cu(i,j))
156            enddo
157            ucov(iip1,j,l)=ucov(1,j,l)
158         enddo
159      enddo
160!$OMP END DO NOWAIT
161
162!  meridional wind
163      jjb=jj_begin
164      jje=jj_end
165      IF (pole_sud) jje=jj_end-1
166!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)   
167      do l=l0,llm
168         do j=jjb,jje
169            vm=0.
170            if(mode.ge.2) then ! compute zonal average
171               do i=1,iim
172                  vm=vm+vcov(i,j,l)*(pext(i,j)+pext(i,j+1))/cv(i,j)
173               enddo
174               vm=vm/(ptot(j)+ptot(j+1))
175            endif
176            ! update vcov
177            do i=1,iim
178               vcov(i,j,l)=vcov(i,j,l)-cst(l)*(vcov(i,j,l)-vm*cv(i,j))
179            enddo
180            vcov(iip1,j,l)=vcov(1,j,l)
181         enddo
182      enddo
183!$OMP END DO
184
185      end subroutine sponge_p
186     
187end module sponge_mod_p
188
Note: See TracBrowser for help on using the repository browser.