Changeset 2eefa58 in flexpart.git for src/concoutput.f90


Ignore:
Timestamp:
May 27, 2019, 3:28:44 PM (5 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
Children:
6741557
Parents:
f963113
Message:

Added Ronas changes for inversion output

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/concoutput.f90

    r20963b1 r2eefa58  
    7272  real :: sp_fact
    7373  real :: outnum,densityoutrecept(maxreceptor),xl,yl
     74! RLT
     75  real :: densitydryrecept(maxreceptor)
     76  real :: factor_dryrecept(maxreceptor)
    7477
    7578!real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    106109  character(LEN=8),save :: file_stat='REPLACE'
    107110  logical :: ldates_file
     111  logical :: lexist
    108112  integer :: ierr
    109113  character(LEN=100) :: dates_char
     
    203207        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
    204208             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 
    205212      end do
    206213    end do
     
    214221!densityoutrecept(i)=rho(iix,jjy,1,2)
    215222    densityoutrecept(i)=rho(iix,jjy,1,mind)
     223! RLT
     224    densitydryrecept(i)=rho_dry(iix,jjy,1,mind)
    216225  end do
    217226
     227! RLT
     228! conversion factor for output relative to dry air
     229  factor_drygrid=densityoutgrid/densitydrygrid
     230  factor_dryrecept=densityoutrecept/densitydryrecept
    218231
    219232! Output is different for forward and backward simulations
     
    353366! Concentration output
    354367!*********************
    355         if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5).or.(iout.eq.6)) then
     368        if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
    356369
    357370! Wet deposition
     
    614627  end do
    615628
     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
    616672  if (gridtotal.gt.0.) gridtotalunc=gridsigmatotal/gridtotal
    617673  if (wetgridtotal.gt.0.) wetgridtotalunc=wetgridsigmatotal/ &
     
    640696  endif
    641697
    642 
     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
    643715
    644716! Reinitialization of grid
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG