Changes in src/drydepokernel.f90 [4c64400:1c0d5e6] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/drydepokernel.f90

    r4c64400 r1c0d5e6  
    4040  !                                                                            *
    4141  !*****************************************************************************
    42   ! Changes:
    43   ! eso 10/2016: Added option to disregard kernel
    44   !
    45   !*****************************************************************************
    46 
    4742
    4843  use unc_mod
     
    5247  implicit none
    5348
    54   real(dep_prec), dimension(maxspec) :: deposit
    55   real :: x,y,ddx,ddy,xl,yl,wx,wy,w
     49  real :: x,y,deposit(maxspec),ddx,ddy,xl,yl,wx,wy,w
    5650  integer :: ix,jy,ixp,jyp,ks,nunc,nage,kp
    5751
     
    8074  endif
    8175
    82   ! If no kernel is used, direct attribution to grid cell
    83   !******************************************************
    84 
    85   if (lnokernel) then
    86     do ks=1,nspec
    87       if ((abs(deposit(ks)).gt.0).and.DRYDEPSPEC(ks)) then
    88         if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
    89              (jy.le.numygrid-1)) then
    90           drygridunc(ix,jy,ks,kp,nunc,nage)= &
    91                drygridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)
    92         end if
    93       end if
    94     end do
    95   else ! use kernel
    96 
    9776
    9877  ! Determine mass fractions for four grid points
    9978  !**********************************************
    100   do ks=1,nspec
     79    do ks=1,nspec
    10180
    102    if ((abs(deposit(ks)).gt.0).and.DRYDEPSPEC(ks)) then
     81    if ((abs(deposit(ks)).gt.0).and.DRYDEPSPEC(ks)) then
    10382
    104    if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
     83    if (.not.usekernel) then
     84       drygridunc(ix,jy,ks,kp,nunc,nage)= &
     85           drygridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)
     86    else
     87      if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
    10588        (jy.le.numygrid-1)) then
    106      w=wx*wy
    107      drygridunc(ix,jy,ks,kp,nunc,nage)= &
    108           drygridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
    109      continue
    110    endif
     89       w=wx*wy
     90      drygridunc(ix,jy,ks,kp,nunc,nage)= &
     91           drygridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
     92     endif
    11193
    112   if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgrid-1).and. &
     94    if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgrid-1).and. &
    11395       (jyp.le.numygrid-1)) then
    11496    w=(1.-wx)*(1.-wy)
    11597      drygridunc(ixp,jyp,ks,kp,nunc,nage)= &
    11698           drygridunc(ixp,jyp,ks,kp,nunc,nage)+deposit(ks)*w
    117   endif
     99    endif
    118100
    119   if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgrid-1).and. &
     101    if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgrid-1).and. &
    120102       (jy.le.numygrid-1)) then
    121     w=(1.-wx)*wy
     103      w=(1.-wx)*wy
    122104      drygridunc(ixp,jy,ks,kp,nunc,nage)= &
    123105           drygridunc(ixp,jy,ks,kp,nunc,nage)+deposit(ks)*w
    124   endif
     106    endif
    125107
    126   if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgrid-1).and. &
     108    if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgrid-1).and. &
    127109       (jyp.le.numygrid-1)) then
    128     w=wx*(1.-wy)
     110      w=wx*(1.-wy)
    129111      drygridunc(ix,jyp,ks,kp,nunc,nage)= &
    130112           drygridunc(ix,jyp,ks,kp,nunc,nage)+deposit(ks)*w
    131   endif
     113    endif
    132114
    133   endif
     115    endif ! kernel
     116    endif ! deposit>0
    134117
    135   end do
    136 end if
     118    end do
    137119
    138120end subroutine drydepokernel
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG