Changes in src/concoutput_surf.f90 [2eefa58:16b61a5] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/concoutput_surf.f90

    r2eefa58 r16b61a5  
    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),
     
    104101  character :: adate*8,atime*6
    105102  character(len=3) :: anspec
    106   logical :: lexist
    107103
    108104
     
    184180        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,2)*dz1+ &
    185181             rho(iix,jjy,kzz-1,2)*dz2)/dz
    186 ! RLT
    187         densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,2)*dz1+ &
    188              rho_dry(iix,jjy,kzz-1,2)*dz2)/dz
    189182      end do
    190183    end do
     
    197190    jjy=max(min(nint(yl),nymin1),0)
    198191    densityoutrecept(i)=rho(iix,jjy,1,2)
    199 ! RLT
    200     densitydryrecept(i)=rho_dry(iix,jjy,1,2)
    201192  end do
    202193
    203 ! RLT
    204 ! conversion factor for output relative to dry air
    205   factor_drygrid=densityoutgrid/densitydrygrid
    206   factor_dryrecept=densityoutrecept/densitydryrecept
    207194
    208195! Output is different for forward and backward simulations
     
    609596  end do
    610597
    611 ! RLT Aug 2017
    612 ! Write out conversion factor for dry air
    613   inquire(file=path(2)(1:length(2))//'factor_drygrid',exist=lexist)
    614   if (lexist) then
    615     ! open and append
    616     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
    617             status='old',action='write',access='append')
    618   else
    619     ! create new
    620     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
    621             status='new',action='write')
    622   endif
    623   sp_count_i=0
    624   sp_count_r=0
    625   sp_fact=-1.
    626   sp_zer=.true.
    627   do kz=1,1
    628     do jy=0,numygrid-1
    629       do ix=0,numxgrid-1
    630         if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
    631           if (sp_zer.eqv..true.) then ! first value not equal to one
    632             sp_count_i=sp_count_i+1
    633             sparse_dump_i(sp_count_i)= &
    634                   ix+jy*numxgrid+kz*numxgrid*numygrid
    635             sp_zer=.false.
    636             sp_fact=sp_fact*(-1.)
    637           endif
    638           sp_count_r=sp_count_r+1
    639           sparse_dump_r(sp_count_r)= &
    640                sp_fact*factor_drygrid(ix,jy,kz)
    641         else ! factor is one
    642           sp_zer=.true.
    643         endif
    644       end do
    645     end do
    646   end do
    647   write(unitoutfactor) sp_count_i
    648   write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
    649   write(unitoutfactor) sp_count_r
    650   write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
    651   close(unitoutfactor)
    652 
    653 
    654598  if (gridtotal.gt.0.) gridtotalunc=gridsigmatotal/gridtotal
    655599  if (wetgridtotal.gt.0.) wetgridtotalunc=wetgridsigmatotal/ &
     
    678622  endif
    679623
    680 ! RLT Aug 2017
    681 ! Write out conversion factor for dry air
    682   if (numreceptor.gt.0) then
    683     inquire(file=path(2)(1:length(2))//'factor_dryreceptor',exist=lexist)
    684      if (lexist) then
    685      ! open and append
    686       open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
    687               status='old',action='write',access='append')
    688     else
    689       ! create new
    690       open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
    691               status='new',action='write')
    692     endif
    693     write(unitoutfactor) itime
    694     write(unitoutfactor) (factor_dryrecept(i),i=1,numreceptor)
    695     close(unitoutfactor)
    696   endif
     624
    697625
    698626! Reinitialization of grid
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG