Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/readreleases.f90

    • Property svn:executable set to *
    r13 r4  
    3333  !     Update: 29 January 2001                                                *
    3434  !     Release altitude can be either in magl or masl                         *
    35   !     Update: Aug 2013 IP                                                                        *
     35  !                                                                            *
    3636  !*****************************************************************************
    3737  !                                                                            *
     
    5555  ! xpoint2,ypoint2     geograf. coordinates of upper right corner of release  *
    5656  !                     area                                                   *
    57   ! before: weta, wetb          parameters to determine the wet scavenging coefficient *
    58   ! weta, wetb          parameters to determine the below-cloud scavenging (NIK)     *
    59   ! weta_in, wetb_in    parameters to determine the in-cloud scavenging    (NIK)    *
    60   ! wetc_in, wetd_in    parameters to determine the in-cloud scavenging    (NIK)    * 
     57  ! weta, wetb          parameters to determine the wet scavenging coefficient *
    6158  ! zpoint1,zpoint2     height range, over which release takes place           *
    62   ! num_min_discrete    if less, release cannot be randomized and happens at   *
    63   !                     time mid-point of release interval                     *
    6459  !                                                                            *
    6560  !*****************************************************************************
     
    7368
    7469  integer :: numpartmax,i,j,id1,it1,id2,it2,specnum_rel,idum,stat
    75   integer,parameter :: num_min_discrete=100
    7670  real :: vsh(ni),fracth(ni),schmih(ni),releaserate,xdum,cun
    77   real(kind=dp) :: jul1,jul2,julm,juldate
     71  real(kind=dp) :: jul1,jul2,juldate
    7872  character(len=50) :: line
    7973  logical :: old
     
    283277    dryvel(i)=dryvel(i)*0.01         ! conversion to m/s
    284278
    285 
    286 
    287279  ! Check if wet deposition or OH reaction shall be calculated
    288280  !***********************************************************
    289281    if (weta(i).gt.0.)  then
    290282      WETDEP=.true.
    291       !write (*,*) 'Wetdeposition switched on: ',weta(i),i
    292        write (*,*) 'Wet deposition switched on'
    293        write (*,*) 'Below-cloud scavenging coefficients: ',weta(i),i
    294    endif
    295 
    296 ! NIK 31.01.2013
    297     if (weta_in(i).gt.0.)  then
    298       write (*,*) 'In-cloud scavenging coefficients: ',weta_in(i),wetb_in(i), wetc_in(i), wetd_in(i),i
    299     endif
    300 
     283      write (*,*) 'Wetdeposition switched on: ',weta(i),i
     284    endif
    301285    if (ohreact(i).gt.0) then
    302286      OHREA=.true.
     
    392376  jul1=juldate(id1,it1)
    393377  jul2=juldate(id2,it2)
    394   julm=(jul1+jul2)/2.
    395378  if (jul1.gt.jul2) then
    396379    write(*,*) 'FLEXPART MODEL ERROR'
     
    408391        stop
    409392      endif
    410       if (npart(numpoint).gt.num_min_discrete) then
    411         ireleasestart(numpoint)=int((jul1-bdate)*86400.)
    412         ireleaseend(numpoint)=int((jul2-bdate)*86400.)
    413       else
    414         ireleasestart(numpoint)=int((julm-bdate)*86400.)
    415         ireleaseend(numpoint)=int((julm-bdate)*86400.)
    416       endif
     393      ireleasestart(numpoint)=int((jul1-bdate)*86400.)
     394      ireleaseend(numpoint)=int((jul2-bdate)*86400.)
    417395    else if (ldirect.eq.-1) then
    418396      if ((jul1.lt.edate).or.(jul2.gt.bdate)) then
     
    423401        stop
    424402      endif
    425       if (npart(numpoint).gt.num_min_discrete) then
    426         ireleasestart(numpoint)=int((jul1-bdate)*86400.)
    427         ireleaseend(numpoint)=int((jul2-bdate)*86400.)
    428       else
    429         ireleasestart(numpoint)=int((julm-bdate)*86400.)
    430         ireleaseend(numpoint)=int((julm-bdate)*86400.)
    431       endif
     403      ireleasestart(numpoint)=int((jul1-bdate)*86400.)
     404      ireleaseend(numpoint)=int((jul2-bdate)*86400.)
    432405    endif
    433406  endif
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG