Changes in src/concoutput_mpi.f90 [6a678e3:20963b1] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/concoutput_mpi.f90

    r6a678e3 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
     
    113113  integer :: ierr
    114114  character(LEN=100) :: dates_char
    115 !  character :: dates_char
    116115
    117116! Measure execution time
     
    129128! This fixes a bug where the dates file kept growing across multiple runs
    130129
    131 ! If 'dates' file exists, make a backup
     130! If 'dates' file exists in output directory, make a backup
    132131  inquire(file=path(2)(1:length(2))//'dates', exist=ldates_file)
    133132  if (ldates_file.and.init) then
     
    258257
    259258    write(anspec,'(i3.3)') ks
    260     if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
    261       if (ldirect.eq.1) then
    262         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// &
    263282             atime//'_'//anspec,form='unformatted')
    264       else
    265         open(unitoutgrid,file=path(2)(1:length(2))//'grid_time_'//adate// &
    266              atime//'_'//anspec,form='unformatted')
     283
     284        write(unitoutgridppt) itime
    267285      endif
    268       write(unitoutgrid) itime
    269     endif
    270 
    271     if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
    272       open(unitoutgridppt,file=path(2)(1:length(2))//'grid_pptv_'//adate// &
    273            atime//'_'//anspec,form='unformatted')
    274 
    275       write(unitoutgridppt) itime
    276     endif
     286    endif ! if deposition output
    277287
    278288    do kp=1,maxpointspec_act
     
    354364! Concentration output
    355365!*********************
    356         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
    357367
    358368! Wet deposition
     
    449459                  endif
    450460                  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
    451466                  sparse_dump_r(sp_count_r)= &
    452467                       sp_fact* &
    453468                       grid(ix,jy,kz)* &
    454469                       factor3d(ix,jy,kz)/tot_mu(ks,kp)
     470                  end if
     471
     472
    455473!                 if ((factor(ix,jy,kz)/tot_mu(ks,kp)).eq.0)
    456474!    +              write (*,*) factor(ix,jy,kz),tot_mu(ks,kp),ks,kp
     
    638656!*************************
    639657
    640   do ks=1,nspec
    641     do kp=1,maxpointspec_act
    642       do i=1,numreceptor
    643         creceptor(i,ks)=0.
    644       end do
    645       do jy=0,numygrid-1
    646         do ix=0,numxgrid-1
    647           do l=1,nclassunc
    648             do nage=1,nageclass
    649               do kz=1,numzgrid
    650                 gridunc(ix,jy,kz,ks,kp,l,nage)=0.
    651               end do
    652             end do
    653           end do
    654         end do
    655       end do
    656     end do
    657   end do
     658  creceptor(:,:)=0.
     659  gridunc(:,:,:,:,:,:,:)=0.
    658660
    659661  if (mp_measure_time) call mpif_mtime('rootonly',1)
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG