Changes in src/advance.f90 [a652cd5:94735e2] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/advance.f90

    ra652cd5 r94735e2  
    117117  real :: usigold,vsigold,wsigold,r,rs
    118118  real :: uold,vold,wold,vdepo(maxspec)
     119  real :: h1(2)
    119120  !real uprof(nzmax),vprof(nzmax),wprof(nzmax)
    120121  !real usigprof(nzmax),vsigprof(nzmax),wsigprof(nzmax)
     
    223224
    224225
     226 ! Determine the lower left corner and its distance to the current position
     227  !*************************************************************************
     228
     229  ddx=xt-real(ix)
     230  ddy=yt-real(jy)
     231  rddx=1.-ddx
     232  rddy=1.-ddy
     233  p1=rddx*rddy
     234  p2=ddx*rddy
     235  p3=rddx*ddy
     236  p4=ddx*ddy
     237
     238 ! Calculate variables for time interpolation
     239  !*******************************************
     240
     241  dt1=real(itime-memtime(1))
     242  dt2=real(memtime(2)-itime)
     243  dtt=1./(dt1+dt2)
     244
    225245  ! Compute maximum mixing height around particle position
    226246  !*******************************************************
     
    229249  if (ngrid.le.0) then
    230250    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
     251       mind=memind(k) ! eso: compatibility with 3-field version
     252       if (interpolhmix) then
     253             h1(k)=p1*hmix(ix ,jy ,1,mind) &
     254                 + p2*hmix(ixp,jy ,1,mind) &
     255                 + p3*hmix(ix ,jyp,1,mind) &
     256                 + p4*hmix(ixp,jyp,1,mind)
     257        else
     258          do j=jy,jyp
     259            do i=ix,ixp
     260               if (hmix(i,j,1,mind).gt.h) h=hmix(i,j,1,mind)
     261            end do
     262          end do
     263        endif
    237264    end do
    238265    tropop=tropopause(nix,njy,1,1)
     
    249276  endif
    250277
     278  if (interpolhmix) h=(h1(1)*dt2+h1(2)*dt1)*dtt
    251279  zeta=zt/h
    252280
     
    446474        endif
    447475
     476        if (turboff) then
     477!sec switch off turbulence
     478          up=0.0
     479          vp=0.0
     480          wp=0.0
     481          delz=0.
     482        endif
     483
    448484  !****************************************************
    449485  ! Compute turbulent vertical displacement of particle
     
    647683  endif
    648684
     685  if (turboff) then
     686!sec switch off turbulence
     687    ux=0.0
     688    vy=0.0
     689    wp=0.0
     690  endif
    649691
    650692  ! If particle represents only a single species, add gravitational settling
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG