Changeset 5184a7c in flexpart.git for src/advance.f90


Ignore:
Timestamp:
Jun 20, 2017, 9:09:35 AM (7 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
b5127f9
Parents:
a76d954
Message:

Enable settling with multiple species if from separate releases

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/advance.f90

    re52967c r5184a7c  
    535535
    536536      if (mdomainfill.eq.0) then
    537 ! ESO 05.2015  Changed this to fix MQUASILAG option, where nrelpoint is
    538 !              particle number and thus xmass array goes out of bounds
    539 !        do nsp=1,nspec
    540 !           if (xmass(nrelpoint,nsp).gt.eps2) goto 887
    541 !         end do
    542 ! 887     nsp=min(nsp,nspec)
    543         if (nspec.eq.1.and.density(1).gt.0.) then
    544           call get_settling(itime,real(xt),real(yt),zt,nspec,settling)  !bugfix
     537        if (lsettling) then
     538          do nsp=1,nspec
     539            if (xmass(nrelpoint,nsp).gt.eps2) exit
     540          end do
     541          if (nsp.gt.nspec) then
     542  ! This should never happen         
     543            write(*,*) 'advance.f90: ERROR: could not find releasepoint'
     544            stop
     545          end if
     546          if (density(nsp).gt.0.) then
     547            call get_settling(itime,real(xt),real(yt),zt,nsp,settling)  !bugfix
     548            w=w+settling
     549          end if
    545550        end if
    546         w=w+settling
    547551      endif
    548552
     
    700704  !*************************************************************************
    701705
    702 
    703 
    704     if (mdomainfill.eq.0) then
    705 ! ESO 05.2015  Changed this to fix MQUASILAG option, where nrelpoint is
    706 !              particle number and thus xmass array goes out of bounds
    707 
    708 !      do nsp=1,nspec
    709 !         if (xmass(nrelpoint,nsp).gt.eps2) goto 888
    710 !       end do
    711 ! 888   nsp=min(nsp,nspec)
    712 !        if (density(nsp).gt.0.) then
    713       if (nspec.eq.1.and.density(1).gt.0.) then
    714         call get_settling(itime,real(xt),real(yt),zt,nspec,settling)  !bugfix
     706  if (mdomainfill.eq.0) then
     707    if (lsettling) then
     708      do nsp=1,nspec
     709        if (xmass(nrelpoint,nsp).gt.eps2) exit
     710      end do
     711      if (nsp.gt.nspec) then
     712  ! This should never happen         
     713        write(*,*) 'advance.f90: ERROR: could not find releasepoint'
     714        stop
    715715      end if
    716       w=w+settling
     716      if (density(nsp).gt.0.) then
     717        call get_settling(itime,real(xt),real(yt),zt,nsp,settling)  !bugfix
     718        w=w+settling
     719      end if
    717720    endif
     721  end if
     722
    718723
    719724  ! Calculate position at time step itime+lsynctime
     
    910915
    911916  if (mdomainfill.eq.0) then
    912 ! ESO 05.2015  Changed this to fix MQUASILAG option, where nrelpoint is
    913 !              particle number and thus xmass array goes out of bounds
    914 !    do nsp=1,nspec
    915 !       if (xmass(nrelpoint,nsp).gt.eps2) goto 889
    916 !     end do
    917 ! 889   nsp=min(nsp,nspec)
    918 !      if (density(nsp).gt.0.) then
    919     if (nspec.eq.1.and.density(1).gt.0.) then
    920       call get_settling(itime+ldt,real(xt),real(yt),zt,nspec,settling)  !bugfix
    921     end if
    922     w=w+settling
    923   endif
     917    if (lsettling) then
     918      do nsp=1,nspec
     919        if (xmass(nrelpoint,nsp).gt.eps2) exit
     920      end do
     921      if (nsp.gt.nspec) then
     922  ! This should never happen         
     923        write(*,*) 'advance.f90: ERROR: could not find releasepoint'
     924        stop
     925      end if
     926      if (density(nsp).gt.0.) then
     927        call get_settling(itime+ldt,real(xt),real(yt),zt,nsp,settling) !bugfix
     928        w=w+settling
     929      end if
     930    endif
     931  end if
    924932
    925933
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG