Changeset f3054ea in flexpart.git for src/timemanager_mpi.f90


Ignore:
Timestamp:
Aug 27, 2020, 8:00:15 PM (4 years ago)
Author:
Espen Sollum <eso@…>
Branches:
GFS_025, dev
Children:
4ab2fbf
Parents:
a756649
Message:

Changed from grib_api to eccodes. MPI: implemented linversionout=1; fixed calculation of grid_initial fields.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    r0c8c7f2 rf3054ea  
    109109  implicit none
    110110
     111  integer(selected_int_kind(16)) :: idummy,idummy2
    111112  integer :: metdata_format
    112113  logical :: reqv_state=.false. ! .true. if waiting for a MPI_Irecv to complete
     
    115116  integer :: ip,irec
    116117  integer :: loutnext,loutstart,loutend
    117   integer :: ix,jy,ldeltat,itage,nage,idummy
     118  integer :: ix,jy,ldeltat,itage,nage
    118119  integer :: i_nan=0,ii_nan,total_nan_intl=0  !added by mc to check instability in CBL scheme
    119120  integer :: numpart_tot_mpi ! for summing particles on all processes
     
    177178!********************************************************************
    178179
    179     if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
     180!    if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
    180181   
    181182    if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     
    298299
    299300    if (lmpreader.and.lmp_use_reader) then
    300       if (itime.lt.ideltas*ldirect) then
     301      if (abs(itime).lt.ideltas*ldirect) then
    301302        cycle
    302303      else
     
    498499              creceptor(:,:)=0.
    499500            end if
    500           else
     501          else ! surf only
    501502            if (lroot) then
    502503              if (lnetcdfout.eq.1) then
     
    506507#endif
    507508              else
    508                 call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     509                if (linversionout.eq.1) then
     510                  call concoutput_inversion(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     511                else
     512                  call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     513                end if
    509514              end if
    510515            else
     
    534539
    535540              else
    536                 call concoutput_surf_nest(itime,outnum)
     541                if(linversionout.eq.1) then
     542                  if (lroot) then
     543                    call concoutput_inversion_nest(itime,outnum)
     544                  else
     545                    griduncn(:,:,:,:,:,:,:)=0.
     546                  end if
     547                else
     548                  if (lroot) then
     549                    call concoutput_surf_nest(itime,outnum)
     550                  else
     551                    griduncn(:,:,:,:,:,:,:)=0.
     552                  end if
     553                end if
    537554              end if
    538555            else
     
    742759       do ks=1,nspec
    743760         if  ((xscav_frac1(j,ks).lt.0)) then
    744             call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy,wetscav)
     761            call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy2,wetscav)
    745762            if (wetscav.gt.0) then
    746763                xscav_frac1(j,ks)=wetscav* &
     
    895912!*****************************************************************************
    896913
    897 ! eso :TODO: this not implemented yet (transfer particles to PID 0 or rewrite)
    898 ! the tools to do this are already in mpi_mod.f90
    899   if (lroot) then
    900     do j=1,numpart
    901       if (linit_cond.ge.1) call initial_cond_calc(itime,j)
    902     end do
    903   end if
    904 
    905 
     914  do j=1,numpart
     915    if (linit_cond.ge.1) call initial_cond_calc(itime,j)
     916  end do
     917
     918! Transfer sum of init_cond field to root process, for output
     919  call mpif_tm_reduce_initcond
     920   
    906921  if (ipout.eq.2) then
    907922! MPI process 0 creates the file, the other processes append to it
     
    915930  end if
    916931
    917 ! eso :TODO: MPI
    918   if (linit_cond.ge.1.and.lroot) call initial_cond_output(itime)   ! dump initial cond. field
     932 
     933  if (linit_cond.ge.1.and.lroot) then
     934    if(linversionout.eq.1) then
     935      call initial_cond_output_inversion(itime)   ! dump initial cond. field
     936    else
     937      call initial_cond_output(itime)   ! dump initial cond. fielf
     938    endif
     939  endif
    919940
    920941
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG