Changeset 1070b4c in flexpart.git for src/concoutput_mpi.f90


Ignore:
Timestamp:
Aug 27, 2020, 9:51:56 PM (4 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
GFS_025, dev
Children:
b0ecb61
Parents:
8c0ae9b (diff), a803521 (diff)
Note: this is a merge changeset, the changes displayed below correspond to the merge itself.
Use the (diff) links above to see all the changes relative to each parent.
Message:

Merge branch 'espen' into dev

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/concoutput_mpi.f90

    r92fab65 ra803521  
    5959  real :: sp_fact
    6060  real :: outnum,densityoutrecept(maxreceptor),xl,yl
     61! RLT
     62  real :: densitydryrecept(maxreceptor)
     63  real :: factor_dryrecept(maxreceptor)
    6164
    6265!real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    9396  character(LEN=8),save :: file_stat='REPLACE'
    9497  logical :: ldates_file
     98  logical :: lexist
    9599  integer :: ierr
    96100  character(LEN=100) :: dates_char
     
    194198        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
    195199             rho(iix,jjy,kzz-1,mind)*dz2)/dz
     200! RLT
     201        densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,mind)*dz1+ &
     202             rho_dry(iix,jjy,kzz-1,mind)*dz2)/dz 
    196203      end do
    197204    end do
     
    205212    !densityoutrecept(i)=rho(iix,jjy,1,2)
    206213    densityoutrecept(i)=rho(iix,jjy,1,mind)
     214! RLT
     215    densitydryrecept(i)=rho_dry(iix,jjy,1,mind)
    207216  end do
    208217
     218! RLT
     219! conversion factor for output relative to dry air
     220  factor_drygrid=densityoutgrid/densitydrygrid
     221  factor_dryrecept=densityoutrecept/densitydryrecept
    209222
    210223! Output is different for forward and backward simulations
     
    259272        write(unitoutgrid) itime
    260273      endif
    261 
    262274      if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
    263275        open(unitoutgridppt,file=path(2)(1:length(2))//'grid_pptv_'//adate// &
    264276             atime//'_'//anspec,form='unformatted')
    265 
    266277        write(unitoutgridppt) itime
    267278      endif
     
    607618  end do
    608619
     620! RLT Aug 2017
     621! Write out conversion factor for dry air
     622  inquire(file=path(2)(1:length(2))//'factor_drygrid',exist=lexist)
     623  if (lexist) then
     624    ! open and append
     625    open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
     626            status='old',action='write',access='append')
     627  else
     628    ! create new
     629    open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
     630            status='new',action='write')
     631  endif
     632  sp_count_i=0
     633  sp_count_r=0
     634  sp_fact=-1.
     635  sp_zer=.true.
     636  do kz=1,numzgrid
     637    do jy=0,numygrid-1
     638      do ix=0,numxgrid-1
     639        if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
     640          if (sp_zer.eqv..true.) then ! first value not equal to one
     641            sp_count_i=sp_count_i+1
     642            sparse_dump_i(sp_count_i)= &
     643                  ix+jy*numxgrid+kz*numxgrid*numygrid
     644            sp_zer=.false.
     645            sp_fact=sp_fact*(-1.)
     646          endif
     647          sp_count_r=sp_count_r+1
     648          sparse_dump_r(sp_count_r)= &
     649               sp_fact*factor_drygrid(ix,jy,kz)
     650        else ! factor is one
     651          sp_zer=.true.
     652        endif
     653      end do
     654    end do
     655  end do
     656  write(unitoutfactor) sp_count_i
     657  write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
     658  write(unitoutfactor) sp_count_r
     659  write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
     660  close(unitoutfactor)
     661
     662
    609663  if (gridtotal.gt.0.) gridtotalunc=gridsigmatotal/gridtotal
    610664  if (wetgridtotal.gt.0.) wetgridtotalunc=wetgridsigmatotal/ &
     
    633687  endif
    634688
    635 
     689! RLT Aug 2017
     690! Write out conversion factor for dry air
     691  if (numreceptor.gt.0) then
     692    inquire(file=path(2)(1:length(2))//'factor_dryreceptor',exist=lexist)
     693     if (lexist) then
     694     ! open and append
     695      open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
     696              status='old',action='write',access='append')
     697    else
     698      ! create new
     699      open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
     700              status='new',action='write')
     701    endif
     702    write(unitoutfactor) itime
     703    write(unitoutfactor) (factor_dryrecept(i),i=1,numreceptor)
     704    close(unitoutfactor)
     705  endif
    636706
    637707! Reinitialization of grid
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG