LMDZ
flott_gwd_rando_m.F90
Go to the documentation of this file.
2 
3  implicit none
4 
5 contains
6 
7  SUBROUTINE flott_gwd_rando(DTIME, pp, tt, uu, vv, prec, zustr, zvstr, d_u, &
8  d_v,east_gwstress,west_gwstress)
9 
10  ! Parametrization of the momentum flux deposition due to a discrete
11  ! number of gravity waves.
12  ! Author: F. Lott
13  ! July, 12th, 2012
14  ! Gaussian distribution of the source, source is precipitation
15  ! Reference: Lott (JGR, vol 118, page 8897, 2013)
16 
17  !ONLINE:
18  use dimphy, only: klon, klev
19  use assert_m, only: assert
20  include "YOMCST.h"
21  include "clesphys.h"
22  ! OFFLINE:
23  ! include "dimensions.h"
24  ! include "dimphy.h"
25  ! END OF DIFFERENCE ONLINE-OFFLINE
26  include "YOEGWD.h"
27 
28  ! 0. DECLARATIONS:
29 
30  ! 0.1 INPUTS
31  REAL, intent(in)::DTIME ! Time step of the Physics
32  REAL, intent(in):: pp(:, :) ! (KLON, KLEV) Pressure at full levels
33  REAL, intent(in):: prec(:) ! (klon) Precipitation (kg/m^2/s)
34  REAL, intent(in):: TT(:, :) ! (KLON, KLEV) Temp at full levels
35  REAL, intent(in):: UU(:, :) ! (KLON, KLEV) Zonal wind at full levels
36  REAL, intent(in):: VV(:, :) ! (KLON, KLEV) Merid wind at full levels
37 
38  ! 0.2 OUTPUTS
39  REAL, intent(out):: zustr(:), zvstr(:) ! (KLON) Surface Stresses
40 
41  REAL, intent(inout):: d_u(:, :), d_v(:, :)
42  REAL, intent(inout):: east_gwstress(:, :) ! Profile of eastward stress
43  REAL, intent(inout):: west_gwstress(:, :) ! Profile of westward stress
44 
45  ! (KLON, KLEV) tendencies on winds
46 
47  ! O.3 INTERNAL ARRAYS
48  REAL BVLOW(klon)
49  REAL DZ ! Characteristic depth of the Source
50 
51  INTEGER II, JJ, LL
52 
53  ! 0.3.0 TIME SCALE OF THE LIFE CYCLE OF THE WAVES PARAMETERIZED
54 
55  REAL DELTAT
56 
57  ! 0.3.1 GRAVITY-WAVES SPECIFICATIONS
58 
59  INTEGER, PARAMETER:: NK = 2, np = 2, no = 2, nw = nk * np * no
60  INTEGER JK, JP, JO, JW
61  INTEGER, PARAMETER:: NA = 5 !number of realizations to get the phase speed
62  REAL KMIN, KMAX ! Min and Max horizontal wavenumbers
63  REAL CMAX ! standard deviation of the phase speed distribution
64  REAL RUWMAX,SAT ! ONLINE SPECIFIED IN run.def
65  REAL CPHA ! absolute PHASE VELOCITY frequency
66  REAL ZK(nw, klon) ! Horizontal wavenumber amplitude
67  REAL ZP(nw, klon) ! Horizontal wavenumber angle
68  REAL ZO(nw, klon) ! Absolute frequency !
69 
70  ! Waves Intr. freq. at the 1/2 lev surrounding the full level
71  REAL ZOM(nw, klon), ZOP(nw, klon)
72 
73  ! Wave EP-fluxes at the 2 semi levels surrounding the full level
74  REAL WWM(nw, klon), WWP(nw, klon)
75 
76  REAL RUW0(nw, klon) ! Fluxes at launching level
77 
78  REAL RUWP(nw, klon), RVWP(nw, klon)
79  ! Fluxes X and Y for each waves at 1/2 Levels
80 
81  INTEGER LAUNCH, LTROP ! Launching altitude and tropo altitude
82 
83  REAL XLAUNCH ! Controle the launching altitude
84  REAL XTROP ! SORT of Tropopause altitude
85  REAL RUW(klon, klev + 1) ! Flux x at semi levels
86  REAL RVW(klon, klev + 1) ! Flux y at semi levels
87 
88  REAL PRMAX ! Maximum value of PREC, and for which our linear formula
89  ! for GWs parameterisation apply
90 
91  ! 0.3.2 PARAMETERS OF WAVES DISSIPATIONS
92 
93  REAL RDISS, ZOISEC ! COEFF DE DISSIPATION, SECURITY FOR INTRINSIC FREQ
94 
95  ! 0.3.3 BACKGROUND FLOW AT 1/2 LEVELS AND VERTICAL COORDINATE
96 
97  REAL H0 ! Characteristic Height of the atmosphere
98  REAL PR, TR ! Reference Pressure and Temperature
99 
100  REAL ZH(klon, klev + 1) ! Log-pressure altitude
101 
102  REAL UH(klon, klev + 1), VH(klon, klev + 1) ! Winds at 1/2 levels
103  REAL PH(klon, klev + 1) ! Pressure at 1/2 levels
104  REAL PSEC ! Security to avoid division by 0 pressure
105  REAL PHM1(klon, klev + 1) ! 1/Press at 1/2 levels
106  REAL BV(klon, klev + 1) ! Brunt Vaisala freq. (BVF) at 1/2 levels
107  REAL BVSEC ! Security to avoid negative BVF
108 
109  !-----------------------------------------------------------------
110 
111  ! 1. INITIALISATIONS
112 
113  ! 1.1 Basic parameter
114 
115  ! Are provided from elsewhere (latent heat of vaporization, dry
116  ! gaz constant for air, gravity constant, heat capacity of dry air
117  ! at constant pressure, earth rotation rate, pi).
118 
119  ! 1.2 Tuning parameters of V14
120 
121 
122  rdiss = 1. ! Diffusion parameter
123  ! ONLINE
124  ruwmax=gwd_rando_ruwmax
125  sat=gwd_rando_sat
126  !END ONLINE
127  ! OFFLINE
128  ! RUWMAX= 1.75 ! Launched flux
129  ! SAT=0.25 ! Saturation parameter
130  ! END OFFLINE
131 
132  prmax = 20. / 24. /3600.
133  ! maximum of rain for which our theory applies (in kg/m^2/s)
134 
135  ! Characteristic depth of the source
136  dz = 1000.
137  xlaunch=0.5 ! Parameter that control launching altitude
138  xtrop=0.2 ! Parameter that control tropopause altitude
139  deltat=24.*3600. ! Time scale of the waves (first introduced in 9b)
140  ! OFFLINE
141  ! DELTAT=DTIME
142  ! END OFFLINE
143 
144  kmin = 2.e-5
145  ! minimum horizontal wavenumber (inverse of the subgrid scale resolution)
146 
147  kmax = 1.e-3 ! Max horizontal wavenumber
148  cmax = 30. ! Max phase speed velocity
149 
150  tr = 240. ! Reference Temperature
151  pr = 101300. ! Reference pressure
152  h0 = rd * tr / rg ! Characteristic vertical scale height
153 
154  bvsec = 5.e-3 ! Security to avoid negative BVF
155  psec = 1.e-6 ! Security to avoid division by 0 pressure
156  zoisec = 1.e-6 ! Security FOR 0 INTRINSIC FREQ
157 
158  !ONLINE
159  call assert(klon == (/size(pp, 1), size(tt, 1), size(uu, 1), &
160  size(vv, 1), size(zustr), size(zvstr), size(d_u, 1), &
161  size(d_v, 1), &
162  size(east_gwstress, 1), size(west_gwstress, 1) /), &
163  "FLOTT_GWD_RANDO klon")
164  call assert(klev == (/size(pp, 2), size(tt, 2), size(uu, 2), &
165  size(vv, 2), size(d_u, 2), size(d_v, 2), &
166  size(east_gwstress,2), size(west_gwstress,2) /), &
167  "FLOTT_GWD_RANDO klev")
168  !END ONLINE
169 
170  IF(deltat < dtime)THEN
171  print *, 'flott_gwd_rando: deltat < dtime!'
172  stop 1
173  ENDIF
174 
175  IF (klev < nw) THEN
176  print *, 'flott_gwd_rando: you will have problem with random numbers'
177  stop 1
178  ENDIF
179 
180  ! 2. EVALUATION OF THE BACKGROUND FLOW AT SEMI-LEVELS
181 
182  ! Pressure and Inv of pressure
183  DO ll = 2, klev
184  ph(:, ll) = exp((log(pp(:, ll)) + log(pp(:, ll - 1))) / 2.)
185  phm1(:, ll) = 1. / ph(:, ll)
186  end DO
187 
188  ph(:, klev + 1) = 0.
189  phm1(:, klev + 1) = 1. / psec
190  ph(:, 1) = 2. * pp(:, 1) - ph(:, 2)
191 
192  ! Launching altitude
193 
194  launch=0
195  ltrop =0
196  DO ll = 1, klev
197  IF (ph(klon / 2, ll) / ph(klon / 2, 1) > xlaunch) launch = ll
198  ENDDO
199  DO ll = 1, klev
200  IF (ph(klon / 2, ll) / ph(klon / 2, 1) > xtrop) ltrop = ll
201  ENDDO
202 
203  ! Log pressure vert. coordinate
204  DO ll = 1, klev + 1
205  zh(:, ll) = h0 * log(pr / (ph(:, ll) + psec))
206  end DO
207 
208  ! BV frequency
209  DO ll = 2, klev
210  ! BVSEC: BV Frequency (UH USED IS AS A TEMPORARY ARRAY DOWN TO WINDS)
211  uh(:, ll) = 0.5 * (tt(:, ll) + tt(:, ll - 1)) &
212  * rd**2 / rcpd / h0**2 + (tt(:, ll) &
213  - tt(:, ll - 1)) / (zh(:, ll) - zh(:, ll - 1)) * rd / h0
214  end DO
215  bvlow(:) = 0.5 * (tt(:, ltrop )+ tt(:, launch)) &
216  * rd**2 / rcpd / h0**2 + (tt(:, ltrop ) &
217  - tt(:, launch))/(zh(:, ltrop )- zh(:, launch)) * rd / h0
218 
219  uh(:, 1) = uh(:, 2)
220  uh(:, klev + 1) = uh(:, klev)
221  bv(:, 1) = uh(:, 2)
222  bv(:, klev + 1) = uh(:, klev)
223  ! SMOOTHING THE BV HELPS
224  DO ll = 2, klev
225  bv(:, ll)=(uh(:, ll+1)+2.*uh(:, ll)+uh(:, ll-1))/4.
226  end DO
227 
228  bv=max(sqrt(max(bv, 0.)), bvsec)
229  bvlow=max(sqrt(max(bvlow, 0.)), bvsec)
230 
231 
232  ! WINDS
233  DO ll = 2, klev
234  uh(:, ll) = 0.5 * (uu(:, ll) + uu(:, ll - 1)) ! Zonal wind
235  vh(:, ll) = 0.5 * (vv(:, ll) + vv(:, ll - 1)) ! Meridional wind
236  end DO
237  uh(:, 1) = 0.
238  vh(:, 1) = 0.
239  uh(:, klev + 1) = uu(:, klev)
240  vh(:, klev + 1) = vv(:, klev)
241 
242  ! 3 WAVES CHARACTERISTICS CHOSEN RANDOMLY AT THE LAUNCH ALTITUDE
243 
244  ! The mod functions of weird arguments are used to produce the
245  ! waves characteristics in an almost stochastic way
246 
247  jw = 0
248  DO jp = 1, np
249  DO jk = 1, nk
250  DO jo = 1, no
251  jw = jw + 1
252  ! Angle
253  DO ii = 1, klon
254  ! Angle (0 or PI so far)
255  zp(jw, ii) = (sign(1., 0.5 - mod(tt(ii, jw) * 10., 1.)) + 1.) &
256  * rpi / 2.
257  ! Horizontal wavenumber amplitude
258  zk(jw, ii) = kmin + (kmax - kmin) * mod(tt(ii, jw) * 100., 1.)
259  ! Horizontal phase speed
260  cpha = 0.
261  DO jj = 1, na
262  cpha = cpha + &
263  cmax*2.*(mod(tt(ii, jw+3*jj)**2, 1.)-0.5)*sqrt(3.)/sqrt(na*1.)
264  END DO
265  IF (cpha.LT.0.) THEN
266  cpha = -1.*cpha
267  zp(jw,ii) = zp(jw,ii) + rpi
268  ENDIF
269  ! Absolute frequency is imposed
270  zo(jw, ii) = cpha * zk(jw, ii)
271  ! Intrinsic frequency is imposed
272  zo(jw, ii) = zo(jw, ii) &
273  + zk(jw, ii) * cos(zp(jw, ii)) * uh(ii, launch) &
274  + zk(jw, ii) * sin(zp(jw, ii)) * vh(ii, launch)
275  ! Momentum flux at launch lev
276  ruw0(jw, ii) = ruwmax
277  ENDDO
278  end DO
279  end DO
280  end DO
281 
282  ! 4. COMPUTE THE FLUXES
283 
284  ! 4.1 Vertical velocity at launching altitude to ensure
285  ! the correct value to the imposed fluxes.
286 
287  DO jw = 1, nw
288 
289  ! Evaluate intrinsic frequency at launching altitude:
290  zop(jw, :) = zo(jw, :) &
291  - zk(jw, :) * cos(zp(jw, :)) * uh(:, launch) &
292  - zk(jw, :) * sin(zp(jw, :)) * vh(:, launch)
293 
294  ! VERSION WITH CONVECTIVE SOURCE
295 
296  ! Vertical velocity at launch level, value to ensure the
297  ! imposed factor related to the convective forcing:
298  ! precipitations.
299 
300  ! tanh limitation to values above prmax:
301  wwp(jw, :) = ruw0(jw, :) &
302  * (rd / rcpd / h0 * rlvtt * prmax * tanh(prec(:) / prmax))**2
303 
304  ! Factor related to the characteristics of the waves:
305  wwp(jw, :) = wwp(jw, :) * zk(jw, :)**3 / kmin / bvlow(:) &
306  / max(abs(zop(jw, :)), zoisec)**3
307 
308  ! Moderation by the depth of the source (dz here):
309  wwp(jw, :) = wwp(jw, :) &
310  * exp(- bvlow(:)**2 / max(abs(zop(jw, :)), zoisec)**2 * zk(jw, :)**2 &
311  * dz**2)
312 
313  ! Put the stress in the right direction:
314  ruwp(jw, :) = zop(jw, :) / max(abs(zop(jw, :)), zoisec)**2 &
315  * bv(:, launch) * cos(zp(jw, :)) * wwp(jw, :)**2
316  rvwp(jw, :) = zop(jw, :) / max(abs(zop(jw, :)), zoisec)**2 &
317  * bv(:, launch) * sin(zp(jw, :)) * wwp(jw, :)**2
318  end DO
319 
320 
321  ! 4.2 Uniform values below the launching altitude
322 
323  DO ll = 1, launch
324  ruw(:, ll) = 0
325  rvw(:, ll) = 0
326  DO jw = 1, nw
327  ruw(:, ll) = ruw(:, ll) + ruwp(jw, :)
328  rvw(:, ll) = rvw(:, ll) + rvwp(jw, :)
329  end DO
330  end DO
331 
332  ! 4.3 Loop over altitudes, with passage from one level to the next
333  ! done by i) conserving the EP flux, ii) dissipating a little,
334  ! iii) testing critical levels, and vi) testing the breaking.
335 
336  DO ll = launch, klev - 1
337  ! Warning: all the physics is here (passage from one level
338  ! to the next)
339  DO jw = 1, nw
340  zom(jw, :) = zop(jw, :)
341  wwm(jw, :) = wwp(jw, :)
342  ! Intrinsic Frequency
343  zop(jw, :) = zo(jw, :) - zk(jw, :) * cos(zp(jw, :)) * uh(:, ll + 1) &
344  - zk(jw, :) * sin(zp(jw, :)) * vh(:, ll + 1)
345 
346  ! No breaking (Eq.6)
347  ! Dissipation (Eq. 8)
348  wwp(jw, :) = wwm(jw, :) * exp(- 2. * rdiss * pr / (ph(:, ll + 1) &
349  + ph(:, ll)) * ((bv(:, ll + 1) + bv(:, ll)) / 2.)**3 &
350  / max(abs(zop(jw, :) + zom(jw, :)) / 2., zoisec)**4 &
351  * zk(jw, :)**3 * (zh(:, ll + 1) - zh(:, ll)))
352 
353  ! Critical levels (forced to zero if intrinsic frequency changes sign)
354  ! Saturation (Eq. 12)
355  wwp(jw, :) = min(wwp(jw, :), max(0., &
356  sign(1., zop(jw, :) * zom(jw, :))) * abs(zop(jw, :))**3 &
357  / bv(:, ll + 1) * exp(- zh(:, ll + 1) / h0) * kmin**2 &
358  * sat**2 / zk(jw, :)**4)
359  end DO
360 
361  ! Evaluate EP-flux from Eq. 7 and give the right orientation to
362  ! the stress
363 
364  DO jw = 1, nw
365  ruwp(jw, :) = sign(1., zop(jw, :))*cos(zp(jw, :)) * wwp(jw, :)
366  rvwp(jw, :) = sign(1., zop(jw, :))*sin(zp(jw, :)) * wwp(jw, :)
367  end DO
368 
369  ruw(:, ll + 1) = 0.
370  rvw(:, ll + 1) = 0.
371 
372  DO jw = 1, nw
373  ruw(:, ll + 1) = ruw(:, ll + 1) + ruwp(jw, :)
374  rvw(:, ll + 1) = rvw(:, ll + 1) + rvwp(jw, :)
375  east_gwstress(:, ll)=east_gwstress(:, ll)+max(0.,ruwp(jw,:))/float(nw)
376  west_gwstress(:, ll)=west_gwstress(:, ll)+min(0.,ruwp(jw,:))/float(nw)
377  end DO
378  end DO
379 ! OFFLINE ONLY
380 ! PRINT *,'SAT PROFILE:'
381 ! DO LL=1,KLEV
382 ! PRINT *,ZH(KLON/2,LL)/1000.,SAT*(2.+TANH(ZH(KLON/2,LL)/H0-8.))
383 ! ENDDO
384 
385  ! 5 CALCUL DES TENDANCES:
386 
387  ! 5.1 Rectification des flux au sommet et dans les basses couches
388 
389  ruw(:, klev + 1) = 0.
390  rvw(:, klev + 1) = 0.
391  ruw(:, 1) = ruw(:, launch)
392  rvw(:, 1) = rvw(:, launch)
393  DO ll = 1, launch
394  ruw(:, ll) = ruw(:, launch+1)
395  rvw(:, ll) = rvw(:, launch+1)
396  east_gwstress(:, ll) = east_gwstress(:, launch)
397  west_gwstress(:, ll) = west_gwstress(:, launch)
398  end DO
399 
400  ! AR-1 RECURSIVE FORMULA (13) IN VERSION 4
401  DO ll = 1, klev
402  d_u(:, ll) = (1.-dtime/deltat) * d_u(:, ll) + dtime/deltat/REAL(NW) * &
403  RG * (ruw(:, ll + 1) - ruw(:, ll)) &
404  / (ph(:, ll + 1) - ph(:, ll)) * DTIME
405  ! NO AR-1 FOR MERIDIONAL TENDENCIES
406  d_v(:, ll) = 1./REAL(NW) * &
407  RG * (rvw(:, ll + 1) - rvw(:, ll)) &
408  / (ph(:, ll + 1) - ph(:, ll)) * DTIME
409  ENDDO
410 
411  ! Cosmetic: evaluation of the cumulated stress
412  zustr = 0.
413  zvstr = 0.
414  DO ll = 1, klev
415  zustr = zustr + d_u(:, ll) / rg * (ph(:, ll + 1) - ph(:, ll))/dtime
416  zvstr = zvstr + d_v(:, ll) / rg * (ph(:, ll + 1) - ph(:, ll))/dtime
417  ENDDO
418 
419  END SUBROUTINE flott_gwd_rando
420 
421 end module flott_gwd_rando_m
integer, save klon
Definition: dimphy.F90:3
integer, save klev
Definition: dimphy.F90:7
subroutine flott_gwd_rando(DTIME, pp, tt, uu, vv, prec, zustr, zvstr, d_u, d_v, east_gwstress, west_gwstress)
!$Id NSTRA real GKLIFT real GVSEC REAL GWD_RANDO_RUWMAX!Maximum Eliassen Palm flux at launch in FLOTT_GWD_rando REAL GWD_RANDO_SAT!saturation parameter in FLOTT_GWD_rando!S_c in REAL GWD_FRONT_SAT!Same as GWD_RANDO params but for fronal GWs COMMON YOEGWD gwd_rando_sat
Definition: YOEGWD.h:20
Definition: dimphy.F90:1
real rg
Definition: comcstphy.h:1