source: flexpart.git/src/getrc.f90 @ 3481cc1

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file since 3481cc1 was 3481cc1, checked in by Ignacio Pisso <ip@…>, 4 years ago

move license from headers to a different file

  • Property mode set to 100644
File size: 4.1 KB
Line 
1subroutine getrc(nc,i,j,t,gr,rh,rr,rc)
2  !                 i  i i i i  i  i  o
3  !*****************************************************************************
4  !                                                                            *
5  !  Calculation of the surface resistance according to the procedure given    *
6  !  in:                                                                       *
7  !  Wesely (1989): Parameterization of surface resistances to gaseous         *
8  !  dry deposition in regional-scale numerical models.                        *
9  !  Atmos. Environ. 23, 1293-1304.                                            *
10  !                                                                            *
11  !                                                                            *
12  !      AUTHOR: Andreas Stohl, 19 May 1995                                    *
13  !                                                                            *
14  !*****************************************************************************
15  !                                                                            *
16  ! Variables:                                                                 *
17  !                                                                            *
18  ! reldiff(maxspec)  diffusivity of H2O/diffusivity of component i            *
19  ! gr [W/m2]       global radiation                                           *
20  ! i               index of seasonal category                                 *
21  ! j               index of landuse class                                     *
22  ! ldep(maxspec)          1, if deposition shall be calculated for species i  *
23  ! nc                   actual number of chemical components                  *
24  ! rcl(maxspec,5,8) [s/m] Lower canopy resistance                             *
25  ! rgs(maxspec,5,8) [s/m] Ground resistance                                   *
26  ! rlu(maxspec,5,8) [s/m] Leaf cuticular resistance                           *
27  ! rm(maxspec) [s/m]      Mesophyll resistance                                *
28  ! t [C]           temperature                                                *
29  !                                                                            *
30  !*****************************************************************************
31
32  use par_mod
33  use com_mod
34
35  implicit none
36
37  integer :: i,j,ic,nc
38  real :: gr,rh,rr,t,rs,rsm,corr,rluc,rclc,rgsc,rdc,rluo
39  real :: rc(maxspec)
40
41
42  ! Compute stomatal resistance
43  !****************************
44  ! Sabine Eckhardt, Dec 06: use 1E25 instead of 99999. for infinite res.
45
46  if ((t.gt.0.).and.(t.lt.40.)) then
47    rs=ri(i,j)*(1.+(200./(gr+0.1))**2)*(400./(t*(40.-t)))
48  else
49    rs=1.E25
50  !  rs=99999.
51  endif
52
53
54  ! Correct stomatal resistance for effect of dew and rain
55  !*******************************************************
56
57  if ((rh.gt.0.9).or.(rr.gt.0.)) rs=rs*3.
58
59  ! Compute the lower canopy resistance
60  !************************************
61
62  rdc=100.*(1.+1000./(gr+10.))
63
64
65  corr=1000.*exp(-1.*t-4.)
66  do ic=1,nc
67    if (reldiff(ic).gt.0.) then
68
69  ! Compute combined stomatal and mesophyll resistance
70  !***************************************************
71
72      rsm=rs*reldiff(ic)+rm(ic)
73
74  ! Correct leaf cuticular, lower canopy and ground resistance
75  !***********************************************************
76
77      rluc=rlu(ic,i,j)+corr
78      rclc=rcl(ic,i,j)+corr
79      rgsc=rgs(ic,i,j)+corr
80
81  ! Correct leaf cuticular resistance for effect of dew and rain
82  !*************************************************************
83
84      if (rr.gt.0.) then
85        rluo=1./(1./1000.+1./(3.*rluc))
86        rluc=1./(1./(3.*rluc)+1.e-7*henry(ic)+f0(ic)/rluo)
87      else if (rh.gt.0.9) then
88        rluo=1./(1./3000.+1./(3.*rluc))
89        rluc=1./(1./(3.*rluc)+1.e-7*henry(ic)+f0(ic)/rluo)
90      endif
91
92  ! Combine resistances to give total resistance
93  !*********************************************
94
95      rc(ic)=1./(1./rsm+1./rluc+1./(rdc+rclc)+1./(rac(i,j)+rgsc))
96  ! Sabine Eckhardt, Dec 06: avoid possible excessively high vdep
97      if (rc(ic).lt.10.) rc(ic)=10.
98    endif
99  end do
100
101end subroutine getrc
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG