Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/timemanager.f90

    r20 r30  
    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                            *
     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                                                 *
    4749  !*****************************************************************************
    4850  !                                                                            *
    4951  ! Variables:                                                                 *
    50   ! DEP                .true. if either wet or dry deposition is switched on   *
     52  ! dep                .true. if either wet or dry deposition is switched on   *
    5153  ! decay(maxspec) [1/s] decay constant for radioactive decay                  *
    52   ! DRYDEP             .true. if dry deposition is switched on                 *
     54  ! drydep             .true. if dry deposition is switched on                 *
    5355  ! ideltas [s]        modelling period                                        *
    5456  ! itime [s]          actual temporal position of calculation                 *
     
    7072  ! prob               probability of absorption at ground due to dry          *
    7173  !                    deposition                                              *
    72   ! WETDEP             .true. if wet deposition is switched on                 *
     74  ! wetdep             .true. if wet deposition is switched on                 *
    7375  ! weight             weight for each concentration sample (1/2 or 1)         *
    7476  ! uap(maxpart),ucp(maxpart),uzp(maxpart) = random velocities due to          *
     
    9294  use par_mod
    9395  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
    9499
    95100  implicit none
     
    129134
    130135
     136  itime=0
     137  !write(*,45) itime,numpart,gridtotalunc,wetgridtotalunc,drygridtotalunc
     138  write(*,46) float(itime)/3600,itime,numpart
    131139  if (verbosity.gt.0) then
    132140    write (*,*) 'timemanager> starting simulation'
     
    138146
    139147  do itime=0,ideltas,lsynctime
    140 
    141148
    142149  ! Computation of wet deposition, OH reaction and mass transfer
     
    150157  !********************************************************************
    151158
    152     if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     159    if (wetdep .and. itime .ne. 0 .and. numpart .gt. 0) then
    153160        if (verbosity.gt.0) then
    154161           write (*,*) 'timemanager> call wetdepo'
     
    157164    endif
    158165
    159     if (OHREA .and. itime .ne. 0 .and. numpart .gt. 0) &
     166    if (ohrea .and. itime .ne. 0 .and. numpart .gt. 0) &
    160167         call ohreaction(itime,lsynctime,loutnext)
    161168
    162     if (ASSSPEC .and. itime .ne. 0 .and. numpart .gt. 0) then
     169    if (assspec .and. itime .ne. 0 .and. numpart .gt. 0) then
    163170       stop 'associated species not yet implemented!'
    164171  !     call transferspec(itime,lsynctime,loutnext)
     
    238245  !***********************************************************************
    239246
    240     if (DEP.and.(itime.eq.loutnext).and.(ldirect.gt.0)) then
     247    if (dep.and.(itime.eq.loutnext).and.(ldirect.gt.0)) then
    241248      do ks=1,nspec
    242249      do kp=1,maxpointspec_act
     
    348355        if ((iout.le.3.).or.(iout.eq.5)) then
    349356          if (surf_only.ne.1) then
    350           call concoutput(itime,outnum,gridtotalunc, &
    351                wetgridtotalunc,drygridtotalunc)
     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
    352364          else 
    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
     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
    365382          endif
    366383
    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)
     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
    369401          outnum=0.
    370402        endif
    371403        if ((iout.eq.4).or.(iout.eq.5)) call plumetraj(itime)
    372404        if (iflux.eq.1) call fluxoutput(itime)
    373         write(*,45) itime,numpart,gridtotalunc,wetgridtotalunc, &
    374              drygridtotalunc
    375 45      format(i9,' SECONDS SIMULATED: ',i8, &
    376              ' PARTICLES:    Uncertainty: ',3f7.3)
     405        !write(*,45) itime,numpart,gridtotalunc,wetgridtotalunc,drygridtotalunc
     406        write(*,46) float(itime)/3600,itime,numpart
     40745      format(i9,' SECONDS SIMULATED: ',i8, ' PARTICLES:    Uncertainty: ',3f7.3)
     40846      format(' Simulated ',f7.1,' hours (',i9,' s), ',i8, ' particles')
    377409        if (ipout.ge.1) call partoutput(itime)    ! dump particle positions
    378410        loutnext=loutnext+loutstep
     
    472504  !****************************
    473505
    474         xold=xtra1(j)
    475         yold=ytra1(j)
     506        xold=real(xtra1(j))
     507        yold=real(ytra1(j))
    476508        zold=ztra1(j)
    477509
     
    513545            endif
    514546
    515             if (DRYDEPSPEC(ks)) then        ! dry deposition
     547            if (drydepspec(ks)) then        ! dry deposition
    516548              drydeposit(ks)=xmass1(j,ks)*prob(ks)*decfact
    517549              xmass1(j,ks)=xmass1(j,ks)*(1.-prob(ks))*decfact
     
    524556            endif
    525557
    526 
    527558            if (mdomainfill.eq.0) then
    528559              if (xmass(npoint(j),ks).gt.0.) &
     
    536567          if (xmassfract.lt.0.0001) then   ! terminate all particles carrying less mass
    537568            itra1(j)=-999999999
     569            if (verbosity.gt.0) then
     570              print*,'terminated particle ',j,' for small mass'
     571            endif
    538572          endif
    539573
    540574  !        Sabine Eckhardt, June 2008
    541575  !        don't create depofield for backward runs
    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)
     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
    548581          endif
    549582
     
    552585
    553586          if (abs(itra1(j)-itramem(j)).ge.lage(nageclass)) then
    554             if (linit_cond.ge.1) &
    555                  call initial_cond_calc(itime+lsynctime,j)
     587            if (linit_cond.ge.1) call initial_cond_calc(itime+lsynctime,j)
    556588            itra1(j)=-999999999
     589            if (verbosity.gt.0) then
     590              print*,'terminated particle ',j,' for age'
     591            endif
    557592          endif
    558593        endif
     
    582617
    583618  if (iflux.eq.1) then
    584       deallocate(flux)
     619    deallocate(flux)
    585620  endif
    586   if (OHREA.eqv..TRUE.) then
    587       deallocate(OH_field,OH_field_height)
     621  if (ohrea.eqv..TRUE.) then
     622    deallocate(OH_field,OH_field_height)
    588623  endif
    589624  if (ldirect.gt.0) then
    590   deallocate(drygridunc,wetgridunc)
     625    deallocate(drygridunc,wetgridunc)
    591626  endif
    592627  deallocate(gridunc)
     
    595630  deallocate(xmasssave)
    596631  if (nested_output.eq.1) then
    597      deallocate(orooutn, arean, volumen)
    598      if (ldirect.gt.0) then
    599      deallocate(griduncn,drygriduncn,wetgriduncn)
    600      endif
     632    deallocate(orooutn, arean, volumen)
     633    if (ldirect.gt.0) then
     634      deallocate(griduncn,drygriduncn,wetgriduncn)
     635    endif
    601636  endif
    602637  deallocate(outheight,outheighthalf)
    603   deallocate(oroout, area, volume)
     638  deallocate(oroout,area,volume)
    604639
    605640end subroutine timemanager
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG