Changeset 505a96e in flexpart.git for src/timemanager_mpi.f90


Ignore:
Timestamp:
May 22, 2018, 2:40:40 PM (6 years ago)
Author:
Ignacio Pisso <Ignacio.Pisso@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
cd6e10c, 77778f8
Parents:
3d04845 (diff), 20963b1 (diff)
Note: this is a merge changeset, the changes displayed below correspond to the merge itself.
Use the (diff) links above to see all the changes relative to each parent.
Message:

Pull: Merge branch 'dev' of https://git.nilu.no/flexpart/flexpart into dev

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    rd8eed02 r20963b1  
    102102  use com_mod
    103103  use mpi_mod
     104#ifdef USE_NCF
    104105  use netcdf_output_mod, only: concoutput_netcdf,concoutput_nest_netcdf,&
    105106       &concoutput_surf_netcdf,concoutput_surf_nest_netcdf
     107#endif
    106108
    107109  implicit none
     
    113115  integer :: ip
    114116  integer :: loutnext,loutstart,loutend
    115   integer :: ix,jy,ldeltat,itage,nage
     117  integer :: ix,jy,ldeltat,itage,nage,idummy
    116118  integer :: i_nan=0,ii_nan,total_nan_intl=0  !added by mc to check instability in CBL scheme
    117119  integer :: numpart_tot_mpi ! for summing particles on all processes
    118   real :: outnum,weight,prob(maxspec)
    119   real :: decfact
     120  real :: outnum,weight,prob(maxspec), prob_rec(maxspec), decfact,wetscav
    120121
    121122  real(sp) :: gridtotalunc
     
    123124       & drydeposit(maxspec)=0_dep_prec
    124125  real :: xold,yold,zold,xmassfract
     126  real :: grfraction(3)
    125127  real, parameter :: e_inv = 1.0/exp(1.0)
    126128
     
    157159!CGZ-lifetime: set lifetime to 0
    158160
     161  if (.not.lusekerneloutput) write(*,*) 'Not using the kernel'
     162  if (turboff) write(*,*) 'Turbulence switched off'
    159163
    160164
     
    481485            if (lroot) then
    482486              if (lnetcdfout.eq.1) then
     487#ifdef USE_NCF
    483488                call concoutput_netcdf(itime,outnum,gridtotalunc,wetgridtotalunc,&
    484489                     &drygridtotalunc)
     490#endif
    485491              else
    486492                call concoutput(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     
    494500            if (lroot) then
    495501              if (lnetcdfout.eq.1) then
     502#ifdef USE_NCF
    496503                call concoutput_surf_netcdf(itime,outnum,gridtotalunc,wetgridtotalunc,&
    497504                     &drygridtotalunc)
     505#endif
    498506              else
    499507                call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     
    513521            call mpif_tm_reduce_grid_nest
    514522 
    515            if (mp_measure_time) call mpif_mtime('iotime',0)
     523            if (mp_measure_time) call mpif_mtime('iotime',0)
    516524
    517525            if (lnetcdfout.eq.0) then
     
    526534              else  ! :TODO: check for zeroing in the netcdf module
    527535                call concoutput_surf_nest(itime,outnum)
    528 
    529536              end if
    530 
    531537            else
    532 
     538#ifdef USE_NCF
    533539              if (surf_only.ne.1) then
    534540                if (lroot) then             
     
    544550                end if
    545551              endif
    546 
    547 
     552#endif
    548553            end if
    549554          end if
    550          
    551 
    552555          outnum=0.
    553556        endif
     
    707710        zold=ztra1(j)
    708711
     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
    709748! Integrate Lagevin equation for lsynctime seconds
    710749!*************************************************
     
    808847                 call initial_cond_calc(itime+lsynctime,j)
    809848            itra1(j)=-999999999
    810             !print*, 'terminated particle ',j,'for age'
     849            if (verbosity.gt.0) then
     850              print*, 'terminated particle ',j,'for age'
     851            endif
    811852          endif
    812853        endif
     
    819860
    820861
    821 ! Added by mc: counter of "unstable" particle velocity during a time scale
    822 !   of maximumtl=20 minutes (defined in com_mod)
    823 
     862! Counter of "unstable" particle velocity during a time scale
     863! of maximumtl=20 minutes (defined in com_mod)
     864!************************************************************
    824865    total_nan_intl=0
    825866    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