Changeset 5f9d14a in flexpart.git for src/concoutput_surf_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/concoutput_surf_mpi.f90

    • Property mode changed from 100755 to 100644
    r8a65cb0 r5f9d14a  
    105105  character :: adate*8,atime*6
    106106  character(len=3) :: anspec
     107  integer :: mind
     108! mind        eso:added to get consistent results between 2&3-fields versions
    107109
    108110! Measure execution time
    109   if (mp_measure_time) then
    110     call cpu_time(mp_root_time_beg)
    111     mp_root_wtime_beg = mpi_wtime()
    112   end if
    113 
    114   if (verbosity.eq.1) then
    115      print*,'inside concoutput_surf '
    116      CALL SYSTEM_CLOCK(count_clock)
    117      WRITE(*,*) 'SYSTEM_CLOCK',count_clock - count_clock0   
    118   endif
     111  if (mp_measure_time) call mpif_mtime('rootonly',0)
     112
    119113
    120114  ! Determine current calendar date, needed for the file name
     
    165159  !*******************************************************************
    166160
     161  mind=memind(2)
    167162  do kz=1,numzgrid
    168163    if (kz.eq.1) then
     
    187182        iix=max(min(nint(xl),nxmin1),0)
    188183        jjy=max(min(nint(yl),nymin1),0)
    189         densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,2)*dz1+ &
    190              rho(iix,jjy,kzz-1,2)*dz2)/dz
     184        ! densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,2)*dz1+ &
     185        !      rho(iix,jjy,kzz-1,2)*dz2)/dz
     186        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
     187             rho(iix,jjy,kzz-1,mind)*dz2)/dz
    191188      end do
    192189    end do
    193190  end do
    194191
    195     do i=1,numreceptor
    196       xl=xreceptor(i)
    197       yl=yreceptor(i)
    198       iix=max(min(nint(xl),nxmin1),0)
    199       jjy=max(min(nint(yl),nymin1),0)
    200       densityoutrecept(i)=rho(iix,jjy,1,2)
    201     end do
     192  do i=1,numreceptor
     193    xl=xreceptor(i)
     194    yl=yreceptor(i)
     195    iix=max(min(nint(xl),nxmin1),0)
     196    jjy=max(min(nint(yl),nymin1),0)
     197    !densityoutrecept(i)=rho(iix,jjy,1,2)
     198    densityoutrecept(i)=rho(iix,jjy,1,mind)
     199  end do
    202200
    203201
     
    655653  end do
    656654
    657   if (mp_measure_time) then
    658     call cpu_time(mp_root_time_end)
    659     mp_root_wtime_end = mpi_wtime()
    660     mp_root_time_total = mp_root_time_total + (mp_root_time_end - mp_root_time_beg)
    661     mp_root_wtime_total = mp_root_wtime_total + (mp_root_wtime_end - mp_root_wtime_beg)
    662   end if
    663 
     655  if (mp_measure_time) call mpif_mtime('rootonly',1)
     656 
    664657end subroutine concoutput_surf
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG