Changeset 660bcb7 in flexpart.git for src/timemanager.f90


Ignore:
Timestamp:
Nov 24, 2014, 1:36:35 PM (9 years ago)
Author:
Anne Fouilloux <annefou@…>
Branches:
NetCDF
Children:
3073eaf
Parents:
4bf4a69
Message:

NETCDF outputs from svn trunk (hasod: ADD: netcdf module file)
I did not take changes in advance.f90; it will be added later.
I also changed OPENs where status was set to new and access is set to APPEND (had problems on abel.uio.no with intel compilers 2013.sp1.3)
It should contains technical changes only and results should be identical.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/timemanager.f90

    rb4d29ce r660bcb7  
    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  use netcdf_output_mod, only: concoutput_netcdf, concoutput_nest_netcdf,concoutput_surf_netcdf, concoutput_surf_nest_netcdf
    9497
    9598  implicit none
     
    129132
    130133
     134  itime=0
    131135  !write(*,45) itime,numpart,gridtotalunc,wetgridtotalunc,drygridtotalunc
    132136  write(*,46) float(itime)/3600,itime,numpart
     
    141145  do itime=0,ideltas,lsynctime
    142146
    143 
    144147  ! Computation of wet deposition, OH reaction and mass transfer
    145148  ! between two species every lsynctime seconds
     
    152155  !********************************************************************
    153156
    154     if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     157    if (wetdep .and. itime .ne. 0 .and. numpart .gt. 0) then
    155158        if (verbosity.gt.0) then
    156159           write (*,*) 'timemanager> call wetdepo'
     
    159162    endif
    160163
    161     if (OHREA .and. itime .ne. 0 .and. numpart .gt. 0) &
     164    if (ohrea .and. itime .ne. 0 .and. numpart .gt. 0) &
    162165         call ohreaction(itime,lsynctime,loutnext)
    163166
    164     if (ASSSPEC .and. itime .ne. 0 .and. numpart .gt. 0) then
     167    if (assspec .and. itime .ne. 0 .and. numpart .gt. 0) then
    165168       stop 'associated species not yet implemented!'
    166169  !     call transferspec(itime,lsynctime,loutnext)
     
    240243  !***********************************************************************
    241244
    242     if (DEP.and.(itime.eq.loutnext).and.(ldirect.gt.0)) then
     245    if (dep.and.(itime.eq.loutnext).and.(ldirect.gt.0)) then
    243246      do ks=1,nspec
    244247      do kp=1,maxpointspec_act
     
    350353        if ((iout.le.3.).or.(iout.eq.5)) then
    351354          if (surf_only.ne.1) then
    352           call concoutput(itime,outnum,gridtotalunc, &
    353                wetgridtotalunc,drygridtotalunc)
     355            if (lnetcdfout.eq.1) then
     356              call concoutput_netcdf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     357            else
     358              call concoutput(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     359            endif
    354360          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
     361            if (verbosity.eq.1) then
     362             print*,'call concoutput_surf '
     363             call system_clock(count_clock)
     364             write(*,*) 'system clock',count_clock - count_clock0   
     365            endif
     366            if (lnetcdfout.eq.1) then
     367              call concoutput_surf_netcdf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     368            else
     369              call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
     370              if (verbosity.eq.1) then
     371                print*,'called concoutput_surf '
     372                call system_clock(count_clock)
     373                write(*,*) 'system clock',count_clock - count_clock0   
     374              endif
     375            endif
    367376          endif
    368377
    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)
     378          if (nested_output .eq. 1) then
     379            if (lnetcdfout.eq.0) then
     380              if (surf_only.ne.1) then
     381                call concoutput_nest(itime,outnum)
     382              else
     383                call concoutput_surf_nest(itime,outnum)
     384              endif
     385            else
     386              if (surf_only.ne.1) then
     387                call concoutput_nest_netcdf(itime,outnum)
     388              else
     389                call concoutput_surf_nest_netcdf(itime,outnum)
     390              endif
     391            endif
     392          endif
    371393          outnum=0.
    372394        endif
     
    474496  !****************************
    475497
    476         xold=xtra1(j)
    477         yold=ytra1(j)
     498        xold=real(xtra1(j))
     499        yold=real(ytra1(j))
    478500        zold=ztra1(j)
    479501
     
    515537            endif
    516538
    517             if (DRYDEPSPEC(ks)) then        ! dry deposition
     539            if (drydepspec(ks)) then        ! dry deposition
    518540              drydeposit(ks)=xmass1(j,ks)*prob(ks)*decfact
    519541              xmass1(j,ks)=xmass1(j,ks)*(1.-prob(ks))*decfact
     
    526548            endif
    527549
    528 
    529550            if (mdomainfill.eq.0) then
    530551              if (xmass(npoint(j),ks).gt.0.) &
     
    538559          if (xmassfract.lt.0.0001) then   ! terminate all particles carrying less mass
    539560            itra1(j)=-999999999
     561            if (verbosity.gt.0) then
     562              print*,'terminated particle ',j,' for small mass'
     563            endif
    540564          endif
    541565
    542566  !        Sabine Eckhardt, June 2008
    543567  !        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)
     568          if (drydep.AND.(ldirect.eq.1)) then
     569            call drydepokernel(nclass(j),drydeposit,real(xtra1(j)),real(ytra1(j)),nage,kp)
     570            if (nested_output.eq.1) then
     571              call drydepokernel_nest(nclass(j),drydeposit,real(xtra1(j)),real(ytra1(j)),nage,kp)
     572            endif
    550573          endif
    551574
     
    554577
    555578          if (abs(itra1(j)-itramem(j)).ge.lage(nageclass)) then
    556             if (linit_cond.ge.1) &
    557                  call initial_cond_calc(itime+lsynctime,j)
     579            if (linit_cond.ge.1) call initial_cond_calc(itime+lsynctime,j)
    558580            itra1(j)=-999999999
     581            if (verbosity.gt.0) then
     582              print*,'terminated particle ',j,' for age'
     583            endif
    559584          endif
    560585        endif
     
    584609
    585610  if (iflux.eq.1) then
    586       deallocate(flux)
     611    deallocate(flux)
    587612  endif
    588   if (OHREA.eqv..TRUE.) then
    589       deallocate(OH_field,OH_field_height)
     613  if (ohrea.eqv..TRUE.) then
     614    deallocate(OH_field,OH_field_height)
    590615  endif
    591616  if (ldirect.gt.0) then
    592   deallocate(drygridunc,wetgridunc)
     617    deallocate(drygridunc,wetgridunc)
    593618  endif
    594619  deallocate(gridunc)
     
    597622  deallocate(xmasssave)
    598623  if (nested_output.eq.1) then
    599      deallocate(orooutn, arean, volumen)
    600      if (ldirect.gt.0) then
    601      deallocate(griduncn,drygriduncn,wetgriduncn)
    602      endif
     624    deallocate(orooutn, arean, volumen)
     625    if (ldirect.gt.0) then
     626      deallocate(griduncn,drygriduncn,wetgriduncn)
     627    endif
    603628  endif
    604629  deallocate(outheight,outheighthalf)
    605   deallocate(oroout, area, volume)
     630  deallocate(oroout,area,volume)
    606631
    607632end subroutine timemanager
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG