source: flexpart.git/src/initialize_cbl_vel.f90

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file was 92fab65, checked in by Ignacio Pisso <ip@…>, 4 years ago

add SPDX-License-Identifier to all .f90 files

  • Property mode set to 100644
File size: 2.3 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine initialize_cbl_vel(idum,zp,ust,wst,h,sigmaw,wp, ol)
5!                              i/o   i  i   i  i     i  o   i 
6
7  use par_mod, only:pi
8  use com_mod, only:ldirect
9  use random_mod, only: gasdev, ran3
10
11  implicit none
12
13!===============================================================================
14! CBL skewed vertical profiles and formulation of LHH 1996 with profile of w3
15! from LHB 2000
16! LHH formulation has been modified to account for variable density profiles and
17! backward in time or forward in time simulations
18! see Cassiani et al. BLM 2014 doi  for explanations and references
19!===============================================================================
20
21
22  real :: usurad2,usurad2p,C0,costluar4,eps
23  parameter  (usurad2=0.7071067812,usurad2p=0.3989422804,C0=2,costluar4=0.66667,eps=0.000001)
24
25  integer idum
26  real :: wp,zp,ust,wst,h,dens,ddens,sigmaw,dsigmawdz,tlw,dcas,dcas1!,ran3,gasdev
27  real :: w3,w2
28  real ::  z, &   
29       skew, &
30       skew2, &
31       radw2, &
32       fluarw,fluarw2, &
33       rluarw, &
34       xluarw, &
35       aluarw, &
36       bluarw, &
37       sigmawa, &
38       sigmawb, & 
39       ath, &
40       bth, &
41       wb,wa
42  real timedir
43  real ol, transition
44
45!--------------------------------------------------------------------------- 
46  timedir=ldirect !direction of time forward (1) or backward(-1)
47  z=zp/h
48
49
50  transition=1.
51  if (-h/ol.lt.15) transition=((sin((((-h/ol)+10.)/10.)*pi)))/2.+0.5  !see also in cbl.f90
52
53  w2=sigmaw*sigmaw
54  w3=(((1.2*z*((1.-z)**(3./2.)))+eps)*wst**3) *transition
55
56  skew=w3/(w2**1.5)
57  skew2=skew*skew
58
59  radw2=sqrt(w2) !sigmaw
60
61  fluarw=costluar4*skew**0.333333333333333
62  fluarw2=fluarw*fluarw
63  rluarw=(1.+fluarw2)**3.*skew2/((3.+fluarw2)**2.*fluarw2)  !-> r
64  xluarw=rluarw**0.5 !----> r^1/2
65
66  aluarw=0.5*(1.-xluarw/(4.+rluarw)**0.5)
67  bluarw=1.-aluarw
68
69  sigmawa=radw2*(bluarw/(aluarw*(1.+fluarw2)))**0.5
70  sigmawb=radw2*(aluarw/(bluarw*(1.+fluarw2)))**0.5
71
72  wa=(fluarw*sigmawa)
73  wb=(fluarw*sigmawb)
74
75  dcas=ran3(idum)
76
77  if (dcas.le.aluarw) then
78    dcas1=gasdev(idum)
79    wp=timedir*(dcas1*sigmawa+wa)
80  else
81    dcas1=gasdev(idum)
82    wp=timedir*(dcas1*sigmawb-wb)
83  end if
84
85  return
86end subroutine initialize_cbl_vel
87
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG