Changeset db712a8 in flexpart.git for src/wetdepokernel_nest.f90


Ignore:
Timestamp:
Mar 3, 2016, 12:34:56 PM (8 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:
38b7917
Parents:
b0434e1
Message:

Completed handling of nested wind fields with cloud water (for wet deposition).

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/wetdepokernel_nest.f90

    re200b7a rdb712a8  
    2020!**********************************************************************
    2121
    22 subroutine wetdepokernel_nest &
    23        (nunc,deposit,x,y,nage,kp)
    24   !        i      i    i i  i    i
     22subroutine wetdepokernel_nest(nunc,deposit,x,y,nage,kp)
     23  !                           i    i       i i i    i
    2524  !*****************************************************************************
    2625  !                                                                            *
     
    5554  integer :: ix,jy,ixp,jyp,ks,kp,nunc,nage
    5655
    57 
     56  real :: dbg_dx, dbg_dy, dbg_xoutshiftn, dbg_youtshiftn, dbg_dxoutn, dbg_dyoutn,dbg_t
    5857
    5958  xl=(x*dx+xoutshiftn)/dxoutn
    6059  yl=(y*dy+youtshiftn)/dyoutn
    61   ix=int(xl)
    62   jy=int(yl)
     60
     61  ! old:
     62  ! ix=int(xl)
     63  ! jy=int(yl)
     64
     65  ! ESO: for xl,yl in range <-.5,-1> we get ix,jy=0 and thus negative
     66  ! wx,wy as the int function rounds upwards for negative numbers.
     67  ! Either use the floor function, or (perhaps more correctly?) use "(xl.gt.-0.5)"
     68  ! in place of "(ix.ge.0)" and similar for the upper boundary.
     69
     70  ! new:
     71  ix=floor(xl)
     72  jy=floor(yl)
     73
    6374  ddx=xl-real(ix)                   ! distance to left cell border
    6475  ddy=yl-real(jy)                   ! distance to lower cell border
     76
    6577
    6678  if (ddx.gt.0.5) then
     
    8092  endif
    8193
    82 
    83   ! Determine mass fractions for four grid points
    84   !**********************************************
     94! Determine mass fractions for four grid points
     95!**********************************************
    8596
    8697  do ks=1,nspec
    87 
    88   if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgridn-1).and. &
    89        (jy.le.numygridn-1)) then
    90     w=wx*wy
     98    if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgridn-1).and. &
     99         (jy.le.numygridn-1)) then
     100      w=wx*wy
    91101      wetgriduncn(ix,jy,ks,kp,nunc,nage)= &
    92102           wetgriduncn(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
    93   endif
     103    endif
    94104
    95   if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgridn-1).and. &
    96        (jyp.le.numygridn-1)) then
    97     w=(1.-wx)*(1.-wy)
     105    if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgridn-1).and. &
     106         (jyp.le.numygridn-1)) then
     107      w=(1.-wx)*(1.-wy)
    98108      wetgriduncn(ixp,jyp,ks,kp,nunc,nage)= &
    99109           wetgriduncn(ixp,jyp,ks,kp,nunc,nage)+deposit(ks)*w
    100   endif
     110    endif
    101111
    102   if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgridn-1).and. &
    103        (jy.le.numygridn-1)) then
    104     w=(1.-wx)*wy
     112    if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgridn-1).and. &
     113         (jy.le.numygridn-1)) then
     114      w=(1.-wx)*wy
    105115      wetgriduncn(ixp,jy,ks,kp,nunc,nage)= &
    106116           wetgriduncn(ixp,jy,ks,kp,nunc,nage)+deposit(ks)*w
    107   endif
     117    endif
    108118
    109   if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgridn-1).and. &
    110        (jyp.le.numygridn-1)) then
    111     w=wx*(1.-wy)
     119    if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgridn-1).and. &
     120         (jyp.le.numygridn-1)) then
     121      w=wx*(1.-wy)
    112122      wetgriduncn(ix,jyp,ks,kp,nunc,nage)= &
    113123           wetgriduncn(ix,jyp,ks,kp,nunc,nage)+deposit(ks)*w
    114   endif
     124    endif
    115125
    116126  end do
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG