Changes in src/advance.f90 [fdc0f03:18adf60] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/advance.f90

    rfdc0f03 r18adf60  
    493493
    494494      if (mdomainfill.eq.0) then
    495         do nsp=1,nspec
    496           if (xmass(nrelpoint,nsp).gt.eps2) goto 887
    497         end do
    498 887     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
     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,nsp,settling)  !bugfix
     503        end if
    503504        w=w+settling
    504505      endif
     
    654655
    655656    if (mdomainfill.eq.0) then
    656       do nsp=1,nspec
    657         if (xmass(nrelpoint,nsp).gt.eps2) goto 888
    658       end do
    659 888   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
     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,nsp,settling)  !bugfix
     667      end if
    664668      w=w+settling
    665669    endif
     
    858862
    859863  if (mdomainfill.eq.0) then
    860     do nsp=1,nspec
    861       if (xmass(nrelpoint,nsp).gt.eps2) goto 889
    862     end do
    863 889   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
     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,nsp,settling)  !bugfix
     873    end if
    868874    w=w+settling
    869875  endif
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG