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


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager.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 timemanager(metdata_format)
     
    10890  implicit none
    10991
    110   integer(selected_int_kind(16)) :: idummy,idummy2
    11192  integer :: metdata_format
    11293  integer :: j,ks,kp,l,n,itime=0,nstop,nstop1
    11394! integer :: ksp
    11495  integer :: loutnext,loutstart,loutend
    115   integer :: ix,jy,ldeltat,itage,nage
     96  integer :: ix,jy,ldeltat,itage,nage,idummy
    11697  integer :: i_nan=0,ii_nan,total_nan_intl=0  !added by mc to check instability in CBL scheme
    11798  real :: outnum,weight,prob_rec(maxspec),prob(maxspec),decfact,wetscav
     
    398379              call concoutput(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    399380            endif
    400           else ! surf only
     381          else
    401382            if (verbosity.eq.1) then
    402               print*,'call concoutput_surf '
    403               call system_clock(count_clock)
    404               write(*,*) 'system clock',count_clock - count_clock0   
     383             print*,'call concoutput_surf '
     384             call system_clock(count_clock)
     385             write(*,*) 'system clock',count_clock - count_clock0   
    405386            endif
    406387            if (lnetcdfout.eq.1) then
     
    417398                endif
    418399              else
    419                 call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     400              call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    420401              endif
    421402              if (verbosity.eq.1) then
     
    435416                  call concoutput_inversion_nest(itime,outnum)
    436417                else
    437                   call concoutput_surf_nest(itime,outnum)
    438                 endif
     418                call concoutput_surf_nest(itime,outnum)
     419              endif
    439420              endif
    440421            else
     
    600581       do ks=1,nspec
    601582         if  ((xscav_frac1(j,ks).lt.0)) then
    602             call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy2,wetscav)
     583            call get_wetscav(itime,lsynctime,loutnext,j,ks,grfraction,idummy,idummy,wetscav)
    603584            if (wetscav.gt.0) then
    604585                xscav_frac1(j,ks)=wetscav* &
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG