Changeset 1070b4c in flexpart.git for src/timemanager_mpi.f90


Ignore:
Timestamp:
Aug 27, 2020, 9:51:56 PM (4 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
GFS_025, dev
Children:
b0ecb61
Parents:
8c0ae9b (diff), a803521 (diff)
Note: this is a merge changeset, the changes displayed below correspond to the merge itself.
Use the (diff) links above to see all the changes relative to each parent.
Message:

Merge branch 'espen' into dev

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager_mpi.f90

    r92fab65 ra803521  
    9191  implicit none
    9292
     93  integer(selected_int_kind(16)) :: idummy,idummy2
    9394  integer :: metdata_format
    9495  logical :: reqv_state=.false. ! .true. if waiting for a MPI_Irecv to complete
     
    9798  integer :: ip,irec
    9899  integer :: loutnext,loutstart,loutend
    99   integer :: ix,jy,ldeltat,itage,nage,idummy
     100  integer :: ix,jy,ldeltat,itage,nage
    100101  integer :: i_nan=0,ii_nan,total_nan_intl=0  !added by mc to check instability in CBL scheme
    101102  integer :: numpart_tot_mpi ! for summing particles on all processes
     
    159160!********************************************************************
    160161
    161     if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
     162!    if (mp_dbg_mode) write(*,*) 'myid, itime: ',mp_pid,itime
    162163   
    163164    if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     
    280281
    281282    if (lmpreader.and.lmp_use_reader) then
    282       if (itime.lt.ideltas*ldirect) then
     283      if (abs(itime).lt.ideltas*ldirect) then
    283284        cycle
    284285      else
     
    480481              creceptor(:,:)=0.
    481482            end if
    482           else
     483          else ! surf only
    483484            if (lroot) then
    484485              if (lnetcdfout.eq.1) then
     
    488489#endif
    489490              else
    490                 call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     491                if (linversionout.eq.1) then
     492                  call concoutput_inversion(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     493                else
     494                  call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     495                end if
    491496              end if
    492497            else
     
    516521
    517522              else
    518                 call concoutput_surf_nest(itime,outnum)
     523                if(linversionout.eq.1) then
     524                  if (lroot) then
     525                    call concoutput_inversion_nest(itime,outnum)
     526                  else
     527                    griduncn(:,:,:,:,:,:,:)=0.
     528                  end if
     529                else
     530                  if (lroot) then
     531                    call concoutput_surf_nest(itime,outnum)
     532                  else
     533                    griduncn(:,:,:,:,:,:,:)=0.
     534                  end if
     535                end if
    519536              end if
    520537            else
     
    724741       do ks=1,nspec
    725742         if  ((xscav_frac1(j,ks).lt.0)) then
    726             call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy,wetscav)
     743            call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy2,wetscav)
    727744            if (wetscav.gt.0) then
    728745                xscav_frac1(j,ks)=wetscav* &
     
    877894!*****************************************************************************
    878895
    879 ! eso :TODO: this not implemented yet (transfer particles to PID 0 or rewrite)
    880 ! the tools to do this are already in mpi_mod.f90
    881   if (lroot) then
    882     do j=1,numpart
    883       if (linit_cond.ge.1) call initial_cond_calc(itime,j)
    884     end do
    885   end if
    886 
    887 
     896  do j=1,numpart
     897    if (linit_cond.ge.1) call initial_cond_calc(itime,j)
     898  end do
     899
     900! Transfer sum of init_cond field to root process, for output
     901  call mpif_tm_reduce_initcond
     902   
    888903  if (ipout.eq.2) then
    889904! MPI process 0 creates the file, the other processes append to it
     
    897912  end if
    898913
    899 ! eso :TODO: MPI
    900   if (linit_cond.ge.1.and.lroot) call initial_cond_output(itime)   ! dump initial cond. field
     914 
     915  if (linit_cond.ge.1.and.lroot) then
     916    if(linversionout.eq.1) then
     917      call initial_cond_output_inversion(itime)   ! dump initial cond. field
     918    else
     919      call initial_cond_output(itime)   ! dump initial cond. fielf
     920    endif
     921  endif
    901922
    902923
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG