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

Last change on this file since 5273 was 5272, checked in by abarral, 2 days ago

Turn paramet.h into a module

  • 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.8 KB
Line 
1!
2! $Id: top_bound.F90 5272 2024-10-24 15:53:15Z abarral $
3!
4SUBROUTINE top_bound(vcov,ucov,teta,masse,dt)
5
6  USE comconst_mod, ONLY: iflag_top_bound, mode_top_bound, &
7        tau_top_bound
8  USE comvert_mod, ONLY: presnivs, preff, scaleheight
9
10  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
11USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
12          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
13IMPLICIT NONE
14  !
15
16
17  include "comgeom2.h"
18
19
20  ! ..  DISSIPATION LINEAIRE A HAUT NIVEAU, RUN MESO,
21  ! F. LOTT DEC. 2006
22  !                             (  10/12/06  )
23
24  !=======================================================================
25  !
26  !   Auteur:  F. LOTT
27  !   -------
28  !
29  !   Objet:
30  !   ------
31  !
32  !   Dissipation lin�aire (ex top_bound de la physique)
33  !
34  !=======================================================================
35
36  ! top_bound sponge layer model:
37  ! Quenching is modeled as: A(t)=Am+A0*exp(-lambda*t)
38  ! where Am is the zonal average of the field (or zero), and lambda the inverse
39  ! of the characteristic quenching/relaxation time scale
40  ! Thus, assuming Am to be time-independent, field at time t+dt is given by:
41  ! A(t+dt)=A(t)-(A(t)-Am)*(1-exp(-lambda*t))
42  ! Moreover lambda can be a function of model level (see below), and relaxation
43  ! can be toward the average zonal field or just zero (see below).
44
45  ! NB: top_bound sponge is only called from leapfrog if ok_strato=.true.
46
47  ! sponge parameters: (loaded/set in conf_gcm.F ; stored in comconst_mod)
48  !    iflag_top_bound=0 for no sponge
49  !    iflag_top_bound=1 for sponge over 4 topmost layers
50  !    iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
51  !    mode_top_bound=0: no relaxation
52  !    mode_top_bound=1: u and v relax towards 0
53  !    mode_top_bound=2: u and v relax towards their zonal mean
54  !    mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
55  !    tau_top_bound : inverse of charactericstic relaxation time scale at
56  !                   the topmost layer (Hz)
57
58
59INCLUDE "comdissipn.h"
60INCLUDE "iniprint.h"
61
62  !   Arguments:
63  !   ----------
64
65  real,intent(inout) :: ucov(iip1,jjp1,llm) ! covariant zonal wind
66  real,intent(inout) :: vcov(iip1,jjm,llm) ! covariant meridional wind
67  real,intent(inout) :: teta(iip1,jjp1,llm) ! potential temperature
68  real,intent(in) :: masse(iip1,jjp1,llm) ! mass of atmosphere
69  real,intent(in) :: dt ! time step (s) of sponge model
70
71  !   Local:
72  !   ------
73
74  REAL :: massebx(iip1,jjp1,llm),masseby(iip1,jjm,llm),zm
75  REAL :: uzon(jjp1,llm),vzon(jjm,llm),tzon(jjp1,llm)
76
77  integer :: i
78  REAL,SAVE :: rdamp(llm) ! quenching coefficient
79  real,save :: lambda(llm) ! inverse or quenching time scale (Hz)
80
81  LOGICAL,SAVE :: first=.true.
82
83  INTEGER :: j,l
84
85  if (iflag_top_bound.eq.0) return
86
87  if (first) then
88     if (iflag_top_bound.eq.1) then
89  ! sponge quenching over the topmost 4 atmospheric layers
90         lambda(:)=0.
91         lambda(llm)=tau_top_bound
92         lambda(llm-1)=tau_top_bound/2.
93         lambda(llm-2)=tau_top_bound/4.
94         lambda(llm-3)=tau_top_bound/8.
95     else if (iflag_top_bound.eq.2) then
96  ! sponge quenching over topmost layers down to pressures which are
97  ! higher than 100 times the topmost layer pressure
98         lambda(:)=tau_top_bound &
99               *max(presnivs(llm)/presnivs(:)-0.01,0.)
100     endif
101
102  ! quenching coefficient rdamp(:)
103      ! rdamp(:)=dt*lambda(:) ! Explicit Euler approx.
104     rdamp(:)=1.-exp(-lambda(:)*dt)
105
106     write(lunout,*)'TOP_BOUND mode',mode_top_bound
107     write(lunout,*)'Sponge layer coefficients'
108     write(lunout,*)'p (Pa)  z(km)  tau(s)   1./tau (Hz)'
109     do l=1,llm
110       if (rdamp(l).ne.0.) then
111         write(lunout,'(6(1pe12.4,1x))') &
112               presnivs(l),log(preff/presnivs(l))*scaleheight, &
113               1./lambda(l),lambda(l)
114       endif
115     enddo
116     first=.false.
117  endif ! of if (first)
118
119  CALL massbar(masse,massebx,masseby)
120
121  ! ! compute zonal average of vcov and u
122  if (mode_top_bound.ge.2) then
123   do l=1,llm
124    do j=1,jjm
125      vzon(j,l)=0.
126      zm=0.
127      do i=1,iim
128  ! NB: we can work using vcov zonal mean rather than v since the
129  ! cv coefficient (which relates the two) only varies with latitudes
130        vzon(j,l)=vzon(j,l)+vcov(i,j,l)*masseby(i,j,l)
131        zm=zm+masseby(i,j,l)
132      enddo
133      vzon(j,l)=vzon(j,l)/zm
134    enddo
135   enddo
136
137   do l=1,llm
138    do j=2,jjm ! excluding poles
139      uzon(j,l)=0.
140      zm=0.
141      do i=1,iim
142        uzon(j,l)=uzon(j,l)+massebx(i,j,l)*ucov(i,j,l)/cu(i,j)
143        zm=zm+massebx(i,j,l)
144      enddo
145      uzon(j,l)=uzon(j,l)/zm
146    enddo
147   enddo
148  else ! ucov and vcov will relax towards 0
149    vzon(:,:)=0.
150    uzon(:,:)=0.
151  endif ! of if (mode_top_bound.ge.2)
152
153  ! ! compute zonal average of potential temperature, if necessary
154  if (mode_top_bound.ge.3) then
155   do l=1,llm
156    do j=2,jjm ! excluding poles
157      zm=0.
158      tzon(j,l)=0.
159      do i=1,iim
160        tzon(j,l)=tzon(j,l)+teta(i,j,l)*masse(i,j,l)
161        zm=zm+masse(i,j,l)
162      enddo
163      tzon(j,l)=tzon(j,l)/zm
164    enddo
165   enddo
166  endif ! of if (mode_top_bound.ge.3)
167
168  if (mode_top_bound.ge.1) then
169   ! ! Apply sponge quenching on vcov:
170   do l=1,llm
171    do i=1,iip1
172      do j=1,jjm
173        vcov(i,j,l)=vcov(i,j,l) &
174              -rdamp(l)*(vcov(i,j,l)-vzon(j,l))
175      enddo
176    enddo
177   enddo
178
179   ! ! Apply sponge quenching on ucov:
180   do l=1,llm
181    do i=1,iip1
182      do j=2,jjm ! excluding poles
183        ucov(i,j,l)=ucov(i,j,l) &
184              -rdamp(l)*(ucov(i,j,l)-cu(i,j)*uzon(j,l))
185      enddo
186    enddo
187   enddo
188  endif ! of if (mode_top_bound.ge.1)
189
190  if (mode_top_bound.ge.3) then
191   ! ! Apply sponge quenching on teta:
192   do l=1,llm
193    do i=1,iip1
194      do j=2,jjm ! excluding poles
195        teta(i,j,l)=teta(i,j,l) &
196              -rdamp(l)*(teta(i,j,l)-tzon(j,l))
197      enddo
198    enddo
199   enddo
200  endif ! of if (mode_top_bound.ge.3)
201
202END SUBROUTINE top_bound
Note: See TracBrowser for help on using the repository browser.