source: flexpart.git/src/advance.f90 @ 7999df47

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since 7999df47 was fdc0f03, checked in by Espen Sollum ATMOS <eso@…>, 8 years ago

Code for cloud water should be correct if the total cw is stored in field clwc (old scheme) or in field qc (new scheme). Minor edits in some files.

  • Property mode set to 100644
File size: 33.2 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 advance(itime,nrelpoint,ldt,up,vp,wp, &
23       usigold,vsigold,wsigold,nstop,xt,yt,zt,prob,icbt)
24  !                     i    i  i/oi/oi/o
25  !  i/o     i/o     i/o     o  i/oi/oi/o i/o  i/o
26  !*****************************************************************************
27  !                                                                            *
28  !  Calculation of turbulent particle trajectories utilizing a                *
29  !  zero-acceleration scheme, which is corrected by a numerically more        *
30  !  accurate Petterssen scheme whenever possible.                             *
31  !                                                                            *
32  !  Particle positions are read in, incremented, and returned to the calling  *
33  !  program.                                                                  *
34  !                                                                            *
35  !  In different regions of the atmosphere (PBL vs. free troposphere),        *
36  !  different parameters are needed for advection, parameterizing turbulent   *
37  !  velocities, etc. For efficiency, different interpolation routines have    *
38  !  been written for these different cases, with the disadvantage that there  *
39  !  exist several routines doing almost the same. They all share the          *
40  !  included file 'interpol_mod'. The following                               *
41  !  interpolation routines are used:                                          *
42  !                                                                            *
43  !  interpol_all(_nests)     interpolates everything (called inside the PBL)  *
44  !  interpol_misslev(_nests) if a particle moves vertically in the PBL,       *
45  !                           additional parameters are interpolated if it     *
46  !                           crosses a model level                            *
47  !  interpol_wind(_nests)    interpolates the wind and determines the         *
48  !                           standard deviation of the wind (called outside   *
49  !                           PBL) also interpolates potential vorticity       *
50  !  interpol_wind_short(_nests) only interpolates the wind (needed for the    *
51  !                           Petterssen scheme)                               *
52  !  interpol_vdep(_nests)    interpolates deposition velocities               *
53  !                                                                            *
54  !                                                                            *
55  !     Author: A. Stohl                                                       *
56  !                                                                            *
57  !     16 December 1997                                                       *
58  !                                                                            *
59  !  Changes:                                                                  *
60  !                                                                            *
61  !  8 April 2000: Deep convection parameterization                            *
62  !                                                                            *
63  !  May 2002: Petterssen scheme introduced                                    *
64  !                                                                            *
65  !*****************************************************************************
66  !                                                                            *
67  ! Variables:                                                                 *
68  ! icbt               1 if particle not transferred to forbidden state,       *
69  !                    else -1                                                 *
70  ! dawsave            accumulated displacement in along-wind direction        *
71  ! dcwsave            accumulated displacement in cross-wind direction        *
72  ! dxsave             accumulated displacement in longitude                   *
73  ! dysave             accumulated displacement in latitude                    *
74  ! h [m]              Mixing height                                           *
75  ! lwindinterv [s]    time interval between two wind fields                   *
76  ! itime [s]          time at which this subroutine is entered                *
77  ! itimec [s]         actual time, which is incremented in this subroutine    *
78  ! href [m]           height for which dry deposition velocity is calculated  *
79  ! ladvance [s]       Total integration time period                           *
80  ! ldirect            1 forward, -1 backward                                  *
81  ! ldt [s]            Time step for the next integration                      *
82  ! lsynctime [s]      Synchronisation interval of FLEXPART                    *
83  ! ngrid              index which grid is to be used                          *
84  ! nrand              index for a variable to be picked from rannumb          *
85  ! nstop              if > 1 particle has left domain and must be stopped     *
86  ! prob               probability of absorption due to dry deposition         *
87  ! rannumb(maxrand)   normally distributed random variables                   *
88  ! rhoa               air density                                             *
89  ! rhograd            vertical gradient of the air density                    *
90  ! up,vp,wp           random velocities due to turbulence (along wind, cross  *
91  !                    wind, vertical wind                                     *
92  ! usig,vsig,wsig     mesoscale wind fluctuations                             *
93  ! usigold,vsigold,wsigold  like usig, etc., but for the last time step       *
94  ! vdepo              Deposition velocities for all species                   *
95  ! xt,yt,zt           Particle position                                       *
96  !                                                                            *
97  !*****************************************************************************
98
99  use point_mod
100  use par_mod
101  use com_mod
102  use interpol_mod
103  use hanna_mod
104  use cmapf_mod
105  use random_mod, only: ran3
106
107  implicit none
108
109  real(kind=dp) :: xt,yt
110  real :: zt,xts,yts,weight
111  integer :: itime,itimec,nstop,ldt,i,j,k,nrand,loop,memindnext,mind
112  integer :: ngr,nix,njy,ks,nsp,nrelpoint
113  real :: dz,dz1,dz2,xlon,ylat,xpol,ypol,gridsize
114  real :: ru,rv,rw,dt,ux,vy,cosfact,xtn,ytn,tropop
115  real :: prob(maxspec),up,vp,wp,dxsave,dysave,dawsave
116  real :: dcwsave
117  real :: usigold,vsigold,wsigold,r,rs
118  real :: uold,vold,wold,vdepo(maxspec)
119  !real uprof(nzmax),vprof(nzmax),wprof(nzmax)
120  !real usigprof(nzmax),vsigprof(nzmax),wsigprof(nzmax)
121  !real rhoprof(nzmax),rhogradprof(nzmax)
122  real :: rhoa,rhograd,delz,dtf,rhoaux,dtftlw,uxscale,wpscale
123  integer(kind=2) :: icbt
124  real,parameter :: eps=nxmax/3.e5,eps2=1.e-9
125  real :: ptot_lhh,Q_lhh,phi_lhh,ath,bth !modified by mc
126  real :: old_wp_buf,dcas,dcas1,del_test !added by mc
127  integer :: i_well,jj,flagrein !test well mixed: modified by mc
128
129
130  !!! CHANGE: TEST OF THE WELL-MIXED CRITERION
131  !  integer,parameter :: iclass=10
132  !  real(kind=dp) :: zacc,tacc,t(iclass),th(0:iclass),hsave
133  !  logical dump
134  !  save zacc,tacc,t,th,hsave,dump
135  !!! CHANGE
136
137  integer :: idummy = -7
138  real    :: settling = 0.
139
140
141  !!! CHANGE: TEST OF THE WELL-MIXED CRITERION
142  !if (idummy.eq.-7) then
143  !open(550,file='WELLMIXEDTEST')
144  !do 17 i=0,iclass
145  !7      th(i)=real(i)/real(iclass)
146  !endif
147  !!! CHANGE
148
149
150  nstop=0
151  do i=1,nmixz
152    indzindicator(i)=.true.
153  end do
154
155
156  if (DRYDEP) then    ! reset probability for deposition
157    do ks=1,nspec
158      depoindicator(ks)=.true.
159      prob(ks)=0.
160    end do
161  endif
162
163  dxsave=0.           ! reset position displacements
164  dysave=0.           ! due to mean wind
165  dawsave=0.          ! and turbulent wind
166  dcwsave=0.
167
168  itimec=itime
169
170  nrand=int(ran3(idummy)*real(maxrand-1))+1
171
172
173  ! Determine whether lat/long grid or polarstereographic projection
174  ! is to be used
175  ! Furthermore, determine which nesting level to be used
176  !*****************************************************************
177
178  if (nglobal.and.(yt.gt.switchnorthg)) then
179    ngrid=-1
180  else if (sglobal.and.(yt.lt.switchsouthg)) then
181    ngrid=-2
182  else
183    ngrid=0
184    do j=numbnests,1,-1
185      if ((xt.gt.xln(j)+eps).and.(xt.lt.xrn(j)-eps).and. &
186           (yt.gt.yln(j)+eps).and.(yt.lt.yrn(j)-eps)) then
187        ngrid=j
188        goto 23
189      endif
190    end do
19123   continue
192  endif
193
194
195  !***************************
196  ! Interpolate necessary data
197  !***************************
198
199  if (abs(itime-memtime(1)).lt.abs(itime-memtime(2))) then
200    memindnext=1
201  else
202    memindnext=2
203  endif
204
205  ! Determine nested grid coordinates
206  !**********************************
207
208  if (ngrid.gt.0) then
209    xtn=(xt-xln(ngrid))*xresoln(ngrid)
210    ytn=(yt-yln(ngrid))*yresoln(ngrid)
211    ix=int(xtn)
212    jy=int(ytn)
213    nix=nint(xtn)
214    njy=nint(ytn)
215  else
216    ix=int(xt)
217    jy=int(yt)
218    nix=nint(xt)
219    njy=nint(yt)
220  endif
221  ixp=ix+1
222  jyp=jy+1
223
224
225  ! Compute maximum mixing height around particle position
226  !*******************************************************
227
228  h=0.
229  if (ngrid.le.0) then
230    do k=1,2
231      mind=memind(k) ! eso: compatibility with 3-field version
232      do j=jy,jyp
233        do i=ix,ixp
234          if (hmix(i,j,1,mind).gt.h) h=hmix(i,j,1,mind)
235        end do
236      end do
237    end do
238    tropop=tropopause(nix,njy,1,1)
239  else
240    do k=1,2
241      mind=memind(k)
242      do j=jy,jyp
243        do i=ix,ixp
244          if (hmixn(i,j,1,mind,ngrid).gt.h) h=hmixn(i,j,1,mind,ngrid)
245        end do
246      end do
247    end do
248    tropop=tropopausen(nix,njy,1,1,ngrid)
249  endif
250
251  zeta=zt/h
252
253
254
255  !*************************************************************
256  ! If particle is in the PBL, interpolate once and then make a
257  ! time loop until end of interval is reached
258  !*************************************************************
259
260  if (zeta.le.1.) then
261
262  ! BEGIN TIME LOOP
263  !================
264
265    loop=0
266100   loop=loop+1
267      if (method.eq.1) then
268        ldt=min(ldt,abs(lsynctime-itimec+itime))
269        itimec=itimec+ldt*ldirect
270      else
271        ldt=abs(lsynctime)
272        itimec=itime+lsynctime
273      endif
274      dt=real(ldt)
275
276      zeta=zt/h
277
278
279      if (loop.eq.1) then
280        if (ngrid.le.0) then
281          xts=real(xt)
282          yts=real(yt)
283          call interpol_all(itime,xts,yts,zt)
284        else
285          call interpol_all_nests(itime,xtn,ytn,zt)
286        endif
287
288      else
289
290
291  ! Determine the level below the current position for u,v,rho
292  !***********************************************************
293
294        do i=2,nz
295          if (height(i).gt.zt) then
296            indz=i-1
297            indzp=i
298            goto 6
299          endif
300        end do
3016       continue
302
303  ! If one of the levels necessary is not yet available,
304  ! calculate it
305  !*****************************************************
306
307        do i=indz,indzp
308          if (indzindicator(i)) then
309            if (ngrid.le.0) then
310              call interpol_misslev(i)
311            else
312              call interpol_misslev_nests(i)
313            endif
314          endif
315        end do
316      endif
317
318
319  ! Vertical interpolation of u,v,w,rho and drhodz
320  !***********************************************
321
322  ! Vertical distance to the level below and above current position
323  ! both in terms of (u,v) and (w) fields
324  !****************************************************************
325
326      dz=1./(height(indzp)-height(indz))
327      dz1=(zt-height(indz))*dz
328      dz2=(height(indzp)-zt)*dz
329
330      u=dz1*uprof(indzp)+dz2*uprof(indz)
331      v=dz1*vprof(indzp)+dz2*vprof(indz)
332      w=dz1*wprof(indzp)+dz2*wprof(indz)
333      rhoa=dz1*rhoprof(indzp)+dz2*rhoprof(indz)
334      rhograd=dz1*rhogradprof(indzp)+dz2*rhogradprof(indz)
335
336
337  ! Compute the turbulent disturbances
338  ! Determine the sigmas and the timescales
339  !****************************************
340
341      if (turbswitch) then
342        call hanna(zt)
343      else
344        call hanna1(zt)
345      endif
346
347
348  !*****************************************
349  ! Determine the new diffusivity velocities
350  !*****************************************
351
352  ! Horizontal components
353  !**********************
354
355      if (nrand+1.gt.maxrand) nrand=1
356      if (dt/tlu.lt..5) then
357        up=(1.-dt/tlu)*up+rannumb(nrand)*sigu*sqrt(2.*dt/tlu)
358      else
359        ru=exp(-dt/tlu)
360        up=ru*up+rannumb(nrand)*sigu*sqrt(1.-ru**2)
361      endif
362      if (dt/tlv.lt..5) then
363        vp=(1.-dt/tlv)*vp+rannumb(nrand+1)*sigv*sqrt(2.*dt/tlv)
364      else
365        rv=exp(-dt/tlv)
366        vp=rv*vp+rannumb(nrand+1)*sigv*sqrt(1.-rv**2)
367      endif
368      nrand=nrand+2
369
370
371      if (nrand+ifine.gt.maxrand) nrand=1
372      rhoaux=rhograd/rhoa
373      dtf=dt*fine
374
375      dtftlw=dtf/tlw
376
377  ! Loop over ifine short time steps for vertical component
378  !********************************************************
379
380      do i=1,ifine
381
382  ! Determine the drift velocity and density correction velocity
383  !*************************************************************
384
385        if (turbswitch) then
386          if (dtftlw.lt..5) then
387  !*************************************************************
388  !************** CBL options added by mc see routine cblf90 ***
389            if (cblflag.eq.1) then  !modified by mc
390              if (-h/ol.gt.5) then  !modified by mc
391              !if (ol.lt.0.) then   !modified by mc 
392              !if (ol.gt.0.) then   !modified by mc : for test
393                  !print  *,zt,wp,ath,bth,tlw,dtf,'prima'
394                  flagrein=0
395                  nrand=nrand+1
396                  old_wp_buf=wp
397                  call cbl(wp,zt,ust,wst,h,rhoa,rhograd,sigw,dsigwdz,tlw,ptot_lhh,Q_lhh,phi_lhh,ath,bth,ol,flagrein) !inside the routine for inverse time
398                  wp=(wp+ath*dtf+bth*rannumb(nrand)*sqrt(dtf))*real(icbt)
399                  ! wp=(wp+ath*dtf+bth*gasdev2(mydum)*sqrt(dtf))*real(icbt)
400                  delz=wp*dtf
401                  if (flagrein.eq.1) then
402                      call re_initialize_particle(zt,ust,wst,h,sigw,old_wp_buf,nrand,ol)
403                      wp=old_wp_buf
404                      delz=wp*dtf
405                      nan_count=nan_count+1
406                  end if
407                  !print  *,zt,wp,ath,bth,tlw,dtf,rannumb(nrand+i),icbt
408                  !pause                 
409              else
410                  nrand=nrand+1
411                  old_wp_buf=wp
412                  ath=-wp/tlw+sigw*dsigwdz+wp*wp/sigw*dsigwdz+sigw*sigw/rhoa*rhograd  !1-note for inverse time should be -wp/tlw*ldirect+... calculated for wp=-wp
413                                                                                      !2-but since ldirect =-1 for inverse time and this must be calculated for (-wp) and
414                                                                                      !3-the gaussian pdf is symmetric (i.e. pdf(w)=pdf(-w) ldirect can be discarded
415                  bth=sigw*rannumb(nrand)*sqrt(2.*dtftlw)
416                  wp=(wp+ath*dtf+bth)*real(icbt) 
417                  delz=wp*dtf
418                  del_test=(1.-wp)/wp !catch infinity value
419                  if (isnan(wp).or.isnan(del_test)) then
420                      nrand=nrand+1                     
421                      wp=sigw*rannumb(nrand)
422                      delz=wp*dtf
423                      nan_count2=nan_count2+1
424                      !print *,'NaN coutner equal to:', nan_count,'reduce ifine if this number became a non-negligible fraction of the particle number'
425                  end if 
426              end if
427  !******************** END CBL option *******************************           
428  !*******************************************************************           
429            else
430                 wp=((1.-dtftlw)*wp+rannumb(nrand+i)*sqrt(2.*dtftlw) &
431                 +dtf*(dsigwdz+rhoaux*sigw))*real(icbt)
432                 delz=wp*sigw*dtf
433            end if
434          else
435            rw=exp(-dtftlw)
436            wp=(rw*wp+rannumb(nrand+i)*sqrt(1.-rw**2) &
437                 +tlw*(1.-rw)*(dsigwdz+rhoaux*sigw))*real(icbt)
438            delz=wp*sigw*dtf
439          endif
440         
441        else
442          rw=exp(-dtftlw)
443          wp=(rw*wp+rannumb(nrand+i)*sqrt(1.-rw**2)*sigw &
444               +tlw*(1.-rw)*(dsigw2dz+rhoaux*sigw**2))*real(icbt)
445          delz=wp*dtf
446        endif
447
448  !****************************************************
449  ! Compute turbulent vertical displacement of particle
450  !****************************************************
451
452        if (abs(delz).gt.h) delz=mod(delz,h)
453
454  ! Determine if particle transfers to a "forbidden state" below the ground
455  ! or above the mixing height
456  !************************************************************************
457
458        if (delz.lt.-zt) then         ! reflection at ground
459          icbt=-1
460          zt=-zt-delz
461        else if (delz.gt.(h-zt)) then ! reflection at h
462          icbt=-1
463          zt=-zt-delz+2.*h
464        else                         ! no reflection
465          icbt=1
466          zt=zt+delz
467        endif
468
469        if (i.ne.ifine) then
470          zeta=zt/h
471          call hanna_short(zt)
472        endif
473
474      end do
475      if (cblflag.ne.1) nrand=nrand+i
476
477  ! Determine time step for next integration
478  !*****************************************
479
480      if (turbswitch) then
481        ldt=int(min(tlw,h/max(2.*abs(wp*sigw),1.e-5), &
482             0.5/abs(dsigwdz))*ctl)
483      else
484        ldt=int(min(tlw,h/max(2.*abs(wp),1.e-5))*ctl)
485      endif
486      ldt=max(ldt,mintime)
487
488
489  ! If particle represents only a single species, add gravitational settling
490  ! velocity. The settling velocity is zero for gases, or if particle
491  ! represents more than one species
492  !*************************************************************************
493
494      if (mdomainfill.eq.0) then
495        do nsp=1,nspec
496          if (xmass(nrelpoint,nsp).gt.eps2) goto 887
497        end do
498887     nsp=min(nsp,nspec)
499!!$        if (density(nsp).gt.0.) &
500!!$             call get_settling(itime,xts,yts,zt,nsp,settling)    !old
501        if (density(nsp).gt.0.) &
502             call get_settling(itime,real(xt),real(yt),zt,nsp,settling)  !bugfix
503        w=w+settling
504      endif
505
506  ! Horizontal displacements during time step dt are small real values compared
507  ! to the position; adding the two, would result in large numerical errors.
508  ! Thus, displacements are accumulated during lsynctime and are added to the
509  ! position at the end
510  !****************************************************************************
511
512      dxsave=dxsave+u*dt
513      dysave=dysave+v*dt
514      dawsave=dawsave+up*dt
515      dcwsave=dcwsave+vp*dt
516      zt=zt+w*dt*real(ldirect)
517
518      ! HSO/AL: Particle managed to go over highest level -> interpolation error in goto 700
519      !          alias interpol_wind (division by zero)
520      if (zt.ge.height(nz)) zt=height(nz)-100.*eps
521
522      if (zt.gt.h) then
523        if (itimec.eq.itime+lsynctime) goto 99
524        goto 700    ! complete the current interval above PBL
525      endif
526
527
528  !!! CHANGE: TEST OF THE WELL-MIXED CRITERION
529  !!! These lines may be switched on to test the well-mixed criterion
530  !if (zt.le.h) then
531  !  zacc=zacc+zt/h*dt
532  !  hsave=hsave+h*dt
533  !  tacc=tacc+dt
534  !  do 67 i=1,iclass
535  !    if ((zt/h.gt.th(i-1)).and.(zt/h.le.th(i)))
536  !    +    t(i)=t(i)+dt
537  !7        continue
538  !endif
539  !if ((mod(itime,10800).eq.0).and.dump) then
540  ! dump=.false.
541  ! write(550,'(i6,12f10.3)') itime,hsave/tacc,zacc/tacc,
542  !    + (t(i)/tacc*real(iclass),i=1,iclass)
543  !  zacc=0.
544  !  tacc=0.
545  !  do 68 i=1,iclass
546  !8        t(i)=0.
547  !  hsave=0.
548  !endif
549  !if (mod(itime,10800).ne.0) dump=.true.
550  !!! CHANGE
551     
552  ! Determine probability of deposition
553  !************************************
554
555      if ((DRYDEP).and.(zt.lt.2.*href)) then
556        do ks=1,nspec
557          if (DRYDEPSPEC(ks)) then
558            if (depoindicator(ks)) then
559              if (ngrid.le.0) then
560                call interpol_vdep(ks,vdepo(ks))
561              else
562                call interpol_vdep_nests(ks,vdepo(ks))
563              endif
564            endif
565  ! correction by Petra Seibert, 10 April 2001
566  !   this formulation means that prob(n) = 1 - f(0)*...*f(n)
567  !   where f(n) is the exponential term
568               prob(ks)=1.+(prob(ks)-1.)* &
569                    exp(-vdepo(ks)*abs(dt)/(2.*href))
570          endif
571        end do
572      endif
573
574      if (zt.lt.0.) zt=min(h-eps2,-1.*zt)    ! if particle below ground -> reflection
575
576      if (itimec.eq.(itime+lsynctime)) then
577        usig=0.5*(usigprof(indzp)+usigprof(indz))
578        vsig=0.5*(vsigprof(indzp)+vsigprof(indz))
579        wsig=0.5*(wsigprof(indzp)+wsigprof(indz))
580        goto 99  ! finished
581      endif
582      goto 100
583
584  ! END TIME LOOP
585  !==============
586
587
588  endif
589
590
591
592  !**********************************************************
593  ! For all particles that are outside the PBL, make a single
594  ! time step. Only horizontal turbulent disturbances are
595  ! calculated. Vertical disturbances are reset.
596  !**********************************************************
597
598
599  ! Interpolate the wind
600  !*********************
601
602700   continue
603  if (ngrid.le.0) then
604    xts=real(xt)
605    yts=real(yt)
606    call interpol_wind(itime,xts,yts,zt)
607  else
608    call interpol_wind_nests(itime,xtn,ytn,zt)
609  endif
610
611
612  ! Compute everything for above the PBL
613
614  ! Assume constant, uncorrelated, turbulent perturbations
615  ! In the stratosphere, use a small vertical diffusivity d_strat,
616  ! in the troposphere, use a larger horizontal diffusivity d_trop.
617  ! Turbulent velocity scales are determined based on sqrt(d_trop/dt)
618  !******************************************************************
619
620  ldt=abs(lsynctime-itimec+itime)
621  dt=real(ldt)
622
623  if (zt.lt.tropop) then  ! in the troposphere
624    uxscale=sqrt(2.*d_trop/dt)
625    if (nrand+1.gt.maxrand) nrand=1
626    ux=rannumb(nrand)*uxscale
627    vy=rannumb(nrand+1)*uxscale
628    nrand=nrand+2
629    wp=0.
630  else if (zt.lt.tropop+1000.) then     ! just above the tropopause: make transition
631    weight=(zt-tropop)/1000.
632    uxscale=sqrt(2.*d_trop/dt*(1.-weight))
633    if (nrand+2.gt.maxrand) nrand=1
634    ux=rannumb(nrand)*uxscale
635    vy=rannumb(nrand+1)*uxscale
636    wpscale=sqrt(2.*d_strat/dt*weight)
637    wp=rannumb(nrand+2)*wpscale+d_strat/1000.
638    nrand=nrand+3
639  else                 ! in the stratosphere
640    if (nrand.gt.maxrand) nrand=1
641    ux=0.
642    vy=0.
643    wpscale=sqrt(2.*d_strat/dt)
644    wp=rannumb(nrand)*wpscale
645    nrand=nrand+1
646  endif
647
648
649  ! If particle represents only a single species, add gravitational settling
650  ! velocity. The settling velocity is zero for gases
651  !*************************************************************************
652
653
654
655    if (mdomainfill.eq.0) then
656      do nsp=1,nspec
657        if (xmass(nrelpoint,nsp).gt.eps2) goto 888
658      end do
659888   nsp=min(nsp,nspec)
660!!$      if (density(nsp).gt.0.) &
661!!$           call get_settling(itime,xts,yts,zt,nsp,settling)    !old
662      if (density(nsp).gt.0.) &
663           call get_settling(itime,real(xt),real(yt),zt,nsp,settling)  !bugfix
664      w=w+settling
665    endif
666
667  ! Calculate position at time step itime+lsynctime
668  !************************************************
669
670  dxsave=dxsave+(u+ux)*dt
671  dysave=dysave+(v+vy)*dt
672  zt=zt+(w+wp)*dt*real(ldirect)
673  if (zt.lt.0.) zt=min(h-eps2,-1.*zt)    ! if particle below ground -> reflection
674
67599   continue
676
677
678
679  !****************************************************************
680  ! Add mesoscale random disturbances
681  ! This is done only once for the whole lsynctime interval to save
682  ! computation time
683  !****************************************************************
684
685
686  ! Mesoscale wind velocity fluctuations are obtained by scaling
687  ! with the standard deviation of the grid-scale winds surrounding
688  ! the particle location, multiplied by a factor turbmesoscale.
689  ! The autocorrelation time constant is taken as half the
690  ! time interval between wind fields
691  !****************************************************************
692
693  r=exp(-2.*real(abs(lsynctime))/real(lwindinterv))
694  rs=sqrt(1.-r**2)
695  if (nrand+2.gt.maxrand) nrand=1
696  usigold=r*usigold+rs*rannumb(nrand)*usig*turbmesoscale
697  vsigold=r*vsigold+rs*rannumb(nrand+1)*vsig*turbmesoscale
698  wsigold=r*wsigold+rs*rannumb(nrand+2)*wsig*turbmesoscale
699
700  dxsave=dxsave+usigold*real(lsynctime)
701  dysave=dysave+vsigold*real(lsynctime)
702
703  zt=zt+wsigold*real(lsynctime)
704  if (zt.lt.0.) zt=-1.*zt    ! if particle below ground -> refletion
705
706  !*************************************************************
707  ! Transform along and cross wind components to xy coordinates,
708  ! add them to u and v, transform u,v to grid units/second
709  ! and calculate new position
710  !*************************************************************
711
712  call windalign(dxsave,dysave,dawsave,dcwsave,ux,vy)
713  dxsave=dxsave+ux   ! comment by mc: comment this line to stop the particles horizontally for test reasons
714  dysave=dysave+vy
715  if (ngrid.ge.0) then
716    cosfact=dxconst/cos((yt*dy+ylat0)*pi180)
717    xt=xt+real(dxsave*cosfact*real(ldirect),kind=dp)
718    yt=yt+real(dysave*dyconst*real(ldirect),kind=dp)
719  else if (ngrid.eq.-1) then      ! around north pole
720    xlon=xlon0+xt*dx                                !comment by mc: compute old particle position
721    ylat=ylat0+yt*dy
722    call cll2xy(northpolemap,ylat,xlon,xpol,ypol)   !convert old particle position in polar stereographic
723    gridsize=1000.*cgszll(northpolemap,ylat,xlon)   !calculate size in m of grid element in polar stereographic coordinate
724    dxsave=dxsave/gridsize                          !increment from meter to grdi unit
725    dysave=dysave/gridsize
726    xpol=xpol+dxsave*real(ldirect)                  !position in grid unit polar stereographic
727    ypol=ypol+dysave*real(ldirect)
728    call cxy2ll(northpolemap,xpol,ypol,ylat,xlon)  !convert to lat long coordinate
729    xt=(xlon-xlon0)/dx                             !convert to grid units in lat long coordinate, comment by mc
730    yt=(ylat-ylat0)/dy
731  else if (ngrid.eq.-2) then    ! around south pole
732    xlon=xlon0+xt*dx
733    ylat=ylat0+yt*dy
734    call cll2xy(southpolemap,ylat,xlon,xpol,ypol)
735    gridsize=1000.*cgszll(southpolemap,ylat,xlon)
736    dxsave=dxsave/gridsize
737    dysave=dysave/gridsize
738    xpol=xpol+dxsave*real(ldirect)
739    ypol=ypol+dysave*real(ldirect)
740    call cxy2ll(southpolemap,xpol,ypol,ylat,xlon)
741    xt=(xlon-xlon0)/dx
742    yt=(ylat-ylat0)/dy
743  endif
744
745
746  ! If global data are available, use cyclic boundary condition
747  !************************************************************
748
749  if (xglobal) then
750    if (xt.ge.real(nxmin1)) xt=xt-real(nxmin1)
751    if (xt.lt.0.) xt=xt+real(nxmin1)
752    if (xt.le.eps) xt=eps
753    if (abs(xt-real(nxmin1)).le.eps) xt=real(nxmin1)-eps
754  endif
755
756  ! HSO/AL: Prevent particles from disappearing at the pole
757  !******************************************************************
758
759  if ( yt.lt.0. ) then
760    xt=mod(xt+180.,360.)
761    yt=-yt
762  else if ( yt.gt.real(nymin1) ) then
763    xt=mod(xt+180.,360.)
764    yt=2*real(nymin1)-yt
765  endif
766
767  ! Check position: If trajectory outside model domain, terminate it
768  !*****************************************************************
769
770  if ((xt.lt.0.).or.(xt.ge.real(nxmin1)).or.(yt.lt.0.).or. &
771       (yt.gt.real(nymin1))) then
772    nstop=3
773    return
774  endif
775
776  ! If particle above highest model level, set it back into the domain
777  !*******************************************************************
778
779  if (zt.ge.height(nz)) zt=height(nz)-100.*eps
780
781
782  !************************************************************************
783  ! Now we could finish, as this was done in FLEXPART versions up to 4.0.
784  ! However, truncation errors of the advection can be significantly
785  ! reduced by doing one iteration of the Petterssen scheme, if this is
786  ! possible.
787  ! Note that this is applied only to the grid-scale winds, not to
788  ! the turbulent winds.
789  !************************************************************************
790
791  ! The Petterssen scheme can only applied with long time steps (only then u
792  ! is the "old" wind as required by the scheme); otherwise do nothing
793  !*************************************************************************
794
795  if (ldt.ne.abs(lsynctime)) return
796
797  ! The Petterssen scheme can only be applied if the ending time of the time step
798  ! (itime+ldt*ldirect) is still between the two wind fields held in memory;
799  ! otherwise do nothing
800  !******************************************************************************
801
802  if (abs(itime+ldt*ldirect).gt.abs(memtime(2))) return
803
804  ! Apply it also only if starting and ending point of current time step are on
805  ! the same grid; otherwise do nothing
806  !*****************************************************************************
807  if (nglobal.and.(yt.gt.switchnorthg)) then
808    ngr=-1
809  else if (sglobal.and.(yt.lt.switchsouthg)) then
810    ngr=-2
811  else
812    ngr=0
813    do j=numbnests,1,-1
814      if ((xt.gt.xln(j)+eps).and.(xt.lt.xrn(j)-eps).and. &
815           (yt.gt.yln(j)+eps).and.(yt.lt.yrn(j)-eps)) then
816        ngr=j
817        goto 43
818      endif
819    end do
82043   continue
821  endif
822
823  if (ngr.ne.ngrid) return
824
825  ! Determine nested grid coordinates
826  !**********************************
827
828  if (ngrid.gt.0) then
829    xtn=(xt-xln(ngrid))*xresoln(ngrid)
830    ytn=(yt-yln(ngrid))*yresoln(ngrid)
831    ix=int(xtn)
832    jy=int(ytn)
833  else
834    ix=int(xt)
835    jy=int(yt)
836  endif
837  ixp=ix+1
838  jyp=jy+1
839
840
841  ! Memorize the old wind
842  !**********************
843
844  uold=u
845  vold=v
846  wold=w
847
848  ! Interpolate wind at new position and time
849  !******************************************
850
851  if (ngrid.le.0) then
852    xts=real(xt)
853    yts=real(yt)
854    call interpol_wind_short(itime+ldt*ldirect,xts,yts,zt)
855  else
856    call interpol_wind_short_nests(itime+ldt*ldirect,xtn,ytn,zt)
857  endif
858
859  if (mdomainfill.eq.0) then
860    do nsp=1,nspec
861      if (xmass(nrelpoint,nsp).gt.eps2) goto 889
862    end do
863889   nsp=min(nsp,nspec)
864!!$    if (density(nsp).gt.0.) &
865!!$         call get_settling(itime+ldt,xts,yts,zt,nsp,settling)    !old
866    if (density(nsp).gt.0.) &
867         call get_settling(itime+ldt,real(xt),real(yt),zt,nsp,settling)  !bugfix
868    w=w+settling
869  endif
870
871
872  ! Determine the difference vector between new and old wind
873  ! (use half of it to correct position according to Petterssen)
874  !*************************************************************
875
876  u=(u-uold)/2.
877  v=(v-vold)/2.
878  w=(w-wold)/2.
879
880
881  ! Finally, correct the old position
882  !**********************************
883
884  zt=zt+w*real(ldt*ldirect)
885  if (zt.lt.0.) zt=min(h-eps2,-1.*zt)    ! if particle below ground -> reflection
886  if (ngrid.ge.0) then
887    cosfact=dxconst/cos((yt*dy+ylat0)*pi180)
888    xt=xt+real(u*cosfact*real(ldt*ldirect),kind=dp)
889    yt=yt+real(v*dyconst*real(ldt*ldirect),kind=dp)
890  else if (ngrid.eq.-1) then      ! around north pole
891    xlon=xlon0+xt*dx
892    ylat=ylat0+yt*dy
893    call cll2xy(northpolemap,ylat,xlon,xpol,ypol)
894    gridsize=1000.*cgszll(northpolemap,ylat,xlon)
895    u=u/gridsize
896    v=v/gridsize
897    xpol=xpol+u*real(ldt*ldirect)
898    ypol=ypol+v*real(ldt*ldirect)
899    call cxy2ll(northpolemap,xpol,ypol,ylat,xlon)
900    xt=(xlon-xlon0)/dx
901    yt=(ylat-ylat0)/dy
902  else if (ngrid.eq.-2) then    ! around south pole
903    xlon=xlon0+xt*dx
904    ylat=ylat0+yt*dy
905    call cll2xy(southpolemap,ylat,xlon,xpol,ypol)
906    gridsize=1000.*cgszll(southpolemap,ylat,xlon)
907    u=u/gridsize
908    v=v/gridsize
909    xpol=xpol+u*real(ldt*ldirect)
910    ypol=ypol+v*real(ldt*ldirect)
911    call cxy2ll(southpolemap,xpol,ypol,ylat,xlon)
912    xt=(xlon-xlon0)/dx
913    yt=(ylat-ylat0)/dy
914  endif
915
916  ! If global data are available, use cyclic boundary condition
917  !************************************************************
918
919  if (xglobal) then
920    if (xt.ge.real(nxmin1)) xt=xt-real(nxmin1)
921    if (xt.lt.0.) xt=xt+real(nxmin1)
922    if (xt.le.eps) xt=eps
923    if (abs(xt-real(nxmin1)).le.eps) xt=real(nxmin1)-eps
924  endif
925
926  ! HSO/AL: Prevent particles from disappearing at the pole
927  !******************************************************************
928
929  if ( yt.lt.0. ) then
930    xt=mod(xt+180.,360.)
931    yt=-yt
932  else if ( yt.gt.real(nymin1) ) then
933    xt=mod(xt+180.,360.)
934    yt=2*real(nymin1)-yt
935  endif
936
937  ! Check position: If trajectory outside model domain, terminate it
938  !*****************************************************************
939
940  if ((xt.lt.0.).or.(xt.ge.real(nxmin1)).or.(yt.lt.0.).or. &
941       (yt.gt.real(nymin1))) then
942    nstop=3
943    return
944  endif
945
946  ! If particle above highest model level, set it back into the domain
947  !*******************************************************************
948
949  if (zt.ge.height(nz)) zt=height(nz)-100.*eps
950
951
952end subroutine advance
953
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG