source: flexpart.git/src/redist.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: 6.8 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine redist (ipart,ktop,ipconv)
5
6  !**************************************************************************
7  ! Do the redistribution of particles due to convection
8  ! This subroutine is called for each particle which is assigned
9  ! a new vertical position randomly, based on the convective redistribution
10  ! matrix
11  !**************************************************************************
12
13  ! Petra Seibert, Feb 2001, Apr 2001, May 2001, Jan 2002, Nov 2002 and
14  ! Andreas Frank, Nov 2002
15
16  ! Caroline Forster:  November 2004 - February 2005
17
18  use par_mod
19  use com_mod
20  use conv_mod
21  use random_mod
22
23  implicit none
24
25  real,parameter :: const=r_air/ga
26  integer :: ipart, ktop,ipconv
27  integer :: k, kz, levnew, levold
28  real,save :: uvzlev(nuvzmax)
29  real :: wsub(nuvzmax)
30  real :: totlevmass, wsubpart
31  real :: temp_levold,temp_levold1
32  real :: sub_levold,sub_levold1
33  real :: pint, pold, rn, tv, tvold, dlevfrac
34  real :: ew,ztold,ffraction
35  real :: tv1, tv2, dlogp, dz, dz1, dz2
36  integer :: iseed = -88
37
38
39
40  ! ipart   ... number of particle to be treated
41
42  ipconv=1
43
44  ! determine height of the eta half-levels (uvzlev)
45  ! do that only once for each grid column
46  ! i.e. when ktop.eq.1
47  !**************************************************************
48
49  if (ktop .le. 1) then
50
51    tvold=tt2conv*(1.+0.378*ew(td2conv)/psconv)
52    pold=psconv
53    uvzlev(1)=0.
54
55    pint = phconv(2)
56  !  determine next virtual temperatures
57    tv1 = tconv(1)*(1.+0.608*qconv(1))
58    tv2 = tconv(2)*(1.+0.608*qconv(2))
59  !  interpolate virtual temperature to half-level
60    tv = tv1 + (tv2-tv1)*(pconv(1)-phconv(2))/(pconv(1)-pconv(2))
61    if (abs(tv-tvold).gt.0.2) then
62      uvzlev(2) = uvzlev(1) + &
63           const*log(pold/pint)* &
64           (tv-tvold)/log(tv/tvold)
65    else
66      uvzlev(2) = uvzlev(1)+ &
67           const*log(pold/pint)*tv
68    endif
69    tvold=tv
70    tv1=tv2
71    pold=pint
72
73  ! integrate profile (calculation of height agl of eta layers) as required
74    do kz = 3, nconvtop+1
75  !    note that variables defined in calcmatrix.f (pconv,tconv,qconv)
76  !    start at the first real ECMWF model level whereas kz and
77  !    thus uvzlev(kz) starts at the surface. uvzlev is defined at the
78  !    half-levels (between the tconv, qconv etc. values !)
79  !    Thus, uvzlev(kz) is the lower boundary of the tconv(kz) cell.
80      pint = phconv(kz)
81  !    determine next virtual temperatures
82      tv2 = tconv(kz)*(1.+0.608*qconv(kz))
83  !    interpolate virtual temperature to half-level
84      tv = tv1 + (tv2-tv1)*(pconv(kz-1)-phconv(kz))/ &
85           (pconv(kz-1)-pconv(kz))
86      if (abs(tv-tvold).gt.0.2) then
87        uvzlev(kz) = uvzlev(kz-1) + &
88             const*log(pold/pint)* &
89             (tv-tvold)/log(tv/tvold)
90      else
91        uvzlev(kz) = uvzlev(kz-1)+ &
92             const*log(pold/pint)*tv
93      endif
94      tvold=tv
95      tv1=tv2
96      pold=pint
97
98    end do
99
100    ktop = 2
101
102  endif ! (if ktop .le. 1) then
103
104  !  determine vertical grid position of particle in the eta system
105  !****************************************************************
106
107  ztold = ztra1(abs(ipart))
108  ! find old particle grid position
109  do kz = 2, nconvtop
110    if (uvzlev(kz) .ge. ztold ) then
111      levold = kz-1
112      goto 30
113    endif
114  end do
115
116  ! Particle is above the potentially convective domain. Skip it.
117  goto 90
118
11930   continue
120
121  ! now redistribute particles
122  !****************************
123
124  !  Choose a random number and find corresponding level of destination
125  !  Random numbers to be evenly distributed in [0,1]
126
127  rn = ran3(iseed)
128
129  ! initialize levnew
130
131  levnew = levold
132
133  ffraction = 0.
134  totlevmass=dpr(levold)/ga
135  do k = 1,nconvtop
136  ! for backward runs use the transposed matrix
137   if (ldirect.eq.1) then
138     ffraction=ffraction+fmassfrac(levold,k) &
139          /totlevmass
140   else
141     ffraction=ffraction+fmassfrac(k,levold) &
142          /totlevmass
143   endif
144   if (rn.le.ffraction) then
145     levnew=k
146  ! avoid division by zero or a too small number
147  ! if division by zero or a too small number happens the
148  ! particle is assigned to the center of the grid cell
149     if (ffraction.gt.1.e-20) then
150      if (ldirect.eq.1) then
151        dlevfrac = (ffraction-rn) / fmassfrac(levold,k) * totlevmass
152      else
153        dlevfrac = (ffraction-rn) / fmassfrac(k,levold) * totlevmass
154      endif
155     else
156       dlevfrac = 0.5
157     endif
158     goto 40
159   endif
160  end do
161
16240   continue
163
164  ! now assign new position to particle
165
166  if (levnew.le.nconvtop) then
167   if (levnew.eq.levold) then
168      ztra1(abs(ipart)) = ztold
169   else
170    dlogp = (1.-dlevfrac)* &
171         (log(phconv(levnew+1))-log(phconv(levnew)))
172    pint = log(phconv(levnew))+dlogp
173    dz1 = pint - log(phconv(levnew))
174    dz2 = log(phconv(levnew+1)) - pint
175    dz = dz1 + dz2
176    ztra1(abs(ipart)) = (uvzlev(levnew)*dz2+uvzlev(levnew+1)*dz1)/dz
177     if (ztra1(abs(ipart)).lt.0.) &
178          ztra1(abs(ipart))=-1.*ztra1(abs(ipart))
179     if (ipconv.gt.0) ipconv=-1
180   endif
181  endif
182
183  ! displace particle according to compensating subsidence
184  ! this is done to those particles, that were not redistributed
185  ! by the matrix
186  !**************************************************************
187
188  if (levnew.le.nconvtop.and.levnew.eq.levold) then
189
190  ztold = ztra1(abs(ipart))
191
192  ! determine compensating vertical velocity at the levels
193  ! above and below the particel position
194  ! increase compensating subsidence by the fraction that
195  ! is displaced by convection to this level
196
197    if (levold.gt.1) then
198     temp_levold = tconv(levold-1) + &
199          (tconv(levold)-tconv(levold-1)) &
200          *(pconv(levold-1)-phconv(levold))/ &
201          (pconv(levold-1)-pconv(levold))
202     sub_levold = sub(levold)/(1.-sub(levold)/dpr(levold)*ga)
203     wsub(levold)=-1.*sub_levold*r_air*temp_levold/(phconv(levold))
204    else
205     wsub(levold)=0.
206    endif
207
208     temp_levold1 = tconv(levold) + &
209          (tconv(levold+1)-tconv(levold)) &
210          *(pconv(levold)-phconv(levold+1))/ &
211          (pconv(levold)-pconv(levold+1))
212     sub_levold1 = sub(levold+1)/(1.-sub(levold+1)/dpr(levold+1)*ga)
213     wsub(levold+1)=-1.*sub_levold1*r_air*temp_levold1/ &
214          (phconv(levold+1))
215
216  ! interpolate wsub to the vertical particle position
217
218  dz1 = ztold - uvzlev(levold)
219  dz2 = uvzlev(levold+1) - ztold
220  dz = dz1 + dz2
221
222  wsubpart = (dz2*wsub(levold)+dz1*wsub(levold+1))/dz
223  ztra1(abs(ipart)) = ztold+wsubpart*real(lsynctime)
224  if (ztra1(abs(ipart)).lt.0.) then
225     ztra1(abs(ipart))=-1.*ztra1(abs(ipart))
226  endif
227
228  endif      !(levnew.le.nconvtop.and.levnew.eq.levold)
229
230  ! Maximum altitude .5 meter below uppermost model level
231  !*******************************************************
232
233 90   continue
234
235  if (ztra1(abs(ipart)) .gt. height(nz)-0.5) &
236       ztra1(abs(ipart)) = height(nz)-0.5
237
238end subroutine redist
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG