Changes in src/timemanager_mpi.f90 [92fab65:f3054ea] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    r92fab65 rf3054ea  
    1 ! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
    2 ! SPDX-License-Identifier: GPL-3.0-or-later
     1!**********************************************************************
     2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
     3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
     4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
     5!                                                                     *
     6! This file is part of FLEXPART.                                      *
     7!                                                                     *
     8! FLEXPART is free software: you can redistribute it and/or modify    *
     9! it under the terms of the GNU General Public License as published by*
     10! the Free Software Foundation, either version 3 of the License, or   *
     11! (at your option) any later version.                                 *
     12!                                                                     *
     13! FLEXPART is distributed in the hope that it will be useful,         *
     14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
     15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
     16! GNU General Public License for more details.                        *
     17!                                                                     *
     18! You should have received a copy of the GNU General Public License   *
     19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
     20!**********************************************************************
    321
    422subroutine timemanager(metdata_format)
     
    91109  implicit none
    92110
     111  integer(selected_int_kind(16)) :: idummy,idummy2
    93112  integer :: metdata_format
    94113  logical :: reqv_state=.false. ! .true. if waiting for a MPI_Irecv to complete
     
    97116  integer :: ip,irec
    98117  integer :: loutnext,loutstart,loutend
    99   integer :: ix,jy,ldeltat,itage,nage,idummy
     118  integer :: ix,jy,ldeltat,itage,nage
    100119  integer :: i_nan=0,ii_nan,total_nan_intl=0  !added by mc to check instability in CBL scheme
    101120  integer :: numpart_tot_mpi ! for summing particles on all processes
     
    159178!********************************************************************
    160179
    161     if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
     180!    if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
    162181   
    163182    if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     
    280299
    281300    if (lmpreader.and.lmp_use_reader) then
    282       if (itime.lt.ideltas*ldirect) then
     301      if (abs(itime).lt.ideltas*ldirect) then
    283302        cycle
    284303      else
     
    480499              creceptor(:,:)=0.
    481500            end if
    482           else
     501          else ! surf only
    483502            if (lroot) then
    484503              if (lnetcdfout.eq.1) then
     
    488507#endif
    489508              else
    490                 call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     509                if (linversionout.eq.1) then
     510                  call concoutput_inversion(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     511                else
     512                  call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     513                end if
    491514              end if
    492515            else
     
    516539
    517540              else
    518                 call concoutput_surf_nest(itime,outnum)
     541                if(linversionout.eq.1) then
     542                  if (lroot) then
     543                    call concoutput_inversion_nest(itime,outnum)
     544                  else
     545                    griduncn(:,:,:,:,:,:,:)=0.
     546                  end if
     547                else
     548                  if (lroot) then
     549                    call concoutput_surf_nest(itime,outnum)
     550                  else
     551                    griduncn(:,:,:,:,:,:,:)=0.
     552                  end if
     553                end if
    519554              end if
    520555            else
     
    724759       do ks=1,nspec
    725760         if  ((xscav_frac1(j,ks).lt.0)) then
    726             call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy,wetscav)
     761            call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy2,wetscav)
    727762            if (wetscav.gt.0) then
    728763                xscav_frac1(j,ks)=wetscav* &
     
    877912!*****************************************************************************
    878913
    879 ! eso :TODO: this not implemented yet (transfer particles to PID 0 or rewrite)
    880 ! the tools to do this are already in mpi_mod.f90
    881   if (lroot) then
    882     do j=1,numpart
    883       if (linit_cond.ge.1) call initial_cond_calc(itime,j)
    884     end do
    885   end if
    886 
    887 
     914  do j=1,numpart
     915    if (linit_cond.ge.1) call initial_cond_calc(itime,j)
     916  end do
     917
     918! Transfer sum of init_cond field to root process, for output
     919  call mpif_tm_reduce_initcond
     920   
    888921  if (ipout.eq.2) then
    889922! MPI process 0 creates the file, the other processes append to it
     
    897930  end if
    898931
    899 ! eso :TODO: MPI
    900   if (linit_cond.ge.1.and.lroot) call initial_cond_output(itime)   ! dump initial cond. field
     932 
     933  if (linit_cond.ge.1.and.lroot) then
     934    if(linversionout.eq.1) then
     935      call initial_cond_output_inversion(itime)   ! dump initial cond. field
     936    else
     937      call initial_cond_output(itime)   ! dump initial cond. fielf
     938    endif
     939  endif
    901940
    902941
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG