source: LMDZ6/trunk/libf/dyn3dmem/top_bound_loc.f90 @ 5301

Last change on this file since 5301 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 6.9 KB
Line 
1!
2! $Id: $
3!
4SUBROUTINE top_bound_loc(vcov,ucov,teta,masse,dt)
5  USE iniprint_mod_h
6  USE comgeom2_mod_h
7  USE comdissipn_mod_h
8  USE parallel_lmdz
9  USE comconst_mod, ONLY: iflag_top_bound, mode_top_bound, &
10        tau_top_bound
11  USE comvert_mod, ONLY: presnivs, preff, scaleheight
12
13  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
14USE paramet_mod_h
15IMPLICIT NONE
16  !
17
18
19
20
21  ! ..  DISSIPATION LINEAIRE A HAUT NIVEAU, RUN MESO,
22  ! F. LOTT DEC. 2006
23  !                             (  10/12/06  )
24
25  !=======================================================================
26  !
27  !   Auteur:  F. LOTT
28  !   -------
29  !
30  !   Objet:
31  !   ------
32  !
33  !   Dissipation lin�aire (ex top_bound de la physique)
34  !
35  !=======================================================================
36
37  ! top_bound sponge layer model:
38  ! Quenching is modeled as: A(t)=Am+A0*exp(-lambda*t)
39  ! where Am is the zonal average of the field (or zero), and lambda the inverse
40  ! of the characteristic quenching/relaxation time scale
41  ! Thus, assuming Am to be time-independent, field at time t+dt is given by:
42  ! A(t+dt)=A(t)-(A(t)-Am)*(1-exp(-lambda*t))
43  ! Moreover lambda can be a function of model level (see below), and relaxation
44  ! can be toward the average zonal field or just zero (see below).
45
46  ! NB: top_bound sponge is only called from leapfrog if ok_strato=.true.
47
48  ! sponge parameters: (loaded/set in conf_gcm.F ; stored in comconst_mod)
49  !    iflag_top_bound=0 for no sponge
50  !    iflag_top_bound=1 for sponge over 4 topmost layers
51  !    iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
52  !    mode_top_bound=0: no relaxation
53  !    mode_top_bound=1: u and v relax towards 0
54  !    mode_top_bound=2: u and v relax towards their zonal mean
55  !    mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
56  !    tau_top_bound : inverse of charactericstic relaxation time scale at
57  !                   the topmost layer (Hz)
58
59
60
61  !   Arguments:
62  !   ----------
63
64  real,intent(inout) :: ucov(iip1,jjb_u:jje_u,llm) ! covariant zonal wind
65  real,intent(inout) :: vcov(iip1,jjb_v:jje_v,llm) ! covariant meridional wind
66  real,intent(inout) :: teta(iip1,jjb_u:jje_u,llm) ! potential temperature
67  real,intent(in) :: masse(iip1,jjb_u:jje_u,llm) ! mass of atmosphere
68  real,intent(in) :: dt ! time step (s) of sponge model
69
70   ! REAL dv(iip1,jjb_v:jje_v,llm),du(iip1,jjb_u:jje_u,llm)
71   ! REAL dh(iip1,jjb_u:jje_u,llm)
72
73  !   Local:
74  !   ------
75  REAL :: massebx(iip1,jjb_u:jje_u,llm),masseby(iip1,jjb_v:jje_v,llm)
76  REAL :: zm
77  REAL :: uzon(jjb_u:jje_u,llm),vzon(jjb_v:jje_v,llm)
78  REAL :: tzon(jjb_u:jje_u,llm)
79
80  integer :: i
81  REAL,SAVE :: rdamp(llm)
82  real,save :: lambda(llm) ! inverse or quenching time scale (Hz)
83  LOGICAL,SAVE :: first=.true.
84  INTEGER :: j,l,jjb,jje
85
86
87  if (iflag_top_bound == 0) return
88
89  if (first) then
90!$OMP BARRIER
91!$OMP MASTER
92     if (iflag_top_bound == 1) then
93  ! sponge quenching over the topmost 4 atmospheric layers
94         lambda(:)=0.
95         lambda(llm)=tau_top_bound
96         lambda(llm-1)=tau_top_bound/2.
97         lambda(llm-2)=tau_top_bound/4.
98         lambda(llm-3)=tau_top_bound/8.
99     else if (iflag_top_bound == 2) then
100  ! sponge quenching over topmost layers down to pressures which are
101  ! higher than 100 times the topmost layer pressure
102         lambda(:)=tau_top_bound &
103               *max(presnivs(llm)/presnivs(:)-0.01,0.)
104     endif
105
106  ! quenching coefficient rdamp(:)
107      ! rdamp(:)=dt*lambda(:) ! Explicit Euler approx.
108     rdamp(:)=1.-exp(-lambda(:)*dt)
109
110     write(lunout,*)'TOP_BOUND mode',mode_top_bound
111     write(lunout,*)'Sponge layer coefficients'
112     write(lunout,*)'p (Pa)  z(km)  tau(s)   1./tau (Hz)'
113     do l=1,llm
114       if (rdamp(l).ne.0.) then
115         write(lunout,'(6(1pe12.4,1x))') &
116               presnivs(l),log(preff/presnivs(l))*scaleheight, &
117               1./lambda(l),lambda(l)
118       endif
119     enddo
120     first=.false.
121!$OMP END MASTER
122!$OMP BARRIER
123  endif ! of if (first)
124
125
126  CALL massbar_loc(masse,massebx,masseby)
127
128  ! ! compute zonal average of vcov (or set it to zero)
129  if (mode_top_bound.ge.2) then
130   jjb=jj_begin
131   jje=jj_end
132   IF (pole_sud) jje=jj_end-1
133!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
134   do l=1,llm
135    do j=jjb,jje
136      zm=0.
137      vzon(j,l)=0
138      do i=1,iim
139  ! NB: we can work using vcov zonal mean rather than v since the
140  ! cv coefficient (which relates the two) only varies with latitudes
141        vzon(j,l)=vzon(j,l)+vcov(i,j,l)*masseby(i,j,l)
142        zm=zm+masseby(i,j,l)
143      enddo
144      vzon(j,l)=vzon(j,l)/zm
145    enddo
146   enddo
147!$OMP END DO NOWAIT
148  else
149!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
150   do l=1,llm
151     vzon(:,l)=0.
152   enddo
153!$OMP END DO NOWAIT
154  endif ! of if (mode_top_bound.ge.2)
155
156  ! ! compute zonal average of u (or set it to zero)
157  if (mode_top_bound.ge.2) then
158   jjb=jj_begin
159   jje=jj_end
160   IF (pole_nord) jjb=jj_begin+1
161   IF (pole_sud)  jje=jj_end-1
162!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
163   do l=1,llm
164    do j=jjb,jje
165      uzon(j,l)=0.
166      zm=0.
167      do i=1,iim
168        uzon(j,l)=uzon(j,l)+massebx(i,j,l)*ucov(i,j,l)/cu(i,j)
169        zm=zm+massebx(i,j,l)
170      enddo
171      uzon(j,l)=uzon(j,l)/zm
172    enddo
173   enddo
174!$OMP END DO NOWAIT
175  else
176!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
177   do l=1,llm
178     uzon(:,l)=0.
179   enddo
180!$OMP END DO NOWAIT
181  endif ! of if (mode_top_bound.ge.2)
182
183  ! ! compute zonal average of potential temperature, if necessary
184  if (mode_top_bound.ge.3) then
185   jjb=jj_begin
186   jje=jj_end
187   IF (pole_nord) jjb=jj_begin+1
188   IF (pole_sud)  jje=jj_end-1
189!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
190   do l=1,llm
191    do j=jjb,jje
192      zm=0.
193      tzon(j,l)=0.
194      do i=1,iim
195        tzon(j,l)=tzon(j,l)+teta(i,j,l)*masse(i,j,l)
196        zm=zm+masse(i,j,l)
197      enddo
198      tzon(j,l)=tzon(j,l)/zm
199    enddo
200   enddo
201!$OMP END DO NOWAIT
202  endif ! of if (mode_top_bound.ge.3)
203
204  if (mode_top_bound.ge.1) then
205   ! ! Apply sponge quenching on vcov:
206   jjb=jj_begin
207   jje=jj_end
208   IF (pole_sud) jje=jj_end-1
209
210!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
211   do l=1,llm
212    do j=jjb,jje
213      do i=1,iip1
214        vcov(i,j,l)=vcov(i,j,l) &
215              -rdamp(l)*(vcov(i,j,l)-vzon(j,l))
216      enddo
217    enddo
218   enddo
219!$OMP END DO NOWAIT
220
221   ! ! Apply sponge quenching on ucov:
222   jjb=jj_begin
223   jje=jj_end
224   IF (pole_nord) jjb=jj_begin+1
225   IF (pole_sud)  jje=jj_end-1
226
227!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
228   do l=1,llm
229    do j=jjb,jje
230      do i=1,iip1
231        ucov(i,j,l)=ucov(i,j,l) &
232              -rdamp(l)*(ucov(i,j,l)-cu(i,j)*uzon(j,l))
233      enddo
234   enddo
235   enddo
236!$OMP END DO NOWAIT
237  endif ! of if (mode_top_bound.ge.1)
238
239  if (mode_top_bound.ge.3) then
240   ! ! Apply sponge quenching on teta:
241   jjb=jj_begin
242   jje=jj_end
243   IF (pole_nord) jjb=jj_begin+1
244   IF (pole_sud)  jje=jj_end-1
245
246!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
247   do l=1,llm
248    do j=jjb,jje
249      do i=1,iip1
250        teta(i,j,l)=teta(i,j,l) &
251              -rdamp(l)*(teta(i,j,l)-tzon(j,l))
252      enddo
253   enddo
254   enddo
255!$OMP END DO NOWAIT
256  endif ! of if (mode_top_bond.ge.3)
257
258END SUBROUTINE top_bound_loc
Note: See TracBrowser for help on using the repository browser.