Ignore:
Timestamp:
Apr 22, 2015, 3:42:35 PM (9 years ago)
Author:
pesei
Message:

Wet dep quick fix and other small changes. Wet depo quick fix not final yet.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/petra/src/wetdepokernel_nest.f90

    r4 r37  
    11!**********************************************************************
    2 ! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
     2! Copyright 1998-2015                                                 *
    33! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
    44! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
     
    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,itage,nage,kp)
     23  !                             i      i    i i   i    i   i
    2524  !*****************************************************************************
    2625  !                                                                            *
     
    3534  !      2 September 2004: Adaptation from wetdepokernel.                      *
    3635  !                                                                            *
     36  !
     37  !  PS, 2/2015: do not use kernel for itage < 3 h
     38  !   same as for concentration in conccalc.f90
    3739  !                                                                            *
    3840  !*****************************************************************************
     
    5355
    5456  real :: x,y,deposit(maxspec),ddx,ddy,xl,yl,wx,wy,w
    55   integer :: ix,jy,ixp,jyp,ks,kp,nunc,nage
     57  integer :: ix,jy,ixp,jyp,ks,kp,nunc,nage,itage
    5658
    5759
     
    8082  endif
    8183
     84  if (itage .lt. itagekernmin) then 
     85   ! no kernel, direct attribution to grid cell
     86   
     87    do ks=1,nspec
     88      if (ix.ge.0 .and. jy.ge.0 .and. &
     89          ix.le.numxgridn-1 .and. jy.le.numygridn-1) &
     90        wetgriduncn(ix,jy,ks,kp,nunc,nage)= &
     91          wetgriduncn(ix,jy,ks,kp,nunc,nage)+deposit(ks)
     92    enddo
     93       
     94  else
     95    ! Determine mass fractions for four grid points & distribute
    8296
    83   ! Determine mass fractions for four grid points
    84   !**********************************************
     97    do ks=1,nspec
    8598
    86   do ks=1,nspec
     99      if ((ix.ge.0).and.(jy.ge.0).and.(ix.le.numxgridn-1).and. &
     100           (jy.le.numygridn-1)) then
     101        w=wx*wy
     102        wetgriduncn(ix,jy,ks,kp,nunc,nage)= &
     103          wetgriduncn(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
     104      endif
    87105
    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
    91       wetgriduncn(ix,jy,ks,kp,nunc,nage)= &
    92            wetgriduncn(ix,jy,ks,kp,nunc,nage)+deposit(ks)*w
     106      if ((ixp.ge.0).and.(jyp.ge.0).and.(ixp.le.numxgridn-1).and. &
     107           (jyp.le.numygridn-1)) then
     108        w=(1.-wx)*(1.-wy)
     109        wetgriduncn(ixp,jyp,ks,kp,nunc,nage)= &
     110          wetgriduncn(ixp,jyp,ks,kp,nunc,nage)+deposit(ks)*w
     111      endif
     112
     113      if ((ixp.ge.0).and.(jy.ge.0).and.(ixp.le.numxgridn-1).and. &
     114           (jy.le.numygridn-1)) then
     115        w=(1.-wx)*wy
     116        wetgriduncn(ixp,jy,ks,kp,nunc,nage)= &
     117          wetgriduncn(ixp,jy,ks,kp,nunc,nage)+deposit(ks)*w
     118      endif
     119
     120      if ((ix.ge.0).and.(jyp.ge.0).and.(ix.le.numxgridn-1).and. &
     121           (jyp.le.numygridn-1)) then
     122        w=wx*(1.-wy)
     123        wetgriduncn(ix,jyp,ks,kp,nunc,nage)= &
     124          wetgriduncn(ix,jyp,ks,kp,nunc,nage)+deposit(ks)*w
     125      endif
     126
     127    end do
     128
    93129  endif
    94 
    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)
    98       wetgriduncn(ixp,jyp,ks,kp,nunc,nage)= &
    99            wetgriduncn(ixp,jyp,ks,kp,nunc,nage)+deposit(ks)*w
    100   endif
    101 
    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
    105       wetgriduncn(ixp,jy,ks,kp,nunc,nage)= &
    106            wetgriduncn(ixp,jy,ks,kp,nunc,nage)+deposit(ks)*w
    107   endif
    108 
    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)
    112       wetgriduncn(ix,jyp,ks,kp,nunc,nage)= &
    113            wetgriduncn(ix,jyp,ks,kp,nunc,nage)+deposit(ks)*w
    114   endif
    115 
    116   end do
    117130end subroutine wetdepokernel_nest
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG