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


Ignore:
Timestamp:
Apr 7, 2021, 8:45:57 AM (3 years ago)
Author:
Sabine <sabine.eckhardt@…>
Branches:
dev
Children:
1228ef7
Parents:
03adec6 (diff), 759df5f (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:

Merge remote-tracking branch 'refs/remotes/origin/dev' into dev

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    rffbe224 r4138764  
     1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
     2! SPDX-License-Identifier: GPL-3.0-or-later
     3
    14subroutine timemanager(metdata_format)
    25
     
    8891  implicit none
    8992
     93  integer(selected_int_kind(16)) :: idummy,idummy2
    9094  integer :: metdata_format
    9195  logical :: reqv_state=.false. ! .true. if waiting for a MPI_Irecv to complete
     
    9498  integer :: ip,irec
    9599  integer :: loutnext,loutstart,loutend
    96   integer :: ix,jy,ldeltat,itage,nage,idummy
     100  integer :: ix,jy,ldeltat,itage,nage
    97101  integer :: i_nan=0,ii_nan,total_nan_intl=0  !added by mc to check instability in CBL scheme
    98102  integer :: numpart_tot_mpi ! for summing particles on all processes
     
    156160!********************************************************************
    157161
    158     if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
     162!    if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
    159163   
    160164    if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     
    277281
    278282    if (lmpreader.and.lmp_use_reader) then
    279       if (itime.lt.ideltas*ldirect) then
     283      if (abs(itime).lt.ideltas*ldirect) then
    280284        cycle
    281285      else
     
    477481              creceptor(:,:)=0.
    478482            end if
    479           else
     483          else ! surf only
    480484            if (lroot) then
    481485              if (lnetcdfout.eq.1) then
     
    485489#endif
    486490              else
    487                 call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     491                if (linversionout.eq.1) then
     492                  call concoutput_inversion(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     493                else
     494                  call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     495                end if
    488496              end if
    489497            else
     
    513521
    514522              else
    515                 call concoutput_surf_nest(itime,outnum)
     523                if(linversionout.eq.1) then
     524                  if (lroot) then
     525                    call concoutput_inversion_nest(itime,outnum)
     526                  else
     527                    griduncn(:,:,:,:,:,:,:)=0.
     528                  end if
     529                else
     530                  if (lroot) then
     531                    call concoutput_surf_nest(itime,outnum)
     532                  else
     533                    griduncn(:,:,:,:,:,:,:)=0.
     534                  end if
     535                end if
    516536              end if
    517537            else
     
    722742       do ks=1,nspec
    723743         if  ((xscav_frac1(j,ks).lt.0)) then
    724             call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy,wetscav)
     744            call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy2,wetscav)
    725745            if (wetscav.gt.0) then
    726746                xscav_frac1(j,ks)=wetscav* &
     
    875895!*****************************************************************************
    876896
    877 ! eso :TODO: this not implemented yet (transfer particles to PID 0 or rewrite)
    878 ! the tools to do this are already in mpi_mod.f90
    879   if (lroot) then
     897  if (linit_cond.ge.1) then
    880898    do j=1,numpart
    881       if (linit_cond.ge.1) call initial_cond_calc(itime,j)
     899      call initial_cond_calc(itime,j)
    882900    end do
     901
     902! Transfer sum of init_cond field to root process, for output
     903    call mpif_tm_reduce_initcond
    883904  end if
    884 
    885 
     905   
    886906  if (ipout.eq.2) then
    887907! MPI process 0 creates the file, the other processes append to it
     
    895915  end if
    896916
    897 ! eso :TODO: MPI
    898   if (linit_cond.ge.1.and.lroot) call initial_cond_output(itime)   ! dump initial cond. field
     917 
     918  if (linit_cond.ge.1.and.lroot) then
     919    if(linversionout.eq.1) then
     920      call initial_cond_output_inversion(itime)   ! dump initial cond. field
     921    else
     922      call initial_cond_output(itime)   ! dump initial cond. fielf
     923    endif
     924  endif
    899925
    900926
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG