Changes in src/concoutput.f90 [2eefa58:20963b1] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/concoutput.f90

    r2eefa58 r20963b1  
    7272  real :: sp_fact
    7373  real :: outnum,densityoutrecept(maxreceptor),xl,yl
    74 ! RLT
    75   real :: densitydryrecept(maxreceptor)
    76   real :: factor_dryrecept(maxreceptor)
    7774
    7875!real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    109106  character(LEN=8),save :: file_stat='REPLACE'
    110107  logical :: ldates_file
    111   logical :: lexist
    112108  integer :: ierr
    113109  character(LEN=100) :: dates_char
     
    207203        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
    208204             rho(iix,jjy,kzz-1,mind)*dz2)/dz
    209 ! RLT
    210         densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,mind)*dz1+ &
    211              rho_dry(iix,jjy,kzz-1,mind)*dz2)/dz 
    212205      end do
    213206    end do
     
    221214!densityoutrecept(i)=rho(iix,jjy,1,2)
    222215    densityoutrecept(i)=rho(iix,jjy,1,mind)
    223 ! RLT
    224     densitydryrecept(i)=rho_dry(iix,jjy,1,mind)
    225216  end do
    226217
    227 ! RLT
    228 ! conversion factor for output relative to dry air
    229   factor_drygrid=densityoutgrid/densitydrygrid
    230   factor_dryrecept=densityoutrecept/densitydryrecept
    231218
    232219! Output is different for forward and backward simulations
     
    366353! Concentration output
    367354!*********************
    368         if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
     355        if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5).or.(iout.eq.6)) then
    369356
    370357! Wet deposition
     
    627614  end do
    628615
    629 ! RLT Aug 2017
    630 ! Write out conversion factor for dry air
    631   inquire(file=path(2)(1:length(2))//'factor_drygrid',exist=lexist)
    632   if (lexist) then
    633     ! open and append
    634     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
    635             status='old',action='write',access='append')
    636   else
    637     ! create new
    638     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
    639             status='new',action='write')
    640   endif
    641   sp_count_i=0
    642   sp_count_r=0
    643   sp_fact=-1.
    644   sp_zer=.true.
    645   do kz=1,numzgrid
    646     do jy=0,numygrid-1
    647       do ix=0,numxgrid-1
    648         if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
    649           if (sp_zer.eqv..true.) then ! first value not equal to one
    650             sp_count_i=sp_count_i+1
    651             sparse_dump_i(sp_count_i)= &
    652                   ix+jy*numxgrid+kz*numxgrid*numygrid
    653             sp_zer=.false.
    654             sp_fact=sp_fact*(-1.)
    655           endif
    656           sp_count_r=sp_count_r+1
    657           sparse_dump_r(sp_count_r)= &
    658                sp_fact*factor_drygrid(ix,jy,kz)
    659         else ! factor is one
    660           sp_zer=.true.
    661         endif
    662       end do
    663     end do
    664   end do
    665   write(unitoutfactor) sp_count_i
    666   write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
    667   write(unitoutfactor) sp_count_r
    668   write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
    669   close(unitoutfactor)
    670 
    671 
    672616  if (gridtotal.gt.0.) gridtotalunc=gridsigmatotal/gridtotal
    673617  if (wetgridtotal.gt.0.) wetgridtotalunc=wetgridsigmatotal/ &
     
    696640  endif
    697641
    698 ! RLT Aug 2017
    699 ! Write out conversion factor for dry air
    700   if (numreceptor.gt.0) then
    701     inquire(file=path(2)(1:length(2))//'factor_dryreceptor',exist=lexist)
    702      if (lexist) then
    703      ! open and append
    704       open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
    705               status='old',action='write',access='append')
    706     else
    707       ! create new
    708       open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
    709               status='new',action='write')
    710     endif
    711     write(unitoutfactor) itime
    712     write(unitoutfactor) (factor_dryrecept(i),i=1,numreceptor)
    713     close(unitoutfactor)
    714   endif
     642
    715643
    716644! Reinitialization of grid
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG