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


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/drydepokernel.f90

    r4c64400 re200b7a  
    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
    10483   if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
    10584        (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
     85    w=wx*wy
     86      drygridunc(ix,jy,ks,kp,nunc,nage)= &
     87           drygridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
     88      continue
     89  endif
    11190
    11291  if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgrid-1).and. &
     
    133112  endif
    134113
    135   end do
    136 end if
     114    end do
    137115
    138116end subroutine drydepokernel
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG