Changeset 20963b1 in flexpart.git for src/concoutput_mpi.f90


Ignore:
Timestamp:
Apr 13, 2018, 2:33:40 PM (6 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:
3d7eebf, 93786a1
Parents:
3f149cc
Message:

Backwards deposition for the MPI version

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/concoutput_mpi.f90

    rb1e0742 r20963b1  
    104104  real,parameter :: weightair=28.97
    105105  logical :: sp_zer
    106   LOGICAL,save :: init=.true.
     106  logical,save :: init=.true.
    107107  character :: adate*8,atime*6
    108108  character(len=3) :: anspec
     
    128128! This fixes a bug where the dates file kept growing across multiple runs
    129129
    130 ! If 'dates' file exists, make a backup
     130! If 'dates' file exists in output directory, make a backup
    131131  inquire(file=path(2)(1:length(2))//'dates', exist=ldates_file)
    132132  if (ldates_file.and.init) then
     
    257257
    258258    write(anspec,'(i3.3)') ks
    259     if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
    260       if (ldirect.eq.1) then
    261         open(unitoutgrid,file=path(2)(1:length(2))//'grid_conc_'//adate// &
     259
     260    if (DRYBKDEP.or.WETBKDEP) then !scavdep output
     261      if (DRYBKDEP) &
     262      open(unitoutgrid,file=path(2)(1:length(2))//'grid_drydep_'//adate// &
     263           atime//'_'//anspec,form='unformatted')
     264      if (WETBKDEP) &
     265      open(unitoutgrid,file=path(2)(1:length(2))//'grid_wetdep_'//adate// &
     266           atime//'_'//anspec,form='unformatted')
     267      write(unitoutgrid) itime
     268    else
     269      if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
     270        if (ldirect.eq.1) then
     271          open(unitoutgrid,file=path(2)(1:length(2))//'grid_conc_'//adate// &
     272               atime//'_'//anspec,form='unformatted')
     273        else
     274          open(unitoutgrid,file=path(2)(1:length(2))//'grid_time_'//adate// &
     275               atime//'_'//anspec,form='unformatted')
     276        endif
     277        write(unitoutgrid) itime
     278      endif
     279
     280      if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
     281        open(unitoutgridppt,file=path(2)(1:length(2))//'grid_pptv_'//adate// &
    262282             atime//'_'//anspec,form='unformatted')
    263       else
    264         open(unitoutgrid,file=path(2)(1:length(2))//'grid_time_'//adate// &
    265              atime//'_'//anspec,form='unformatted')
     283
     284        write(unitoutgridppt) itime
    266285      endif
    267       write(unitoutgrid) itime
    268     endif
    269 
    270     if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
    271       open(unitoutgridppt,file=path(2)(1:length(2))//'grid_pptv_'//adate// &
    272            atime//'_'//anspec,form='unformatted')
    273 
    274       write(unitoutgridppt) itime
    275     endif
     286    endif ! if deposition output
    276287
    277288    do kp=1,maxpointspec_act
     
    353364! Concentration output
    354365!*********************
    355         if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
     366        if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5).or.(iout.eq.6)) then
    356367
    357368! Wet deposition
     
    448459                  endif
    449460                  sp_count_r=sp_count_r+1
     461                  if (lparticlecountoutput) then
     462                    sparse_dump_r(sp_count_r)= &
     463                         sp_fact* &
     464                         grid(ix,jy,kz)
     465                  else
    450466                  sparse_dump_r(sp_count_r)= &
    451467                       sp_fact* &
    452468                       grid(ix,jy,kz)* &
    453469                       factor3d(ix,jy,kz)/tot_mu(ks,kp)
     470                  end if
     471
     472
    454473!                 if ((factor(ix,jy,kz)/tot_mu(ks,kp)).eq.0)
    455474!    +              write (*,*) factor(ix,jy,kz),tot_mu(ks,kp),ks,kp
     
    637656!*************************
    638657
    639   do ks=1,nspec
    640     do kp=1,maxpointspec_act
    641       do i=1,numreceptor
    642         creceptor(i,ks)=0.
    643       end do
    644       do jy=0,numygrid-1
    645         do ix=0,numxgrid-1
    646           do l=1,nclassunc
    647             do nage=1,nageclass
    648               do kz=1,numzgrid
    649                 gridunc(ix,jy,kz,ks,kp,l,nage)=0.
    650               end do
    651             end do
    652           end do
    653         end do
    654       end do
    655     end do
    656   end do
     658  creceptor(:,:)=0.
     659  gridunc(:,:,:,:,:,:,:)=0.
    657660
    658661  if (mp_measure_time) call mpif_mtime('rootonly',1)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG