Changes in src/concoutput_mpi.f90 [f3054ea:92fab65] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/concoutput_mpi.f90

    rf3054ea r92fab65  
    1 !**********************************************************************
    2 ! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
    3 ! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
    4 ! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
    5 !                                                                     *
    6 ! This file is part of FLEXPART.                                      *
    7 !                                                                     *
    8 ! FLEXPART is free software: you can redistribute it and/or modify    *
    9 ! it under the terms of the GNU General Public License as published by*
    10 ! the Free Software Foundation, either version 3 of the License, or   *
    11 ! (at your option) any later version.                                 *
    12 !                                                                     *
    13 ! FLEXPART is distributed in the hope that it will be useful,         *
    14 ! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
    15 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
    16 ! GNU General Public License for more details.                        *
    17 !                                                                     *
    18 ! You should have received a copy of the GNU General Public License   *
    19 ! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
    20 !**********************************************************************
     1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
     2! SPDX-License-Identifier: GPL-3.0-or-later
    213
    224subroutine concoutput(itime,outnum,gridtotalunc,wetgridtotalunc, &
     
    7759  real :: sp_fact
    7860  real :: outnum,densityoutrecept(maxreceptor),xl,yl
    79 ! RLT
    80   real :: densitydryrecept(maxreceptor)
    81   real :: factor_dryrecept(maxreceptor)
    8261
    8362!real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    11493  character(LEN=8),save :: file_stat='REPLACE'
    11594  logical :: ldates_file
    116   logical :: lexist
    11795  integer :: ierr
    11896  character(LEN=100) :: dates_char
     
    216194        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
    217195             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 
    221196      end do
    222197    end do
     
    230205    !densityoutrecept(i)=rho(iix,jjy,1,2)
    231206    densityoutrecept(i)=rho(iix,jjy,1,mind)
    232 ! RLT
    233     densitydryrecept(i)=rho_dry(iix,jjy,1,mind)
    234207  end do
    235208
    236 ! RLT
    237 ! conversion factor for output relative to dry air
    238   factor_drygrid=densityoutgrid/densitydrygrid
    239   factor_dryrecept=densityoutrecept/densitydryrecept
    240209
    241210! Output is different for forward and backward simulations
     
    290259        write(unitoutgrid) itime
    291260      endif
     261
    292262      if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
    293263        open(unitoutgridppt,file=path(2)(1:length(2))//'grid_pptv_'//adate// &
    294264             atime//'_'//anspec,form='unformatted')
     265
    295266        write(unitoutgridppt) itime
    296267      endif
     
    636607  end do
    637608
    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 
    681609  if (gridtotal.gt.0.) gridtotalunc=gridsigmatotal/gridtotal
    682610  if (wetgridtotal.gt.0.) wetgridtotalunc=wetgridsigmatotal/ &
     
    705633  endif
    706634
    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
     635
    724636
    725637! Reinitialization of grid
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG