Changes in src/timemanager_mpi.f90 [3b80e98:16b61a5] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    r3b80e98 r16b61a5  
    104104
    105105  logical :: reqv_state=.false. ! .true. if waiting for a MPI_Irecv to complete
    106   integer :: j,ks,kp,l,n,itime=0,nstop,nstop1,memstat=0 !,mind
     106  integer :: j,ks,kp,l,n,itime=0,nstop,nstop1,memstat=0
    107107! integer :: ksp
    108108  integer :: ip
     
    155155
    156156  do itime=0,ideltas,lsynctime
     157   
    157158
    158159! Computation of wet deposition, OH reaction and mass transfer
     
    166167!********************************************************************
    167168
    168     if (mp_dev_mode) write(*,*) 'myid, itime: ',mp_pid,itime
     169    if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
    169170   
    170171    if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     
    330331      call releaseparticles(itime)
    331332    endif
     333
     334
     335! Check if particles should be redistributed among processes
     336!***********************************************************
     337    call mpif_calculate_part_redist(itime)
    332338
    333339
     
    548554! Decide whether to write an estimate of the number of particles released,
    549555! or exact number (require MPI reduce operation)
    550         if (mp_dev_mode) then
     556        if (mp_dbg_mode) then
    551557          numpart_tot_mpi = numpart
    552558        else
     
    555561
    556562        if (mp_exact_numpart.and..not.(lmpreader.and.lmp_use_reader).and.&
    557              &.not.mp_dev_mode) then
     563             &.not.mp_dbg_mode) then
    558564          call MPI_Reduce(numpart, numpart_tot_mpi, 1, MPI_INTEGER, MPI_SUM, id_root, &
    559565               & mp_comm_used, mp_ierr)
     
    561567       
    562568        !CGZ-lifetime: output species lifetime
    563         if (lroot.or.mp_dev_mode) then
     569        if (lroot.or.mp_dbg_mode) then
    564570        !   write(*,*) 'Overview species lifetime in days', &
    565571        !        real((species_lifetime(:,1)/species_lifetime(:,2))/real(3600.0*24.0))
     
    571577        !   end if
    572578        end if
     579
     580        ! Write number of particles for all processes
     581        if (mp_dev_mode) write(*,*) "PID, itime, numpart", mp_pid,itime,numpart
     582
    573583
    57458445      format(i13,' SECONDS SIMULATED: ',i13, ' PARTICLES:    Uncertainty: ',3f7.3)
     
    860870  endif
    861871  deallocate(gridunc)
    862   deallocate(xpoint1,xpoint2,ypoint1,ypoint2,zpoint1,zpoint2,xmass, checklifetime)
     872  deallocate(xpoint1,xpoint2,ypoint1,ypoint2,zpoint1,zpoint2,xmass)
     873  if (allocated(checklifetime)) deallocate(checklifetime)
    863874  deallocate(ireleasestart,ireleaseend,npart,kindz)
    864875  deallocate(xmasssave)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG