source: flexpart.git/src/advance.f90 @ 4c64400

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

Fixed bug introduced by the MQUASILAG quick fix (18adf6049d9d47356934a37eb7784506f795e220)

  • Property mode set to 100644
File size: 33.5 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! ESO 05.2015  Changed this to fix MQUASILAG option, where nrelpoint is
496!              particle number and thus xmass array goes out of bounds
497!        do nsp=1,nspec
498!           if (xmass(nrelpoint,nsp).gt.eps2) goto 887
499!         end do
500! 887     nsp=min(nsp,nspec)
501        if (nspec.eq.1.and.density(1).gt.0.) then
502          call get_settling(itime,real(xt),real(yt),zt,nspec,settling)  !bugfix
503        end if
504        w=w+settling
505      endif
506
507  ! Horizontal displacements during time step dt are small real values compared
508  ! to the position; adding the two, would result in large numerical errors.
509  ! Thus, displacements are accumulated during lsynctime and are added to the
510  ! position at the end
511  !****************************************************************************
512
513      dxsave=dxsave+u*dt
514      dysave=dysave+v*dt
515      dawsave=dawsave+up*dt
516      dcwsave=dcwsave+vp*dt
517      zt=zt+w*dt*real(ldirect)
518
519      ! HSO/AL: Particle managed to go over highest level -> interpolation error in goto 700
520      !          alias interpol_wind (division by zero)
521      if (zt.ge.height(nz)) zt=height(nz)-100.*eps
522
523      if (zt.gt.h) then
524        if (itimec.eq.itime+lsynctime) goto 99
525        goto 700    ! complete the current interval above PBL
526      endif
527
528
529  !!! CHANGE: TEST OF THE WELL-MIXED CRITERION
530  !!! These lines may be switched on to test the well-mixed criterion
531  !if (zt.le.h) then
532  !  zacc=zacc+zt/h*dt
533  !  hsave=hsave+h*dt
534  !  tacc=tacc+dt
535  !  do 67 i=1,iclass
536  !    if ((zt/h.gt.th(i-1)).and.(zt/h.le.th(i)))
537  !    +    t(i)=t(i)+dt
538  !7        continue
539  !endif
540  !if ((mod(itime,10800).eq.0).and.dump) then
541  ! dump=.false.
542  ! write(550,'(i6,12f10.3)') itime,hsave/tacc,zacc/tacc,
543  !    + (t(i)/tacc*real(iclass),i=1,iclass)
544  !  zacc=0.
545  !  tacc=0.
546  !  do 68 i=1,iclass
547  !8        t(i)=0.
548  !  hsave=0.
549  !endif
550  !if (mod(itime,10800).ne.0) dump=.true.
551  !!! CHANGE
552     
553  ! Determine probability of deposition
554  !************************************
555
556      if ((DRYDEP).and.(zt.lt.2.*href)) then
557        do ks=1,nspec
558          if (DRYDEPSPEC(ks)) then
559            if (depoindicator(ks)) then
560              if (ngrid.le.0) then
561                call interpol_vdep(ks,vdepo(ks))
562              else
563                call interpol_vdep_nests(ks,vdepo(ks))
564              endif
565            endif
566  ! correction by Petra Seibert, 10 April 2001
567  !   this formulation means that prob(n) = 1 - f(0)*...*f(n)
568  !   where f(n) is the exponential term
569               prob(ks)=1.+(prob(ks)-1.)* &
570                    exp(-vdepo(ks)*abs(dt)/(2.*href))
571          endif
572        end do
573      endif
574
575      if (zt.lt.0.) zt=min(h-eps2,-1.*zt)    ! if particle below ground -> reflection
576
577      if (itimec.eq.(itime+lsynctime)) then
578        usig=0.5*(usigprof(indzp)+usigprof(indz))
579        vsig=0.5*(vsigprof(indzp)+vsigprof(indz))
580        wsig=0.5*(wsigprof(indzp)+wsigprof(indz))
581        goto 99  ! finished
582      endif
583      goto 100
584
585  ! END TIME LOOP
586  !==============
587
588
589  endif
590
591
592
593  !**********************************************************
594  ! For all particles that are outside the PBL, make a single
595  ! time step. Only horizontal turbulent disturbances are
596  ! calculated. Vertical disturbances are reset.
597  !**********************************************************
598
599
600  ! Interpolate the wind
601  !*********************
602
603700   continue
604  if (ngrid.le.0) then
605    xts=real(xt)
606    yts=real(yt)
607    call interpol_wind(itime,xts,yts,zt)
608  else
609    call interpol_wind_nests(itime,xtn,ytn,zt)
610  endif
611
612
613  ! Compute everything for above the PBL
614
615  ! Assume constant, uncorrelated, turbulent perturbations
616  ! In the stratosphere, use a small vertical diffusivity d_strat,
617  ! in the troposphere, use a larger horizontal diffusivity d_trop.
618  ! Turbulent velocity scales are determined based on sqrt(d_trop/dt)
619  !******************************************************************
620
621  ldt=abs(lsynctime-itimec+itime)
622  dt=real(ldt)
623
624  if (zt.lt.tropop) then  ! in the troposphere
625    uxscale=sqrt(2.*d_trop/dt)
626    if (nrand+1.gt.maxrand) nrand=1
627    ux=rannumb(nrand)*uxscale
628    vy=rannumb(nrand+1)*uxscale
629    nrand=nrand+2
630    wp=0.
631  else if (zt.lt.tropop+1000.) then     ! just above the tropopause: make transition
632    weight=(zt-tropop)/1000.
633    uxscale=sqrt(2.*d_trop/dt*(1.-weight))
634    if (nrand+2.gt.maxrand) nrand=1
635    ux=rannumb(nrand)*uxscale
636    vy=rannumb(nrand+1)*uxscale
637    wpscale=sqrt(2.*d_strat/dt*weight)
638    wp=rannumb(nrand+2)*wpscale+d_strat/1000.
639    nrand=nrand+3
640  else                 ! in the stratosphere
641    if (nrand.gt.maxrand) nrand=1
642    ux=0.
643    vy=0.
644    wpscale=sqrt(2.*d_strat/dt)
645    wp=rannumb(nrand)*wpscale
646    nrand=nrand+1
647  endif
648
649
650  ! If particle represents only a single species, add gravitational settling
651  ! velocity. The settling velocity is zero for gases
652  !*************************************************************************
653
654
655
656    if (mdomainfill.eq.0) then
657! ESO 05.2015  Changed this to fix MQUASILAG option, where nrelpoint is
658!              particle number and thus xmass array goes out of bounds
659
660!      do nsp=1,nspec
661!         if (xmass(nrelpoint,nsp).gt.eps2) goto 888
662!       end do
663! 888   nsp=min(nsp,nspec)
664!        if (density(nsp).gt.0.) then
665      if (nspec.eq.1.and.density(1).gt.0.) then
666        call get_settling(itime,real(xt),real(yt),zt,nspec,settling)  !bugfix
667      end if
668      w=w+settling
669    endif
670
671  ! Calculate position at time step itime+lsynctime
672  !************************************************
673
674  dxsave=dxsave+(u+ux)*dt
675  dysave=dysave+(v+vy)*dt
676  zt=zt+(w+wp)*dt*real(ldirect)
677  if (zt.lt.0.) zt=min(h-eps2,-1.*zt)    ! if particle below ground -> reflection
678
67999   continue
680
681
682
683  !****************************************************************
684  ! Add mesoscale random disturbances
685  ! This is done only once for the whole lsynctime interval to save
686  ! computation time
687  !****************************************************************
688
689
690  ! Mesoscale wind velocity fluctuations are obtained by scaling
691  ! with the standard deviation of the grid-scale winds surrounding
692  ! the particle location, multiplied by a factor turbmesoscale.
693  ! The autocorrelation time constant is taken as half the
694  ! time interval between wind fields
695  !****************************************************************
696
697  r=exp(-2.*real(abs(lsynctime))/real(lwindinterv))
698  rs=sqrt(1.-r**2)
699  if (nrand+2.gt.maxrand) nrand=1
700  usigold=r*usigold+rs*rannumb(nrand)*usig*turbmesoscale
701  vsigold=r*vsigold+rs*rannumb(nrand+1)*vsig*turbmesoscale
702  wsigold=r*wsigold+rs*rannumb(nrand+2)*wsig*turbmesoscale
703
704  dxsave=dxsave+usigold*real(lsynctime)
705  dysave=dysave+vsigold*real(lsynctime)
706
707  zt=zt+wsigold*real(lsynctime)
708  if (zt.lt.0.) zt=-1.*zt    ! if particle below ground -> refletion
709
710  !*************************************************************
711  ! Transform along and cross wind components to xy coordinates,
712  ! add them to u and v, transform u,v to grid units/second
713  ! and calculate new position
714  !*************************************************************
715
716  call windalign(dxsave,dysave,dawsave,dcwsave,ux,vy)
717  dxsave=dxsave+ux   ! comment by mc: comment this line to stop the particles horizontally for test reasons
718  dysave=dysave+vy
719  if (ngrid.ge.0) then
720    cosfact=dxconst/cos((yt*dy+ylat0)*pi180)
721    xt=xt+real(dxsave*cosfact*real(ldirect),kind=dp)
722    yt=yt+real(dysave*dyconst*real(ldirect),kind=dp)
723  else if (ngrid.eq.-1) then      ! around north pole
724    xlon=xlon0+xt*dx                                !comment by mc: compute old particle position
725    ylat=ylat0+yt*dy
726    call cll2xy(northpolemap,ylat,xlon,xpol,ypol)   !convert old particle position in polar stereographic
727    gridsize=1000.*cgszll(northpolemap,ylat,xlon)   !calculate size in m of grid element in polar stereographic coordinate
728    dxsave=dxsave/gridsize                          !increment from meter to grdi unit
729    dysave=dysave/gridsize
730    xpol=xpol+dxsave*real(ldirect)                  !position in grid unit polar stereographic
731    ypol=ypol+dysave*real(ldirect)
732    call cxy2ll(northpolemap,xpol,ypol,ylat,xlon)  !convert to lat long coordinate
733    xt=(xlon-xlon0)/dx                             !convert to grid units in lat long coordinate, comment by mc
734    yt=(ylat-ylat0)/dy
735  else if (ngrid.eq.-2) then    ! around south pole
736    xlon=xlon0+xt*dx
737    ylat=ylat0+yt*dy
738    call cll2xy(southpolemap,ylat,xlon,xpol,ypol)
739    gridsize=1000.*cgszll(southpolemap,ylat,xlon)
740    dxsave=dxsave/gridsize
741    dysave=dysave/gridsize
742    xpol=xpol+dxsave*real(ldirect)
743    ypol=ypol+dysave*real(ldirect)
744    call cxy2ll(southpolemap,xpol,ypol,ylat,xlon)
745    xt=(xlon-xlon0)/dx
746    yt=(ylat-ylat0)/dy
747  endif
748
749
750  ! If global data are available, use cyclic boundary condition
751  !************************************************************
752
753  if (xglobal) then
754    if (xt.ge.real(nxmin1)) xt=xt-real(nxmin1)
755    if (xt.lt.0.) xt=xt+real(nxmin1)
756    if (xt.le.eps) xt=eps
757    if (abs(xt-real(nxmin1)).le.eps) xt=real(nxmin1)-eps
758  endif
759
760  ! HSO/AL: Prevent particles from disappearing at the pole
761  !******************************************************************
762
763  if ( yt.lt.0. ) then
764    xt=mod(xt+180.,360.)
765    yt=-yt
766  else if ( yt.gt.real(nymin1) ) then
767    xt=mod(xt+180.,360.)
768    yt=2*real(nymin1)-yt
769  endif
770
771  ! Check position: If trajectory outside model domain, terminate it
772  !*****************************************************************
773
774  if ((xt.lt.0.).or.(xt.ge.real(nxmin1)).or.(yt.lt.0.).or. &
775       (yt.gt.real(nymin1))) then
776    nstop=3
777    return
778  endif
779
780  ! If particle above highest model level, set it back into the domain
781  !*******************************************************************
782
783  if (zt.ge.height(nz)) zt=height(nz)-100.*eps
784
785
786  !************************************************************************
787  ! Now we could finish, as this was done in FLEXPART versions up to 4.0.
788  ! However, truncation errors of the advection can be significantly
789  ! reduced by doing one iteration of the Petterssen scheme, if this is
790  ! possible.
791  ! Note that this is applied only to the grid-scale winds, not to
792  ! the turbulent winds.
793  !************************************************************************
794
795  ! The Petterssen scheme can only applied with long time steps (only then u
796  ! is the "old" wind as required by the scheme); otherwise do nothing
797  !*************************************************************************
798
799  if (ldt.ne.abs(lsynctime)) return
800
801  ! The Petterssen scheme can only be applied if the ending time of the time step
802  ! (itime+ldt*ldirect) is still between the two wind fields held in memory;
803  ! otherwise do nothing
804  !******************************************************************************
805
806  if (abs(itime+ldt*ldirect).gt.abs(memtime(2))) return
807
808  ! Apply it also only if starting and ending point of current time step are on
809  ! the same grid; otherwise do nothing
810  !*****************************************************************************
811  if (nglobal.and.(yt.gt.switchnorthg)) then
812    ngr=-1
813  else if (sglobal.and.(yt.lt.switchsouthg)) then
814    ngr=-2
815  else
816    ngr=0
817    do j=numbnests,1,-1
818      if ((xt.gt.xln(j)+eps).and.(xt.lt.xrn(j)-eps).and. &
819           (yt.gt.yln(j)+eps).and.(yt.lt.yrn(j)-eps)) then
820        ngr=j
821        goto 43
822      endif
823    end do
82443   continue
825  endif
826
827  if (ngr.ne.ngrid) return
828
829  ! Determine nested grid coordinates
830  !**********************************
831
832  if (ngrid.gt.0) then
833    xtn=(xt-xln(ngrid))*xresoln(ngrid)
834    ytn=(yt-yln(ngrid))*yresoln(ngrid)
835    ix=int(xtn)
836    jy=int(ytn)
837  else
838    ix=int(xt)
839    jy=int(yt)
840  endif
841  ixp=ix+1
842  jyp=jy+1
843
844
845  ! Memorize the old wind
846  !**********************
847
848  uold=u
849  vold=v
850  wold=w
851
852  ! Interpolate wind at new position and time
853  !******************************************
854
855  if (ngrid.le.0) then
856    xts=real(xt)
857    yts=real(yt)
858    call interpol_wind_short(itime+ldt*ldirect,xts,yts,zt)
859  else
860    call interpol_wind_short_nests(itime+ldt*ldirect,xtn,ytn,zt)
861  endif
862
863  if (mdomainfill.eq.0) then
864! ESO 05.2015  Changed this to fix MQUASILAG option, where nrelpoint is
865!              particle number and thus xmass array goes out of bounds
866!    do nsp=1,nspec
867!       if (xmass(nrelpoint,nsp).gt.eps2) goto 889
868!     end do
869! 889   nsp=min(nsp,nspec)
870!      if (density(nsp).gt.0.) then
871    if (nspec.eq.1.and.density(1).gt.0.) then
872      call get_settling(itime+ldt,real(xt),real(yt),zt,nspec,settling)  !bugfix
873    end if
874    w=w+settling
875  endif
876
877
878  ! Determine the difference vector between new and old wind
879  ! (use half of it to correct position according to Petterssen)
880  !*************************************************************
881
882  u=(u-uold)/2.
883  v=(v-vold)/2.
884  w=(w-wold)/2.
885
886
887  ! Finally, correct the old position
888  !**********************************
889
890  zt=zt+w*real(ldt*ldirect)
891  if (zt.lt.0.) zt=min(h-eps2,-1.*zt)    ! if particle below ground -> reflection
892  if (ngrid.ge.0) then
893    cosfact=dxconst/cos((yt*dy+ylat0)*pi180)
894    xt=xt+real(u*cosfact*real(ldt*ldirect),kind=dp)
895    yt=yt+real(v*dyconst*real(ldt*ldirect),kind=dp)
896  else if (ngrid.eq.-1) then      ! around north pole
897    xlon=xlon0+xt*dx
898    ylat=ylat0+yt*dy
899    call cll2xy(northpolemap,ylat,xlon,xpol,ypol)
900    gridsize=1000.*cgszll(northpolemap,ylat,xlon)
901    u=u/gridsize
902    v=v/gridsize
903    xpol=xpol+u*real(ldt*ldirect)
904    ypol=ypol+v*real(ldt*ldirect)
905    call cxy2ll(northpolemap,xpol,ypol,ylat,xlon)
906    xt=(xlon-xlon0)/dx
907    yt=(ylat-ylat0)/dy
908  else if (ngrid.eq.-2) then    ! around south pole
909    xlon=xlon0+xt*dx
910    ylat=ylat0+yt*dy
911    call cll2xy(southpolemap,ylat,xlon,xpol,ypol)
912    gridsize=1000.*cgszll(southpolemap,ylat,xlon)
913    u=u/gridsize
914    v=v/gridsize
915    xpol=xpol+u*real(ldt*ldirect)
916    ypol=ypol+v*real(ldt*ldirect)
917    call cxy2ll(southpolemap,xpol,ypol,ylat,xlon)
918    xt=(xlon-xlon0)/dx
919    yt=(ylat-ylat0)/dy
920  endif
921
922  ! If global data are available, use cyclic boundary condition
923  !************************************************************
924
925  if (xglobal) then
926    if (xt.ge.real(nxmin1)) xt=xt-real(nxmin1)
927    if (xt.lt.0.) xt=xt+real(nxmin1)
928    if (xt.le.eps) xt=eps
929    if (abs(xt-real(nxmin1)).le.eps) xt=real(nxmin1)-eps
930  endif
931
932  ! HSO/AL: Prevent particles from disappearing at the pole
933  !******************************************************************
934
935  if ( yt.lt.0. ) then
936    xt=mod(xt+180.,360.)
937    yt=-yt
938  else if ( yt.gt.real(nymin1) ) then
939    xt=mod(xt+180.,360.)
940    yt=2*real(nymin1)-yt
941  endif
942
943  ! Check position: If trajectory outside model domain, terminate it
944  !*****************************************************************
945
946  if ((xt.lt.0.).or.(xt.ge.real(nxmin1)).or.(yt.lt.0.).or. &
947       (yt.gt.real(nymin1))) then
948    nstop=3
949    return
950  endif
951
952  ! If particle above highest model level, set it back into the domain
953  !*******************************************************************
954
955  if (zt.ge.height(nz)) zt=height(nz)-100.*eps
956
957
958end subroutine advance
959
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG