source: flexpart.git/src/getrc.f90

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

add SPDX-License-Identifier to all .f90 files

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