source: LMDZ6/branches/Amaury_dev/libf/dyn3d/top_bound.F90

Last change on this file was 5159, checked in by abarral, 7 weeks ago

Put dimensions.h and paramet.h into 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: 6.1 KB
Line 
1! $Id: top_bound.F90 5159 2024-08-02 19:58:25Z dcugnet $
2
3SUBROUTINE top_bound(vcov, ucov, teta, masse, dt)
4
5  USE comconst_mod, ONLY: iflag_top_bound, mode_top_bound, &
6          tau_top_bound
7  USE comvert_mod, ONLY: presnivs, preff, scaleheight
8  USE lmdz_iniprint, ONLY: lunout, prt_level
9  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
10  USE lmdz_comgeom2
11
12USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
13  USE lmdz_paramet
14  IMPLICIT NONE
15  !
16
17
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  !   Arguments:
59  !   ----------
60
61  REAL, INTENT(INOUT) :: ucov(iip1, jjp1, llm) ! covariant zonal wind
62  REAL, INTENT(INOUT) :: vcov(iip1, jjm, llm) ! covariant meridional wind
63  REAL, INTENT(INOUT) :: teta(iip1, jjp1, llm) ! potential temperature
64  REAL, INTENT(IN) :: masse(iip1, jjp1, llm) ! mass of atmosphere
65  REAL, INTENT(IN) :: dt ! time step (s) of sponge model
66
67  !   Local:
68  !   ------
69
70  REAL :: massebx(iip1, jjp1, llm), masseby(iip1, jjm, llm), zm
71  REAL :: uzon(jjp1, llm), vzon(jjm, llm), tzon(jjp1, llm)
72
73  INTEGER :: i
74  REAL, SAVE :: rdamp(llm) ! quenching coefficient
75  REAL, save :: lambda(llm) ! inverse or quenching time scale (Hz)
76
77  LOGICAL, SAVE :: first = .TRUE.
78
79  INTEGER :: j, l
80
81  IF (iflag_top_bound==0) return
82
83  IF (first) THEN
84    IF (iflag_top_bound==1) THEN
85      ! sponge quenching over the topmost 4 atmospheric layers
86      lambda(:) = 0.
87      lambda(llm) = tau_top_bound
88      lambda(llm - 1) = tau_top_bound / 2.
89      lambda(llm - 2) = tau_top_bound / 4.
90      lambda(llm - 3) = tau_top_bound / 8.
91    ELSE IF (iflag_top_bound==2) THEN
92      ! sponge quenching over topmost layers down to pressures which are
93      ! higher than 100 times the topmost layer pressure
94      lambda(:) = tau_top_bound &
95              * max(presnivs(llm) / presnivs(:) - 0.01, 0.)
96    endif
97
98    ! quenching coefficient rdamp(:)
99    ! rdamp(:)=dt*lambda(:) ! Explicit Euler approx.
100    rdamp(:) = 1. - exp(-lambda(:) * dt)
101
102    WRITE(lunout, *)'TOP_BOUND mode', mode_top_bound
103    WRITE(lunout, *)'Sponge layer coefficients'
104    WRITE(lunout, *)'p (Pa)  z(km)  tau(s)   1./tau (Hz)'
105    DO l = 1, llm
106      IF (rdamp(l)/=0.) THEN
107        WRITE(lunout, '(6(1pe12.4,1x))') &
108                presnivs(l), log(preff / presnivs(l)) * scaleheight, &
109                1. / lambda(l), lambda(l)
110      endif
111    enddo
112    first = .FALSE.
113  ENDIF ! of if (first)
114
115  CALL massbar(masse, massebx, masseby)
116
117  ! compute zonal average of vcov and u
118  IF (mode_top_bound>=2) THEN
119    DO l = 1, llm
120      DO j = 1, jjm
121        vzon(j, l) = 0.
122        zm = 0.
123        DO i = 1, iim
124          ! NB: we can work using vcov zonal mean rather than v since the
125          ! cv coefficient (which relates the two) only varies with latitudes
126          vzon(j, l) = vzon(j, l) + vcov(i, j, l) * masseby(i, j, l)
127          zm = zm + masseby(i, j, l)
128        enddo
129        vzon(j, l) = vzon(j, l) / zm
130      enddo
131    enddo
132
133    DO l = 1, llm
134      DO j = 2, jjm ! excluding poles
135        uzon(j, l) = 0.
136        zm = 0.
137        DO i = 1, iim
138          uzon(j, l) = uzon(j, l) + massebx(i, j, l) * ucov(i, j, l) / cu(i, j)
139          zm = zm + massebx(i, j, l)
140        enddo
141        uzon(j, l) = uzon(j, l) / zm
142      enddo
143    enddo
144  else ! ucov and vcov will relax towards 0
145    vzon(:, :) = 0.
146    uzon(:, :) = 0.
147  ENDIF ! of if (mode_top_bound.ge.2)
148
149  ! compute zonal average of potential temperature, if necessary
150  IF (mode_top_bound>=3) THEN
151    DO l = 1, llm
152      DO j = 2, jjm ! excluding poles
153        zm = 0.
154        tzon(j, l) = 0.
155        DO i = 1, iim
156          tzon(j, l) = tzon(j, l) + teta(i, j, l) * masse(i, j, l)
157          zm = zm + masse(i, j, l)
158        enddo
159        tzon(j, l) = tzon(j, l) / zm
160      enddo
161    enddo
162  ENDIF ! of if (mode_top_bound.ge.3)
163
164  IF (mode_top_bound>=1) THEN
165    ! Apply sponge quenching on vcov:
166    DO l = 1, llm
167      DO i = 1, iip1
168        DO j = 1, jjm
169          vcov(i, j, l) = vcov(i, j, l) &
170                  - rdamp(l) * (vcov(i, j, l) - vzon(j, l))
171        enddo
172      enddo
173    enddo
174
175    ! Apply sponge quenching on ucov:
176    DO l = 1, llm
177      DO i = 1, iip1
178        DO j = 2, jjm ! excluding poles
179          ucov(i, j, l) = ucov(i, j, l) &
180                  - rdamp(l) * (ucov(i, j, l) - cu(i, j) * uzon(j, l))
181        enddo
182      enddo
183    enddo
184  ENDIF ! of if (mode_top_bound.ge.1)
185
186  IF (mode_top_bound>=3) THEN
187    ! Apply sponge quenching on teta:
188    DO l = 1, llm
189      DO i = 1, iip1
190        DO j = 2, jjm ! excluding poles
191          teta(i, j, l) = teta(i, j, l) &
192                  - rdamp(l) * (teta(i, j, l) - tzon(j, l))
193        enddo
194      enddo
195    enddo
196  ENDIF ! of if (mode_top_bound.ge.3)
197
198END SUBROUTINE top_bound
Note: See TracBrowser for help on using the repository browser.