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


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager.f90

    r92fab65 rf3054ea  
    1 ! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
    2 ! SPDX-License-Identifier: GPL-3.0-or-later
     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!**********************************************************************
    321
    422subroutine timemanager(metdata_format)
     
    90108  implicit none
    91109
     110  integer(selected_int_kind(16)) :: idummy,idummy2
    92111  integer :: metdata_format
    93112  integer :: j,ks,kp,l,n,itime=0,nstop,nstop1
    94113! integer :: ksp
    95114  integer :: loutnext,loutstart,loutend
    96   integer :: ix,jy,ldeltat,itage,nage,idummy
     115  integer :: ix,jy,ldeltat,itage,nage
    97116  integer :: i_nan=0,ii_nan,total_nan_intl=0  !added by mc to check instability in CBL scheme
    98117  real :: outnum,weight,prob_rec(maxspec),prob(maxspec),decfact,wetscav
     
    379398              call concoutput(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    380399            endif
    381           else
     400          else ! surf only
    382401            if (verbosity.eq.1) then
    383              print*,'call concoutput_surf '
    384              call system_clock(count_clock)
    385              write(*,*) 'system clock',count_clock - count_clock0   
     402              print*,'call concoutput_surf '
     403              call system_clock(count_clock)
     404              write(*,*) 'system clock',count_clock - count_clock0   
    386405            endif
    387406            if (lnetcdfout.eq.1) then
     
    398417                endif
    399418              else
    400               call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     419                call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    401420              endif
    402421              if (verbosity.eq.1) then
     
    416435                  call concoutput_inversion_nest(itime,outnum)
    417436                else
    418                 call concoutput_surf_nest(itime,outnum)
    419               endif
     437                  call concoutput_surf_nest(itime,outnum)
     438                endif
    420439              endif
    421440            else
     
    581600       do ks=1,nspec
    582601         if  ((xscav_frac1(j,ks).lt.0)) then
    583             call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy,wetscav)
     602            call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy2,wetscav)
    584603            if (wetscav.gt.0) then
    585604                xscav_frac1(j,ks)=wetscav* &
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG