Changeset 861805a in flexpart.git for src/timemanager_mpi.f90


Ignore:
Timestamp:
Sep 6, 2016, 9:59:11 AM (8 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
16b61a5, 93786a1
Parents:
0f7835d
Message:

Fix for a problem with the distribution of particles among processes (MPI version)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    r0f7835d r861805a  
    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
     
    274275
    275276    if (mp_measure_time.and..not.(lmpreader.and.lmp_use_reader)) call mpif_mtime('getfields',1)
     277
     278! For validation and tests: call the function below to set all fields to simple
     279! homogeneous values
     280!    if (mp_dev_mode) call set_fields_synthetic
     281
     282!*******************************************************************************
    276283
    277284    if (lmpreader.and.nstop1.gt.1) stop 'NO METEO FIELDS AVAILABLE'
     
    324331      call releaseparticles(itime)
    325332    endif
     333
     334
     335! Check if particles should be redistributed among processes
     336!***********************************************************
     337    call mpif_calculate_part_redist(itime)
    326338
    327339
     
    542554! Decide whether to write an estimate of the number of particles released,
    543555! or exact number (require MPI reduce operation)
    544         if (mp_dev_mode) then
     556        if (mp_dbg_mode) then
    545557          numpart_tot_mpi = numpart
    546558        else
     
    549561
    550562        if (mp_exact_numpart.and..not.(lmpreader.and.lmp_use_reader).and.&
    551              &.not.mp_dev_mode) then
     563             &.not.mp_dbg_mode) then
    552564          call MPI_Reduce(numpart, numpart_tot_mpi, 1, MPI_INTEGER, MPI_SUM, id_root, &
    553565               & mp_comm_used, mp_ierr)
     
    555567       
    556568        !CGZ-lifetime: output species lifetime
    557         if (lroot.or.mp_dev_mode) then
     569        if (lroot.or.mp_dbg_mode) then
    558570        !   write(*,*) 'Overview species lifetime in days', &
    559571        !        real((species_lifetime(:,1)/species_lifetime(:,2))/real(3600.0*24.0))
     
    565577        !   end if
    566578        end if
     579
     580        ! Write particles for all processes
     581        if (mp_dev_mode) write(*,*) "PID, itime, numpart", mp_pid,itime,numpart
     582
    567583
    56858445      format(i13,' SECONDS SIMULATED: ',i13, ' PARTICLES:    Uncertainty: ',3f7.3)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG