Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/timemanager.f90

    r30 r20  
    4343  !     call convection BEFORE new fields are read in BWD mode                 *
    4444  !  Changes Caroline Forster, Feb 2005                                        *
    45   !   new interface between flexpart and convection scheme                     *
    46   !   Emanuel's latest subroutine convect43c.f is used                         *
    47   !  Changes Stefan Henne, Harald Sodemann, 2013-2014                          *
    48   !   added netcdf output code                                                 *
     45  !new interface between flexpart and convection scheme                        *
     46  !Emanuel's latest subroutine convect43c.f is used                            *
    4947  !*****************************************************************************
    5048  !                                                                            *
    5149  ! Variables:                                                                 *
    52   ! dep                .true. if either wet or dry deposition is switched on   *
     50  ! DEP                .true. if either wet or dry deposition is switched on   *
    5351  ! decay(maxspec) [1/s] decay constant for radioactive decay                  *
    54   ! drydep             .true. if dry deposition is switched on                 *
     52  ! DRYDEP             .true. if dry deposition is switched on                 *
    5553  ! ideltas [s]        modelling period                                        *
    5654  ! itime [s]          actual temporal position of calculation                 *
     
    7270  ! prob               probability of absorption at ground due to dry          *
    7371  !                    deposition                                              *
    74   ! wetdep             .true. if wet deposition is switched on                 *
     72  ! WETDEP             .true. if wet deposition is switched on                 *
    7573  ! weight             weight for each concentration sample (1/2 or 1)         *
    7674  ! uap(maxpart),ucp(maxpart),uzp(maxpart) = random velocities due to          *
     
    9492  use par_mod
    9593  use com_mod
    96 #ifdef NETCDF_OUTPUT
    97   use netcdf_output_mod, only: concoutput_netcdf, concoutput_nest_netcdf,concoutput_surf_netcdf, concoutput_surf_nest_netcdf
    98 #endif
    9994
    10095  implicit none
     
    134129
    135130
    136   itime=0
    137   !write(*,45) itime,numpart,gridtotalunc,wetgridtotalunc,drygridtotalunc
    138   write(*,46) float(itime)/3600,itime,numpart
    139131  if (verbosity.gt.0) then
    140132    write (*,*) 'timemanager> starting simulation'
     
    146138
    147139  do itime=0,ideltas,lsynctime
     140
    148141
    149142  ! Computation of wet deposition, OH reaction and mass transfer
     
    157150  !********************************************************************
    158151
    159     if (wetdep .and. itime .ne. 0 .and. numpart .gt. 0) then
     152    if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
    160153        if (verbosity.gt.0) then
    161154           write (*,*) 'timemanager> call wetdepo'
     
    164157    endif
    165158
    166     if (ohrea .and. itime .ne. 0 .and. numpart .gt. 0) &
     159    if (OHREA .and. itime .ne. 0 .and. numpart .gt. 0) &
    167160         call ohreaction(itime,lsynctime,loutnext)
    168161
    169     if (assspec .and. itime .ne. 0 .and. numpart .gt. 0) then
     162    if (ASSSPEC .and. itime .ne. 0 .and. numpart .gt. 0) then
    170163       stop 'associated species not yet implemented!'
    171164  !     call transferspec(itime,lsynctime,loutnext)
     
    245238  !***********************************************************************
    246239
    247     if (dep.and.(itime.eq.loutnext).and.(ldirect.gt.0)) then
     240    if (DEP.and.(itime.eq.loutnext).and.(ldirect.gt.0)) then
    248241      do ks=1,nspec
    249242      do kp=1,maxpointspec_act
     
    355348        if ((iout.le.3.).or.(iout.eq.5)) then
    356349          if (surf_only.ne.1) then
    357             if (lnetcdfout.eq.1) then
    358 #ifdef NETCDF_OUTPUT
    359               call concoutput_netcdf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    360 #endif
    361             else
    362               call concoutput(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    363             endif
     350          call concoutput(itime,outnum,gridtotalunc, &
     351               wetgridtotalunc,drygridtotalunc)
    364352          else 
    365             if (verbosity.eq.1) then
    366              print*,'call concoutput_surf '
    367              call system_clock(count_clock)
    368              write(*,*) 'system clock',count_clock - count_clock0   
    369             endif
    370             if (lnetcdfout.eq.1) then
    371 #ifdef NETCDF_OUTPUT
    372               call concoutput_surf_netcdf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    373 #endif
    374             else
    375               call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    376               if (verbosity.eq.1) then
    377                 print*,'called concoutput_surf '
    378                 call system_clock(count_clock)
    379                 write(*,*) 'system clock',count_clock - count_clock0   
    380               endif
    381             endif
     353  if (verbosity.eq.1) then
     354     print*,'call concoutput_surf '
     355     CALL SYSTEM_CLOCK(count_clock)
     356     WRITE(*,*) 'SYSTEM_CLOCK',count_clock - count_clock0   
     357  endif
     358          call concoutput_surf(itime,outnum,gridtotalunc, &
     359               wetgridtotalunc,drygridtotalunc)
     360  if (verbosity.eq.1) then
     361     print*,'called concoutput_surf '
     362     CALL SYSTEM_CLOCK(count_clock)
     363     WRITE(*,*) 'SYSTEM_CLOCK',count_clock - count_clock0   
     364  endif
    382365          endif
    383366
    384           if (nested_output .eq. 1) then
    385             if (lnetcdfout.eq.0) then
    386               if (surf_only.ne.1) then
    387                 call concoutput_nest(itime,outnum)
    388               else
    389                 call concoutput_surf_nest(itime,outnum)
    390               endif
    391             else
    392 #ifdef NETCDF_OUTPUT
    393               if (surf_only.ne.1) then
    394                 call concoutput_nest_netcdf(itime,outnum)
    395               else
    396                 call concoutput_surf_nest_netcdf(itime,outnum)
    397               endif
    398 #endif
    399             endif
    400           endif
     367          if ((nested_output.eq.1).and.(surf_only.ne.1)) call concoutput_nest(itime,outnum)
     368          if ((nested_output.eq.1).and.(surf_only.eq.1)) call concoutput_surf_nest(itime,outnum)
    401369          outnum=0.
    402370        endif
    403371        if ((iout.eq.4).or.(iout.eq.5)) call plumetraj(itime)
    404372        if (iflux.eq.1) call fluxoutput(itime)
    405         !write(*,45) itime,numpart,gridtotalunc,wetgridtotalunc,drygridtotalunc
    406         write(*,46) float(itime)/3600,itime,numpart
    407 45      format(i9,' SECONDS SIMULATED: ',i8, ' PARTICLES:    Uncertainty: ',3f7.3)
    408 46      format(' Simulated ',f7.1,' hours (',i9,' s), ',i8, ' particles')
     373        write(*,45) itime,numpart,gridtotalunc,wetgridtotalunc, &
     374             drygridtotalunc
     37545      format(i9,' SECONDS SIMULATED: ',i8, &
     376             ' PARTICLES:    Uncertainty: ',3f7.3)
    409377        if (ipout.ge.1) call partoutput(itime)    ! dump particle positions
    410378        loutnext=loutnext+loutstep
     
    504472  !****************************
    505473
    506         xold=real(xtra1(j))
    507         yold=real(ytra1(j))
     474        xold=xtra1(j)
     475        yold=ytra1(j)
    508476        zold=ztra1(j)
    509477
     
    545513            endif
    546514
    547             if (drydepspec(ks)) then        ! dry deposition
     515            if (DRYDEPSPEC(ks)) then        ! dry deposition
    548516              drydeposit(ks)=xmass1(j,ks)*prob(ks)*decfact
    549517              xmass1(j,ks)=xmass1(j,ks)*(1.-prob(ks))*decfact
     
    556524            endif
    557525
     526
    558527            if (mdomainfill.eq.0) then
    559528              if (xmass(npoint(j),ks).gt.0.) &
     
    567536          if (xmassfract.lt.0.0001) then   ! terminate all particles carrying less mass
    568537            itra1(j)=-999999999
    569             if (verbosity.gt.0) then
    570               print*,'terminated particle ',j,' for small mass'
    571             endif
    572538          endif
    573539
    574540  !        Sabine Eckhardt, June 2008
    575541  !        don't create depofield for backward runs
    576           if (drydep.AND.(ldirect.eq.1)) then
    577             call drydepokernel(nclass(j),drydeposit,real(xtra1(j)),real(ytra1(j)),nage,kp)
    578             if (nested_output.eq.1) then
    579               call drydepokernel_nest(nclass(j),drydeposit,real(xtra1(j)),real(ytra1(j)),nage,kp)
    580             endif
     542          if (DRYDEP.AND.(ldirect.eq.1)) then
     543            call drydepokernel(nclass(j),drydeposit,real(xtra1(j)), &
     544                 real(ytra1(j)),nage,kp)
     545            if (nested_output.eq.1) call drydepokernel_nest( &
     546                 nclass(j),drydeposit,real(xtra1(j)),real(ytra1(j)), &
     547                 nage,kp)
    581548          endif
    582549
     
    585552
    586553          if (abs(itra1(j)-itramem(j)).ge.lage(nageclass)) then
    587             if (linit_cond.ge.1) call initial_cond_calc(itime+lsynctime,j)
     554            if (linit_cond.ge.1) &
     555                 call initial_cond_calc(itime+lsynctime,j)
    588556            itra1(j)=-999999999
    589             if (verbosity.gt.0) then
    590               print*,'terminated particle ',j,' for age'
    591             endif
    592557          endif
    593558        endif
     
    617582
    618583  if (iflux.eq.1) then
    619     deallocate(flux)
     584      deallocate(flux)
    620585  endif
    621   if (ohrea.eqv..TRUE.) then
    622     deallocate(OH_field,OH_field_height)
     586  if (OHREA.eqv..TRUE.) then
     587      deallocate(OH_field,OH_field_height)
    623588  endif
    624589  if (ldirect.gt.0) then
    625     deallocate(drygridunc,wetgridunc)
     590  deallocate(drygridunc,wetgridunc)
    626591  endif
    627592  deallocate(gridunc)
     
    630595  deallocate(xmasssave)
    631596  if (nested_output.eq.1) then
    632     deallocate(orooutn, arean, volumen)
    633     if (ldirect.gt.0) then
    634       deallocate(griduncn,drygriduncn,wetgriduncn)
    635     endif
     597     deallocate(orooutn, arean, volumen)
     598     if (ldirect.gt.0) then
     599     deallocate(griduncn,drygriduncn,wetgriduncn)
     600     endif
    636601  endif
    637602  deallocate(outheight,outheighthalf)
    638   deallocate(oroout,area,volume)
     603  deallocate(oroout, area, volume)
    639604
    640605end subroutine timemanager
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG