Changeset 5f9d14a in flexpart.git for src/timemanager_mpi.f90


Ignore:
Timestamp:
Apr 8, 2015, 2:23:27 PM (9 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:
1585284
Parents:
cd85138
Message:

Updated wet depo scheme

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    • Property mode changed from 100755 to 100644
    r8a65cb0 r5f9d14a  
    180180    if (OHREA .and. itime .ne. 0 .and. numpart .gt. 0) then
    181181! readwind process skips this step
    182       if (.not.(lmpreader.and.lmp_use_reader)) then !.or..not.lmp_use_reader)
     182      if (.not.(lmpreader.and.lmp_use_reader)) then
    183183        call ohreaction(itime,lsynctime,loutnext)
    184184      endif
     
    223223      call mpif_gf_send_vars(memstat)
    224224      call mpif_gf_send_vars_nest(memstat)
    225 ! This version is also used whenever 2 fields are needed (in this case,
    226 ! async send/recv is impossible)
     225! Version 2  (lmp_sync=.false.) is also used whenever 2 new fields are read (in which
     226! case async send/recv is impossible.
    227227    else if (.not.lmp_sync.and.lmp_use_reader.and.memstat.ge.32) then
    228228      call mpif_gf_send_vars(memstat)
     
    231231
    232232! Version 2 (lmp_sync=.false.) is for holding three fields in memory. Uses a
    233 ! read-ahead process where sending/receiving of the 3rd fields are done in
     233! read-ahead process where sending/receiving of the 3rd fields is done in
    234234! the background in parallel with performing computations with fields 1&2
    235235!********************************************************************************
     
    241241      end if
    242242
    243 
    244243! COMPLETION CHECK:
    245244! Issued at start of each new field period.
    246245      if (memstat.ne.0.and.memstat.lt.32.and.lmp_use_reader) then
    247 ! :DEV: z0(7) changes with time, so should be dimension (numclass,2)
    248 ! to allow transfer of the future value in the background
     246! TODO: z0(7) changes with time, so should be dimension (numclass,2) to
     247! allow transfer of the future value in the background
     248        call MPI_Bcast(z0,numclass,mp_pp,id_read,MPI_COMM_WORLD,mp_ierr)
    249249        call mpif_gf_request
    250         call MPI_Bcast(z0,numclass,mp_pp,id_read,MPI_COMM_WORLD,mp_ierr)
    251250      end if
    252251
    253 
    254252! RECVEIVING PROCESS(ES):
     253      ! eso TODO: at this point we do not know if clwc/ciwc will be available
     254      ! at next time step. Issue receive request anyway, cancel at mpif_gf_request
    255255      if (memstat.gt.0.and.lmp_use_reader.and..not.lmpreader) then
    256256        call mpif_gf_recv_vars_async(memstat)
     
    755755    if (cblflag.eq.1) print *,j,itime,'nan_synctime',nan_count,'nan_tl',total_nan_intl 
    756756
     757! TODO: delete for release version?
    757758!!-------------------------------------------------------------------------------
    758759! These lines below to test the well-mixed condition, modified by  mc, not to
     
    778779
    779780! eso :TODO: this not implemented yet (transfer particles to PID 0 or rewrite)
    780 ! the tools to do this is in mpi_mod.f90
     781! the tools to do this are already in mpi_mod.f90
    781782  if (lroot) then
    782783    do j=1,numpart
     
    787788
    788789  if (ipout.eq.2) then
    789 ! MPI: process 0 creates the file, the other processes append to it
     790! MPI process 0 creates the file, the other processes append to it
    790791    do ip=0, mp_partgroup_np-1
    791792      if (ip.eq.mp_partid) then
    792         if (mp_dbg_mode) write(*,*) 'call partoutput(itime), proc, mp_partid',ip,mp_partid
     793        !if (mp_dbg_mode) write(*,*) 'call partoutput(itime), proc, mp_partid',ip,mp_partid
    793794        call partoutput(itime)    ! dump particle positions
    794795      end if
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG