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


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/wetdepokernel.f90

    r4c64400 r1c0d5e6  
    4040  !                                                                            *
    4141  !*****************************************************************************
    42   ! Changes:
    43   ! eso 10/2016: Added option to disregard kernel
    44   !
    45   !*****************************************************************************
    4642
    4743  use unc_mod
     
    7773  endif
    7874
    79   ! If no kernel is used, direct attribution to grid cell
    80   !******************************************************
    8175
    82   if (lnokernel) then
    83     do ks=1,nspec
    84       if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
    85            (jy.le.numygrid-1)) then
    86         wetgridunc(ix,jy,ks,kp,nunc,nage)= &
    87              wetgridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)
    88       end if
    89     end do
    90   else ! use kernel
    91    
    9276  ! Determine mass fractions for four grid points
    9377  !**********************************************
     
    9579  do ks=1,nspec
    9680
    97   if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
     81  if (.not.usekernel) then
     82      wetgridunc(ix,jy,ks,kp,nunc,nage)= &
     83           wetgridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)
     84  else
     85    if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
    9886       (jy.le.numygrid-1)) then
    99     w=wx*wy
     87      w=wx*wy
    10088      wetgridunc(ix,jy,ks,kp,nunc,nage)= &
    10189           wetgridunc(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
    102   endif
     90    endif
    10391
    104   if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgrid-1).and. &
     92    if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgrid-1).and. &
    10593       (jyp.le.numygrid-1)) then
    106     w=(1.-wx)*(1.-wy)
     94      w=(1.-wx)*(1.-wy)
    10795      wetgridunc(ixp,jyp,ks,kp,nunc,nage)= &
    10896           wetgridunc(ixp,jyp,ks,kp,nunc,nage)+deposit(ks)*w
    109   endif
     97    endif
    11098
    111   if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgrid-1).and. &
     99    if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgrid-1).and. &
    112100       (jy.le.numygrid-1)) then
    113     w=(1.-wx)*wy
     101      w=(1.-wx)*wy
    114102      wetgridunc(ixp,jy,ks,kp,nunc,nage)= &
    115103           wetgridunc(ixp,jy,ks,kp,nunc,nage)+deposit(ks)*w
    116   endif
     104    endif
    117105
    118   if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgrid-1).and. &
     106    if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgrid-1).and. &
    119107       (jyp.le.numygrid-1)) then
    120     w=wx*(1.-wy)
     108      w=wx*(1.-wy)
    121109      wetgridunc(ix,jyp,ks,kp,nunc,nage)= &
    122110           wetgridunc(ix,jyp,ks,kp,nunc,nage)+deposit(ks)*w
    123   endif
     111    endif
     112  endif
    124113  end do
    125   end if
    126114
    127115end subroutine wetdepokernel
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG