Changeset f3054ea in flexpart.git for src/concoutput_mpi.f90


Ignore:
Timestamp:
Aug 27, 2020, 8:00:15 PM (4 years ago)
Author:
Espen Sollum <eso@…>
Branches:
GFS_025, dev
Children:
4ab2fbf
Parents:
a756649
Message:

Changed from grib_api to eccodes. MPI: implemented linversionout=1; fixed calculation of grid_initial fields.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/concoutput_mpi.f90

    r6741557 rf3054ea  
    7777  real :: sp_fact
    7878  real :: outnum,densityoutrecept(maxreceptor),xl,yl
     79! RLT
     80  real :: densitydryrecept(maxreceptor)
     81  real :: factor_dryrecept(maxreceptor)
    7982
    8083!real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    111114  character(LEN=8),save :: file_stat='REPLACE'
    112115  logical :: ldates_file
     116  logical :: lexist
    113117  integer :: ierr
    114118  character(LEN=100) :: dates_char
     
    212216        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
    213217             rho(iix,jjy,kzz-1,mind)*dz2)/dz
     218! RLT
     219        densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,mind)*dz1+ &
     220             rho_dry(iix,jjy,kzz-1,mind)*dz2)/dz 
    214221      end do
    215222    end do
     
    223230    !densityoutrecept(i)=rho(iix,jjy,1,2)
    224231    densityoutrecept(i)=rho(iix,jjy,1,mind)
     232! RLT
     233    densitydryrecept(i)=rho_dry(iix,jjy,1,mind)
    225234  end do
    226235
     236! RLT
     237! conversion factor for output relative to dry air
     238  factor_drygrid=densityoutgrid/densitydrygrid
     239  factor_dryrecept=densityoutrecept/densitydryrecept
    227240
    228241! Output is different for forward and backward simulations
     
    277290        write(unitoutgrid) itime
    278291      endif
    279 
    280292      if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
    281293        open(unitoutgridppt,file=path(2)(1:length(2))//'grid_pptv_'//adate// &
    282294             atime//'_'//anspec,form='unformatted')
    283 
    284295        write(unitoutgridppt) itime
    285296      endif
     
    625636  end do
    626637
     638! RLT Aug 2017
     639! Write out conversion factor for dry air
     640  inquire(file=path(2)(1:length(2))//'factor_drygrid',exist=lexist)
     641  if (lexist) then
     642    ! open and append
     643    open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
     644            status='old',action='write',access='append')
     645  else
     646    ! create new
     647    open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
     648            status='new',action='write')
     649  endif
     650  sp_count_i=0
     651  sp_count_r=0
     652  sp_fact=-1.
     653  sp_zer=.true.
     654  do kz=1,numzgrid
     655    do jy=0,numygrid-1
     656      do ix=0,numxgrid-1
     657        if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
     658          if (sp_zer.eqv..true.) then ! first value not equal to one
     659            sp_count_i=sp_count_i+1
     660            sparse_dump_i(sp_count_i)= &
     661                  ix+jy*numxgrid+kz*numxgrid*numygrid
     662            sp_zer=.false.
     663            sp_fact=sp_fact*(-1.)
     664          endif
     665          sp_count_r=sp_count_r+1
     666          sparse_dump_r(sp_count_r)= &
     667               sp_fact*factor_drygrid(ix,jy,kz)
     668        else ! factor is one
     669          sp_zer=.true.
     670        endif
     671      end do
     672    end do
     673  end do
     674  write(unitoutfactor) sp_count_i
     675  write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
     676  write(unitoutfactor) sp_count_r
     677  write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
     678  close(unitoutfactor)
     679
     680
    627681  if (gridtotal.gt.0.) gridtotalunc=gridsigmatotal/gridtotal
    628682  if (wetgridtotal.gt.0.) wetgridtotalunc=wetgridsigmatotal/ &
     
    651705  endif
    652706
    653 
     707! RLT Aug 2017
     708! Write out conversion factor for dry air
     709  if (numreceptor.gt.0) then
     710    inquire(file=path(2)(1:length(2))//'factor_dryreceptor',exist=lexist)
     711     if (lexist) then
     712     ! open and append
     713      open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
     714              status='old',action='write',access='append')
     715    else
     716      ! create new
     717      open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
     718              status='new',action='write')
     719    endif
     720    write(unitoutfactor) itime
     721    write(unitoutfactor) (factor_dryrecept(i),i=1,numreceptor)
     722    close(unitoutfactor)
     723  endif
    654724
    655725! Reinitialization of grid
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG