source: flexpart.git/src/richardson.f90 @ 02095e3

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since 02095e3 was 6ecb30a, checked in by Espen Sollum ATMOS <eso@…>, 7 years ago

Merged changes from CTBTO project

  • Property mode set to 100644
File size: 8.9 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine richardson(psurf,ust,ttlev,qvlev,ulev,vlev,nuvz, &
23       akz,bkz,hf,tt2,td2,h,wst,hmixplus,metdata_format)
24  !                        i    i    i     i    i    i    i
25  ! i   i  i   i   i  o  o     o
26  !****************************************************************************
27  !                                                                           *
28  !     Calculation of mixing height based on the critical Richardson number. *
29  !     Calculation of convective time scale.                                 *
30  !     For unstable conditions, one iteration is performed. An excess        *
31  !     temperature (dependent on hf and wst) is calculated, added to the     *
32  !     temperature at the lowest model level. Then the procedure is repeated.*
33  !                                                                           *
34  !     Author: A. Stohl                                                      *
35  !                                                                           *
36  !     22 August 1996                                                        *
37  !                                                                           *
38  !     Literature:                                                           *
39  !     Vogelezang DHP and Holtslag AAM (1996): Evaluation and model impacts  *
40  !     of alternative boundary-layer height formulations. Boundary-Layer     *
41  !     Meteor. 81, 245-269.                                                  *
42  !                                                                           *
43  !****************************************************************************
44  !                                                                           *
45  !     Update: 1999-02-01 by G. Wotawa                                       *
46  !                                                                           *
47  !     Two meter level (temperature, humidity) is taken as reference level   *
48  !     instead of first model level.                                         *
49  !     New input variables tt2, td2 introduced.                              *
50  !                                                                           *
51  !     CHANGE: 17/11/2005 Caroline Forster NCEP GFS version                  *
52  !                                                                           *
53  !     Unified ECMWF and GFS builds                                          *
54  !     Marian Harustak, 12.5.2017                                            *
55  !       - Merged richardson and richardson_gfs into one routine using       *
56  !         if-then for meteo-type dependent code                             *
57  !                                                                           *
58  !****************************************************************************
59  !                                                                           *
60  ! Variables:                                                                *
61  ! h                          mixing height [m]                              *
62  ! hf                         sensible heat flux                             *
63  ! psurf                      surface pressure at point (xt,yt) [Pa]         *
64  ! tv                         virtual temperature                            *
65  ! wst                        convective velocity scale                      *
66  ! metdata_format             format of metdata (ecmwf/gfs)                  *
67  !                                                                           *
68  ! Constants:                                                                *
69  ! ric                        critical Richardson number                     *
70  !                                                                           *
71  !****************************************************************************
72
73  use par_mod
74  use class_gribfile
75
76  implicit none
77
78  integer :: metdata_format
79  integer :: i,k,nuvz,iter,llev,loop_start
80  real :: tv,tvold,zref,z,zold,pint,pold,theta,thetaref,ri
81  real :: akz(nuvz),bkz(nuvz),ulev(nuvz),vlev(nuvz),hf,wst,tt2,td2,ew
82  real :: psurf,ust,ttlev(nuvz),qvlev(nuvz),h,excess
83  real :: thetaold,zl,ul,vl,thetal,ril,hmixplus,wspeed,bvfsq,bvf
84  real :: f_qvsat,rh,rhold,rhl,theta1,theta2,zl1,zl2,thetam
85  real,parameter    :: const=r_air/ga, ric=0.25, b=100., bs=8.5
86  integer,parameter :: itmax=3
87
88  excess=0.0
89  iter=0
90
91  if (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
92    ! NCEP version: find first model level above ground
93    !**************************************************
94
95     llev = 0
96     do i=1,nuvz
97       if (psurf.lt.akz(i)) llev=i
98     end do
99     llev = llev+1
100    ! sec llev should not be 1!
101     if (llev.eq.1) llev = 2
102     if (llev.gt.nuvz) llev = nuvz-1
103    ! NCEP version
104  end if
105
106
107  ! Compute virtual temperature and virtual potential temperature at
108  ! reference level (2 m)
109  !*****************************************************************
110
11130   iter=iter+1
112
113  pold=psurf
114  tvold=tt2*(1.+0.378*ew(td2)/psurf)
115  zold=2.0
116  zref=zold
117  rhold=ew(td2)/ew(tt2)
118
119  thetaref=tvold*(100000./pold)**(r_air/cpa)+excess
120  thetaold=thetaref
121
122
123  ! Integrate z up to one level above zt
124  !*************************************
125  if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
126    loop_start=2
127  else
128    loop_start=llev
129  end if
130  do k=loop_start,nuvz
131    pint=akz(k)+bkz(k)*psurf  ! pressure on model layers
132    tv=ttlev(k)*(1.+0.608*qvlev(k))
133
134    if (abs(tv-tvold).gt.0.2) then
135      z=zold+const*log(pold/pint)*(tv-tvold)/log(tv/tvold)
136    else
137      z=zold+const*log(pold/pint)*tv
138    endif
139
140    theta=tv*(100000./pint)**(r_air/cpa)
141  ! Petra
142    rh = qvlev(k) / f_qvsat( pint, ttlev(k) )
143
144
145  ! Calculate Richardson number at each level
146  !****************************************
147
148    ri=ga/thetaref*(theta-thetaref)*(z-zref)/ &
149         max(((ulev(k)-ulev(2))**2+(vlev(k)-vlev(2))**2+b*ust**2),0.1)
150
151  !  addition of second condition: MH should not be placed in an
152  !  unstable layer (PS / Feb 2000)
153    if (ri.gt.ric .and. thetaold.lt.theta) goto 20
154
155    tvold=tv
156    pold=pint
157    rhold=rh
158    thetaold=theta
159    zold=z
160  end do
161  k=k-1 ! ESO: make sure k <= nuvz (ticket #139)
16220   continue
163
164  ! Determine Richardson number between the critical levels
165  !********************************************************
166
167  zl1=zold
168  theta1=thetaold
169  do i=1,20
170    zl=zold+real(i)/20.*(z-zold)
171    ul=ulev(k-1)+real(i)/20.*(ulev(k)-ulev(k-1))
172    vl=vlev(k-1)+real(i)/20.*(vlev(k)-vlev(k-1))
173    thetal=thetaold+real(i)/20.*(theta-thetaold)
174    rhl=rhold+real(i)/20.*(rh-rhold)
175    ril=ga/thetaref*(thetal-thetaref)*(zl-zref)/ &
176         max(((ul-ulev(2))**2+(vl-vlev(2))**2+b*ust**2),0.1)
177    zl2=zl
178    theta2=thetal
179    if (ril.gt.ric) goto 25
180    zl1=zl
181    theta1=thetal
182  end do
183
18425   continue
185  h=zl
186  thetam=0.5*(theta1+theta2)
187  wspeed=sqrt(ul**2+vl**2)                    ! Wind speed at z=hmix
188  bvfsq=(ga/thetam)*(theta2-theta1)/(zl2-zl1) ! Brunt-Vaisala frequency
189                                              ! at z=hmix
190
191  ! Under stable conditions, limit the maximum effect of the subgrid-scale topography
192  ! by the maximum lifting possible from the available kinetic energy
193  !*****************************************************************************
194
195  if(bvfsq.le.0.) then
196    hmixplus=9999.
197  else
198    bvf=sqrt(bvfsq)
199    hmixplus=wspeed/bvf*convke
200  endif
201
202
203  ! Calculate convective velocity scale
204  !************************************
205
206  if (hf.lt.0.) then
207    wst=(-h*ga/thetaref*hf/cpa)**0.333
208    excess=-bs*hf/cpa/wst
209    if (iter.lt.itmax) goto 30
210  else
211    wst=0.
212  endif
213
214end subroutine richardson
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG