Soil Water Balance (SWB2)
Loading...
Searching...
No Matches
daily_calculation.F90
Go to the documentation of this file.
2
7 use exceptions, only : assert
8 use iso_c_binding, only : c_short, c_int, c_float, c_double, c_bool
9
14
15 use simulation_datetime, only : sim_dt
16
17 use fstring
18 use logfiles
19
20 implicit none
21
22 private
23
25
26contains
27
28 subroutine perform_daily_calculation(cells)
29
30 class(model_domain_t), intent(inout) :: cells
31
32 ! [ LOCALS ]
33 integer (c_int) :: indx, jndx
34 integer (c_int) :: landuse_index
35
36 ! calls elemental
37 call cells%calc_GDD()
38
39 ! calls elemental
40 call cells%update_crop_coefficient()
41 call cells%update_growing_season()
42 call cells%update_rooting_depth()
43 call cells%calc_reference_et()
44
45 ! fog calculation does not explicitly consider canopy fraction
46 call cells%calc_fog()
47
48 ! interception calculation *does* reflect the canopy fraction
49 call cells%calc_interception()
50
51 ! interception term *may* be altered if interception storage is already at a maximium
52 call calculate_interception_mass_balance( interception_storage=cells%interception_storage, &
53 actual_et_interception=cells%actual_et_interception, &
54 interception=cells%interception, &
55 interception_storage_max=cells%interception_storage_max, &
56 reference_et0=cells%reference_et0 )
57
58 ! update crop evapotranspiration; crop_coefficient_kcb defaults to 1.0
59 ! there is less power to evaporate/transpire if there is active evaporation of interception
60 cells%crop_etc = max(cells%reference_et0 - cells%actual_et_interception, 0.0_c_float) * cells%crop_coefficient_kcb
61
62 call cells%calc_snowfall()
63
64 ! actually calculating *potential* snowmelt here; actual snowmelt determined
65 ! in 'calculate_snow_mass_balance'
66 call cells%calc_snowmelt()
67
68 call cells%calc_continuous_frozen_ground_index()
69
70 call calculate_snow_mass_balance( snow_storage=cells%snow_storage, &
71 potential_snowmelt=cells%potential_snowmelt, &
72 snowmelt=cells%snowmelt, &
73 net_snowfall=cells%net_snowfall )
74
75 cells%runon = 0.0_c_float
76 cells%runoff = 0.0_c_float
77 cells%runoff_outside = 0.0_c_float
78
79 !> if flow routing is enabled, the calculations will be made in order from upslope to downslope;
80 !! otherwise, the calculations are made in the natural packing order of the data structure
81 do jndx=1, ubound( cells%sort_order, 1 )
82
83 ! sort_order is a simple series of index values from 1 to # active cells
84 ! indx represents the index of the cell if processed in upstream to downstream order
85
86 indx = cells%sort_order( jndx )
87
88 landuse_index = cells%landuse_index( indx )
89
90 associate( &
91 net_infiltration => cells%net_infiltration( indx ), &
92 pervious_fraction => cells%pervious_fraction( indx ), &
93 irrigation => cells%irrigation( indx ), &
94 direct_net_infiltration => cells%direct_net_infiltration( indx ), &
95 direct_soil_moisture => cells%direct_soil_moisture( indx ), &
96 surface_storage => cells%surface_storage( indx ), &
97 actual_et_impervious => cells%actual_et_impervious( indx ), &
98 actual_et_soil => cells%actual_et_soil( indx ), &
99 actual_et => cells%actual_et( indx ), &
100 surface_storage_excess => cells%surface_storage_excess( indx ), &
101 surface_storage_max => cells%surface_storage_max( indx ), &
102 soil_storage_max => cells%soil_storage_max( indx ), &
103 soil_storage => cells%soil_storage( indx ), &
104 storm_drain_capture => cells%storm_drain_capture( indx ), &
105 gross_precipitation => cells%gross_precip( indx ), &
106 rainfall => cells%rainfall( indx ), &
107 net_rainfall => cells%net_rainfall( indx ), &
108 snowmelt => cells%snowmelt( indx ), &
109 snowfall => cells%snowfall( indx ), &
110 runon => cells%runon( indx ), &
111 runoff => cells%runoff( indx ), &
112 inflow => cells%inflow( indx ), &
113 delta_soil_storage => cells%delta_soil_storage( indx ), &
114 infiltration => cells%infiltration( indx ), &
115 fog => cells%fog( indx ), &
116 interception => cells%interception( indx ), &
117 reference_et0 => cells%reference_et0( indx ), &
118 actual_et_interception => cells%actual_et_interception( indx ), &
119 canopy_cover_fraction => cells%canopy_cover_fraction(indx) )
120
121 ! inflow is calculated over the entire cell (pervious + impervious) area
122 inflow = max( 0.0_c_float, runon + net_rainfall + fog + snowmelt )
123
124 call cells%calc_runoff( indx )
125
126 ! calculating irrigation here because the Hawaii Water Budget method
127 ! needs an updated monthly runoff value to accurately calculate the
128 ! estimated irrigation demand; previously this value was wrong on the
129 ! first day of each month, since the previous month's runoff value was
130 ! being used to estimate the current month's irrigation demand
131 call cells%calc_irrigation( indx )
132
133 ! this is a convoluted call: we are getting an individual capture fraction,
134 ! but supplying a pointer to the active cells so that the first time through,
135 ! gridded data (if supplied) are updated
136 call storm_drain_capture_calculate( storm_drain_capture, indx, cells%active )
137
138 ! prevent calculated runoff from exceeding the day's inflow;
139 ! this can happen when using the monthly runoff fraction method
140 !runoff = max( min( inflow, runoff ), 0.0_c_float )
141
142 ! this routine now generates *all* outputs CORRECTED FOR PERVIOUS AREA
144 surface_storage=surface_storage, &
145 actual_et_impervious=actual_et_impervious, &
146 paved_to_unpaved=surface_storage_excess, &
147 surface_storage_max=surface_storage_max, &
150 net_rainfall=net_rainfall, &
151 snowmelt=snowmelt, &
152 runon=runon, &
153 runoff=runoff, &
154 fog=fog, &
155 reference_et0=reference_et0, &
156 pervious_fraction=pervious_fraction )
157
158 ! ** this statement commented out since pervious fraction correction is
159 ! now being performed in the 'mass_balance__impervious_surface' directly
160 ! modify the surface storage in inches as if the amount calculated for the impervious area
161 ! were to be redistributed uniformly over the total area of the cell
162 !surface_storage_excess = surface_storage_excess * ( 1.0_c_float - pervious_fraction )
163
164 ! e.g. septic system discharge enters here...
165 call cells%calc_direct_soil_moisture( indx )
166
167 ! irrigation not considered to be a contributor to runoff...in addition, infiltration
168 ! term is calculated with respect to the pervious fraction of the cell
169 infiltration = max( 0.0_c_float, &
170 ( ( runon &
171 + net_rainfall &
172 + fog &
173 + snowmelt &
174 + irrigation &
175 + direct_soil_moisture &
176 - runoff ) * pervious_fraction &
177 + surface_storage_excess ) / pervious_fraction )
178
179 ! the following call updates bound variable actual_et_soil
180 call cells%calc_actual_et( indx )
181
182 ! reduce soil actual et by the amount of interception et, if any
183 !actual_et_soil = max( actual_et_soil - actual_et_interception, 0.0_c_float )
184
185 ! OK, supplying a reduced value of reference ET0 to FAO56_two_stage calc
186
187 !actual_et_soil = max( min( actual_et_soil, reference_ET0 - actual_et_interception), 0.0_c_float )
188
189 call calculate_soil_mass_balance( net_infiltration=net_infiltration, &
190 soil_storage=soil_storage, &
191 soil_storage_max=soil_storage_max, &
192 delta_soil_storage=delta_soil_storage, &
193 actual_et_soil=actual_et_soil, &
194 reference_et0=reference_et0, &
195 infiltration=infiltration, &
196 runoff=runoff )
197
198 ! actual et for the entire cell is the weighted average of the ET for pervious and impervious
199 ! fractions of the cell
200 actual_et = actual_et_soil * pervious_fraction &
201 + actual_et_impervious * ( 1.0_c_float - pervious_fraction ) &
202 + actual_et_interception * canopy_cover_fraction
203
204 call cells%calc_climatic_water_deficit( indx )
205
206 if ( runoff < 0.) &
207 call logs%write( "line "//ascharacter(__line__)//": Negative runoff, indx= " &
208 //ascharacter(indx)//" col, row= "//ascharacter(cells%col_num_1D( indx )) &
209 //", "//ascharacter( cells%row_num_1D( indx ) ) )
210
211 call cells%calc_direct_net_infiltration( indx )
212
213 ! reporting of net_infiltration and irrigation must be adjusted to account for zero
214 ! irrigation and net_infiltration associated with the impervious areas
215
216 net_infiltration = net_infiltration * pervious_fraction + direct_net_infiltration
217 irrigation = irrigation * pervious_fraction
218
219 call cells%calc_maximum_net_infiltration( indx )
220
221 ! NOTE: only way for "runon" to be positive is if D8 flow routing
222 ! is enabled.
223
224 ! rejected net_infiltration + runoff will be routed downslope if routing option is turned on
225 call cells%calc_routing( index=indx )
226
227 end associate
228
229 enddo
230
231 end subroutine perform_daily_calculation
232
233!--------------------------------------------------------------------------------------------------
234
235 subroutine minmaxmean( variable , varname, logical_vector )
236
237 real (c_float), dimension(:) :: variable
238 character (len=*), intent(in) :: varname
239 logical, intent(in), optional :: logical_vector(:)
240
241 ! [ LOCALS ]
242 integer (c_int) :: iCount
243 character (len=30) :: sVarname
244 character (len=14) :: sMin
245 character (len=14) :: sMax
246 character (len=14) :: sMean
247 character (len=10) :: sCount
248
249 write (svarname, fmt="(a30)") adjustl(varname)
250
251 if (size( variable, 1) > 0 .and. present( logical_vector ) ) then
252 write (smin, fmt="(g14.3)") minval(variable, logical_vector)
253 write (smax, fmt="(g14.3)") maxval(variable, logical_vector)
254 write (smean, fmt="(g14.3)") sum(variable, logical_vector) &
255 / count( logical_vector )
256 write (scount, fmt="(i10)") count( logical_vector )
257
258 elseif (size( variable, 1) > 0 ) then
259 write (smin, fmt="(g14.3)") minval(variable)
260 write (smax, fmt="(g14.3)") maxval(variable)
261 write (smean, fmt="(g14.3)") sum(variable) / size(variable,1)
262 write (scount, fmt="(i10)") size(variable,1)
263
264 else
265 write (smin, fmt="(g14.3)") -9999.
266 write (smax, fmt="(g14.3)") -9999.
267 write (smean, fmt="(g14.3)") -9999.
268 write (scount, fmt="(i10)") 0
269 endif
270
271 call logs%write( adjustl(svarname)//" | "//adjustl(smin)//" | "//adjustl(smax) &
272 //" | "//adjustl(smean)//" | "//adjustl(scount), iloglevel=log_debug, lecho=.true._c_bool )
273
274 end subroutine minmaxmean
275
276
277end module daily_calculation
elemental subroutine, public update_continuous_frozen_ground_index(fcfgi, ftmax_f, ftmin_f, fsnowcover)
Update the continuous frozen ground index (CFGI) for a cell.
subroutine minmaxmean(variable, varname, logical_vector)
subroutine, public perform_daily_calculation(cells)
Provides support for assessing the effect of irrigation on recharge values by estimating the irrigati...
Definition irrigation.F90:8
type(logfile_t), public logs
Definition logfiles.F90:62
elemental subroutine, public calculate_impervious_surface_mass_balance(surface_storage, actual_et_impervious, paved_to_unpaved, surface_storage_max, storm_drain_capture, storm_drain_capture_fraction, net_rainfall, snowmelt, runon, runoff, fog, reference_et0, pervious_fraction)
elemental subroutine, public calculate_interception_mass_balance(interception_storage, actual_et_interception, interception, interception_storage_max, reference_et0)
elemental subroutine calculate_snow_mass_balance(snow_storage, potential_snowmelt, snowmelt, net_snowfall)
elemental subroutine, public calculate_soil_mass_balance(net_infiltration, soil_storage, actual_et_soil, runoff, delta_soil_storage, reference_et0, soil_storage_max, infiltration)
type(date_range_t), public sim_dt
real(c_float), dimension(:), allocatable, public storm_drain_capture_fraction
subroutine, public storm_drain_capture_calculate(capture_fraction, indx, is_cell_active)