Changes in src/concoutput_nest.f90 [2eefa58:7d02c2f] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/concoutput_nest.f90

    r2eefa58 r7d02c2f  
    7070  real :: sp_fact
    7171  real :: outnum,densityoutrecept(maxreceptor),xl,yl
    72 ! RLT
    73   real :: densitydryrecept(maxreceptor)
    74   real :: factor_dryrecept(maxreceptor)
    7572
    7673  !real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    9996  character :: adate*8,atime*6
    10097  character(len=3) :: anspec
    101   logical :: lexist
    10298  integer :: mind
    10399! mind        eso:added to ensure identical results between 2&3-fields versions
     
    168164        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
    169165             rho(iix,jjy,kzz-1,mind)*dz2)/dz
    170 ! RLT
    171         densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,mind)*dz1+ &
    172              rho_dry(iix,jjy,kzz-1,mind)*dz2)/dz
    173166      end do
    174167    end do
     
    182175    !densityoutrecept(i)=rho(iix,jjy,1,2)
    183176    densityoutrecept(i)=rho(iix,jjy,1,mind)
    184 ! RLT
    185     densitydryrecept(i)=rho_dry(iix,jjy,1,mind)
    186177  end do
    187178
    188 ! RLT
    189 ! conversion factor for output relative to dry air
    190   factor_drygrid=densityoutgrid/densitydrygrid
    191   factor_dryrecept=densityoutrecept/densitydryrecept
    192179
    193180  ! Output is different for forward and backward simulations
     
    564551  end do
    565552
    566 ! RLT Aug 2017
    567 ! Write out conversion factor for dry air
    568   inquire(file=path(2)(1:length(2))//'factor_drygrid_nest',exist=lexist)
    569   if (lexist) then
    570     ! open and append
    571     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid_nest',form='unformatted',&
    572             status='old',action='write',access='append')
    573   else
    574     ! create new
    575     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid_nest',form='unformatted',&
    576             status='new',action='write')
    577   endif
    578   sp_count_i=0
    579   sp_count_r=0
    580   sp_fact=-1.
    581   sp_zer=.true.
    582   do kz=1,numzgrid
    583     do jy=0,numygridn-1
    584       do ix=0,numxgridn-1
    585         if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
    586           if (sp_zer.eqv..true.) then ! first value not equal to one
    587             sp_count_i=sp_count_i+1
    588             sparse_dump_i(sp_count_i)= &
    589                   ix+jy*numxgridn+kz*numxgridn*numygridn
    590             sp_zer=.false.
    591             sp_fact=sp_fact*(-1.)
    592           endif
    593           sp_count_r=sp_count_r+1
    594           sparse_dump_r(sp_count_r)= &
    595                sp_fact*factor_drygrid(ix,jy,kz)
    596         else ! factor is one
    597           sp_zer=.true.
    598         endif
    599       end do
    600     end do
    601   end do
    602   write(unitoutfactor) sp_count_i
    603   write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
    604   write(unitoutfactor) sp_count_r
    605   write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
    606   close(unitoutfactor)
    607553
    608554
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG