Changeset 4c64400 in flexpart.git for src/drydepokernel.f90


Ignore:
Timestamp:
Nov 8, 2016, 4:42:27 PM (7 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
c8fc724
Parents:
16b61a5
Message:

Bugfix for double precision dry deposition calculation. Added (hardcoded) option to not use output kernel. Version/date string updated.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/drydepokernel.f90

    re200b7a r4c64400  
    4040  !                                                                            *
    4141  !*****************************************************************************
     42  ! Changes:
     43  ! eso 10/2016: Added option to disregard kernel
     44  !
     45  !*****************************************************************************
     46
    4247
    4348  use unc_mod
     
    4752  implicit none
    4853
    49   real :: x,y,deposit(maxspec),ddx,ddy,xl,yl,wx,wy,w
     54  real(dep_prec), dimension(maxspec) :: deposit
     55  real :: x,y,ddx,ddy,xl,yl,wx,wy,w
    5056  integer :: ix,jy,ixp,jyp,ks,nunc,nage,kp
    5157
     
    7480  endif
    7581
     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
    7697
    7798  ! Determine mass fractions for four grid points
    7899  !**********************************************
    79     do ks=1,nspec
     100  do ks=1,nspec
    80101
    81     if ((abs(deposit(ks)).gt.0).and.DRYDEPSPEC(ks)) then
     102   if ((abs(deposit(ks)).gt.0).and.DRYDEPSPEC(ks)) then
    82103
    83104   if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgrid-1).and. &
    84105        (jy.le.numygrid-1)) then
    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
     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
    90111
    91112  if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgrid-1).and. &
     
    112133  endif
    113134
    114     end do
     135  end do
     136end if
    115137
    116138end subroutine drydepokernel
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG