Ignore:
Timestamp:
Oct 21, 2014, 8:08:00 AM (10 years ago)
Author:
hasod
Message:

ADD: Optional (compressed) netcdf output added. Activated via COMMAND
file. During compile time switches -DNETCDF_OUTPUT -cpp need to be
invoked. Compliation and linking is shown in makefile.netcdf

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/timemanager.f90

    r27 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
    131137  !write(*,45) itime,numpart,gridtotalunc,wetgridtotalunc,drygridtotalunc
    132138  write(*,46) float(itime)/3600,itime,numpart
     
    141147  do itime=0,ideltas,lsynctime
    142148
    143 
    144149  ! Computation of wet deposition, OH reaction and mass transfer
    145150  ! between two species every lsynctime seconds
     
    152157  !********************************************************************
    153158
    154     if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     159    if (wetdep .and. itime .ne. 0 .and. numpart .gt. 0) then
    155160        if (verbosity.gt.0) then
    156161           write (*,*) 'timemanager> call wetdepo'
     
    159164    endif
    160165
    161     if (OHREA .and. itime .ne. 0 .and. numpart .gt. 0) &
     166    if (ohrea .and. itime .ne. 0 .and. numpart .gt. 0) &
    162167         call ohreaction(itime,lsynctime,loutnext)
    163168
    164     if (ASSSPEC .and. itime .ne. 0 .and. numpart .gt. 0) then
     169    if (assspec .and. itime .ne. 0 .and. numpart .gt. 0) then
    165170       stop 'associated species not yet implemented!'
    166171  !     call transferspec(itime,lsynctime,loutnext)
     
    240245  !***********************************************************************
    241246
    242     if (DEP.and.(itime.eq.loutnext).and.(ldirect.gt.0)) then
     247    if (dep.and.(itime.eq.loutnext).and.(ldirect.gt.0)) then
    243248      do ks=1,nspec
    244249      do kp=1,maxpointspec_act
     
    350355        if ((iout.le.3.).or.(iout.eq.5)) then
    351356          if (surf_only.ne.1) then
    352           call concoutput(itime,outnum,gridtotalunc, &
    353                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
    354364          else 
    355   if (verbosity.eq.1) then
    356      print*,'call concoutput_surf '
    357      CALL SYSTEM_CLOCK(count_clock)
    358      WRITE(*,*) 'SYSTEM_CLOCK',count_clock - count_clock0   
    359   endif
    360           call concoutput_surf(itime,outnum,gridtotalunc, &
    361                wetgridtotalunc,drygridtotalunc)
    362   if (verbosity.eq.1) then
    363      print*,'called concoutput_surf '
    364      CALL SYSTEM_CLOCK(count_clock)
    365      WRITE(*,*) 'SYSTEM_CLOCK',count_clock - count_clock0   
    366   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
    367382          endif
    368383
    369           if ((nested_output.eq.1).and.(surf_only.ne.1)) call concoutput_nest(itime,outnum)
    370           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
    371401          outnum=0.
    372402        endif
     
    474504  !****************************
    475505
    476         xold=xtra1(j)
    477         yold=ytra1(j)
     506        xold=real(xtra1(j))
     507        yold=real(ytra1(j))
    478508        zold=ztra1(j)
    479509
     
    515545            endif
    516546
    517             if (DRYDEPSPEC(ks)) then        ! dry deposition
     547            if (drydepspec(ks)) then        ! dry deposition
    518548              drydeposit(ks)=xmass1(j,ks)*prob(ks)*decfact
    519549              xmass1(j,ks)=xmass1(j,ks)*(1.-prob(ks))*decfact
     
    526556            endif
    527557
    528 
    529558            if (mdomainfill.eq.0) then
    530559              if (xmass(npoint(j),ks).gt.0.) &
     
    538567          if (xmassfract.lt.0.0001) then   ! terminate all particles carrying less mass
    539568            itra1(j)=-999999999
     569            if (verbosity.gt.0) then
     570              print*,'terminated particle ',j,' for small mass'
     571            endif
    540572          endif
    541573
    542574  !        Sabine Eckhardt, June 2008
    543575  !        don't create depofield for backward runs
    544           if (DRYDEP.AND.(ldirect.eq.1)) then
    545             call drydepokernel(nclass(j),drydeposit,real(xtra1(j)), &
    546                  real(ytra1(j)),nage,kp)
    547             if (nested_output.eq.1) call drydepokernel_nest( &
    548                  nclass(j),drydeposit,real(xtra1(j)),real(ytra1(j)), &
    549                  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
    550581          endif
    551582
     
    554585
    555586          if (abs(itra1(j)-itramem(j)).ge.lage(nageclass)) then
    556             if (linit_cond.ge.1) &
    557                  call initial_cond_calc(itime+lsynctime,j)
     587            if (linit_cond.ge.1) call initial_cond_calc(itime+lsynctime,j)
    558588            itra1(j)=-999999999
     589            if (verbosity.gt.0) then
     590              print*,'terminated particle ',j,' for age'
     591            endif
    559592          endif
    560593        endif
     
    584617
    585618  if (iflux.eq.1) then
    586       deallocate(flux)
     619    deallocate(flux)
    587620  endif
    588   if (OHREA.eqv..TRUE.) then
    589       deallocate(OH_field,OH_field_height)
     621  if (ohrea.eqv..TRUE.) then
     622    deallocate(OH_field,OH_field_height)
    590623  endif
    591624  if (ldirect.gt.0) then
    592   deallocate(drygridunc,wetgridunc)
     625    deallocate(drygridunc,wetgridunc)
    593626  endif
    594627  deallocate(gridunc)
     
    597630  deallocate(xmasssave)
    598631  if (nested_output.eq.1) then
    599      deallocate(orooutn, arean, volumen)
    600      if (ldirect.gt.0) then
    601      deallocate(griduncn,drygriduncn,wetgriduncn)
    602      endif
     632    deallocate(orooutn, arean, volumen)
     633    if (ldirect.gt.0) then
     634      deallocate(griduncn,drygriduncn,wetgriduncn)
     635    endif
    603636  endif
    604637  deallocate(outheight,outheighthalf)
    605   deallocate(oroout, area, volume)
     638  deallocate(oroout,area,volume)
    606639
    607640end subroutine timemanager
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG