Changes in src/timemanager_mpi.f90 [ec7fc72:8ed5f11] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    rec7fc72 r8ed5f11  
    228228    if (mp_measure_time.and..not.(lmpreader.and.lmp_use_reader)) call mpif_mtime('getfields',0)
    229229
     230! Two approaches to MPI getfields is implemented:
    230231! Version 1 (lmp_sync=.true.) uses a read-ahead process where send/recv is done
    231232! in sync at start of each new field time interval
     233!
     234! Version 2 (lmp_sync=.false.) is for holding three fields in memory. Uses a
     235! read-ahead process where sending/receiving of the 3rd fields is done in
     236! the background in parallel with performing computations with fields 1&2
     237!********************************************************************************
     238
    232239    if (lmp_sync.and.lmp_use_reader.and.memstat.gt.0) then
    233240      call mpif_gf_send_vars(memstat)
    234241      if (numbnests>0) call mpif_gf_send_vars_nest(memstat)
    235 ! Version 2  (lmp_sync=.false., see below) is also used whenever 2 new fields are
     242! Version 2  (lmp_sync=.false.) is also used whenever 2 new fields are
    236243! read (as at first time step), in which case async send/recv is impossible.
    237244    else if (.not.lmp_sync.and.lmp_use_reader.and.memstat.ge.32) then
     
    240247    end if
    241248
    242 ! Version 2 (lmp_sync=.false.) is for holding three fields in memory. Uses a
    243 ! read-ahead process where sending/receiving of the 3rd fields is done in
    244 ! the background in parallel with performing computations with fields 1&2
    245 !********************************************************************************
    246249    if (.not.lmp_sync) then
    247250   
    248 ! READER PROCESS:
     251! Reader process:
    249252      if (memstat.gt.0..and.memstat.lt.32.and.lmp_use_reader.and.lmpreader) then
    250253        if (mp_dev_mode) write(*,*) 'Reader process: calling mpif_gf_send_vars_async'
     
    252255      end if
    253256
    254 ! COMPLETION CHECK:
     257! Completion check:
    255258! Issued at start of each new field period.
    256259      if (memstat.ne.0.and.memstat.lt.32.and.lmp_use_reader) then
     
    258261      end if
    259262
    260 ! RECVEIVING PROCESS(ES):
    261       ! eso TODO: at this point we do not know if clwc/ciwc will be available
    262       ! at next time step. Issue receive request anyway, cancel at mpif_gf_request
     263! Recveiving process(es):
     264! eso TODO: at this point we do not know if clwc/ciwc will be available
     265! at next time step. Issue receive request anyway, cancel at mpif_gf_request
    263266      if (memstat.gt.0.and.lmp_use_reader.and..not.lmpreader) then
    264267        if (mp_dev_mode) write(*,*) 'Receiving process: calling mpif_gf_send_vars_async. PID: ', mp_pid
     
    490493          endif
    491494          if (mp_measure_time) call mpif_mtime('iotime',1)
     495
     496! :TODO: Correct calling of conc_surf above?
     497
     498!   call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     499! endif
    492500
    493501          if (nested_output.eq.1) then
     
    686694
    687695        if (mp_measure_time) call mpif_mtime('advance',0)
     696!mp_advance_wtime_beg = mpi_wtime()
    688697
    689698        call advance(itime,npoint(j),idt(j),uap(j),ucp(j),uzp(j), &
     
    692701
    693702        if (mp_measure_time) call mpif_mtime('advance',1)
     703
     704        ! mp_advance_wtime_end = mpi_wtime()
     705        ! mp_advance_wtime_total = mp_advance_wtime_total + (mp_advance_wtime_end - &
     706        !      & mp_advance_wtime_beg)
    694707
    695708
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG