Changeset d6a0977 in flexpart.git for src/timemanager_mpi.f90


Ignore:
Timestamp:
Dec 14, 2015, 3:10:04 PM (8 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:
f75967d
Parents:
88d8c3d
Message:

Updates to Henrik's wet depo scheme

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    ra1f4dd6 rd6a0977  
    139139!**********************************************************************
    140140
     141
     142!  itime=0
     143  if (lroot) then
     144  !  write(*,45) itime,numpart*mp_partgroup_np,gridtotalunc,wetgridtotalunc,drygridtotalunc
     145    write(*,46) float(itime)/3600,itime,numpart*mp_partgroup_np
     146   
     147    if (verbosity.gt.0) then
     148      write (*,*) 'timemanager> starting simulation'
     149    end if
     150  end if ! (lroot)
     151
     152!CGZ-lifetime: set lifetime to 0
     153  checklifetime(:,:)=0
     154  species_lifetime(:,:)=0
     155  print*, 'Initialized lifetime'
     156!CGZ-lifetime: set lifetime to 0
     157
     158
     159
    141160  do itime=0,ideltas,lsynctime
    142161
     
    544563        endif
    545564       
    546         if (lroot) then
     565        !CGZ-lifetime: output species lifetime
     566        ! if (lroot) then
     567        !   write(*,*) 'Overview species lifetime in days', &
     568        !        real((species_lifetime(:,1)/species_lifetime(:,2))/real(3600.0*24.0))
     569        !   write(*,*) 'all info:',species_lifetime
    547570          write(*,45) itime,numpart_tot_mpi,gridtotalunc,&
    548571               &wetgridtotalunc,drygridtotalunc
    549           if (verbosity.gt.0) then
    550             write (*,*) 'timemanager> starting simulation'
    551           end if
    552         end if
     572        !   if (verbosity.gt.0) then
     573        !     write (*,*) 'timemanager> starting simulation'
     574        !   end if
     575        ! end if
    553576
    55457745      format(i13,' SECONDS SIMULATED: ',i13, ' PARTICLES:    Uncertainty: ',3f7.3)
     
    729752
    730753            if (mdomainfill.eq.0) then
    731               if (xmass(npoint(j),ks).gt.0.) &
     754              if (xmass(npoint(j),ks).gt.0.)then
    732755                   xmassfract=max(xmassfract,real(npart(npoint(j)))* &
    733756                   xmass1(j,ks)/xmass(npoint(j),ks))
     757                   
     758                   !CGZ-lifetime: Check mass fraction left/save lifetime
     759                   if(lroot.and.real(npart(npoint(j)))*xmass1(j,ks)/xmass(npoint(j),ks).lt.0.01.and.checklifetime(j,ks).eq.0.)then
     760                       !Mass below 1% of initial >register lifetime
     761                       checklifetime(j,ks)=abs(itra1(j)-itramem(j))
     762
     763                       species_lifetime(ks,1)=species_lifetime(ks,1)+abs(itra1(j)-itramem(j))
     764                       species_lifetime(ks,2)= species_lifetime(ks,2)+1
     765                   endif
     766                   !CGZ-lifetime: Check mass fraction left/save lifetime
     767                   
     768              endif
    734769            else
    735770              xmassfract=1.
     
    737772          end do
    738773
    739           if (xmassfract.lt.0.0001) then   ! terminate all particles carrying less mass
     774          if (xmassfract.lt.0.00005 .and. sum(real(npart(npoint(j)))*xmass1(j,:)).lt.1.0) then   ! terminate all particles carrying less mass
     775          !            print*,'terminated particle ',j,' for small mass (', sum(real(npart(npoint(j)))* &
     776          !         xmass1(j,:)), ' of ', sum(xmass(npoint(j),:)),')'
    740777            itra1(j)=-999999999
    741778          endif
     
    758795                 call initial_cond_calc(itime+lsynctime,j)
    759796            itra1(j)=-999999999
     797            !print*, 'terminated particle ',j,'for age'
    760798          endif
    761799        endif
     
    828866  endif
    829867  deallocate(gridunc)
    830   deallocate(xpoint1,xpoint2,ypoint1,ypoint2,zpoint1,zpoint2,xmass)
     868  deallocate(xpoint1,xpoint2,ypoint1,ypoint2,zpoint1,zpoint2,xmass, checklifetime)
    831869  deallocate(ireleasestart,ireleaseend,npart,kindz)
    832870  deallocate(xmasssave)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG