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


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    rf3054ea r92fab65  
    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 !**********************************************************************
     1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
     2! SPDX-License-Identifier: GPL-3.0-or-later
    213
    224subroutine timemanager(metdata_format)
     
    10991  implicit none
    11092
    111   integer(selected_int_kind(16)) :: idummy,idummy2
    11293  integer :: metdata_format
    11394  logical :: reqv_state=.false. ! .true. if waiting for a MPI_Irecv to complete
     
    11697  integer :: ip,irec
    11798  integer :: loutnext,loutstart,loutend
    118   integer :: ix,jy,ldeltat,itage,nage
     99  integer :: ix,jy,ldeltat,itage,nage,idummy
    119100  integer :: i_nan=0,ii_nan,total_nan_intl=0  !added by mc to check instability in CBL scheme
    120101  integer :: numpart_tot_mpi ! for summing particles on all processes
     
    178159!********************************************************************
    179160
    180 !    if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
     161    if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
    181162   
    182163    if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     
    299280
    300281    if (lmpreader.and.lmp_use_reader) then
    301       if (abs(itime).lt.ideltas*ldirect) then
     282      if (itime.lt.ideltas*ldirect) then
    302283        cycle
    303284      else
     
    499480              creceptor(:,:)=0.
    500481            end if
    501           else ! surf only
     482          else
    502483            if (lroot) then
    503484              if (lnetcdfout.eq.1) then
     
    507488#endif
    508489              else
    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
     490                call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    514491              end if
    515492            else
     
    539516
    540517              else
    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
     518                call concoutput_surf_nest(itime,outnum)
    554519              end if
    555520            else
     
    759724       do ks=1,nspec
    760725         if  ((xscav_frac1(j,ks).lt.0)) then
    761             call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy2,wetscav)
     726            call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy,wetscav)
    762727            if (wetscav.gt.0) then
    763728                xscav_frac1(j,ks)=wetscav* &
     
    912877!*****************************************************************************
    913878
    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    
     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
    921888  if (ipout.eq.2) then
    922889! MPI process 0 creates the file, the other processes append to it
     
    930897  end if
    931898
    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
     899! eso :TODO: MPI
     900  if (linit_cond.ge.1.and.lroot) call initial_cond_output(itime)   ! dump initial cond. field
    940901
    941902
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG