Changeset 5f42c27 in flexpart.git for src/mpi_mod.f90


Ignore:
Timestamp:
May 13, 2015, 1:42:50 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:
598e9da
Parents:
fb0d416
Message:

Changed path to OH binaries

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/mpi_mod.f90

    rfb0d416 r5f42c27  
    117117  logical, parameter :: mp_dbg_out = .false.
    118118  logical, parameter :: mp_time_barrier=.true.
    119   logical, parameter :: mp_measure_time=.true.
     119  logical, parameter :: mp_measure_time=.false.
    120120
    121121! for measuring CPU/Wall time
     
    139139  real(dp) :: mp_conccalc_time_beg, mp_conccalc_time_end, mp_conccalc_time_total=0.
    140140  real(dp) :: mp_total_wtime_beg, mp_total_wtime_end, mp_total_wtime_total=0.
     141  real(dp) :: mp_vt_wtime_beg, mp_vt_wtime_end, mp_vt_wtime_total
     142  real(sp) :: mp_vt_time_beg, mp_vt_time_end, mp_vt_time_total
    141143
    142144! dat_lun           logical unit number for i/o
     
    418420
    419421
    420 
    421422! redefine numpart as 'numpart per process' throughout the code
    422423!**************************************************************
     
    438439
    439440    integer :: i
    440 
    441 
    442 !***********************************************************************
    443 
    444441
    445442! Time for MPI communications
     
    17341731    end if
    17351732
    1736 
    17371733    if ((WETDEP).and.(ldirect.gt.0)) then
    17381734      call MPI_Reduce(wetgriduncn, wetgriduncn0, grid_size2d, mp_pp, MPI_SUM, id_root, &
     
    18521848        mp_io_time_total = mp_io_time_total + (mp_io_time_end - &
    18531849             & mp_io_time_beg)
     1850      end if
     1851
     1852    case ('verttransform')
     1853      if (imode.eq.0) then
     1854        mp_vt_wtime_beg = mpi_wtime()
     1855        call cpu_time(mp_vt_time_beg)
     1856      else
     1857        mp_vt_wtime_end = mpi_wtime()
     1858        call cpu_time(mp_vt_time_end)
     1859
     1860        mp_vt_wtime_total = mp_vt_wtime_total + (mp_vt_wtime_end - &
     1861             & mp_vt_wtime_beg)
     1862        mp_vt_time_total = mp_vt_time_total + (mp_vt_time_end - &
     1863             & mp_vt_time_beg)
    18541864      end if
    18551865
     
    19561966          write(*,FMT='(A60,TR1,F9.2)') 'TOTAL WALL TIME FOR CONCCALC:',&
    19571967               & mp_conccalc_time_total
     1968          ! write(*,FMT='(A60,TR1,F9.2)') 'TOTAL WALL TIME FOR VERTTRANSFORM:',&
     1969          !      & mp_vt_wtime_total
     1970          ! write(*,FMT='(A60,TR1,F9.2)') 'TOTAL CPU TIME FOR VERTTRANSFORM:',&
     1971          !      & mp_vt_time_total
    19581972! NB: the 'flush' function is possibly a gfortran-specific extension
    19591973          call flush()
     
    20212035    subroutine write_data_dbg(array_in, array_name, tstep, ident)
    20222036!***********************************************************************
    2023 ! Write one-dimensional arrays to disk (for debugging purposes)
     2037! Write one-dimensional arrays to file (for debugging purposes)
    20242038!***********************************************************************
    20252039      implicit none
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG