source: LMDZ6/trunk/libf/dyn3d/top_bound.F90 @ 5300

Last change on this file since 5300 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.6 KB
Line 
1!
2! $Id: top_bound.F90 5285 2024-10-28 13:33:29Z abarral $
3!
4SUBROUTINE top_bound(vcov,ucov,teta,masse,dt)
5
6  USE iniprint_mod_h
7USE comgeom2_mod_h
8  USE comdissipn_mod_h
9USE 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,jjp1,llm) ! covariant zonal wind
65  real,intent(inout) :: vcov(iip1,jjm,llm) ! covariant meridional wind
66  real,intent(inout) :: teta(iip1,jjp1,llm) ! potential temperature
67  real,intent(in) :: masse(iip1,jjp1,llm) ! mass of atmosphere
68  real,intent(in) :: dt ! time step (s) of sponge model
69
70  !   Local:
71  !   ------
72
73  REAL :: massebx(iip1,jjp1,llm),masseby(iip1,jjm,llm),zm
74  REAL :: uzon(jjp1,llm),vzon(jjm,llm),tzon(jjp1,llm)
75
76  integer :: i
77  REAL,SAVE :: rdamp(llm) ! quenching coefficient
78  real,save :: lambda(llm) ! inverse or quenching time scale (Hz)
79
80  LOGICAL,SAVE :: first=.true.
81
82  INTEGER :: j,l
83
84  if (iflag_top_bound.eq.0) return
85
86  if (first) then
87     if (iflag_top_bound.eq.1) then
88  ! sponge quenching over the topmost 4 atmospheric layers
89         lambda(:)=0.
90         lambda(llm)=tau_top_bound
91         lambda(llm-1)=tau_top_bound/2.
92         lambda(llm-2)=tau_top_bound/4.
93         lambda(llm-3)=tau_top_bound/8.
94     else if (iflag_top_bound.eq.2) then
95  ! sponge quenching over topmost layers down to pressures which are
96  ! higher than 100 times the topmost layer pressure
97         lambda(:)=tau_top_bound &
98               *max(presnivs(llm)/presnivs(:)-0.01,0.)
99     endif
100
101  ! quenching coefficient rdamp(:)
102      ! rdamp(:)=dt*lambda(:) ! Explicit Euler approx.
103     rdamp(:)=1.-exp(-lambda(:)*dt)
104
105     write(lunout,*)'TOP_BOUND mode',mode_top_bound
106     write(lunout,*)'Sponge layer coefficients'
107     write(lunout,*)'p (Pa)  z(km)  tau(s)   1./tau (Hz)'
108     do l=1,llm
109       if (rdamp(l).ne.0.) then
110         write(lunout,'(6(1pe12.4,1x))') &
111               presnivs(l),log(preff/presnivs(l))*scaleheight, &
112               1./lambda(l),lambda(l)
113       endif
114     enddo
115     first=.false.
116  endif ! of if (first)
117
118  CALL massbar(masse,massebx,masseby)
119
120  ! ! compute zonal average of vcov and u
121  if (mode_top_bound.ge.2) then
122   do l=1,llm
123    do j=1,jjm
124      vzon(j,l)=0.
125      zm=0.
126      do i=1,iim
127  ! NB: we can work using vcov zonal mean rather than v since the
128  ! cv coefficient (which relates the two) only varies with latitudes
129        vzon(j,l)=vzon(j,l)+vcov(i,j,l)*masseby(i,j,l)
130        zm=zm+masseby(i,j,l)
131      enddo
132      vzon(j,l)=vzon(j,l)/zm
133    enddo
134   enddo
135
136   do l=1,llm
137    do j=2,jjm ! excluding poles
138      uzon(j,l)=0.
139      zm=0.
140      do i=1,iim
141        uzon(j,l)=uzon(j,l)+massebx(i,j,l)*ucov(i,j,l)/cu(i,j)
142        zm=zm+massebx(i,j,l)
143      enddo
144      uzon(j,l)=uzon(j,l)/zm
145    enddo
146   enddo
147  else ! ucov and vcov will relax towards 0
148    vzon(:,:)=0.
149    uzon(:,:)=0.
150  endif ! of if (mode_top_bound.ge.2)
151
152  ! ! compute zonal average of potential temperature, if necessary
153  if (mode_top_bound.ge.3) then
154   do l=1,llm
155    do j=2,jjm ! excluding poles
156      zm=0.
157      tzon(j,l)=0.
158      do i=1,iim
159        tzon(j,l)=tzon(j,l)+teta(i,j,l)*masse(i,j,l)
160        zm=zm+masse(i,j,l)
161      enddo
162      tzon(j,l)=tzon(j,l)/zm
163    enddo
164   enddo
165  endif ! of if (mode_top_bound.ge.3)
166
167  if (mode_top_bound.ge.1) then
168   ! ! Apply sponge quenching on vcov:
169   do l=1,llm
170    do i=1,iip1
171      do j=1,jjm
172        vcov(i,j,l)=vcov(i,j,l) &
173              -rdamp(l)*(vcov(i,j,l)-vzon(j,l))
174      enddo
175    enddo
176   enddo
177
178   ! ! Apply sponge quenching on ucov:
179   do l=1,llm
180    do i=1,iip1
181      do j=2,jjm ! excluding poles
182        ucov(i,j,l)=ucov(i,j,l) &
183              -rdamp(l)*(ucov(i,j,l)-cu(i,j)*uzon(j,l))
184      enddo
185    enddo
186   enddo
187  endif ! of if (mode_top_bound.ge.1)
188
189  if (mode_top_bound.ge.3) then
190   ! ! Apply sponge quenching on teta:
191   do l=1,llm
192    do i=1,iip1
193      do j=2,jjm ! excluding poles
194        teta(i,j,l)=teta(i,j,l) &
195              -rdamp(l)*(teta(i,j,l)-tzon(j,l))
196      enddo
197    enddo
198   enddo
199  endif ! of if (mode_top_bound.ge.3)
200
201END SUBROUTINE top_bound
Note: See TracBrowser for help on using the repository browser.