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


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    r16b61a5 r3b80e98  
    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
     106  integer :: j,ks,kp,l,n,itime=0,nstop,nstop1,memstat=0 !,mind
    107107! integer :: ksp
    108108  integer :: ip
     
    155155
    156156  do itime=0,ideltas,lsynctime
    157    
    158157
    159158! Computation of wet deposition, OH reaction and mass transfer
     
    167166!********************************************************************
    168167
    169     if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
     168    if (mp_dev_mode) write(*,*) 'myid, itime: ',mp_pid,itime
    170169   
    171170    if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     
    331330      call releaseparticles(itime)
    332331    endif
    333 
    334 
    335 ! Check if particles should be redistributed among processes
    336 !***********************************************************
    337     call mpif_calculate_part_redist(itime)
    338332
    339333
     
    554548! Decide whether to write an estimate of the number of particles released,
    555549! or exact number (require MPI reduce operation)
    556         if (mp_dbg_mode) then
     550        if (mp_dev_mode) then
    557551          numpart_tot_mpi = numpart
    558552        else
     
    561555
    562556        if (mp_exact_numpart.and..not.(lmpreader.and.lmp_use_reader).and.&
    563              &.not.mp_dbg_mode) then
     557             &.not.mp_dev_mode) then
    564558          call MPI_Reduce(numpart, numpart_tot_mpi, 1, MPI_INTEGER, MPI_SUM, id_root, &
    565559               & mp_comm_used, mp_ierr)
     
    567561       
    568562        !CGZ-lifetime: output species lifetime
    569         if (lroot.or.mp_dbg_mode) then
     563        if (lroot.or.mp_dev_mode) then
    570564        !   write(*,*) 'Overview species lifetime in days', &
    571565        !        real((species_lifetime(:,1)/species_lifetime(:,2))/real(3600.0*24.0))
     
    577571        !   end if
    578572        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 
    583573
    58457445      format(i13,' SECONDS SIMULATED: ',i13, ' PARTICLES:    Uncertainty: ',3f7.3)
     
    870860  endif
    871861  deallocate(gridunc)
    872   deallocate(xpoint1,xpoint2,ypoint1,ypoint2,zpoint1,zpoint2,xmass)
    873   if (allocated(checklifetime)) deallocate(checklifetime)
     862  deallocate(xpoint1,xpoint2,ypoint1,ypoint2,zpoint1,zpoint2,xmass, checklifetime)
    874863  deallocate(ireleasestart,ireleaseend,npart,kindz)
    875864  deallocate(xmasssave)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG