SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
ch_dep_town.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE ch_dep_town ( PRESA_TOWN, PUSTAR_TOWN,PTA, PTRAD, PWALL_O_HOR, &
7  psv, hsv, pdep)
8  !###########################################################
9  !
10  !!
11  !!
12  !!
13  !! PURPOSE
14  !! -------
15  !!
16  !! Compute dry deposition velocity for chemical species
17  !!
18  !! AUTHOR
19  !! ------
20  !! P.Tulet * Laboratoire d'Aerologie*
21  !!
22  !! MODIFICATIONS
23  !! -------------
24  !! Original 20/02/97
25  !! Modification 21/07/00 (Guenais/Tulet) add deposition on town
26  !! Modification 18/07/03 (Tulet) surface externalization
27  !!
28  !-------------------------------------------------------------------------------
29  !
30  !* 0. DECLARATIONS
31  ! ------------
32  !
33  USE modd_ch_surf
34  USE modd_csts
35  !
36 !
37  USE yomhook ,ONLY : lhook, dr_hook
38  USE parkind1 ,ONLY : jprb
39 !
40  IMPLICIT NONE
41  !
42  !* 0.1 Declarations of dummy arguments :
43  !
44  REAL, DIMENSION(:), INTENT(IN) :: presa_town ! aerodynamic resistances
45  REAL, DIMENSION(:), INTENT(IN) :: pustar_town ! frition velocities
46  REAL, DIMENSION(:), INTENT(IN) :: pta ! air temperature forcing (K)
47  REAL, DIMENSION(:), INTENT(IN) :: ptrad ! radiative temperature (K)
48  REAL, DIMENSION(:), INTENT(IN) :: pwall_o_hor ! normalized wall surface
49  REAL, DIMENSION(:,:), INTENT(OUT) :: pdep ! deposition dry velocity (m/s)
50  REAL, DIMENSION(:,:), INTENT(IN) :: psv
51  CHARACTER(LEN=6), DIMENSION(:),INTENT(IN) :: hsv
52  !
53  !
54  !
55  !* 0.2 Declarations of local variables :
56  !
57  !
58  REAL :: zstownrc_so2
59  ! donnees pour Rcsoil au SO2 Wesely (89)
60  ! Hemisphere nord latitudes temperees
61  REAL :: zstownrc_o3
62  ! donnees pour Rcsoil au O3 Wesely (89)
63  ! Hemisphere nord latitudes temperees
64  REAL , DIMENSION(SIZE(PTRAD,1),SIZE(HSV,1)) :: zscmdt
65  ! Sc(:)hmidt number
66  REAL , DIMENSION(SIZE(PTRAD,1),SIZE(HSV,1)) :: zdiffmolval
67  ! Molecular diffusivity
68  REAL , DIMENSION(SIZE(PTRAD,1),SIZE(HSV,1)) :: ztownrb
69  ! snow quasi-laminar resistance
70  REAL , DIMENSION(SIZE(PTRAD,1),SIZE(HSV,1)) :: ztownrc
71  ! towm surface resistance
72 
73  REAL , DIMENSION(SIZE(PTRAD,1),SIZE(HSV,1)) :: zrestown
74  ! final town resistance
75  REAL, DIMENSION(SIZE(PTRAD,1)) :: ztown_max
76  REAL, DIMENSION(SIZE(PTRAD,1)) :: ztcor
77  REAL,DIMENSION(SIZE(PUSTAR_TOWN,1)) ::zustar_town
78  INTEGER :: jsv
79  REAL(KIND=JPRB) :: zhook_handle
80  !
81  !============================================================================
82  ! Primilary
83  ! ---------
84 
85  !Default values
86  !--------------
87  IF (lhook) CALL dr_hook('CH_DEP_TOWN',0,zhook_handle)
88  ztownrc(:,:) = 9999.
89  zrestown(:,:)= 9999.0
90  ztownrb(:,:) = 9999.
91  !
92  ! INDEX OF VEGTYPE
93  ! ****************
94  zstownrc_so2 = 400. ! Town
95  zstownrc_o3 = 300. ! Town
96 
97  zustar_town(:) = max(pustar_town(:), 1e-9)
98  !
99  ! 1.0 Aerodynamic resistance for the differents COVER TYPE
100  ! ----------------------------------------------------
101  ! PRESA_TOWN(:) ! Aerodynamic resistance for TOWN
102  !
103  ! 2.0 Quasi-laminar resistance (Hicks, 1987)
104  ! ------------------------
105  !
106  !
107  ! compute molecular diffusivity for each species (Langevin, 1905)
108  ! ----------------------------------------------
109  DO jsv=1,SIZE(hsv,1)
110  zdiffmolval(:,jsv) = 2.22e-05 + 1.46e-07 * (ptrad(:) - 273.0) * &
111  sqrt(18. / xsrealmassmolval(jsv))
112  zscmdt(:,jsv)=0.15e-4 / zdiffmolval(:,jsv)
113  ENDDO
114  !
115  !
116  ! For town
117  ! --------
118  DO jsv=1,SIZE(hsv,1)
119  ztownrb(:,jsv) = ((zscmdt(:,jsv)/0.72)**(2./3.)) &
120  / (xkarman*zustar_town(:))
121  ENDDO
122  !
123  ! 3. Surface resistance
124  ! ------------------
125  ! 3.3.4 Surface temperature correction
126  ! ------------------------------
127  ztcor(:) = 0.
128  WHERE(ptrad(:) < 271.)
129  ztcor(:) = 1000 * exp(-ptrad(:) + 269.)
130  ztcor(:) = min(2.5e3, ztcor(:))
131  END WHERE
132 
133 
134  DO jsv=1,SIZE(hsv,1)
135  ztownrc(:,jsv) = ztcor(:) + (1.e5*zstownrc_so2)/ (xsrealhenryval(jsv,1) * &
136  exp(xsrealhenryval(jsv,2)* (1./298. - 1./pta(:))))
137  ENDDO
138 
139  !
140  ! 6.0 Compute town resistance
141  ! -----------------------
142  !
143  DO jsv=1,SIZE(hsv,1)
144  zrestown(:,jsv) = presa_town(:) + &
145  ztownrb(:,jsv) + ztownrc(:,jsv)
146  ENDDO
147  !
148  ! Town fraction increased to consider the vertical surfaces of buildings
149  ztown_max(:) = 1. + pwall_o_hor(:)
150 
151 
152  ! 7.0 Compute final dry deposition velocity on urban area
153  ! ---------------------------------------------------
154  !
155  DO jsv=1,SIZE(hsv,1)
156  pdep(:,jsv) = ztown_max(:) / zrestown(:,jsv)
157  ENDDO
158 IF (lhook) CALL dr_hook('CH_DEP_TOWN',1,zhook_handle)
159 
160 
161  !
162 END SUBROUTINE ch_dep_town
subroutine ch_dep_town(PRESA_TOWN, PUSTAR_TOWN, PTA, PTRAD, PWALL_O_HOR, PSV, HSV, PDEP)
Definition: ch_dep_town.F90:6