Changes in src/timemanager_mpi.f90 [20963b1:d8eed02] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    r20963b1 rd8eed02  
    102102  use com_mod
    103103  use mpi_mod
    104 #ifdef USE_NCF
    105104  use netcdf_output_mod, only: concoutput_netcdf,concoutput_nest_netcdf,&
    106105       &concoutput_surf_netcdf,concoutput_surf_nest_netcdf
    107 #endif
    108106
    109107  implicit none
     
    115113  integer :: ip
    116114  integer :: loutnext,loutstart,loutend
    117   integer :: ix,jy,ldeltat,itage,nage,idummy
     115  integer :: ix,jy,ldeltat,itage,nage
    118116  integer :: i_nan=0,ii_nan,total_nan_intl=0  !added by mc to check instability in CBL scheme
    119117  integer :: numpart_tot_mpi ! for summing particles on all processes
    120   real :: outnum,weight,prob(maxspec), prob_rec(maxspec), decfact,wetscav
     118  real :: outnum,weight,prob(maxspec)
     119  real :: decfact
    121120
    122121  real(sp) :: gridtotalunc
     
    124123       & drydeposit(maxspec)=0_dep_prec
    125124  real :: xold,yold,zold,xmassfract
    126   real :: grfraction(3)
    127125  real, parameter :: e_inv = 1.0/exp(1.0)
    128126
     
    159157!CGZ-lifetime: set lifetime to 0
    160158
    161   if (.not.lusekerneloutput) write(*,*) 'Not using the kernel'
    162   if (turboff) write(*,*) 'Turbulence switched off'
    163159
    164160
     
    485481            if (lroot) then
    486482              if (lnetcdfout.eq.1) then
    487 #ifdef USE_NCF
    488483                call concoutput_netcdf(itime,outnum,gridtotalunc,wetgridtotalunc,&
    489484                     &drygridtotalunc)
    490 #endif
    491485              else
    492486                call concoutput(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     
    500494            if (lroot) then
    501495              if (lnetcdfout.eq.1) then
    502 #ifdef USE_NCF
    503496                call concoutput_surf_netcdf(itime,outnum,gridtotalunc,wetgridtotalunc,&
    504497                     &drygridtotalunc)
    505 #endif
    506498              else
    507499                call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     
    521513            call mpif_tm_reduce_grid_nest
    522514 
    523             if (mp_measure_time) call mpif_mtime('iotime',0)
     515           if (mp_measure_time) call mpif_mtime('iotime',0)
    524516
    525517            if (lnetcdfout.eq.0) then
     
    534526              else  ! :TODO: check for zeroing in the netcdf module
    535527                call concoutput_surf_nest(itime,outnum)
     528
    536529              end if
     530
    537531            else
    538 #ifdef USE_NCF
     532
    539533              if (surf_only.ne.1) then
    540534                if (lroot) then             
     
    550544                end if
    551545              endif
    552 #endif
     546
     547
    553548            end if
    554549          end if
     550         
     551
    555552          outnum=0.
    556553        endif
     
    710707        zold=ztra1(j)
    711708
    712    
    713   ! RECEPTOR: dry/wet depovel
    714   !****************************
    715   ! Before the particle is moved
    716   ! the calculation of the scavenged mass shall only be done once after release
    717   ! xscav_frac1 was initialised with a negative value
    718 
    719       if  (DRYBKDEP) then
    720        do ks=1,nspec
    721          if  ((xscav_frac1(j,ks).lt.0)) then
    722             call get_vdep_prob(itime,xtra1(j),ytra1(j),ztra1(j),prob_rec)
    723             if (DRYDEPSPEC(ks)) then        ! dry deposition
    724                xscav_frac1(j,ks)=prob_rec(ks)
    725              else
    726                 xmass1(j,ks)=0.
    727                 xscav_frac1(j,ks)=0.
    728              endif
    729          endif
    730         enddo
    731        endif
    732 
    733        if (WETBKDEP) then
    734        do ks=1,nspec
    735          if  ((xscav_frac1(j,ks).lt.0)) then
    736             call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy,wetscav)
    737             if (wetscav.gt.0) then
    738                 xscav_frac1(j,ks)=wetscav* &
    739                        (zpoint2(npoint(j))-zpoint1(npoint(j)))*grfraction(1)
    740             else
    741                 xmass1(j,ks)=0.
    742                 xscav_frac1(j,ks)=0.
    743             endif
    744          endif
    745         enddo
    746        endif
    747 
    748709! Integrate Lagevin equation for lsynctime seconds
    749710!*************************************************
     
    847808                 call initial_cond_calc(itime+lsynctime,j)
    848809            itra1(j)=-999999999
    849             if (verbosity.gt.0) then
    850               print*, 'terminated particle ',j,'for age'
    851             endif
     810            !print*, 'terminated particle ',j,'for age'
    852811          endif
    853812        endif
     
    860819
    861820
    862 ! Counter of "unstable" particle velocity during a time scale
    863 ! of maximumtl=20 minutes (defined in com_mod)
    864 !************************************************************
     821! Added by mc: counter of "unstable" particle velocity during a time scale
     822!   of maximumtl=20 minutes (defined in com_mod)
     823
    865824    total_nan_intl=0
    866825    i_nan=i_nan+1 ! added by mc to count nan during a time of maxtl (i.e. maximum tl fixed here to 20 minutes, see com_mod)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG