SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
urban_hydro.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 urban_hydro(PWS_ROOF_MAX,PWS_ROAD_MAX, PWS_ROOF, PWS_ROAD, &
7  prr, pirrig_road, ptstep, pbld, ple_roof, &
8  ple_road, prunoff_strlroof, prunoff_road )
9 ! ##########################################################################
10 !
11 !!**** *URBAN_HYDRO*
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 ! Computes the evolution of prognostic water reservoirs
17 ! of urbanized areas.
18 !
19 !
20 !!** METHOD
21 ! ------
22 !
23 !
24 ! The roof reservoir runoff goes directly into the road reservoir.
25 !
26 ! Runoff occurs for road reservoir (too much water), as well as drainage
27 ! (evacuation system, typical time scale: 1 day)
28 !
29 !
30 !
31 !
32 !! EXTERNAL
33 !! --------
34 !!
35 !!
36 !! IMPLICIT ARGUMENTS
37 !! ------------------
38 !!
39 !! MODD_CST
40 !!
41 !!
42 !! REFERENCE
43 !! ---------
44 !!
45 !!
46 !! AUTHOR
47 !! ------
48 !!
49 !! V. Masson * Meteo-France *
50 !!
51 !! MODIFICATIONS
52 !! -------------
53 !! Original 23/01/98
54 !-------------------------------------------------------------------------------
55 !
56 !* 0. DECLARATIONS
57 ! ------------
58 !
59 USE modd_csts,ONLY : xlvtt
60 !
61 !
62 USE yomhook ,ONLY : lhook, dr_hook
63 USE parkind1 ,ONLY : jprb
64 !
65 IMPLICIT NONE
66 !
67 !* 0.1 declarations of arguments
68 !
69 !
70 REAL, DIMENSION(:), INTENT(IN) :: pws_roof_max ! maximum deepness of roof water reservoir
71 REAL, DIMENSION(:), INTENT(IN) :: pws_road_max ! maximum deepness of road water reservoir
72 
73 REAL, DIMENSION(:), INTENT(INOUT) :: pws_roof ! roof water reservoir
74 REAL, DIMENSION(:), INTENT(INOUT) :: pws_road ! road water reservoir
75 REAL, DIMENSION(:), INTENT(IN) :: prr ! rain rate
76 REAL, DIMENSION(:), INTENT(IN) :: pirrig_road ! watering rate for roads
77 REAL, INTENT(IN) :: ptstep ! time step
78 REAL, DIMENSION(:), INTENT(IN) :: pbld ! fraction of buildings
79 REAL, DIMENSION(:), INTENT(IN) :: ple_roof ! latent heat flux over roof
80 REAL, DIMENSION(:), INTENT(IN) :: ple_road ! latent heat flux over road
81 !
82 REAL, DIMENSION(:), INTENT(OUT) :: prunoff_strlroof ! runoff (kg/m2/s)
83 REAL, DIMENSION(:), INTENT(OUT) :: prunoff_road ! runoff (kg/m2/s)
84 REAL(KIND=JPRB) :: zhook_handle
85 !
86 !* 0.2 declarations of local variables
87 !
88 !
89 !-------------------------------------------------------------------------------
90 !
91 !* 1. Roof reservoir evolution
92 ! ------------------------
93 !
94 !
95 ! evolution of the water reservoir
96 ! (if we don't consider the runoff)
97 ! PRR in kg/m2/s therefore PWS in mm
98 !
99 IF (lhook) CALL dr_hook('URBAN_HYDRO',0,zhook_handle)
100 pws_roof(:) = pws_roof(:) &
101  - ptstep * ( ple_roof(:) / xlvtt - prr(:) )
102 !
103 ! Ws_town must be positive
104 !
105 pws_roof(:) = max(0., pws_roof(:))
106 !
107 ! if Ws_town > Ws_town_max,
108 ! there is runoff
109 !
110 prunoff_strlroof(:) = max(0., (pws_roof(:) - pws_roof_max(:)) / ptstep )
111 !
112 pws_roof(:) = min(pws_roof(:), pws_roof_max(:))
113 !
114 !-------------------------------------------------------------------------------
115 !
116 !* 2. Road reservoir evolution
117 ! ------------------------
118 !
119 !
120 ! evolution of the water reservoir
121 ! (if we don't consider the runoff)
122 ! PRR in kg/m2/s therefore PWS in mm
123 !
124 pws_road(:) = pws_road(:) &
125  - ptstep * ( ple_road(:) / xlvtt - prr(:) - pirrig_road(:) )
126 !
127 ! Ws_town must be positive
128 !
129 pws_road(:) = max(0., pws_road(:))
130 !
131 ! if Ws_town > Ws_town_max,
132 ! there is runoff
133 !
134 prunoff_road(:) = max(0., (pws_road(:) - pws_road_max(:)) / ptstep )
135 !
136 pws_road(:) = min(pws_road(:), pws_road_max(:))
137 !
138 !-------------------------------------------------------------------------------
139 IF (lhook) CALL dr_hook('URBAN_HYDRO',1,zhook_handle)
140 !
141 !-------------------------------------------------------------------------------
142 !
143 END SUBROUTINE urban_hydro
subroutine urban_hydro(PWS_ROOF_MAX, PWS_ROAD_MAX, PWS_ROOF, PWS_ROAD, PRR, PIRRIG_ROAD, PTSTEP, PBLD, PLE_ROOF, PLE_ROAD, PRUNOFF_STRLROOF, PRUNOFF_ROAD)
Definition: urban_hydro.F90:6