SUEWS API Site
Documentation of SUEWS source code
suews_ctrl_const.f95
Go to the documentation of this file.
1! sg feb 2012 - added some comments
2! sg feb 2012 - changed number of surfaces to allocatable array
3! lj jun 2012 - snow part added
4! HW, LJ Oct 2014 - fixes to the structure
5! HCW 03 Mar 2015 - tidied
6! HCW 03 Jul 2015 - added albedo max & min to SUEWS_NonVeg.txt (min not used), SUEWS_Veg.txt, SUEWS_Water.txt (min not used)
7! LJ 06 Jul 2015 - changed alb_snow, albsnowmin and albsnowmax to SnowAlb, SnowAlbMin and SnowAlbMax (to be systematic with
8! other variables). Similarly denssnow changed to SnowDens. cMDS_SnowAlb=29 added.
9! HCW 10 Mar 2016 - variable vsmd added for soil moisture of vegetated surfaces
10! TS 14 Mar 2016 - multiple addtions for AnOHM
11! HCW 14 Jun 2016 - updated columns for ESTM and column names for AnOHM
12! HCW 26 Aug 2016 - CO2 flux added
13! HCW 16 Jan 2017 - WhereWhen module added to store info relating to grid and datetime
14! MH 16 Jun 2017 - Added biogenic CO2 and edited Site_Select
15! MH 21 Jun 2017 - Added anthropogenic CO2 and edited Site_Select
16
17!==================================================================================================
19
20 IMPLICIT NONE
21
22 ! ---- Set parameters for reading in data ------------------------------------------------------
23! #ifdef nc
24! INTEGER, PARAMETER:: MaxNumberOfGrids = 90000 !Max no. grids !TS changed to 90000 for large-scale simulation based on netCDF IO
25! #else
26 INTEGER, PARAMETER :: maxnumberofgrids = 10000 !Max no. grids !HCW changed to 2000 from 10000 so prog can run on windows (2GB lim)
27! #endif
28 INTEGER, PARAMETER :: maxlinesmet = 8640 !Max no. lines to read in one go (for all grids, ie MaxLinesMet/NumberOfGrids each)
29
30 ! ---- Surface types ---------------------------------------------------------------------------
31 INTEGER, PARAMETER :: nsurf = 7 !Total number of surfaces
32 INTEGER, PARAMETER :: nvegsurf = 3 !Number of surfaces that are vegetated
33 INTEGER, PARAMETER :: nsurfincsnow = nsurf + 1 !Number of surfaces + snow
34 ! INTEGER, DIMENSION(MaxNumberOfGrids) :: nsurf_roof_grid !Number of extra roof facets (e.g., green roofs, etc.)
35 ! INTEGER, DIMENSION(MaxNumberOfGrids) :: nsurf_wall_grid !Number of extra building facets (e.g., green walls, etc.)
36 INTEGER, PARAMETER :: ndepth = 5 !Number of depth levels for facets
37 ! INTEGER, PARAMETER :: nlayer_max = 5 !max Number of allowed roof types
38 INTEGER, PARAMETER :: nlayer_max = 100 !max Number of allowed roof types
39
40 ! SPARTACUS related
41 INTEGER, PARAMETER :: nspec = 1 !Number of spectral bands
42 INTEGER, PARAMETER :: nsw = 1 !Number of shortwave bands
43 INTEGER, PARAMETER :: nlw = 1 !Number of longwave bands
44 INTEGER, PARAMETER :: ncol = 1 !Number of tiles used: SUEWS does not have multiple tiles so ncol=1
45
46 INTEGER, PARAMETER :: pavsurf = 1, & !When all surfaces considered together (1-7)
47 bldgsurf = 2, &
48 conifsurf = 3, &
49 decidsurf = 4, &
50 grasssurf = 5, & !New surface classes: Grass = 5th/7 surfaces
51 bsoilsurf = 6, & !New surface classes: Bare soil = 6th/7 surfaces
52 watersurf = 7, &
53 excesssurf = 8, & !Runoff or subsurface soil in WGWaterDist
54 nsurfdonotreceivedrainage = 0, & !Number of surfaces that do not receive drainage water (green roof)
55 ivconif = 1, & !When only vegetated surfaces considered (1-3)
56 ivdecid = 2, &
57 ivgrass = 3
58
59 REAL(kind(1d0)), DIMENSION(nsurf) :: sfr_surf !Surface fractions [-]
60
61 ! ---- Set number of columns in input files ----------------------------------------------------
62 INTEGER, PARAMETER :: ncolumnssiteselect = 105 !SUEWS_SiteSelect.txt
63 INTEGER, PARAMETER :: ncolumnsnonveg = 24 !SUEWS_NonVeg.txt
64 INTEGER, PARAMETER :: ncolumnsveg = 38 !SUEWS_Veg.txt
65 INTEGER, PARAMETER :: ncolumnswater = 22 !SUEWS_Water.txt
66 INTEGER, PARAMETER :: ncolumnssnow = 25 !SUEWS_Snow.txt
67 INTEGER, PARAMETER :: ncolumnssoil = 9 !SUEWS_Soil.txt
68 INTEGER, PARAMETER :: ncolumnsconductance = 13 !SUEWS_Conductance.txt
69 INTEGER, PARAMETER :: ncolumnsohmcoefficients = 4 !SUEWS_OHMCoefficients.txt
70 INTEGER, PARAMETER :: ncolumnsestmcoefficients = 52 !SUEWS_ESTMCoefficients.txt ! S.O. 04 Feb 2016
71 INTEGER, PARAMETER :: ncolumnsanthropogenic = 39 !SUEWS_AnthropogenicEmission.txt
72 INTEGER, PARAMETER :: ncolumnsirrigation = 26 !SUEWS_Irrigation.txt
73 INTEGER, PARAMETER :: ncolumnsprofiles = 25 !SUEWS_Profiles.txt
74 INTEGER, PARAMETER :: ncolumnswgwaterdist = 10 !SUEWS_WithinGridWaterDist.txt
75 INTEGER, PARAMETER :: ncolumnsbiogen = 9 !SUEWS_BiogenCO2.txt
76 INTEGER, PARAMETER :: ncolumnsmetforcingdata = 24 !Meteorological forcing file (_data.txt)
77 INTEGER, PARAMETER :: ncolsestmdata = 13 !ESTM input file (_ESTM_Ts_data.txt))
78
79 ! ---- Set number of columns in output files ---------------------------------------------------
80 INTEGER, PARAMETER :: ncolumnsdataoutsuews = 87, & !Main output file (_5.txt). dataOutSUEWS created in SUEWS_Calculations.f95
81 ncolumnsdataoutsnow = 103, &
84 ncolumnsdataoutbl = 22, &
85 ncolumnsdataoutestm = 5 + 27, &
86 ncolumnsdataoutehc = 5 + 7*2 + 15*(1 + 4 + 2)*2, &
88 ncolumnsdataoutrsl = 30*4 + 5 + 13 + 2, &
89 ncolumnsdataoutdebug = 5 + 103 + 14 + 5 + 4 + 3 + 1, &
90 ncolumnsdataoutspartacus = 5 + 7 + 4*15 + 3 + 6*15 + 2*15 + 4
91
92 ! ---- Define input file headers ---------------------------------------------------------------
93 CHARACTER(len=20), DIMENSION(ncolumnsSiteSelect) :: headersiteselect_file !Header for SiteSelect.txt
94 CHARACTER(len=20), DIMENSION(ncolumnsNonVeg) :: headernonveg_file !Header for the nonveg surface
95 CHARACTER(len=20), DIMENSION(ncolumnsNonVeg) :: headernonveg_reqd !Expected header for the nonveg surface
96 CHARACTER(len=20), DIMENSION(ncolumnsVeg) :: headerveg_file !Header for the veg surface
97 CHARACTER(len=20), DIMENSION(ncolumnsVeg) :: headerveg_reqd !Expected header for the veg surface
98 CHARACTER(len=20), DIMENSION(ncolumnsWater) :: headerwater_file !Header for water surface
99 CHARACTER(len=20), DIMENSION(ncolumnsWater) :: headerwater_reqd !Expected header for water surface
100 CHARACTER(len=20), DIMENSION(ncolumnsSnow) :: headersnow_file !Header for Snow surface
101 CHARACTER(len=20), DIMENSION(ncolumnsSnow) :: headersnow_reqd !Expected header for Snow surface
102 CHARACTER(len=20), DIMENSION(ncolumnsSoil) :: headersoil_file !Header for soils
103 CHARACTER(len=20), DIMENSION(ncolumnsSoil) :: headersoil_reqd !Expected header for soils
104 CHARACTER(len=20), DIMENSION(ncolumnsConductance) :: headercond_file !Header for conductances
105 CHARACTER(len=20), DIMENSION(ncolumnsConductance) :: headercond_reqd !Expected header for conductances
106 CHARACTER(len=20), DIMENSION(ncolumnsOHMCoefficients) :: headerohmcoefficients_file !Header for soils
107 CHARACTER(len=20), DIMENSION(ncolumnsOHMCoefficients) :: headerohmcoefficients_reqd !Expected header for soils
108 CHARACTER(len=20), DIMENSION(ncolumnsESTMCoefficients) :: headerestmcoefficients_file !Header for soils ! S.O. 04 Feb 2016
109 CHARACTER(len=20), DIMENSION(ncolumnsESTMCoefficients) :: headerestmcoefficients_reqd !Expected header for soils ! S.O. 04 Feb 2016
110 CHARACTER(len=20), DIMENSION(ncolumnsAnthropogenic) :: headeranthropogenic_file !Header for QF
111 CHARACTER(len=20), DIMENSION(ncolumnsAnthropogenic) :: headeranthropogenic_reqd !Expected header for QF
112 CHARACTER(len=20), DIMENSION(ncolumnsIrrigation) :: headerirrigation_file !Header for Irrigation
113 CHARACTER(len=20), DIMENSION(ncolumnsIrrigation) :: headerirrigation_reqd !Expected header for Irrigation
114 CHARACTER(len=20), DIMENSION(ncolumnsProfiles) :: headerprofiles_file !Header for Profiles
115 CHARACTER(len=20), DIMENSION(ncolumnsProfiles) :: headerprofiles_reqd !Expected header for Profiles
116 CHARACTER(len=20), DIMENSION(ncolumnsWGWaterDist) :: headerwgwaterdist_file !Header for Profiles
117 CHARACTER(len=20), DIMENSION(ncolumnsWGWaterDist) :: headerwgwaterdist_reqd !Expected header for Profiles
118 CHARACTER(len=20), DIMENSION(ncolumnsBiogen) :: headerbiogen_file !Header for Biogen
119 CHARACTER(len=20), DIMENSION(ncolumnsBiogen) :: headerbiogen_reqd !Expected header for Biogen
120
121 ! ---- Define output file headers --------------------------------------------------------------
122 INTEGER, DIMENSION(:), ALLOCATABLE :: usecolumnsdataout !Column numbers used to select output variables
123 ! If change lengths in SUEWS_Output.f95, also need to adjust here
124 CHARACTER(len=14*ncolumnsDataOutSUEWS) :: headeruse, formatuse, headerusenosep, formatusenosep !Header and format in correct form
125 CHARACTER(len=52*ncolumnsDataOutSUEWS) :: longnmuse
126 CHARACTER(len=14*ncolumnsDataOutSUEWS) :: unitsuse
127 CHARACTER(len=3*ncolumnsDataOutSUEWS) :: aggreguse
128 CHARACTER(len=4*ncolumnsDataOutSUEWS) :: colnosuse
129
130 ! ---- Define arrays to store input information from SiteInfo spreadsheet ----------------------
131 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: siteselect !Stores info from SiteSelect.txt
132 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: nonveg_coeff !Coefficients for the nonveg surfaces
133 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: veg_coeff !Coefficients for the veg surfaces
134 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: water_coeff !Coefficients for the water surface
135 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: snow_coeff !Coefficients for snow
136 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: soil_coeff !Coefficients for soil
137 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: conductance_coeff !Coefficients for conductances
138 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: ohmcoefficients_coeff !Coefficients for OHMCoefficients
139 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: estmcoefficients_coeff !Coefficients for ESTMCoefficients ! S.O. 04 Feb 2016
140 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: anthropogenic_coeff !Coefficients for AnthropogenicEmissions
141 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: irrigation_coeff !Coefficients for Irrigation
142 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: profiles_coeff !Coefficients for Profiles
143 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: wgwaterdist_coeff !Coefficients for WithinGridWaterDist
144 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: biogen_coeff !Coefficients for BiogenCO2
145
146 ! ---- Define arrays for model calculations ----------------------------------------------------
147 INTEGER, DIMENSION(:), ALLOCATABLE :: grididmatrix !Array containing GridIDs in SiteSelect after sorting
148 INTEGER, DIMENSION(:), ALLOCATABLE :: grididmatrix0 !Array containing GridIDs in SiteSelect in the original order
149 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: surfacechar !Array for surface characteristics
150 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: metforcingdata !Array for meteorological forcing data
151 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: metforcingdata_grid !Array for meteorological forcing data of one grid used by AnOHM
152 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: estmforcingdata !Array for ESTM forcing data
153 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: modeldailystate !DailyState array
154 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: dailystatefirstopen
155 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: modeloutputdata !Output data matrix
156 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutsuews !Main data output matrix
157 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutrsl !Main data output matrix
158 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutbl !CBL output matrix
159 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutsolweig !SOLWEIG POI output matrix
160 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutbeers ! BEERS output matrix
161 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutdebug !debugging info matrix
162 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutspartacus !SPARTACUS output matrix
163 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutsnow !Main data output matrix
164 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutestm !ESTM output matrix
165 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutehc !EHC output matrix
166 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dataoutdailystate !DailyState output array
167
168 ! -------- output per each timestep ----------------------------------------------------------------
169 REAL(kind(1d0)), DIMENSION(5) :: datetimeline ! output of datetime info per each timestep
170 REAL(kind(1d0)), DIMENSION(ncolumnsDataOutSUEWS - 5) :: dataoutlinesuews ! output of SUEWS results per each timestep
171 REAL(kind(1d0)), DIMENSION(ncolumnsDataOutSnow - 5) :: dataoutlinesnow ! output of snow results per each timestep
172 ! REAL(KIND(1D0)), DIMENSION(ncolumnsDataOutRSL - 5) ::dataOutLineRSL ! output of snow results per each timestep
173 REAL(kind(1d0)), DIMENSION(ncolumnsDataOutRSL - 5 + 12) :: dataoutlinersl ! output of snow results per each timestep
174 REAL(kind(1d0)), DIMENSION(ncolumnsdataOutSOLWEIG - 5) :: dataoutlinesolweig ! output of snow results per each timestep
175 REAL(kind(1d0)), DIMENSION(ncolumnsDataOutBEERS - 5) :: dataoutlinebeers ! output of snow results per each timestep
176 REAL(kind(1d0)), DIMENSION(ncolumnsDataOutDebug) :: dataoutlinedebug ! output line for debugging info
177 REAL(kind(1d0)), DIMENSION(ncolumnsDataOutSPARTACUS) :: dataoutlinespartacus ! output line for SPARTACUS per each timestep (1hr?)
178 REAL(kind(1d0)), DIMENSION(ncolumnsDataOutDailyState - 5) :: dailystateline ! output of DailyState results per each timestep
179
180 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: metfordisagg !Array for original met forcing data (for disaggregation)
181 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: metfordisaggprev, metfordisaggnext !Stores last and next row of met data
182
183 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: estmfordisagg !Array for original ESTM forcing data (for disaggregation)
184 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: estmfordisaggprev, estmfordisaggnext !Stores last and next row of ESTM data
185
186 ! ---- Define array for hourly profiles interpolated to tstep ----------------------------------
187 ! REAL(KIND(1d0)),DIMENSION(:,:,:),ALLOCATABLE:: TstepProfiles
188 ! REAL(KIND(1d0)),DIMENSION(:,:), ALLOCATABLE:: AHProf_tstep
189 ! REAL(KIND(1d0)),DIMENSION(:,:), ALLOCATABLE:: WUProfM_tstep
190 ! REAL(KIND(1d0)),DIMENSION(:,:), ALLOCATABLE:: WUProfA_tstep
191 ! REAL(KIND(1d0)),DIMENSION(:,:), ALLOCATABLE:: HumActivity_tstep
192 ! REAL(KIND(1d0)),DIMENSION(:,:), ALLOCATABLE:: TraffProf_tstep
193 ! REAL(KIND(1d0)),DIMENSION(:,:), ALLOCATABLE:: PopProf_tstep
194
195 REAL(kind(1d0)), DIMENSION(0:23, 2) :: ahprof_24hr !Anthropogenic heat profiles for (1)weekdays / (2)weekends
196 REAL(kind(1d0)), DIMENSION(0:23, 2) :: humactivity_24hr !Human actvity profiles for (1)weekdays / (2)weekends
197 REAL(kind(1d0)), DIMENSION(0:23, 2) :: traffprof_24hr !Traffic profiles for (1)weekdays / (2)weekends
198 REAL(kind(1d0)), DIMENSION(0:23, 2) :: popprof_24hr !Population profiles for (1)weekdays / (2)weekends
199 REAL(kind(1d0)), DIMENSION(0:23, 2) :: wuprofm_24hr !Hourly profiles for water use (manual irrigation)
200 REAL(kind(1d0)), DIMENSION(0:23, 2) :: wuprofa_24hr !Hourly profiles for water use (automatic irrigation)
201
202 ! ---- For ESTM
203 REAL(kind(1d0)), ALLOCATABLE, DIMENSION(:, :) :: ts5mindata !surface temperature input data
204 REAL(kind(1d0)), ALLOCATABLE, DIMENSION(:) :: ts5mindata_ir !=ts5mindata(ir,:), ts input for the current timestep
205 REAL(kind(1d0)), ALLOCATABLE, DIMENSION(:) :: tair24hr
206 REAL(kind(1d0)), DIMENSION(ncolumnsDataOutESTM - 5) :: dataoutlineestm !ESTM output for the current timestep and grid
207
208 ! ---- For ESTM_ext
209 REAL(kind(1d0)), DIMENSION(ncolumnsDataOutEHC - 5) :: dataoutlineehc !ESTM output for the current timestep and grid
210
211 ! Column numbers for TstepProfiles
212 INTEGER :: ctp_enusewd = 1, &
213 ctp_enusewe = 2, &
214 ctp_wumanuwd = 3, &
215 ctp_wumanuwe = 4, &
216 ctp_wuautowd = 5, &
217 ctp_wuautowe = 6, &
218 ctp_snowcwd = 7, &
219 ctp_snowcwe = 8, &
220 ctp_humactivitywd = 9, &
221 ctp_humactivitywe = 10, &
222 ctp_traffprofwd = 11, &
223 ctp_traffprofwe = 12, &
224 ctp_popprofwd = 13, &
225 ctp_popprofwe = 14
226 !-----------------------------------------------------------------------------------------------
227
228 ! ---- Water balance for each surface ---------------------------------------------------------
229 !These variables are expressed as depths [mm] over each surface(is); the depth therefore varies with sfr_surf(is)
230 REAL(kind(1d0)), DIMENSION(nsurf) :: addwater !Water from other surfaces (WGWaterDist in SUEWS_ReDistributeWater.f95) [mm]
231 REAL(kind(1d0)), DIMENSION(nsurf) :: addwaterrunoff !Fraction of water going to runoff/sub-surface soil (WGWaterDist) [-]
232 ! N.B. this is not an amount; drain(is)*AddWaterRunoff(is) is the amount [mm]
233 REAL(kind(1d0)), DIMENSION(nsurf) :: chang !Change in state [mm]
234 REAL(kind(1d0)), DIMENSION(nsurf) :: drain !Drainage of each surface type [mm]
235 REAL(kind(1d0)), DIMENSION(nsurf) :: evap !Evaporation from each surface type [mm]
236 REAL(kind(1d0)), DIMENSION(nsurf) :: runoff !Runoff from each surface type [mm]
237 REAL(kind(1d0)), DIMENSION(nsurf) :: runoffsoil !Soil runoff from each soil sub-surface [mm]
238 REAL(kind(1d0)), DIMENSION(nsurf) :: smd_nsurf !Soil moisture deficit of each sub-surface [mm]
239 REAL(kind(1d0)), DIMENSION(nsurf) :: smd_nsurfout !Soil moisture deficit of each sub-surface (written out) [mm]
240 REAL(kind(1d0)), DIMENSION(nsurf) :: soilstore_surf !Soil moisture of each surface type [mm]
241 REAL(kind(1d0)), DIMENSION(nsurf) :: soilstoreold !Soil moisture of each surface type from previous timestep [mm]
242 REAL(kind(1d0)), DIMENSION(nsurf) :: state_surf !Wetness status of each surface type [mm]
243 REAL(kind(1d0)), DIMENSION(nsurf) :: stateout !Wetness status of each surface type (written out) [mm]
244 REAL(kind(1d0)), DIMENSION(nsurf) :: stateold !Wetness status of each surface type from previous timestep [mm]
245 REAL(kind(1d0)), DIMENSION(nsurf) :: rss_nsurf !Surface resistance after wet/partially wet adjustment for each surface
246
247 REAL(kind(1d0)), DIMENSION(nsurf) :: wetthresh_surf !When state_id > WetThresh, RS=0 limit in SUEWS_evap [mm] (specified in input files)
248 REAL(kind(1d0)), DIMENSION(nsurf) :: statelimit_surf !Limit for state_id of each surface type [mm] (specified in input files)
249
250 REAL(kind(1d0)), DIMENSION(1) :: waterdepth !Depth of open water
251
252 ! ---- Soil characteristics specified in input files -------------------------------------------
253 REAL(kind(1d0)), DIMENSION(nsurf) :: sathydraulicconduct !Saturated hydraulic conductivity for each soil subsurface [mm s-1]
254 REAL(kind(1d0)), DIMENSION(nsurf) :: soildepth !Depth of sub-surface soil store for each surface [mm]
255 REAL(kind(1d0)), DIMENSION(nsurf) :: soilstorecap_surf !Capacity of soil store for each surface [mm]
256
257 ! ---- Within-grid water distribution matrix ---------------------------------------------------
258 REAL(kind(1d0)), DIMENSION(nsurf + 1, nsurf - 1) :: waterdist !Within-grid water distribution to other surfaces and runoff/soil store [-]
259
260 ! ---- Drainage characteristics ----------------------------------------------------------------
261 REAL(kind(1d0)), DIMENSION(6, nsurf) :: storedrainprm !Storage capacities and drainage equation info for each surface
262 ! 1 - min storage capacity [mm]
263 ! 2 - Drainage equation to use
264 ! 3 - Drainage coeff 1 [units depend on choice of eqn]
265 ! 4 - Drainage coeff 2 [units depend on choice of eqn]
266 ! 5 - max storage capacity [mm]
267 ! 6 - current storage capacity [mm]
268 !-----------------------------------------------------------------------------------------------
269
270 ! ---- Define arrays at daily timestep ---------------------------------------------------------
271 INTEGER, PARAMETER :: ndays = 366 !Max no. days in a year used to specify size of daily arrays
272 !! Could delete NDays and allocate these elsewhere once no. days is known
273 ! REAL(KIND(1d0)),DIMENSION( 0:ndays, 5):: GDD !Growing Degree Days (see SUEWS_DailyState.f95)
274 ! REAL(KIND(1d0)),DIMENSION(-4:ndays, 6):: HDD !Heating Degree Days (see SUEWS_DailyState.f95)
275 ! REAL(KIND(1d0)),DIMENSION( 0:ndays, 9):: WUDay !Daily water use for EveTr, DecTr, Grass [mm] (see SUEWS_DailyState.f95)
276 ! REAL(KIND(1d0)),DIMENSION(-4:ndays, nvegsurf):: LAI !LAI for each veg surface [m2 m-2]
277
278 REAL(kind(1d0)), DIMENSION(nvegsurf) :: gdd_id, gdd_id_prev !Growing Degree Days (see SUEWS_DailyState.f95)
279 REAL(kind(1d0)), DIMENSION(nvegsurf) :: sdd_id !Growing Degree Days (see SUEWS_DailyState.f95)
280 REAL(kind(1d0)) :: tmin_id, tmax_id, lenday_id
281 REAL(kind(1d0)), DIMENSION(12) :: hdd_id
282 REAL(kind(1d0)), DIMENSION(9) :: wuday_id, wuday_id_prev !Daily water use for EveTr, DecTr, Grass [mm] (see SUEWS_DailyState.f95)
283 REAL(kind(1d0)), DIMENSION(nvegsurf) :: lai_id, lai_id_prev !LAI for each veg surface [m2 m-2]
284
285 ! Seasonality of deciduous trees accounted for by the following variables which change with time
286 ! REAL(KIND(1d0)),DIMENSION( 0:ndays):: DecidCap !Storage capacity of deciduous trees [mm]
287 ! REAL(KIND(1d0)),DIMENSION( 0:ndays):: porosity !Porosity of deciduous trees [-]
288 ! REAL(KIND(1d0)),DIMENSION( 0:ndays):: albDecTr !Albedo of deciduous trees [-]
289 ! REAL(KIND(1d0)),DIMENSION( 0:ndays):: albEveTr !Albedo of evergreen trees [-]
290 ! REAL(KIND(1d0)),DIMENSION( 0:ndays):: albGrass !Albedo of grass[-]
291
292 REAL(kind(1d0)) :: albmin_dectr, & !Min albedo for deciduous trees [-]
293 albmax_dectr, & !Max albedo for deciduous trees [-]
294 capmin_dec, & !Min storage capacity for deciduous trees [mm] (from input information)
295 capmax_dec, & !Max storage capacity for deciduous trees [mm] (from input information)
296 pormin_dec, & !Min porosity for deciduous trees
297 pormax_dec, & !Max porosity for deciduous trees
298 albmin_evetr, & !Min albedo for evergreen trees [-]
299 albmax_evetr, & !Max albedo for evergreen trees [-]
300 albmin_grass, & !Min albedo for grass [-]
301 albmax_grass !Max albedo for grass [-]
302
303 ! Replicate arrays needed for DailyState, adding dimension to identify the grid, HCW 27 Nov 2014
304 !! Could delete MaxNumberOfGrids and allocate these elsewhere once NumberOfGrids is known
305 ! REAL(KIND(1d0)),DIMENSION( 0:ndays, 5,MaxNumberOfGrids):: GDD_grids
306 ! REAL(KIND(1d0)),DIMENSION(-4:ndays, 6,MaxNumberOfGrids):: HDD_grids
307 ! REAL(KIND(1d0)),DIMENSION( 0:ndays, 9,MaxNumberOfGrids):: WUDay_grids
308 ! REAL(KIND(1d0)),DIMENSION(-4:ndays, nvegsurf,MaxNumberOfGrids):: LAI_grids
309
310 REAL(kind(1d0)), DIMENSION(nvegsurf, MaxNumberOfGrids) :: gdd_id_grids
311 REAL(kind(1d0)), DIMENSION(nvegsurf, MaxNumberOfGrids) :: sdd_id_grids
312 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: tmin_id_grids
313 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: tmax_id_grids
314 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: lenday_id_grids
315 REAL(kind(1d0)), DIMENSION(12, MaxNumberOfGrids) :: hdd_id_grids
316 REAL(kind(1d0)), DIMENSION(9, MaxNumberOfGrids) :: wuday_id_grids
317 REAL(kind(1d0)), DIMENSION(nvegsurf, MaxNumberOfGrids) :: lai_id_grids
318
319 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids):: albDecTr_grids
320 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids):: DecidCap_grids
321 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids):: porosity_grids
322 !
323 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids):: albEveTr_grids
324 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids):: albGrass_grids
325
326 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: decidcap_id_grids
327 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: albdectr_id_grids
328 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: albevetr_id_grids
329 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: albgrass_id_grids
330 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: porosity_id_grids
331
332 REAL(kind(1d0)) :: decidcap_id
333 REAL(kind(1d0)) :: albdectr_id
334 REAL(kind(1d0)) :: albevetr_id
335 REAL(kind(1d0)) :: albgrass_id
336 REAL(kind(1d0)) :: porosity_id
337
338 ! AnOHM related: added by TS 01 Mar 2016
339 ! store AnOHM coef. of all sfc. by TS 09 Apr 2016
340 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids):: Bo_grids
341 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids):: mAH_grids
342 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids):: a1AnOHM_grids
343 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids):: a2AnOHM_grids
344 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids):: a3AnOHM_grids
345 ! REAL(KIND(1d0)),DIMENSION( 0:ndays,MaxNumberOfGrids,nsurf,3):: a123AnOHM_gs
346 REAL(kind(1d0)) :: xbo ! daily Bowen ratio
347 !! store water states for AnOHM iteration, by TS 13 Apr 2016
348 !REAL(KIND(1d0)),DIMENSION(0:ndays,MaxNumberOfGrids,nsurf):: soilmoistDay !Soil moisture of each surface type at the end of a day [mm], 13 Apr 2016 TS
349 !REAL(KIND(1d0)),DIMENSION(0:ndays,MaxNumberOfGrids,nsurf):: stateDay !Wetness status of each existing surface type at the end of a day [mm], 13 Apr 2016 TS
350
351 ! Day of week, month and season (used for water use and energy use calculations, and in OHM)
352 ! INTEGER,DIMENSION(0:ndays,3)::DayofWeek !1 - day of week; 2 - month; 3 - season
353 !-----------------------------------------------------------------------------------------------
354
355 ! --- Vegetation phenology ---------------------------------------------------------------------
356 ! Parameters provided in input information for each vegetation surface (SUEWS_Veg.txt)
357 REAL(kind(1d0)), DIMENSION(nvegsurf) :: baset !Base temperature for growing degree days [degC]
358 REAL(kind(1d0)), DIMENSION(nvegsurf) :: basete !Base temperature for senescence degree days [degC]
359 REAL(kind(1d0)), DIMENSION(nvegsurf) :: gddfull !Growing degree days needed for full capacity [degC]
360 REAL(kind(1d0)), DIMENSION(nvegsurf) :: sddfull !Senescence degree days needed to initiate leaf off [degC]
361 REAL(kind(1d0)), DIMENSION(nvegsurf) :: laimin !Min LAI [m2 m-2]
362 REAL(kind(1d0)), DIMENSION(nvegsurf) :: laimax !Max LAI [m2 m-2]
363 REAL(kind(1d0)), DIMENSION(nvegsurf) :: maxconductance !Max conductance [mm s-1]
364 REAL(kind(1d0)), DIMENSION(4, nvegsurf) :: laipower !Coeffs for LAI equation: 1,2 - leaf growth; 3,4 - leaf off
365 !! N.B. currently DecTr only, although input provided for all veg types
366 INTEGER, DIMENSION(nvegsurf) :: laitype !LAI equation to use: original (0) or new (1)
367 !real(kind(1d0))::GDDmax,SDDMax ! Max GDD and SDD across all veg types [degC] (removed HCW 03 Mar 2015)
368
369 REAL(kind(1d0)), DIMENSION(nvegsurf) :: biogenco2code, & !Biogenic CO2 Code for SUEWS_BiogenCO2.txt
370 alpha_bioco2, &
371 beta_bioco2, &
372 theta_bioco2, &
375 resp_a, &
376 resp_b, &
378
379 !No longer used (removed HCW 27 Nov 2014)
380 !real(kind(1d0)),dimension(0:23)::runT ! running average T for the day
381 !real(kind(1d0)),dimension(0:23)::runP ! running total Precip for the day
382 !real (kind(1d0))::avT_h, totP_h ! daily running average Temp, Total precip
383 !-----------------------------------------------------------------------------------------------
384
385 ! ---- Variables related to NARP ---------------------------------------------------------------
386 REAL(kind(1d0)), DIMENSION(nsurf) :: alb !Albedo of each surface type [-]
387 REAL(kind(1d0)), DIMENSION(nsurf) :: emis !Emissivity of each surface type [-]
388
389 REAL(kind(1d0)) :: bulkalbedo !Bulk albedo for whole surface (areally-weighted)
390
391 ! Radiation balance components for different surfaces
392 REAL(kind(1d0)), DIMENSION(nsurf) :: tsurf_ind, & !Surface temperature for each surface [degC]
393 tsurf_ind_snow, & !Snow surface temperature for each surface [degC]
395 REAL(kind(1d0)), DIMENSION(nsurf) :: kup_ind, & !Outgoing shortwave radiation for each surface [W m-2]
396 kup_ind_snow, & !Outgoing shortwave radiation for each snow surface [W m-2]
398 REAL(kind(1d0)), DIMENSION(nsurf) :: lup_ind, & !Outgoing longwave radiation for each surface [W m-2]
399 lup_ind_snow, & !Outgoing longwave radiation for each snow surface [W m-2]
401 REAL(kind(1d0)), DIMENSION(nsurf) :: qn1_ind, & !Net all-wave radiation for each surface [W m-2]
402 qn1_ind_snow, & !Net all-wave radiation for each snow surface [W m-2]
404
405 ! ---- NARP-specific parameters ----------------------------------------------------------------
406 REAL(kind(1d0)) :: narp_lat, narp_long, narp_year, narp_tz, &
408 REAL(kind(1d0)) :: narp_g(365) !!QUESTION: Should this be NDays? - HCW
409 INTEGER :: narp_nperhour
410 REAL(kind(1d0)), ALLOCATABLE :: narp_kdown_hr(:)
411 ! Constants required
412 REAL(kind(1d0)), PARAMETER :: deg2rad = 0.017453292, &
413 rad2deg = 57.29577951, &
414 sigma_sb = 5.67e-8
415 !-----------------------------------------------------------------------------------------------
416
417 ! ---- OHM coefficients ------------------------------------------------------------------------
418 REAL(kind(1d0)), DIMENSION(nsurf + 1, 4, 3) :: ohm_coef !Array for OHM coefficients
419 REAL(kind(1d0)), DIMENSION(nsurf + 1) :: ohm_threshsw, ohm_threshwd !Arrays for OHM thresholds
420 REAL(kind(1d0)) :: a1, a2, a3 !OHM coefficients, a1 [-]; a2 [h]; a3 [W m-2]
421 ! REAL(KIND(1d0)),DIMENSION(:,:),ALLOCATABLE:: qn1_store, qn1_S_store !Q* values for each timestep over previous hr (_S for snow)
422 ! REAL(KIND(1d0)),DIMENSION(:,:),ALLOCATABLE:: qn1_av_store, qn1_S_av_store !Hourly Q* values for each timestep over previous 2 hr
423 ! REAL(KIND(1d0)),DIMENSION(:),ALLOCATABLE::qn1_store_grid,qn1_av_store_grid
424 ! REAL(KIND(1d0)),DIMENSION(:),ALLOCATABLE::qn1_S_store_grid,qn1_S_av_store_grid
425
426 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: tair_av_grids
427 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: qn_av_grids, qn_s_av_grids
428 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: dqndt_grids, dqnsdt_grids
429 REAL(kind(1d0)) :: qn_av, dqndt
430 REAL(kind(1d0)) :: tair_av
431 REAL(kind(1d0)) :: qn_s_av, dqnsdt
432
433 !-----------------------------------------------------------------------------------------------
434
435 ! ---- Snow-related variables ------------------------------------------------------------------
436 REAL(kind(1d0)), DIMENSION(nsurf) :: changsnow, & !Change in snowpack in mm
437 maxsnowvol, & !! Maximum snow volume
438 snowwater, & !!Liquid water in the snow pack of ith surface
439 ev_snow, & !!Evaporation from snowpack in mm
440 mw_ind, & !Melt water from individual surface in mm
441 mw_indday, & !!Melt water per day from each surface type in m3
442 runoffsnow, & !!Runoff from snowpack in mm and in m3
443 snowdens, & !Density of snow
444 snowfrac, & !!Surface fraction of snow cover
445 icefrac, &
446 snowinit, &
447 snowdepth, & !Depth of snow in cm
448 snowtosurf, & !Meltwater flowing from snow to surface
449 volswe, &
450 statefraction, & !Fraction of state that can freeze
451 freezmelt, & !Amount of freezing meltwater in mm for the ith surface area
452 qm_freezstate, & !Heat by freezing of surface state
453 freezstate, & !Amount of freezing state in mm for the ith surface area
455 qm_melt, & !Heat consumption by snow melt
456 qm_rain, & !Heat by rain falling on snow
457 rainonsnow, & !Liquid precipitation falling on snow ()
459 deltaqi
460
461 REAL(kind(1d0)), DIMENSION(nsurf, MaxNumberOfGrids) :: icefrac_grids
462
463 REAL(kind(1d0)), DIMENSION(nsurf) :: snowpack, & !Amount of snow on each surface in mm
465 INTEGER, DIMENSION(nsurf) :: heig, & !snow layer height
467 snowcalcswitch = 0 !Defines if snow related balance is made
468 !-----------------------------------------------------------------------------------------------
469
470 ! ---- Grid connections ------------------------------------------------------------------------
471 !! Grid connections needs coding, currently no water transfer between grids
472 ! Added HCW 14 Nov 2014
473 INTEGER, PARAMETER :: nconns = 8 !Number of grids for between-grid connections
474 REAL(kind(1d0)), DIMENSION(nconns) :: gridtofrac !Fraction of water moving to the grid specified in GridTo [-]
475 REAL(kind(1d0)), DIMENSION(nconns) :: gridto !Grid that water moves to
476 !!character(len=15),dimension(2,MaxNumberOfGrids)::GridConnections !List of different grid corrections
477 !!real (kind(1d0)),dimension(MaxNumberOfGrids):: GridConnectionsFrac !Fraction of water moving between the different grids
478 !-----------------------------------------------------------------------------------------------
479
480 ! ---- AnOHM related variable, added by TS, 01 Mar 2016 ---------------------------------------------------------------
481 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: a1anohm, a2anohm, a3anohm ! OHM coefficients, a1 [-]; a2 [h]; a3 [W m-2]
482 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: mahanohm ! daily mean AH [W m-2]
483 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: boanohmstart ! initial Bo for interation [-]
484 REAL(kind(1d0)), DIMENSION(MaxNumberOfGrids) :: boanohmend ! final Bo for interation [-]
485 REAL(kind(1d0)), DIMENSION(nsurf) :: cpanohm ! heat capacity [J m-3 K-1]
486 REAL(kind(1d0)), DIMENSION(nsurf) :: kkanohm ! thermal conductivity [W m-1 K-1]
487 REAL(kind(1d0)), DIMENSION(nsurf) :: chanohm ! bulk transfer coef. [-]
488 !-----------------------------------------------------------------------------------------------
489
490 !------------------- ESTM variables for SUEWS surfaces---------------------------------------------------------
491 INTEGER :: nlayer !Number of vertical layers
492 INTEGER, DIMENSION(:), ALLOCATABLE :: nlayer_grids !Number of vertical layers for each grid
493
494 ! roof
495 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: sfr_roof
496 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: tsfc_roof
497 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: k_roof
498 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: cp_roof
499 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: dz_roof
500 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: tin_roof
501 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: alb_roof
502 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: emis_roof
503 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: state_roof
504 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: statelimit_roof
505 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: wetthresh_roof
506 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: soilstore_roof
507 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: soilstorecap_roof
508 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: temp_roof
509 ! larger container arrays for different grids
510 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: tsfc_roof_grids
511 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: sfr_roof_grids
512 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: k_roof_grids
513 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: cp_roof_grids
514 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dz_roof_grids
515 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: tin_roof_grids
516 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: alb_roof_grids
517 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: emis_roof_grids
518 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: state_roof_grids
519 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: statelimit_roof_grids
520 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: wetthresh_roof_grids
521 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: soilstore_roof_grids
522 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: soilstorecap_roof_grids
523 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: temp_roof_grids
524
525 ! wall
526 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: sfr_wall
527 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: tsfc_wall
528 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: k_wall
529 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: cp_wall
530 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: dz_wall
531 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: tin_wall
532 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: alb_wall
533 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: emis_wall
534 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: state_wall
535 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: statelimit_wall
536 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: wetthresh_wall
537 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: soilstore_wall
538 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: soilstorecap_wall
539 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: temp_wall
540 ! larger container arrays for different grids
541 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: tsfc_wall_grids
542 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: sfr_wall_grids
543 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: k_wall_grids
544 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: cp_wall_grids
545 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dz_wall_grids
546 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: tin_wall_grids
547 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: alb_wall_grids
548 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: emis_wall_grids
549 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: state_wall_grids
550 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: statelimit_wall_grids
551 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: wetthresh_wall_grids
552 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: soilstore_wall_grids
553 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: soilstorecap_wall_grids
554 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: temp_wall_grids
555
556 ! standard suews surfaces
557 ! INTEGER :: nsurf !Number of surf facets
558 ! REAL(KIND(1D0)), DIMENSION(:), ALLOCATABLE :: sfr_surf
559 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: tsfc_surf
560 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: k_surf
561 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: cp_surf
562 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: dz_surf
563 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: tin_surf
564 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: temp_surf
565 ! INTEGER :: nsurf_grids !Number of surf_grids facets
566 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: tsfc_surf_grids
567 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: k_surf_grids
568 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: cp_surf_grids
569 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: dz_surf_grids
570 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: tin_surf_grids
571 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: temp_surf_grids
572 !-----------------------------------------------------------------------------------------------
573
574 !------------------- SPARTACUS variables for SUEWS subsurfaces----------------------------------------------
575 ! INTEGER, PARAMETER :: JPRD = SELECTED_REAL_KIND(13,300) ! same as kind(1d0)
576 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: height
577 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: building_frac
578 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: veg_frac
579 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: building_scale
580 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: veg_scale
581 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: veg_ext
582 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: veg_fsd
583 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: veg_contact_fraction
584 ! REAL(KIND(1D0)), DIMENSION(:, :), ALLOCATABLE :: alb_roof
585 ! REAL(KIND(1D0)), DIMENSION(:, :), ALLOCATABLE :: alb_wall
586 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: roof_albedo_dir_mult_fact
587 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: wall_specular_frac
588 ! REAL(KIND(1D0)), DIMENSION(:, :), ALLOCATABLE :: emis_roof
589 ! REAL(KIND(1D0)), DIMENSION(:, :), ALLOCATABLE :: emis_wall
590
591 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: height_grids
592 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: building_frac_grids
593 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: veg_frac_grids
594 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: building_scale_grids
595 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: veg_scale_grids
596 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: veg_ext_grids
597 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: veg_fsd_grids
598 REAL(kind(1d0)), DIMENSION(:, :), ALLOCATABLE :: veg_contact_fraction_grids
599 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: roof_albedo_dir_mult_fact_grids
600 REAL(kind(1d0)), DIMENSION(:, :, :), ALLOCATABLE :: wall_specular_frac_grids
601
602 ! SPARTACUS input variables
610 !------------------- ESTM_ext variables for heterogeneous facets---------------------------------------------------------
611 REAL(kind(1d0)), DIMENSION(5, nsurfIncSnow) :: zsurf_suewssurfs, &
614
615 !-----------------------------------------------------------------------------------------------
616
617 !---------------------------------- Column numbers ---------------------------------------------
618
619 ! ---- Set column numbering for SurfaceChar ----------------------------------------------------
620 ! Columns 1:80 are the same as in SiteSelect.txt and defined below
621 INTEGER :: cc !Column counter
622 INTEGER, PARAMETER :: ccendsi = ncolumnssiteselect
623
624 ! Applicable to each surface
625 INTEGER, DIMENSION(nsurf) :: c_albmin = (/(cc, cc=ccendsi + 0*nsurf + 1, ccendsi + 0*nsurf + nsurf, 1)/) !Min. albedo
626 INTEGER, DIMENSION(nsurf) :: c_albmax = (/(cc, cc=ccendsi + 1*nsurf + 1, ccendsi + 1*nsurf + nsurf, 1)/) !Max. albedo
627 INTEGER, DIMENSION(nsurf) :: c_emis = (/(cc, cc=ccendsi + 2*nsurf + 1, ccendsi + 2*nsurf + nsurf, 1)/) !Emissivity
628 INTEGER, DIMENSION(nsurf) :: c_stormin = (/(cc, cc=ccendsi + 3*nsurf + 1, ccendsi + 3*nsurf + nsurf, 1)/) !Min. storage capacity (canopy)
629 INTEGER, DIMENSION(nsurf) :: c_stormax = (/(cc, cc=ccendsi + 4*nsurf + 1, ccendsi + 4*nsurf + nsurf, 1)/) !Max. storage capacity (canopy)
630 INTEGER, DIMENSION(nsurf) :: c_wetthresh = (/(cc, cc=ccendsi + 5*nsurf + 1, ccendsi + 5*nsurf + nsurf, 1)/) !Threshold for wet evaporation [mm]
631 INTEGER, DIMENSION(nsurf) :: c_statelimit = (/(cc, cc=ccendsi + 6*nsurf + 1, ccendsi + 6*nsurf + nsurf, 1)/) !Limit for surface state [mm]
632 INTEGER, DIMENSION(nsurf) :: c_dreq = (/(cc, cc=ccendsi + 7*nsurf + 1, ccendsi + 7*nsurf + nsurf, 1)/) !Drainage equation
633 INTEGER, DIMENSION(nsurf) :: c_drcoef1 = (/(cc, cc=ccendsi + 8*nsurf + 1, ccendsi + 8*nsurf + nsurf, 1)/) !Drainage coef. 1
634 INTEGER, DIMENSION(nsurf) :: c_drcoef2 = (/(cc, cc=ccendsi + 9*nsurf + 1, ccendsi + 9*nsurf + nsurf, 1)/) !Drainage coef. 2
635 INTEGER, DIMENSION(nsurf) :: c_soiltcode = (/(cc, cc=ccendsi + 10*nsurf + 1, ccendsi + 10*nsurf + nsurf, 1)/) !Soil type code
636
637 ! N.B. not included in SUEWS_Water.txt
638 INTEGER, DIMENSION(nsurf) :: c_snowlimpat = (/(cc, cc=ccendsi + 11*nsurf + 1, ccendsi + 11*nsurf + nsurf, 1)/) !Snow limit for patchiness
639 ! N.B. currently only in SUEWS_NonVeg.txt
640 INTEGER, DIMENSION(nsurf) :: c_snowlimrem = (/(cc, cc=ccendsi + 12*nsurf + 1, ccendsi + 12*nsurf + nsurf, 1)/) !Snow limit for removal
641 ! AnOHM TS
642 INTEGER, DIMENSION(nsurf) :: c_cpanohm = (/(cc, cc=ccendsi + 13*nsurf + 1, ccendsi + 13*nsurf + nsurf, 1)/) !heat capacity, AnOHM TS
643 INTEGER, DIMENSION(nsurf) :: c_kkanohm = (/(cc, cc=ccendsi + 14*nsurf + 1, ccendsi + 14*nsurf + nsurf, 1)/) !heat conductivity, AnOHM TS
644 INTEGER, DIMENSION(nsurf) :: c_chanohm = (/(cc, cc=ccendsi + 15*nsurf + 1, ccendsi + 15*nsurf + nsurf, 1)/) !bulk transfer coef., AnOHM TS
645
646 ! Find current column number
647 INTEGER, PARAMETER :: ccendi = (ccendsi + 15*nsurf + nsurf) !add columns for AnOHM, AnOHM TS
648
649 ! Applicable to vegetated surfaces only
650 INTEGER, DIMENSION(NVegSurf) :: c_baset = (/(cc, cc=ccendi + 0*nvegsurf + 1, ccendi + 0*nvegsurf + nvegsurf, 1)/) !Base temp. for leaf-on
651 INTEGER, DIMENSION(NVegSurf) :: c_basete = (/(cc, cc=ccendi + 1*nvegsurf + 1, ccendi + 1*nvegsurf + nvegsurf, 1)/) !Base temp. for leaf-off
652 INTEGER, DIMENSION(NVegSurf) :: c_gddfull = (/(cc, cc=ccendi + 2*nvegsurf + 1, ccendi + 2*nvegsurf + nvegsurf, 1)/) !GDD for full LAI
653 INTEGER, DIMENSION(NVegSurf) :: c_sddfull = (/(cc, cc=ccendi + 3*nvegsurf + 1, ccendi + 3*nvegsurf + nvegsurf, 1)/) !SDD for start of leaf-fall
654 INTEGER, DIMENSION(NVegSurf) :: c_laimin = (/(cc, cc=ccendi + 4*nvegsurf + 1, ccendi + 4*nvegsurf + nvegsurf, 1)/) !Min. LAI
655 INTEGER, DIMENSION(NVegSurf) :: c_laimax = (/(cc, cc=ccendi + 5*nvegsurf + 1, ccendi + 5*nvegsurf + nvegsurf, 1)/) !Max. LAI
656 INTEGER, DIMENSION(NVegSurf) :: c_porositymin = (/(cc, cc=ccendi + 6*nvegsurf + 1, ccendi + 6*nvegsurf + nvegsurf, 1)/) !Min. Porosity
657 INTEGER, DIMENSION(NVegSurf) :: c_porositymax = (/(cc, cc=ccendi + 7*nvegsurf + 1, ccendi + 7*nvegsurf + nvegsurf, 1)/) !Max. Porosity
658 INTEGER, DIMENSION(NVegSurf) :: c_gsmax = (/(cc, cc=ccendi + 8*nvegsurf + 1, ccendi + 8*nvegsurf + nvegsurf, 1)/) !Max. conductance
659 INTEGER, DIMENSION(NVegSurf) :: c_laieq = (/(cc, cc=ccendi + 9*nvegsurf + 1, ccendi + 9*nvegsurf + nvegsurf, 1)/) !LAI equation
660 INTEGER, DIMENSION(NVegSurf) :: c_leafgp1 = (/(cc, cc=ccendi + 10*nvegsurf + 1, ccendi + 10*nvegsurf + nvegsurf, 1)/) !Leaf growth power 1
661 INTEGER, DIMENSION(NVegSurf) :: c_leafgp2 = (/(cc, cc=ccendi + 11*nvegsurf + 1, ccendi + 11*nvegsurf + nvegsurf, 1)/) !Leaf growth power 2
662 INTEGER, DIMENSION(NVegSurf) :: c_leafop1 = (/(cc, cc=ccendi + 12*nvegsurf + 1, ccendi + 12*nvegsurf + nvegsurf, 1)/) !Leaf-off power 1
663 INTEGER, DIMENSION(NVegSurf) :: c_leafop2 = (/(cc, cc=ccendi + 13*nvegsurf + 1, ccendi + 13*nvegsurf + nvegsurf, 1)/) !Leaf-off power 2
664 INTEGER, DIMENSION(NVegSurf) :: c_biogenco2code = (/(cc, cc=ccendi + 14*nvegsurf + 1, ccendi + 14*nvegsurf + nvegsurf, 1)/) !Biogenic CO2 Code
665 ! Find current column number
666 INTEGER, PARAMETER :: ccendp = (ccendi + 14*nvegsurf + nvegsurf)
667
668 ! Applicable to water surfaces only
669 INTEGER :: c_waterdepth = (ccendp + 1)
670
671 ! Find current column number
672 INTEGER, PARAMETER :: ccendw = (ccendp + 1)
673
674 ! Applicable to snow only
675 INTEGER :: c_snowrmfactor = (ccendw + 1)
676 INTEGER :: c_snowtmfactor = (ccendw + 2)
677 INTEGER :: c_snowalbmin = (ccendw + 3)
678 INTEGER :: c_snowalbmax = (ccendw + 4)
679 !integer:: c_SnowAlb = (ccEndW+ 5)
680 INTEGER :: c_snowemis = (ccendw + 6)
681 INTEGER :: c_snowtau_a = (ccendw + 7)
682 INTEGER :: c_snowtau_f = (ccendw + 8)
683 INTEGER :: c_snowplimalb = (ccendw + 9)
684 INTEGER :: c_snowsdmin = (ccendw + 10)
685 INTEGER :: c_snowsdmax = (ccendw + 11)
686 INTEGER :: c_snowtau_r = (ccendw + 12)
687 INTEGER :: c_snowcrwmin = (ccendw + 13)
688 INTEGER :: c_snowcrwmax = (ccendw + 14)
689 INTEGER :: c_snowplimsnow = (ccendw + 15)
690
691 ! Find current column number
692 INTEGER, PARAMETER :: ccendsn = (ccendw + 15)
693
694 ! Soil information
695 INTEGER, DIMENSION(nsurf) :: c_soildepth = (/(cc, cc=ccendsn + 0*nsurf + 1, ccendsn + 0*nsurf + nsurf, 1)/) ! Volumetric SM capacity
696 INTEGER, DIMENSION(nsurf) :: c_soilstcap = (/(cc, cc=ccendsn + 1*nsurf + 1, ccendsn + 1*nsurf + nsurf, 1)/) ! Volumetric SM capacity
697 INTEGER, DIMENSION(nsurf) :: c_ksat = (/(cc, cc=ccendsn + 2*nsurf + 1, ccendsn + 2*nsurf + nsurf, 1)/) ! Saturated hydraulic conductivity
698 INTEGER, DIMENSION(nsurf) :: c_soildens = (/(cc, cc=ccendsn + 3*nsurf + 1, ccendsn + 3*nsurf + nsurf, 1)/) ! Soil Density
699 INTEGER, DIMENSION(nsurf) :: c_soilinfrate = (/(cc, cc=ccendsn + 4*nsurf + 1, ccendsn + 4*nsurf + nsurf, 1)/) ! Soil infiltration rate
700 INTEGER, DIMENSION(nsurf) :: c_obssmdepth = (/(cc, cc=ccendsn + 5*nsurf + 1, ccendsn + 5*nsurf + nsurf, 1)/) ! Depth of SM obs
701 INTEGER, DIMENSION(nsurf) :: c_obssmmax = (/(cc, cc=ccendsn + 6*nsurf + 1, ccendsn + 6*nsurf + nsurf, 1)/) ! Obs maximum SM [kg kg-1 OR m3 m-3]
702 INTEGER, DIMENSION(nsurf) :: c_obssnrfrac = (/(cc, cc=ccendsn + 7*nsurf + 1, ccendsn + 7*nsurf + nsurf, 1)/) ! Obs fraction of soil without rocks
703
704 ! Find current column number
705 INTEGER, PARAMETER :: ccendso = (ccendsn + 7*nsurf + nsurf)
706
707 ! Surface conductance
708 INTEGER :: c_gsg1 = (ccendso + 1)
709 INTEGER :: c_gsg2 = (ccendso + 2)
710 INTEGER :: c_gsg3 = (ccendso + 3)
711 INTEGER :: c_gsg4 = (ccendso + 4)
712 INTEGER :: c_gsg5 = (ccendso + 5)
713 INTEGER :: c_gsg6 = (ccendso + 6)
714 INTEGER :: c_gsth = (ccendso + 7)
715 INTEGER :: c_gstl = (ccendso + 8)
716 INTEGER :: c_gss1 = (ccendso + 9)
717 INTEGER :: c_gss2 = (ccendso + 10)
718 INTEGER :: c_gskmax = (ccendso + 11)
719 INTEGER :: c_gsmodel = (ccendso + 12)
720
721 ! Find current column number
722 INTEGER, PARAMETER :: ccendgs = (ccendso + 12)
723
724 ! OHM codes
725 INTEGER, DIMENSION(nsurfIncSnow) :: c_ohmcode_swet = (/(cc, cc=ccendgs + 0*nsurfincsnow + 1, &
726 ccendgs + 0*nsurfincsnow + nsurfincsnow, 1)/) !OHM code (summer wet)
727 INTEGER, DIMENSION(nsurfIncSnow) :: c_ohmcode_sdry = (/(cc, cc=ccendgs + 1*nsurfincsnow + 1, &
728 ccendgs + 1*nsurfincsnow + nsurfincsnow, 1)/) !OHM code (summer dry)
729 INTEGER, DIMENSION(nsurfIncSnow) :: c_ohmcode_wwet = (/(cc, cc=ccendgs + 2*nsurfincsnow + 1, &
730 ccendgs + 2*nsurfincsnow + nsurfincsnow, 1)/) !OHM code (winter wet)
731 INTEGER, DIMENSION(nsurfIncSnow) :: c_ohmcode_wdry = (/(cc, cc=ccendgs + 3*nsurfincsnow + 1, &
732 ccendgs + 3*nsurfincsnow + nsurfincsnow, 1)/) !OHM code (winter dry)
733 INTEGER, DIMENSION(nsurfIncSnow) :: c_a1_swet = (/(cc, cc=ccendgs + 4*nsurfincsnow + 1, &
734 ccendgs + 4*nsurfincsnow + nsurfincsnow, 1)/) !OHM a1 (summer wet)
735 INTEGER, DIMENSION(nsurfIncSnow) :: c_a2_swet = (/(cc, cc=ccendgs + 5*nsurfincsnow + 1, &
736 ccendgs + 5*nsurfincsnow + nsurfincsnow, 1)/) !OHM a2 (summer wet)
737 INTEGER, DIMENSION(nsurfIncSnow) :: c_a3_swet = (/(cc, cc=ccendgs + 6*nsurfincsnow + 1, &
738 ccendgs + 6*nsurfincsnow + nsurfincsnow, 1)/) !OHM a3 (summer wet)
739 INTEGER, DIMENSION(nsurfIncSnow) :: c_a1_sdry = (/(cc, cc=ccendgs + 7*nsurfincsnow + 1, &
740 ccendgs + 7*nsurfincsnow + nsurfincsnow, 1)/) !OHM a1 (summer dry)
741 INTEGER, DIMENSION(nsurfIncSnow) :: c_a2_sdry = (/(cc, cc=ccendgs + 8*nsurfincsnow + 1, &
742 ccendgs + 8*nsurfincsnow + nsurfincsnow, 1)/) !OHM a2 (summer dry)
743 INTEGER, DIMENSION(nsurfIncSnow) :: c_a3_sdry = (/(cc, cc=ccendgs + 9*nsurfincsnow + 1, &
744 ccendgs + 9*nsurfincsnow + nsurfincsnow, 1)/) !OHM a3 (summer dry)
745 INTEGER, DIMENSION(nsurfIncSnow) :: c_a1_wwet = (/(cc, cc=ccendgs + 10*nsurfincsnow + 1, &
746 ccendgs + 10*nsurfincsnow + nsurfincsnow, 1)/) !OHM a1 (winter wet)
747 INTEGER, DIMENSION(nsurfIncSnow) :: c_a2_wwet = (/(cc, cc=ccendgs + 11*nsurfincsnow + 1, &
748 ccendgs + 11*nsurfincsnow + nsurfincsnow, 1)/) !OHM a2 (winter wet)
749 INTEGER, DIMENSION(nsurfIncSnow) :: c_a3_wwet = (/(cc, cc=ccendgs + 12*nsurfincsnow + 1, &
750 ccendgs + 12*nsurfincsnow + nsurfincsnow, 1)/) !OHM a3 (winter wet)
751 INTEGER, DIMENSION(nsurfIncSnow) :: c_a1_wdry = (/(cc, cc=ccendgs + 13*nsurfincsnow + 1, &
752 ccendgs + 13*nsurfincsnow + nsurfincsnow, 1)/) !OHM a1 (winter dry)
753 INTEGER, DIMENSION(nsurfIncSnow) :: c_a2_wdry = (/(cc, cc=ccendgs + 14*nsurfincsnow + 1, &
754 ccendgs + 14*nsurfincsnow + nsurfincsnow, 1)/) !OHM a2 (winter dry)
755 INTEGER, DIMENSION(nsurfIncSnow) :: c_a3_wdry = (/(cc, cc=ccendgs + 15*nsurfincsnow + 1, &
756 ccendgs + 15*nsurfincsnow + nsurfincsnow, 1)/) !OHM a3 (winter dry)
757
758 INTEGER, DIMENSION(nsurfIncSnow) :: c_ohmthresh_sw = (/(cc, cc=ccendgs + 16*nsurfincsnow + 1, &
759 ccendgs + 16*nsurfincsnow + nsurfincsnow, 1)/) !OHM Threshold (summer/winter)
760 INTEGER, DIMENSION(nsurfIncSnow) :: c_ohmthresh_wd = (/(cc, cc=ccendgs + 17*nsurfincsnow + 1, &
761 ccendgs + 17*nsurfincsnow + nsurfincsnow, 1)/) !OHM Threshold (wet/dry)
762
763 ! ESTM code for each surface inclduing snow
764 INTEGER, DIMENSION(nsurfIncSnow) :: c_estmcode = (/(cc, cc=ccendgs + 18*nsurfincsnow + 1, &
765 ccendgs + 18*nsurfincsnow + nsurfincsnow, 1)/) !ESTM code
766
767 ! Find current column number
768 INTEGER, PARAMETER :: ccendo = (ccendgs + 18*nsurfincsnow + nsurfincsnow)
769
770 ! Anthropogenic Emissions
771 INTEGER :: c_baset_hc = (ccendo + 1)
772 INTEGER :: c_qf_a1 = (ccendo + 2)
773 INTEGER :: c_qf_b1 = (ccendo + 3)
774 INTEGER :: c_qf_c1 = (ccendo + 4)
775 INTEGER :: c_qf_a2 = (ccendo + 5)
776 INTEGER :: c_qf_b2 = (ccendo + 6)
777 INTEGER :: c_qf_c2 = (ccendo + 7)
778 INTEGER :: c_ahmin_wd = (ccendo + 8)
779 INTEGER :: c_ahmin_we = (ccendo + 9)
780 INTEGER :: c_ahslopeheating_wd = (ccendo + 10)
781 INTEGER :: c_ahslopeheating_we = (ccendo + 11)
782 INTEGER :: c_ahslopecooling_wd = (ccendo + 12)
783 INTEGER :: c_ahslopecooling_we = (ccendo + 13)
784 INTEGER :: c_tcriticheating_we = (ccendo + 14)
785 INTEGER :: c_tcriticheating_wd = (ccendo + 15)
786 INTEGER :: c_tcriticcooling_we = (ccendo + 16)
787 INTEGER :: c_tcriticcooling_wd = (ccendo + 17)
788 INTEGER :: c_enprofwd = (ccendo + 18)
789 INTEGER :: c_enprofwe = (ccendo + 19)
790 INTEGER :: c_co2mwd = (ccendo + 20)
791 INTEGER :: c_co2mwe = (ccendo + 21)
792 INTEGER :: c_traffprofwd = (ccendo + 22)
793 INTEGER :: c_traffprofwe = (ccendo + 23)
794 INTEGER :: c_popprofwd = (ccendo + 24)
795 INTEGER :: c_popprofwe = (ccendo + 25)
796 INTEGER :: c_minqfmetab = (ccendo + 26)
797 INTEGER :: c_maxqfmetab = (ccendo + 27)
798 INTEGER :: c_minfcmetab = (ccendo + 28)
799 INTEGER :: c_maxfcmetab = (ccendo + 29)
800 INTEGER :: c_frpddwe = (ccendo + 30)
801 INTEGER :: c_frfossilfuel_heat = (ccendo + 31)
802 INTEGER :: c_frfossilfuel_nonheat = (ccendo + 32)
803 INTEGER :: c_ef_umolco2perj = (ccendo + 33)
804 INTEGER :: c_enef_v_jkm = (ccendo + 34)
805 INTEGER :: c_fcef_v_kgkmwd = (ccendo + 35)
806 INTEGER :: c_fcef_v_kgkmwe = (ccendo + 36)
807 INTEGER :: c_co2pointsource = (ccendo + 37)
808 INTEGER :: c_trafficunits = (ccendo + 38)
809
810 ! Find current column number
811 INTEGER, PARAMETER :: ccenda = (ccendo + 38)
812
813 ! Irrigation
814 INTEGER :: c_iestart = (ccenda + 1)
815 INTEGER :: c_ieend = (ccenda + 2)
816 INTEGER :: c_intwu = (ccenda + 3)
817 INTEGER :: c_faut = (ccenda + 4)
818 INTEGER :: c_h_maintain = (ccenda + 5)
819 INTEGER, DIMENSION(3) :: c_ie_a = (/(cc, cc=ccenda + 5 + 0*3 + 1, ccenda + 5 + 0*3 + 3, 1)/) ! Automatic irrigation coeffs
820 INTEGER, DIMENSION(3) :: c_ie_m = (/(cc, cc=ccenda + 5 + 1*3 + 1, ccenda + 5 + 1*3 + 3, 1)/) ! Manual irrigation coeffs
821 INTEGER, DIMENSION(7) :: c_daywat = (/(cc, cc=ccenda + 11 + 0*7 + 1, ccenda + 11 + 0*7 + 7, 1)/) ! Irrigation allowed on each day
822 INTEGER, DIMENSION(7) :: c_daywatper = (/(cc, cc=ccenda + 11 + 1*7 + 1, ccenda + 11 + 1*7 + 7, 1)/) ! Fraction properties using irrigation allowed on each day
823
824 ! Find current column number
825 INTEGER, PARAMETER :: ccendir = (ccenda + 11 + 1*7 + 7)
826
827 ! Hourly profiles
828 INTEGER, DIMENSION(24) :: c_hrprofenusewd = (/(cc, cc=ccendir + 0*24 + 1, ccendir + 0*24 + 24, 1)/) ! Energy use, weekdays
829 INTEGER, DIMENSION(24) :: c_hrprofenusewe = (/(cc, cc=ccendir + 1*24 + 1, ccendir + 1*24 + 24, 1)/) ! Energy use, weekends
830 INTEGER, DIMENSION(24) :: c_hrprofwumanuwd = (/(cc, cc=ccendir + 2*24 + 1, ccendir + 2*24 + 24, 1)/) ! Water use, manual, weekdays
831 INTEGER, DIMENSION(24) :: c_hrprofwumanuwe = (/(cc, cc=ccendir + 3*24 + 1, ccendir + 3*24 + 24, 1)/) ! Water use, manual, weekends
832 INTEGER, DIMENSION(24) :: c_hrprofwuautowd = (/(cc, cc=ccendir + 4*24 + 1, ccendir + 4*24 + 24, 1)/) ! Water use, automatic, weekdays
833 INTEGER, DIMENSION(24) :: c_hrprofwuautowe = (/(cc, cc=ccendir + 5*24 + 1, ccendir + 5*24 + 24, 1)/) ! Water use, automatic, weekends
834 INTEGER, DIMENSION(24) :: c_hrprofsnowcwd = (/(cc, cc=ccendir + 6*24 + 1, ccendir + 6*24 + 24, 1)/) ! Snow clearing, weekdays
835 INTEGER, DIMENSION(24) :: c_hrprofsnowcwe = (/(cc, cc=ccendir + 7*24 + 1, ccendir + 7*24 + 24, 1)/) ! Snow clearing, weekends
836 INTEGER, DIMENSION(24) :: c_hrprofhumactivitywd = (/(cc, cc=ccendir + 8*24 + 1, ccendir + 8*24 + 24, 1)/) ! Human activity, weekdays
837 INTEGER, DIMENSION(24) :: c_hrprofhumactivitywe = (/(cc, cc=ccendir + 9*24 + 1, ccendir + 9*24 + 24, 1)/) ! Human activity, weekends
838 INTEGER, DIMENSION(24) :: c_hrproftraffwd = (/(cc, cc=ccendir + 10*24 + 1, ccendir + 10*24 + 24, 1)/) ! Traffic, weekdays
839 INTEGER, DIMENSION(24) :: c_hrproftraffwe = (/(cc, cc=ccendir + 11*24 + 1, ccendir + 11*24 + 24, 1)/) ! Traffic, weekends
840 INTEGER, DIMENSION(24) :: c_hrprofpopwd = (/(cc, cc=ccendir + 12*24 + 1, ccendir + 12*24 + 24, 1)/) ! Population, weekdays
841 INTEGER, DIMENSION(24) :: c_hrprofpopwe = (/(cc, cc=ccendir + 13*24 + 1, ccendir + 13*24 + 24, 1)/) ! Population, weekends
842
843 ! Find current column number
844 INTEGER, PARAMETER :: ccendpr = (ccendir + 13*24 + 24)
845
846 ! Within-grid water distribution (for each surface)
847 INTEGER, DIMENSION(nsurf) :: c_wgtopaved = (/(cc, cc=ccendpr + 0*nsurf + 1, ccendpr + 0*nsurf + nsurf, 1)/) !Water dist to Paved
848 INTEGER, DIMENSION(nsurf) :: c_wgtobldgs = (/(cc, cc=ccendpr + 1*nsurf + 1, ccendpr + 1*nsurf + nsurf, 1)/) !Water dist to Bldgs
849 INTEGER, DIMENSION(nsurf) :: c_wgtoevetr = (/(cc, cc=ccendpr + 2*nsurf + 1, ccendpr + 2*nsurf + nsurf, 1)/) !Water dist to EveTr
850 INTEGER, DIMENSION(nsurf) :: c_wgtodectr = (/(cc, cc=ccendpr + 3*nsurf + 1, ccendpr + 3*nsurf + nsurf, 1)/) !Water dist to DecTr
851 INTEGER, DIMENSION(nsurf) :: c_wgtograss = (/(cc, cc=ccendpr + 4*nsurf + 1, ccendpr + 4*nsurf + nsurf, 1)/) !Water dist to Grass
852 INTEGER, DIMENSION(nsurf) :: c_wgtobsoil = (/(cc, cc=ccendpr + 5*nsurf + 1, ccendpr + 5*nsurf + nsurf, 1)/) !Water dist to BSoil
853 INTEGER, DIMENSION(nsurf) :: c_wgtowater = (/(cc, cc=ccendpr + 6*nsurf + 1, ccendpr + 6*nsurf + nsurf, 1)/) !Water dist to Water
854 INTEGER, DIMENSION(nsurf) :: c_wgtorunoff = (/(cc, cc=ccendpr + 7*nsurf + 1, ccendpr + 7*nsurf + nsurf, 1)/) !Water dist to runoff
855 INTEGER, DIMENSION(nsurf) :: c_wgtosoilstore = (/(cc, cc=ccendpr + 8*nsurf + 1, ccendpr + 8*nsurf + nsurf, 1)/) !Water dist to sub-surface soil
856
857 ! Find current column number
858 INTEGER, PARAMETER :: cbendwg = (ccendpr + 8*nsurf + nsurf)
859
860 ! Biogenic CO2
861 INTEGER, DIMENSION(nvegsurf) :: c_alpha_bioco2 = (/(cc, cc=cbendwg + 0*nvegsurf + 1, cbendwg + 0*nvegsurf + nvegsurf, 1)/)
862 INTEGER, DIMENSION(nvegsurf) :: c_beta_bioco2 = (/(cc, cc=cbendwg + 1*nvegsurf + 1, cbendwg + 1*nvegsurf + nvegsurf, 1)/)
863 INTEGER, DIMENSION(nvegsurf) :: c_theta_bioco2 = (/(cc, cc=cbendwg + 2*nvegsurf + 1, cbendwg + 2*nvegsurf + nvegsurf, 1)/)
864 INTEGER, DIMENSION(nvegsurf) :: c_alpha_enh_bioco2 = (/(cc, cc=cbendwg + 3*nvegsurf + 1, cbendwg + 3*nvegsurf + nvegsurf, 1)/)
865 INTEGER, DIMENSION(nvegsurf) :: c_beta_enh_bioco2 = (/(cc, cc=cbendwg + 4*nvegsurf + 1, cbendwg + 4*nvegsurf + nvegsurf, 1)/)
866 INTEGER, DIMENSION(nvegsurf) :: c_resp_a = (/(cc, cc=cbendwg + 5*nvegsurf + 1, cbendwg + 5*nvegsurf + nvegsurf, 1)/)
867 INTEGER, DIMENSION(nvegsurf) :: c_resp_b = (/(cc, cc=cbendwg + 6*nvegsurf + 1, cbendwg + 6*nvegsurf + nvegsurf, 1)/)
868 INTEGER, DIMENSION(nvegsurf) :: c_min_res_bioco2 = (/(cc, cc=cbendwg + 7*nvegsurf + 1, cbendwg + 7*nvegsurf + nvegsurf, 1)/)
869
870 ! Find current column number
871 INTEGER, PARAMETER :: ccendb = (cbendwg + 7*nvegsurf + nvegsurf)
872
873 !ESTM
874 ! Roof/surface characteristics for all surfaces including snow
875 INTEGER, DIMENSION(nsurfIncSnow) :: &
886 c_surf_k4 = [(cc, cc=ccendb + 10*nsurfincsnow + 1, ccendb + 10*nsurfincsnow + nsurfincsnow, 1)], &
889 c_surf_k5 = [(cc, cc=ccendb + 13*nsurfincsnow + 1, ccendb + 13*nsurfincsnow + nsurfincsnow, 1)], &
891 ! Find current column number
892 INTEGER, PARAMETER :: ccendestmb = (ccendb + 14*nsurfincsnow + nsurfincsnow)
893 ! Other ESTM characteristics are for built surfaces only
894 INTEGER :: c_wall_thick1 = (ccendestmb + 1)
895 INTEGER :: c_wall_k1 = (ccendestmb + 2)
896 INTEGER :: c_wall_rhocp1 = (ccendestmb + 3)
897 INTEGER :: c_wall_thick2 = (ccendestmb + 4)
898 INTEGER :: c_wall_k2 = (ccendestmb + 5)
899 INTEGER :: c_wall_rhocp2 = (ccendestmb + 6)
900 INTEGER :: c_wall_thick3 = (ccendestmb + 7)
901 INTEGER :: c_wall_k3 = (ccendestmb + 8)
902 INTEGER :: c_wall_rhocp3 = (ccendestmb + 9)
903 INTEGER :: c_wall_thick4 = (ccendestmb + 10)
904 INTEGER :: c_wall_k4 = (ccendestmb + 11)
905 INTEGER :: c_wall_rhocp4 = (ccendestmb + 12)
906 INTEGER :: c_wall_thick5 = (ccendestmb + 13)
907 INTEGER :: c_wall_k5 = (ccendestmb + 14)
908 INTEGER :: c_wall_rhocp5 = (ccendestmb + 15)
909 INTEGER :: c_internal_thick1 = (ccendestmb + 16)
910 INTEGER :: c_internal_k1 = (ccendestmb + 17)
911 INTEGER :: c_internal_rhocp1 = (ccendestmb + 18)
912 INTEGER :: c_internal_thick2 = (ccendestmb + 19)
913 INTEGER :: c_internal_k2 = (ccendestmb + 20)
914 INTEGER :: c_internal_rhocp2 = (ccendestmb + 21)
915 INTEGER :: c_internal_thick3 = (ccendestmb + 22)
916 INTEGER :: c_internal_k3 = (ccendestmb + 23)
917 INTEGER :: c_internal_rhocp3 = (ccendestmb + 24)
918 INTEGER :: c_internal_thick4 = (ccendestmb + 25)
919 INTEGER :: c_internal_k4 = (ccendestmb + 26)
920 INTEGER :: c_internal_rhocp4 = (ccendestmb + 27)
921 INTEGER :: c_internal_thick5 = (ccendestmb + 28)
922 INTEGER :: c_internal_k5 = (ccendestmb + 29)
923 INTEGER :: c_internal_rhocp5 = (ccendestmb + 30)
924 INTEGER :: c_nroom = (ccendestmb + 31)
925 INTEGER :: c_alb_ibld = (ccendestmb + 32)
926 INTEGER :: c_em_ibld = (ccendestmb + 33)
927 INTEGER :: c_ch_iwall = (ccendestmb + 34)
928 INTEGER :: c_ch_iroof = (ccendestmb + 35)
929 INTEGER :: c_ch_ibld = (ccendestmb + 36)
930 ! Find current column number
931 INTEGER, PARAMETER :: ccendestmm = (ccendestmb + 36)
932 ! For Paved surfaces, there are 3 possible ESTM classes (with _Surf characteristics only)
933 INTEGER, DIMENSION(3) :: c_surf_thick1_paved = (/(cc, cc=ccendestmm + 0*3 + 1, ccendestmm + 0*3 + 3, 1)/)
934 INTEGER, DIMENSION(3) :: c_surf_k1_paved = (/(cc, cc=ccendestmm + 1*3 + 1, ccendestmm + 1*3 + 3, 1)/)
935 INTEGER, DIMENSION(3) :: c_surf_rhocp1_paved = (/(cc, cc=ccendestmm + 2*3 + 1, ccendestmm + 2*3 + 3, 1)/)
936 INTEGER, DIMENSION(3) :: c_surf_thick2_paved = (/(cc, cc=ccendestmm + 3*3 + 1, ccendestmm + 3*3 + 3, 1)/)
937 INTEGER, DIMENSION(3) :: c_surf_k2_paved = (/(cc, cc=ccendestmm + 4*3 + 1, ccendestmm + 4*3 + 3, 1)/)
938 INTEGER, DIMENSION(3) :: c_surf_rhocp2_paved = (/(cc, cc=ccendestmm + 5*3 + 1, ccendestmm + 5*3 + 3, 1)/)
939 INTEGER, DIMENSION(3) :: c_surf_thick3_paved = (/(cc, cc=ccendestmm + 6*3 + 1, ccendestmm + 6*3 + 3, 1)/)
940 INTEGER, DIMENSION(3) :: c_surf_k3_paved = (/(cc, cc=ccendestmm + 7*3 + 1, ccendestmm + 7*3 + 3, 1)/)
941 INTEGER, DIMENSION(3) :: c_surf_rhocp3_paved = (/(cc, cc=ccendestmm + 8*3 + 1, ccendestmm + 8*3 + 3, 1)/)
942 INTEGER, DIMENSION(3) :: c_surf_thick4_paved = (/(cc, cc=ccendestmm + 9*3 + 1, ccendestmm + 9*3 + 3, 1)/)
943 INTEGER, DIMENSION(3) :: c_surf_k4_paved = (/(cc, cc=ccendestmm + 10*3 + 1, ccendestmm + 10*3 + 3, 1)/)
944 INTEGER, DIMENSION(3) :: c_surf_rhocp4_paved = (/(cc, cc=ccendestmm + 11*3 + 1, ccendestmm + 11*3 + 3, 1)/)
945 INTEGER, DIMENSION(3) :: c_surf_thick5_paved = (/(cc, cc=ccendestmm + 12*3 + 1, ccendestmm + 12*3 + 3, 1)/)
946 INTEGER, DIMENSION(3) :: c_surf_k5_paved = (/(cc, cc=ccendestmm + 13*3 + 1, ccendestmm + 13*3 + 3, 1)/)
947 INTEGER, DIMENSION(3) :: c_surf_rhocp5_paved = (/(cc, cc=ccendestmm + 14*3 + 1, ccendestmm + 14*3 + 3, 1)/)
948 ! Find current column number
949 INTEGER, PARAMETER :: ccendestmmp = (ccendestmm + 14*3 + 3)
950 ! For Bldgs surfaces, there are 5 possible ESTM classes (all characteristics)
951 INTEGER, DIMENSION(5) :: c_surf_thick1_bldgs = (/(cc, cc=ccendestmmp + 0*5 + 1, ccendestmmp + 0*5 + 5, 1)/)
952 INTEGER, DIMENSION(5) :: c_surf_k1_bldgs = (/(cc, cc=ccendestmmp + 1*5 + 1, ccendestmmp + 1*5 + 5, 1)/)
953 INTEGER, DIMENSION(5) :: c_surf_rhocp1_bldgs = (/(cc, cc=ccendestmmp + 2*5 + 1, ccendestmmp + 2*5 + 5, 1)/)
954 INTEGER, DIMENSION(5) :: c_surf_thick2_bldgs = (/(cc, cc=ccendestmmp + 3*5 + 1, ccendestmmp + 3*5 + 5, 1)/)
955 INTEGER, DIMENSION(5) :: c_surf_k2_bldgs = (/(cc, cc=ccendestmmp + 4*5 + 1, ccendestmmp + 4*5 + 5, 1)/)
956 INTEGER, DIMENSION(5) :: c_surf_rhocp2_bldgs = (/(cc, cc=ccendestmmp + 5*5 + 1, ccendestmmp + 5*5 + 5, 1)/)
957 INTEGER, DIMENSION(5) :: c_surf_thick3_bldgs = (/(cc, cc=ccendestmmp + 6*5 + 1, ccendestmmp + 6*5 + 5, 1)/)
958 INTEGER, DIMENSION(5) :: c_surf_k3_bldgs = (/(cc, cc=ccendestmmp + 7*5 + 1, ccendestmmp + 7*5 + 5, 1)/)
959 INTEGER, DIMENSION(5) :: c_surf_rhocp3_bldgs = (/(cc, cc=ccendestmmp + 8*5 + 1, ccendestmmp + 8*5 + 5, 1)/)
960 INTEGER, DIMENSION(5) :: c_surf_thick4_bldgs = (/(cc, cc=ccendestmmp + 9*5 + 1, ccendestmmp + 9*5 + 5, 1)/)
961 INTEGER, DIMENSION(5) :: c_surf_k4_bldgs = (/(cc, cc=ccendestmmp + 10*5 + 1, ccendestmmp + 10*5 + 5, 1)/)
962 INTEGER, DIMENSION(5) :: c_surf_rhocp4_bldgs = (/(cc, cc=ccendestmmp + 11*5 + 1, ccendestmmp + 11*5 + 5, 1)/)
963 INTEGER, DIMENSION(5) :: c_surf_thick5_bldgs = (/(cc, cc=ccendestmmp + 12*5 + 1, ccendestmmp + 12*5 + 5, 1)/)
964 INTEGER, DIMENSION(5) :: c_surf_k5_bldgs = (/(cc, cc=ccendestmmp + 13*5 + 1, ccendestmmp + 13*5 + 5, 1)/)
965 INTEGER, DIMENSION(5) :: c_surf_rhocp5_bldgs = (/(cc, cc=ccendestmmp + 14*5 + 1, ccendestmmp + 14*5 + 5, 1)/)
966 INTEGER, DIMENSION(5) :: c_wall_thick1_bldgs = (/(cc, cc=ccendestmmp + 15*5 + 1, ccendestmmp + 15*5 + 5, 1)/)
967 INTEGER, DIMENSION(5) :: c_wall_k1_bldgs = (/(cc, cc=ccendestmmp + 16*5 + 1, ccendestmmp + 16*5 + 5, 1)/)
968 INTEGER, DIMENSION(5) :: c_wall_rhocp1_bldgs = (/(cc, cc=ccendestmmp + 17*5 + 1, ccendestmmp + 17*5 + 5, 1)/)
969 INTEGER, DIMENSION(5) :: c_wall_thick2_bldgs = (/(cc, cc=ccendestmmp + 18*5 + 1, ccendestmmp + 18*5 + 5, 1)/)
970 INTEGER, DIMENSION(5) :: c_wall_k2_bldgs = (/(cc, cc=ccendestmmp + 19*5 + 1, ccendestmmp + 19*5 + 5, 1)/)
971 INTEGER, DIMENSION(5) :: c_wall_rhocp2_bldgs = (/(cc, cc=ccendestmmp + 20*5 + 1, ccendestmmp + 20*5 + 5, 1)/)
972 INTEGER, DIMENSION(5) :: c_wall_thick3_bldgs = (/(cc, cc=ccendestmmp + 21*5 + 1, ccendestmmp + 21*5 + 5, 1)/)
973 INTEGER, DIMENSION(5) :: c_wall_k3_bldgs = (/(cc, cc=ccendestmmp + 22*5 + 1, ccendestmmp + 22*5 + 5, 1)/)
974 INTEGER, DIMENSION(5) :: c_wall_rhocp3_bldgs = (/(cc, cc=ccendestmmp + 23*5 + 1, ccendestmmp + 23*5 + 5, 1)/)
975 INTEGER, DIMENSION(5) :: c_wall_thick4_bldgs = (/(cc, cc=ccendestmmp + 24*5 + 1, ccendestmmp + 24*5 + 5, 1)/)
976 INTEGER, DIMENSION(5) :: c_wall_k4_bldgs = (/(cc, cc=ccendestmmp + 25*5 + 1, ccendestmmp + 25*5 + 5, 1)/)
977 INTEGER, DIMENSION(5) :: c_wall_rhocp4_bldgs = (/(cc, cc=ccendestmmp + 26*5 + 1, ccendestmmp + 26*5 + 5, 1)/)
978 INTEGER, DIMENSION(5) :: c_wall_thick5_bldgs = (/(cc, cc=ccendestmmp + 27*5 + 1, ccendestmmp + 27*5 + 5, 1)/)
979 INTEGER, DIMENSION(5) :: c_wall_k5_bldgs = (/(cc, cc=ccendestmmp + 28*5 + 1, ccendestmmp + 28*5 + 5, 1)/)
980 INTEGER, DIMENSION(5) :: c_wall_rhocp5_bldgs = (/(cc, cc=ccendestmmp + 29*5 + 1, ccendestmmp + 29*5 + 5, 1)/)
981 INTEGER, DIMENSION(5) :: c_internal_thick1_bldgs = (/(cc, cc=ccendestmmp + 30*5 + 1, ccendestmmp + 30*5 + 5, 1)/)
982 INTEGER, DIMENSION(5) :: c_internal_k1_bldgs = (/(cc, cc=ccendestmmp + 31*5 + 1, ccendestmmp + 31*5 + 5, 1)/)
983 INTEGER, DIMENSION(5) :: c_internal_rhocp1_bldgs = (/(cc, cc=ccendestmmp + 32*5 + 1, ccendestmmp + 32*5 + 5, 1)/)
984 INTEGER, DIMENSION(5) :: c_internal_thick2_bldgs = (/(cc, cc=ccendestmmp + 33*5 + 1, ccendestmmp + 33*5 + 5, 1)/)
985 INTEGER, DIMENSION(5) :: c_internal_k2_bldgs = (/(cc, cc=ccendestmmp + 34*5 + 1, ccendestmmp + 34*5 + 5, 1)/)
986 INTEGER, DIMENSION(5) :: c_internal_rhocp2_bldgs = (/(cc, cc=ccendestmmp + 35*5 + 1, ccendestmmp + 35*5 + 5, 1)/)
987 INTEGER, DIMENSION(5) :: c_internal_thick3_bldgs = (/(cc, cc=ccendestmmp + 36*5 + 1, ccendestmmp + 36*5 + 5, 1)/)
988 INTEGER, DIMENSION(5) :: c_internal_k3_bldgs = (/(cc, cc=ccendestmmp + 37*5 + 1, ccendestmmp + 37*5 + 5, 1)/)
989 INTEGER, DIMENSION(5) :: c_internal_rhocp3_bldgs = (/(cc, cc=ccendestmmp + 38*5 + 1, ccendestmmp + 38*5 + 5, 1)/)
990 INTEGER, DIMENSION(5) :: c_internal_thick4_bldgs = (/(cc, cc=ccendestmmp + 39*5 + 1, ccendestmmp + 39*5 + 5, 1)/)
991 INTEGER, DIMENSION(5) :: c_internal_k4_bldgs = (/(cc, cc=ccendestmmp + 40*5 + 1, ccendestmmp + 40*5 + 5, 1)/)
992 INTEGER, DIMENSION(5) :: c_internal_rhocp4_bldgs = (/(cc, cc=ccendestmmp + 41*5 + 1, ccendestmmp + 41*5 + 5, 1)/)
993 INTEGER, DIMENSION(5) :: c_internal_thick5_bldgs = (/(cc, cc=ccendestmmp + 42*5 + 1, ccendestmmp + 42*5 + 5, 1)/)
994 INTEGER, DIMENSION(5) :: c_internal_k5_bldgs = (/(cc, cc=ccendestmmp + 43*5 + 1, ccendestmmp + 43*5 + 5, 1)/)
995 INTEGER, DIMENSION(5) :: c_internal_rhocp5_bldgs = (/(cc, cc=ccendestmmp + 44*5 + 1, ccendestmmp + 44*5 + 5, 1)/)
996 INTEGER, DIMENSION(5) :: c_nroom_bldgs = (ccendestmmp + 44*5 + 5 + 1)
997 INTEGER, DIMENSION(5) :: c_alb_ibld_bldgs = (ccendestmmp + 44*5 + 5 + 2)
998 INTEGER, DIMENSION(5) :: c_em_ibld_bldgs = (ccendestmmp + 44*5 + 5 + 3)
999 INTEGER, DIMENSION(5) :: c_ch_iwall_bldgs = (ccendestmmp + 44*5 + 5 + 4)
1000 INTEGER, DIMENSION(5) :: c_ch_iroof_bldgs = (ccendestmmp + 44*5 + 5 + 5)
1001 INTEGER, DIMENSION(5) :: c_ch_ibld_bldgs = (ccendestmmp + 44*5 + 5 + 6)
1002
1003 !Last column number for SurfaceChar array
1004 INTEGER, PARAMETER :: maxncols_c = (ccendestmmp + 44*5 + 5 + 6)
1005 !-----------------------------------------------------------------------------------------------
1006
1007 ! ---- Set column numbering for ModelOutputData ------------------------------------------------
1008 ! Applicable to each surface
1009 INTEGER, PARAMETER :: ccmod = 32
1010 INTEGER, DIMENSION(nsurf) :: cmod_state = (/(cc, cc=ccmod + 0*nsurf + 1, ccmod + 0*nsurf + nsurf, 1)/) !Above ground state
1011 INTEGER, DIMENSION(nsurf) :: cmod_soilstate = (/(cc, cc=ccmod + 1*nsurf + 1, ccmod + 1*nsurf + nsurf, 1)/) !Below ground state (soil store)
1012 INTEGER, DIMENSION(nsurf) :: cmod_snowwaterstate = (/(cc, cc=ccmod + 2*nsurf + 1, ccmod + 2*nsurf + nsurf, 1)/) !Liquid (melted) water
1013 INTEGER, DIMENSION(nsurf) :: cmod_snowpack = (/(cc, cc=ccmod + 3*nsurf + 1, ccmod + 3*nsurf + nsurf, 1)/) !SWE
1014 INTEGER, DIMENSION(nsurf) :: cmod_snowfrac = (/(cc, cc=ccmod + 4*nsurf + 1, ccmod + 4*nsurf + nsurf, 1)/) !Snow fraction
1015 INTEGER, DIMENSION(nsurf) :: cmod_snowdens = (/(cc, cc=ccmod + 5*nsurf + 1, ccmod + 5*nsurf + nsurf, 1)/) !Snow density
1016
1017 !Last column number for ModelOutputData array
1018 INTEGER, PARAMETER :: maxncols_cmod = ccmod + 5*nsurf + nsurf
1019 !-----------------------------------------------------------------------------------------------
1020
1021 ! ---- Set column numbering for ModelDailyState ------------------------------------------------
1022 ! Applicable to each surface
1023 INTEGER, PARAMETER :: ccmds = 30
1024 INTEGER, DIMENSION(nsurf) :: cmds_snowdens = (/(cc, cc=ccmds + 0*nsurf + 1, ccmds + 0*nsurf + nsurf, 1)/) !Snow density
1025
1026 !Last column number for ModelDailyState array
1027 INTEGER, PARAMETER :: maxncols_cmds = ccmds + 0*nsurf + nsurf
1028 !-----------------------------------------------------------------------------------------------
1029
1030 ! ---- Set column numbering for ESTM_Ts_data input file ===-------------------------------------
1031 ! HCW 15 June 2016
1032 INTEGER, PARAMETER :: cts_iy = 1
1033 INTEGER, PARAMETER :: cts_id = 2
1034 INTEGER, PARAMETER :: cts_it = 3
1035 INTEGER, PARAMETER :: cts_imin = 4
1036 INTEGER, PARAMETER :: cts_tiair = 5
1037 INTEGER, PARAMETER :: cts_tsurf = 6
1038 INTEGER, PARAMETER :: cts_troof = 7
1039 INTEGER, PARAMETER :: cts_troad = 8
1040 INTEGER, PARAMETER :: cts_twall = 9
1041 INTEGER, PARAMETER :: cts_twall_n = 10
1042 INTEGER, PARAMETER :: cts_twall_e = 11
1043 INTEGER, PARAMETER :: cts_twall_s = 12
1044 INTEGER, PARAMETER :: cts_twall_w = 13
1045
1046END MODULE allocatearray
1047!==================================================================================================
1048
1049!==================================================================================================
1051
1052 IMPLICIT NONE
1053
1054 INTEGER :: firstyear, & !First year to run (specified in SiteSelect.txt)
1055 lastyear, & !Last year to run (specified in SiteSelect.txt)
1056 firstgrid, & !First grid to run (as in SiteSelect)
1057 lastgrid, & !Last grid to run (as in SiteSelect)
1058 numberofgrids, & !Number of grids
1059 gridcounter, & !Counter for grids (i.e. from 1 to NumberOfGrids)
1060 readblocksmetdata, & !Number of blocks of met data to read (for each grid, for each year)
1061 readblocksorigmetdata, & !Number of blocks of original met data to read (for each grid, for each year)
1062 readlinesmetdata, & !Number of lines of met data in each block (for each grid)
1063 readlinesorigmetdata, & !Number of lines of original met data in each block (before downscaling)
1064 readlinesorigestmdata, & !Number of lines of original ESTM data in each block (before downscaling)
1065 readlinesorigmetdatamax, & !No. lines of original met data in each block (adjusts for last block (equivalent of irMax))
1066 readlinesorigestmdatamax, & !No. lines of original ESTM data in each block
1067 nlinesorigmetdata, & !Number of lines in original met data file
1068 nlinesorigestmdata, & !Number of lines in original ESTM data file
1069 nlinesmetdata, & !Number of lines in Met Forcing file
1070 nlinesestmdata, & !Number of lines in ESTM Forcing file
1071 nlinessiteselect, & !Number of lines in SUEWS_SiteSelect.txt
1072 nlinesnonveg, & !Number of lines in SUEWS_NonVeg.txt
1073 nlinesveg, & !Number of lines in SUEWS_Veg.txt
1074 nlineswater, & !Number of lines in SUEWS_Water.txt
1075 nlinessnow, & !Number of lines in SUEWS_Snow.txt
1076 nlinessoil, & !Number of lines in SUEWS_Soil.txt
1077 nlinesconductance, & !Number of lines in SUEWS_Conductance.txt
1078 nlinesohmcoefficients, & !Number of lines in SUEWS_OHMCoefficients.txt
1079 nlinesestmcoefficients, & !Number of lines in SUEWS_ESTMCoefficients.txt
1080 nlinesanthropogenic, & !Number of lines in SUEWS_AnthropogenicEmission.txt
1081 nlinesirrigation, & !Number of lines in SUEWS_Irrigation.txt
1082 nlinesprofiles, & !Number of lines in SUEWS_Profiles.txt
1083 nlineswgwaterdist, & !Number of lines in SUEWS_WGWaterDist.txt
1084 nlinesbiogen, & !Number of lines in SUEWS_BiogenCO2.txt
1085 nlines, & !Number of lines in different files
1086 skippedlines, & !Number of lines to skip over before reading each block of met data
1087 skippedlinesorig, & !Number of lines to skip over before reading each block of data from original met file
1088 skippedlinesorigestm, & !Number of lines to skip over before reading each block of data from original ESTM file
1089 iv5 !Counter for code matching.
1090
1091END MODULE initial
1092!==================================================================================================
1093
1094!==================================================================================================
1096
1097 IMPLICIT NONE
1098
1099 CHARACTER(len=90) :: progname = 'SUEWS_V2021a'
1100
1101 ! ---- Run information ------------------------------------------------------------------------
1102 CHARACTER(len=20) :: filecode !Set in RunControl
1103 CHARACTER(len=150) :: fileinputpath, & !Filepath for input files (set in RunControl)
1104 fileoutputpath !Filepath for output files (set in RunControl)
1105 ! ---- File names -----------------------------------------------------------------------------
1106 CHARACTER(len=150) :: fileout, & !Output file name
1107 filechoices, & !Run characteristics file name
1108 filestateinit, & !Run characteristics file name
1109 filemet, & !Meteorological forcing file name
1110 fileorigmet, & !Original meteorological forcing file name (i.e. before downscaling)
1111 fileorigestm, & !Original ESTM forcing file name (i.e. before downscaling)
1112 filedscdmet, & !Downscaled meteorological forcing file name
1113 filedscdestm, & !Downscaled ESTM forcing file name
1114 filedaily, & !Daily State output file name
1115 fileestmts, & !ESTM input file name
1116 solweigpoiout, & !SOLWEIG poi file name
1117 blout, & !CLB output file name
1118 fileout_tt, & !Output file name (for resolution at model time-step)
1120
1121 INTEGER :: skipheadersiteinfo = 2 !Number of header lines to skip in SiteInfo files
1122 INTEGER :: skipheadermet = 1 !Number of header lines to skip in met forcing file
1123
1124 ! ---- Model options set in RunControl --------------------------------------------------------
1125 INTEGER :: emissionsmethod, & ! anthropogenic emissions method
1126 basetmethod, & ! base temperature method for HDD/CDD calculations used in QF module
1127 cbluse, & !CBL slab model used (1) or not used (0)
1128 multiplemetfiles, & !Indicates whether a single met file is used for all grids (0) or one for each grid (1)
1129 multipleinitfiles, & !Indicates whether a single initial conditions file is used for all grids (0) or one for each grid (1)
1130 multipleestmfiles, & !Indicates whether a single ESTM input data file is used for all grids (0) or one for each grid (1)
1131 multiplelayoutfiles, & !Indicates whether a single grid layout input data file is used for all grids (0) or one for each grid (1)
1132 keeptstepfilesin, & !Delete (0) or keep (1) input met files at resolution of tstep (used by python, not fortran)
1133 keeptstepfilesout, & !Delete (0) or keep (1) output files at resolution of tstep (used by python, not fortran)
1134 resolutionfilesin, & !Specify resolution of input file [s]
1135 resolutionfilesout, & !Specify resolution of output file [s]
1136 resolutionfilesinestm, & !Specify resolution of ESTM input file [s]
1137 writeoutoption, & !Choose variables to include in main output file
1138 netradiationmethod, & !Options for net all-wave radiation calculation
1139 ohmincqf, & !OHM calculation uses Q* only (0) or Q*+QF (1)
1140 storageheatmethod, & !OHM (1); QS in met file (2); AnOHM(3); ESTM(4)
1141 snowuse, & !Snow part used (1) or not used (0)
1142 ! SOLWEIGuse, & !SOLWEIG part used (calculates Tmrt and other fluxes on a grid, FL)
1143 smdmethod, & !Use modelled (0) or observed(1,2) soil moisture
1144 waterusemethod, & !Use modelled (0) or observed (1) water use
1145 roughlenmommethod, & !Defines method for calculating z0 & zd
1146 disaggmethod, & ! Sets disaggregation method for original met forcing data
1147 disaggmethodestm, & ! Sets disaggregation method for original met forcing data
1148 raindisaggmethod, & ! Sets disaggregation method for original met forcing data for rainfall
1149 rainamongn, & ! Number of subintervals over which to disaggregate rainfall
1150 kdownzen, & ! Controls whether Kdown disaggregation uses zenith angle (1) or not (0)
1151 suppresswarnings = 1, & ! Set to 1 to prevent warnings.txt file from being written
1152 diagmethod, & !Specify the approach for near surface diagnostic: 0, MOST; 1, RSL; 2, Auto (MOST+RSL)
1153 diagnose, & !Set to 1 to get print-out of model progress
1154 diagnosedisagg, & !Set to 1 to get print-out of met forcing disaggregation progress
1155 ! ncMode, & !Write output file in netCDF (1) or not (0) , TS, 09 Dec 2016
1156 ! nRow, & !number of rows of checker board layout in the netCDF output, TS, 09 Dec 2016
1157 ! nCol, & !number of columns of checker board layout in the netCDF output, TS, 09 Dec 2016
1158 diagnosedisaggestm, & !Set to 1 to get print-out of ESTM forcing disaggregation progress
1159 diagqn, diagqs !Set to 1 to print values/components
1160
1161 ! For more complex downscaling allow different RainAmongN for different intensities
1162 INTEGER, DIMENSION(5) :: multrainamongn ! RainAmongN for each intensity bin
1163 REAL(kind(1d0)), DIMENSION(5) :: multrainamongnupperi ! Upper bound of intensity bin for which to apply MultRainAmongN
1164
1165 ! ---- Model options currently set in model, but may be moved to RunControl at a later date
1166 INTEGER :: albedochoice, & !No additional albedo varaition (0); zenith angle calculation (1)
1167 !Currently set to 0 in SUEWS_Initial
1168 inputmetformat, & !Defines format for met input data: LUMPS format(1) or SUEWS format(10)
1169 !Currently set to 10 in SUEWS_Initial
1170 evapmethod, & !Evaporation calculated according to Rutter (1) or Shuttleworth (2)
1171 !Currently set to 2 in OverallRunControl
1172 laicalcyes, & !Use observed (0) or modelled (1) LAI
1173 !Currently set to 1 in OverallRunControl
1174 writedailystate !Daily state file written (1)
1175 !Currently set to 1 in SUEWS_Initial
1176
1177 ! ---- Other options used within model --------------------------------------------------------
1178 INTEGER :: ldown_option !Parameterisation used for downward longwave radiation (1/2/3)
1179
1180 ! ---- Output file numbers --------------------------------------------------------------------
1181 INTEGER :: lfnout, & !Error Output write units
1182 lfnoutc, & !Clean output write units
1183 lfnold !!Was used for GridConnections
1184
1185 INTEGER :: outputformats !Used to control writing out of output file format
1186
1187 ! ---- Other options set in RunControl --------------------------------------------------------
1188 REAL(kind(1d0)) :: timezone !Timezone (GMT=0)
1189
1190 ! ---- Variables in alphabetical order --------------------------------------------------------
1191 !! Add units
1192 REAL(kind(1d0)) :: alpha_qhqe, & !Alpha parameter used in LUMPS QH and QE calculations [-]
1193 alt, & !Altitude [m]
1194 ! avdens, & !Average air density, moved to by TS, 27 Aug 2019
1195 avkdn, & !Average downwelling shortwave radiation
1196 avrh, & !Average relative humidity
1197 avts, & !Average surface temperature
1198 avu1, & !Average wind speed
1199 avu10_ms, & !Average wind speed at 10 m
1200 azimuth, & !Sun azimuth in degrees
1201 baset_hc, & !Base temperature for QF
1202 buildenergyuse, & ! Building energy use
1203 co2mwd, & !Diurnal activity profile (weekday)
1204 co2mwe, & !Diurnal activity profile (weekend)
1205 co2pointsource, & !CO2 point source [kg C day-1]
1206 e_mod, & !Modelled latent heat flux with LUMPS [W m-2]
1207 ef_umolco2perj, & !CO2 emission factor for fuels used for building heating [umol CO2 J-1]
1208 emis_snow, & !Emissivity of snow
1209 enef_v_jkm, & !Heat release per vehicle per meter of travel [J km-1 veh-1]
1210 enprofwd, & !Diurnal energy use profile (weekday)
1211 enprofwe, & !Diurnal energy use profile (weekend)
1212 fc, & !CO2 flux [umol m-2 s-1]
1213 fc_anthro, & !CO2 flux (anthropogenic part) [umol m-2 s-1]
1214 fc_biogen, & !CO2 flux (biogenic part) [umol m-2 s-1]
1215 fc_build, & !CO2 flux (building energy use component) [umol m-2 s-1]
1216 fc_metab, & !CO2 flux (human metabolism component) [umol m-2 s-1]
1217 fc_photo, & !CO2 flux (photosynthesis component) [umol m-2 s-1]
1218 fc_point, & !CO2 flux (Point source component) [umol m-2 s-1]
1219 fc_respi, & !CO2 flux (non-human respiration component) [umol m-2 s-1]
1220 fc_traff, & !CO2 flux (traffic component) [umol m-2 s-1]
1221 fcld, & !Cloud fraction modelled
1222 fcld_obs, & !Cloud fraction observed
1223 frfossilfuel_heat, & !Fraction of fossil fuels used for building heating relative to district heating
1224 frfossilfuel_nonheat, & !Fraction of fossil fuels used for energy consumption relative to district heating
1225 frpddwe, & !Fraction of weekend population to weekday population
1226 h_mod, & !Modelled sensible heat flux with LUMPS [W m-2]
1227 kclear, & !Theoretical downward shortwave radiation
1228 kdiff, & !Diffuse shortwave radiation
1229 kdir, & !Direct shortwave radiation
1230 kup, & !Upward shortwave radiation
1231 lai_obs, & !LAI for study area provided in met forcing file
1232 lat, & !Latitude
1233 ldown, & !Downward longwave radiation
1234 ldown_obs, & !Downwelling longwave radiation
1235 lng, & !Longitude
1236 lup, & !Upward longwave radiation
1237 maxfcmetab, & !Maximum (day) CO2 from human metabolism
1238 maxqfmetab, & !Maximum (day) anthropogenic heat from human metabolism
1239 minfcmetab, & !Minimum (night) CO2 from human metabolism
1240 minqfmetab, & !Minimum (night) anthropogenic heat from human metabolism
1241 popdensnighttime, & ! Nighttime population density [ha-1] (i.e. residents)
1242 popprofwd, & !Diurnal profile for population density (weekday)
1243 popprofwe, & !Diurnal profile for population density (weekend)
1244 precip, & !Precipitation per timestep [mm]
1245 precip_hr, & !Precipitation [mm hr-1]
1246 press_hpa, & !Station air pressure in hPa
1247 pres_kpa, & !Station air pressure in kPa
1248 q2_gkg, & ! Specific humidity at 2 m
1249 qe, & !Observed latent heat flux
1250 qe_obs, &
1251 qf_build, & !Anthropogenic heat flux from building [W m-2]
1252 qf_metab, & !Anthropogenic heat flux from human metabolism [W m-2]
1253 qf_traff, & !Anthropogenic heat flux from traffic [W m-2]
1254 qf_obs, & !Observed anthropogenic heat flux
1255 qf_sahp, & !Anthropogenic heat flux calculated by SAHP
1256 qf_sahp_base, & !Anthropogenic heat flux calculated by SAHP (temp independent part)
1257 qf_sahp_heat, & !Anthropogenic heat flux calculated by SAHP (heating part only)
1258 qf_sahp_ac, & !AC contribution
1259 qh, & !Observed sensible heat flux
1260 qh_obs, &
1261 qh_r, & !Sensible heat flux calculated using resistance method
1262 qn1, & !Net all-wave radiation for the study area
1263 qn1_bup, &
1264 qn1_obs, & !Observed new all-wave radiation
1265 qn1_s, & !Total net all-wave radiation for the SnowPack
1266 qn1_snowfree, & !Total net all-wave radiation for the snowfree surface
1267 qs_obs, & !Observed storage heat flux
1268 qsanohm, & !Simulated storage heat flux by AnOHM, TS 30 May 2016
1269 qsestm, & !Simulated storage heat flux by ESTM, TS 30 May 2016
1270 snow, & !snow cover
1271 snowfrac_obs, & !Observed snow cover
1272 temp_c, & !Air temperature
1273 t2_c, & !Air temperature at 2 m, TS 20 May 2017
1274 trafficunits, & !Option for traffic units (1=[veh km m-2 day-1] 2=[veh km cap-1 day-1])
1275 traffprofwd, & !Diurnal traffic profile (weekday)
1276 traffprofwe, & !Diurnal traffic profile (weekend)
1277 trans_site, & !Atmospheric transmissivity
1278 tsurf, & !Surface temperature
1279 wdir, & ! Wind direction
1280 wu_m3, & !Water use provided in met forcing file [m3]
1281 xsmd, & !Measured soil moisture deficit
1282 year, & !Year of the measurements
1283 zenith_deg !Sun zenith angle in degrees
1284
1285 REAL(kind(1d0)), DIMENSION(2) :: qf_a, qf_b, qf_c, & !Qf coefficients
1286 ah_min, & !Minimum anthropogenic heat flux (AnthropHeatMethod = 1)
1287 ah_slope_heating, & !Slope of the antrhropogenic heat flux calculation (AnthropHeatMethod = 1)
1289 fcef_v_kgkm, &
1290 ! NumCapita, &
1292 baset_heating, & !Critical temperature
1293 baset_cooling, & !Critical cooling temperature
1294 trafficrate, & !Traffic rate
1295 qf0_beu
1296
1297 ! INTEGER,DIMENSION(2)::DayLightSavingDay !DOY when daylight saving changes
1298 INTEGER :: startdls !DOY when daylight saving starts
1299 INTEGER :: enddls !DOY when daylight saving ends
1300
1301 INTEGER :: ncblstep !number of time steps of Runge-kutta methods in one hour
1302
1303 !---------Water bucket (see B. Offerle's PhD)----------------------------------
1304 REAL(kind(1d0)) :: drainrt, & !Drainage rate of the water bucket [mm hr-1]
1305 rainbucket, & !RAINFALL RESERVOIR [mm]
1306 raincover, &
1307 rainmaxres, & !Maximum water bucket reservoir [mm]
1308 rainres, & ! [mm]
1309 tempveg !TEMPORARY VEGETATIVE SURFACE FRACTION ADJUSTED BY RAINFALL
1310
1311 !---------SOLWEIG variables---------------------------------------------------
1312 REAL(kind(1d0)) :: absl, & ! Absorption coefficient of longwave radiation of a person
1313 absk, & ! Absorption coefficient of shortwave radiation of a person
1314 heightgravity, & ! Centre of gravity for a standing person
1315 transmin, & ! Tranmissivity of K through decidious vegetation (leaf on)
1316 transmax ! Tranmissivity of K through decidious vegetation (leaf off)
1317
1318 INTEGER :: posture, & ! 1.Standing, 2.Sitting
1319 usevegdem, & ! With vegetation (1)
1320 row, & ! Y coordinate for point of interest
1321 col, & ! X coordinate for point of interest
1322 onlyglobal, & ! if no diffuse and direct SW, then =1
1323 solweigpoi_out, & ! write output variables at point of interest
1324 tmrt_out, & ! write output Tmrt grid
1325 lup2d_out, & ! write output Lup grid
1326 ldown2d_out, & ! write output Ldown grid
1327 kup2d_out, & ! write output Kup grid
1328 kdown2d_out, & ! write output Kdown grid
1329 gvf_out, & ! write output GroundViewFActor grid
1330 solweig_ldown, & ! 1= use SOLWEIG code to estimate Ldown, 0=use SEUWS
1331 outinterval, & ! Output interval in minutes
1332 runforgrid ! If only one grid should be run. All grids -999
1333
1334 CHARACTER(len=150) :: dsmpath, & ! Path to DSMs
1335 dsmname, & ! Ground and building DSM
1336 cdsmname, & ! Canopy DSM
1337 tdsmname, & ! Trunk zone DSM
1338 svfpath, & ! Path to SVFs
1339 svfsuffix, & !
1340 buildingsname ! Boolean matrix for locations of building pixels
1341
1342 !--------- AnOHM related variables----------------------------------
1343 ! to be added here
1344
1345END MODULE data_in
1346!==================================================================================================
1347
1349 IMPLICIT NONE
1350
1351 REAL(kind(1d0)) :: adjmeltfact, & !Factor between melt and freezing factors
1352 snowfallcum, & !Cumulative snowfall
1353 fwh, & !Weighted freezing water
1354 lvs_j_kg, & !Latent heat of sublimation in J/kg
1355 mwh, & !Weighted hourly water melt
1356 mwstore, & !Meltwater storage
1357 preciplimit, & !Temperature limit when precipitation occurs as snow
1358 preciplimitalb, & !Precipitation limit for albedo change (in mm)
1359 qm, & !Snow melt associated heat flux
1360 qmfreez, & !Energy released in freezing of meltwater or surface state
1361 qmrain, &
1362 qn1_snow, & !Net all-wave radiation of SnowPack
1363 qn1_nosnow, & !Same for the snow free surface
1364 radmeltfact, & !Radiation melt factor
1365 snowalb, & !Snow albedo
1366 snowalbmin, & !Minimum snow albedo
1367 snowalbmax, & !Maximum snow albedo
1368 snowdensmin, & !Minimum density of snow
1369 snowdensmax, & !Maximum density of snow
1370 snowlimbldg, & !Snow removal limits for roofs in mm)
1371 snowlimpaved, & !Snow removal limits for paved surfaces in mm)
1372 swe, & !Weighted snow water equivalent (in mm)
1373 tau_a, & !Time constans related to albedo change
1374 tau_f, &
1375 tau_r, & !Time constant for density increase.
1376 tempmeltfact, & !Temperature melt factor
1377 volday, & !Volume of the melted water per day
1378 zf, &
1379 waterholdcapfrac, & !Water holding capacity factor
1380 crwmin, & !Free water holding capacity of deep SnowPack
1381 crwmax !Free water holding capacity of shallow SnowPack
1382
1383 REAL(kind(1d0)), DIMENSION(2) :: snowremoval = 0 ! Removal of snow in mm
1384 REAL(kind(1d0)), DIMENSION(0:23, 2) :: snowprof_24hr ! Timing of snow removal (0 or 1) Hourly, WD/WE
1385
1386 INTEGER :: snowfractionchoice = 2 !Choice how fraction of snow is calculated
1387
1388END MODULE snowmod
1389!===================================================================================
1390
1391!==================================================================================================
1393 IMPLICIT NONE
1394 REAL(kind(1d0)) :: notused = -55.55, reall, nan = -999, pnan = 999
1395 INTEGER :: notusedi = -55, ios_out
1396 INTEGER :: errorchoice, warningchoice !errorChoice/warningChoice defines if problems.txt/warnings.txt is opened for the first time
1397END MODULE defaultnotused
1398!==================================================================================================
1399
1400!==================================================================================================
1401MODULE time
1402 INTEGER :: iy, & !Year
1403 id, & !Day of year
1404 it, & !Hour
1405 imin, & !Minutes
1406 isec, & !Seconds
1407 dls !day lightsavings =1 + 1h) =0
1408
1409 REAL(kind(1d0)) :: dectime !Decimal time
1410 REAL(kind(1d0)) :: tstepcount !Count number of timesteps in this day
1411 INTEGER :: nofdaysthisyear !Based on whether leap year or not
1412 INTEGER :: dt_since_start ! time since simulation starts [s]
1413
1414 INTEGER :: iy_prev_t, id_prev_t !Value of iy and id at previous timestep
1415
1416END MODULE time
1417!==================================================================================================
1418
1419!===================================================================================
1421 REAL(kind(1d0)) :: grav = 9.80665 !g - gravity - physics today august 1987
1422END MODULE mod_grav
1423
1424!===================================================================================
1425
1426!===================================================================================
1428 REAL(kind(1d0)) :: ipthreshold_mmhr = 10 !Threshold for intense precipitation [mm hr-1]
1429
1430END MODULE thresh
1431
1432!===================================================================================
1433MODULE gas
1434 ! press (mb) ea (mb)
1435 IMPLICIT NONE
1436 REAL(kind(1d0)) :: comp = 0.9995
1437 REAL(kind(1d0)) :: epsil = 0.62197 !ratio molecular weight of water vapor/dry air (kg/mol/kg/mol)
1438 REAL(kind(1d0)) :: epsil_gkg = 621.97 !ratio molecular weight of water vapor/dry air in g/kg
1439 REAL(kind(1d0)) :: dry_gas = 8.31451 !Dry gas constant (J/k/mol)
1440 REAL(kind(1d0)) :: gas_ct_wat = 461.05 !Gas constant for water (J/kg/K)
1441 REAL(kind(1d0)) :: molar = 0.028965 !Dry air molar fraction in kg/mol
1442 REAL(kind(1d0)) :: molar_wat_vap = 0.0180153 !Molar fraction of water vapor in kg/mol
1443 REAL(kind(1d0)) :: gas_ct_dry = 8.31451/0.028965 !j/kg/k=dry_gas/molar
1444 REAL(kind(1d0)) :: gas_ct_wv = 8.31451/0.0180153 !j/kg/kdry_gas/molar_wat_vap
1445END MODULE gas
1446
1447!**********************************************
1448MODULE mod_z
1449 REAL(kind(1d0)) :: zzd, & !Active measurement height (meas. height-displac. height)
1450 z0m, & !Aerodynamic roughness length
1451 zdm, & !Displacement height
1452 z0m_in, & !Aerodynamic roughness length set in SiteSelect
1453 zdm_in, & !Displacement height set in SiteSelect
1454 z !Windspeed height
1455 REAL(kind(1e10)) :: z0v !Roughness length for vapour
1456END MODULE mod_z
1457
1458!**********************************************
1459MODULE resist !Variables related surface resistance calculations (P. 1744 in G&O1991)
1460 IMPLICIT NONE
1461 REAL(kind(1d0)) :: th, & !Maximum temperature limit
1462 tl, & !Minimum temperature limit
1463 kmax, & !Annual maximum hourly solar radiation
1464 g1, g2, g3, g4, & !Fitted parameters related to
1465 g5, g6, s1, s2, & !surface res. calculations
1466 tc, & !Temperature parameter 1
1467 tc2 !Temperature parameter 2
1468 INTEGER :: gsmodel !Choice of gs parameterisation (1 = Ja11, 2 = Wa16)
1469END MODULE resist
1470
1471!**********************************************
1472MODULE moist
1473 IMPLICIT NONE
1474
1475 REAL(kind(1d0)) :: avcp, & !Specific heat capacity
1476 dens_dry, & !Dry air density kg m-3
1477 avdens, & !Average air density
1478 dq, & !Specific humidity deficit
1479 ea_hpa, & !Water vapour pressure in hPa
1480 es_hpa, & !Saturation vapour pressure in hPa
1481 lv_j_kg, & !Latent heat of vaporization in [J kg-1]
1482 tlv, & !Latent heat of vaporization per timestep [J kg-1 s-1] (tlv=lv_J_kg/tstep_real)
1483 psyc_hpa, & !Psychometric constant in hPa
1484 psycice_hpa, & !Psychometric constant in hPa for snow
1485 s_pa, & !Vapour pressure versus temperature slope in Pa
1486 s_hpa, & !Vapour pressure versus temperature slope in hPa
1487 sice_hpa, & !Vapour pressure versus temperature slope in hPa above ice/snow
1488 vpd_hpa, & !Vapour pressure deficit in hPa
1489 vpd_pa, & !Vapour pressure deficit in Pa
1490 waterdens = 999.8395 !Density of water in 0 cel deg
1491
1492END MODULE moist
1493!**********************************************
1494
1496 IMPLICIT NONE
1497
1498 REAL(kind(1d0)) :: areaunir, & !Unirrigated area
1499 areair, & !Irrigated area
1500 bldgh, & !Mean building height
1501 faibldg, & !Frontal area fraction of buildings
1502 faitree, & !Frontal area fraction of trees
1503 faievetree, & !Frontal area fraction of evergreen trees
1504 faidectree, & !Frontal area fraction of deciduous trees
1505 grassfractionirrigated, & !Irrigated grass fraction for LUMPS
1506 pavedfractionirrigated, & !Irrigated paved area fraction for LUMPS
1507 treeh, & !Mean tree height
1508 evetreeh, & !Height of evergreen trees
1509 dectreeh, & !Height of deciduous trees
1510 treefractionirrigated, & !Irrigated tree fraction for LUMPS
1511 veg_fr, & !Vegetation fraction from land area
1512 !- For LUMPS - dependent on user choice & water
1513 vegfraction, & ! sum of vegetation -not including water
1514 impervfraction, & ! sum of surface cover fractions for impervious surfaces
1515 pervfraction, & ! sum of surface cover fractions for pervious surfaces
1516 nonwaterfraction, & ! sum of surface cover fractions for all except water surfaces
1517 areazh !=(sfr_surf(BldgSurf)+sfr_surf(ConifSurf)+sfr_surf(DecidSurf)) !Total area of buildings and trees
1518
1519 INTEGER :: idgis, & !Time integers used in the code
1520 itgis, & !
1521 veg_type = 1 !Defines how vegetation is calculated for LUMPS
1522
1523END MODULE gis_data
1524
1525!************************************************************
1527 IMPLICIT NONE
1528
1529 INTEGER :: tstep, & !Timestep [s] at which the model is run (set in RunControl)
1530 tstep_prev, & !Timestep [s] of previous timestamp !NB: not used by SUEWS, but by WRF-SUEWS for adaptive time step
1531 nsh, & !Number of timesteps per hour
1532 nsd, & !Number of timesteps per day
1533 nsdorig, & !Number of timesteps per day for original met forcing file
1534 t_interval, & !Number of seconds in an hour [s] (now set in OverallRunControl)
1535 npertstepin, nperestm ! Number of model time-steps per input resolution (ResolutionFilesIn/Tstep)
1536
1537 REAL(kind(1d0)) :: nsh_real, & !nsh cast as a real for use in calculations
1538 tstep_real, & !tstep cast as a real for use in calculations
1539 npertstepin_real, nperestm_real !Nper as real
1540
1541 REAL(kind(1d0)) :: halftimestep !In decimal time based on interval
1542
1543 !Options for model setup (switches, etc) mainly set in RunControl
1544 INTEGER :: stabilitymethod, & !Defines stability functions used (set in RunControl)
1545 roughlenheatmethod !Defines method for calculating roughness length for heat (set in RunControl)
1546
1547 INTEGER :: in
1548 INTEGER :: is !Integer to count over surface types
1549
1550 !These are variables which currently have been removed from SuesInput.nml
1551 INTEGER :: aerodynamicresistancemethod = 2 !The method used to calculate aerodynamic resistance
1552
1553 INTEGER :: ie_start, & !Starting time of water use (DOY)
1554 ie_end !Ending time of water use (DOY)
1555
1556 REAL(kind(1d0)), DIMENSION(2) :: surplusevap !Surplus for evaporation in 5 min timestep
1557 ! sg -- need to determine size
1558
1559 !Variables listed in SuesInput.nml
1560 REAL(kind(1d0)) :: flowchange, & !Difference between the input and output flow in the water body
1561 pipecapacity, & !Capacity of pipes to transfer water
1562 runofftowater, & !Fraction of surface runoff going to water body
1563 smcap, & !Volumetric/gravimetric soil moisture capacity
1564 soildensity, & !Bulk density of soil
1565 soildepthmeas, & !Soil depth of the measured soil moisture
1566 soilrocks, & !Fraction of rocks in soil
1567 surfacearea, & !Surface area of the study area [m2]
1568 surfacearea_ha, & !Surface area of the study area [ha]
1569 waterbodytype, & !If water body type is pond/lake (=1) or river (=2)
1570 waterstorcap, & !Capacity of water body when surface is wet
1571 wuareaevetr_m2, & !Water use area (evergreen trees) [m2]
1572 wuareadectr_m2, & !Water use area (deciduous trees) [m2]
1573 wuareagrass_m2, & !Water use area (grass) [m2]
1574 wuareatotal_m2, & !Water use area (total) [m2]
1575 wu_evetr, & !Water use for evergreen trees/shrubs [mm]
1576 wu_dectr, & !Water use for deciduous trees/shrubs [mm]
1577 wu_grass !Water use for grass [mm]
1578
1579 !Other related to SUES
1580 REAL(kind(1d0)) :: additionalwater, & !Water flow from other grids
1581 ch_per_interval, & !Change in state per interval
1582 chsnow_per_interval, & !Change in snow state per interval
1583 di_dt, & !Water flow between two stores
1584 dr_per_interval, & !Drainage per interval
1585 ev_per_interval, & !Evaporation per interval
1586 surf_chang_per_tstep, & !Change in surface state per timestep [mm] (for whole surface)
1587 tot_chang_per_tstep, & !Change in surface and SoilState per timestep [mm] (for whole surface)
1588 nwstate_per_tstep, & !State per timestep [mm] (for whole surface, excluding water body)
1589 state_per_tstep, & !State per timestep [mm] (for whole surface)
1590 drain_per_tstep, & !Drainage per timestep [mm] (for whole surface, excluding water body)
1591 runoff_per_tstep, & !Runoff per timestep [mm] (for whole surface)
1592 runoffsoil_per_tstep, & !Runoff to deep soil per timestep [mm] (for whole surface, excluding water body)
1593 ev_per_tstep, & !Evaporation per timestep [mm] (for whole surface)
1594 qe_per_tstep, & !QE [W m-2] (for whole surface)
1595 p_mm, & !Inputs to surface water balance
1596 pin, & !Rain per time interval
1597 fai, & !Areally weighted frontal area fraction
1598 pai, & !Areally weighted plan area fraction
1599 rb, & !Boundary layer resistance
1600 ! Water leaving each grid for grid-to-grid connectivity
1601 runoffagimpervious, & !Above ground runoff from impervious surface [mm] for whole surface area
1602 runoffagveg, & !Above ground runoff from vegetated surfaces [mm] for whole surface area
1603 runoffwaterbody, & !Above ground runoff from water surface [mm] for whole surface area
1604 runoffpipes, & !Runoff in pipes [mm] for whole surface area
1605 runoffagimpervious_m3, & !Volume of above ground runoff from impervious surface [m3]
1606 runoffagveg_m3, & !Volume of above ground runoff from vegetated surfaces [m3]
1607 runoffwaterbody_m3, & !Volume of above ground runoff from water surface [m3]
1608 runoffpipes_m3, & !Volume of runoff in pipes [m3]
1609 runoff_per_interval, & ! Total water transported to each grid for grid-to-grid connectivity
1610 addimpervious, & !Water from impervious surfaces of other grids [mm] for whole surface area
1611 addveg, & !Water from vegetated surfaces of other grids [mm] for whole surface area
1612 addwaterbody, & !Water from water surface of other grids [mm] for whole surface area
1613 addpipes, & !Water in pipes from other grids [mm] for whole surface area
1615 qe_per_interval, & !latent heat per interval
1616 soilmoistcap, &
1617 soilstate, & !Area-averaged soil moisture [mm] for whole surface
1618 st_per_interval, & !Surface state per interval
1619 surpluswaterbody, & !Extra runoff that goes to water body [mm] as specified by RunoffToWater
1620 tlv_sub, &
1621 overuse = 0, &
1622 zh !Areally weighted roughness element height
1623
1624 !Calculation of u*,stability and aerodynamic resistance
1625 REAL(kind(1d0)) :: h, & !Kinematic sensible heat flux [K m s-1] used to calculate friction velocity
1626 l_mod, & !Monin-Obukhov length (either measured or modelled)
1627 psim, & !Stability function of momentum
1628 psih, & !Stability function of heat
1629 ra, & !Aerodynamic resistance
1630 rasnow, & !Aerodynamic resistance over snow
1631 tstar, & !T*
1632 ustar, & !Friction velocity
1633 z0_gis !Roughness length for momentum from gis input file
1634
1635 !Surface resistance related variables
1636 REAL(kind(1d0)) :: resistsurf, & !Surface resistance
1637 gdq, & !G(dq)
1638 qnm, & !QMAX/(QMAX+G2)
1639 gq, & !G(Q*)
1640 gtemp, & !G(T)
1641 gl, & !G(LAI)
1642 sdp, & !S1/G6+S2
1643 smd, & !Soil moisture deficit of the soil surface layer
1644 vsmd, & !Soil moisture deficit for vegetated surfaces only (QUESTION: what about BSoil?)
1645 gs, & !G(Soil moisture deficit)
1646 gsc, & !Surface Layer Conductance
1647 rss !Surface resistance after wet/partially wet adjustment
1648
1649 !SUES latent heat flux related variables
1650 REAL(kind(1d0)) :: vdrc, & !Second term up in calculation of E
1651 numpm, & !Numerator of PM equation
1652 sp, & !Term in calculation of E
1653 sae, & !Same
1654 ev, & !Evaporation
1655 rst, & !Flag in SUEWS_Evap (gets set to 1 if surface dry; 0 if surface wet)
1656 qeph, & !Latent heat flux (W m^-2)
1657 qeout !Latent heat flux [W m-2]
1658
1659 REAL(kind(1d0)), DIMENSION(:), ALLOCATABLE :: qhforcbl, qeforcbl ! Stores previous timestep qh and qe for CBL model. Added by HCW 21 Mar 2017
1660 INTEGER :: qh_choice ! selection of qh use to drive CBL growth 1=Suews 2=lumps 3=obs
1661
1662 !Water use related variables
1663 REAL(kind(1d0)) :: ext_wu, & !External water use for the model timestep [mm] (over whole study area)
1664 faut, & !Fraction of irrigated area using automatic irrigation
1665 h_maintain, & ! ponding water depth to maintain [mm] (over whole study area)
1666 int_wu, & !Internal water use for the model timestep [mm] (over whole study area)
1667 irrfracpaved, & !Fraction of paved which are irrigated
1668 irrfracbldgs, & !Fraction of buildings which are irrigated
1669 irrfracevetr, & !Fraction of evergreen trees which are irrigated
1670 irrfracdectr, & !Fraction of deciduous trees which are irrigated
1671 irrfracgrass, & !Fraction of grass which is irrigated
1672 irrfracbsoil, & !Fraction of bare soil which is irrigated
1673 irrfracwater, & !Fraction of water which is irrigated
1674 internalwateruse_h !Internal water use [mm h-1]
1675
1676 ! 7 - number of days in week
1677 REAL(kind(1d0)), DIMENSION(7) :: daywatper, & !% of houses following daily water
1678 daywat !Days of watering allowed
1679 ! REAL(KIND(1d0)), DIMENSION(0:23, 2):: WUProfM_24hr, & !Hourly profiles for water use (manual irrigation)
1680 ! WUProfA_24hr !Hourly profiles for water use (automatic irrigation)
1681
1682 REAL(kind(1d0)), DIMENSION(3) :: ie_a, ie_m !Coefficients for automatic and manual irrigation models
1683
1684END MODULE sues_data
1685
1686!**********************************************
1687!===================================================================================
1689 IMPLICIT NONE
1690 REAL(kind(1d0)) :: vegphenlumps, deltalai
1691END MODULE vegphenogy
1692
1694 CHARACTER(len=90) :: smithfile !file for NARP
1695END MODULE filename
1696
1698
1699 REAL(kind(1d0)) :: laiinitialevetr, &
1702 porosity0, &
1703 decidcap0, &
1704 albdectr0, &
1705 albevetr0, &
1706 albgrass0, &
1707 temp_c0, &
1708 gdd_1_0, &
1709 gdd_2_0, &
1723 snowpackpaved, &
1724 snowpackbldgs, &
1725 snowpackevetr, &
1726 snowpackdectr, &
1727 snowpackgrass, &
1728 snowpackbsoil, &
1729 snowpackwater, &
1730 snowalb0 !,&
1731 ! BoInit !initial Bo for AnOHM, TS 13 Jul 2016 ! removed, TS 30 Jan 2018
1732
1733 INTEGER :: id_prev
1734
1735END MODULE initialcond
1736
1737!-------------------------------------------------
1738!New modules for the column numbers
1739
1740!-------------------------------------------------------------------------
1742
1743 IMPLICIT NONE
1744
1745 !========== Columns for ModelDailyState array =========================
1746
1747 INTEGER :: cmds_id_prev = 3, &
1748 cmds_hdd1 = 4, &
1749 cmds_hdd2 = 5, &
1750 cmds_tempc = 6, &
1751 cmds_tempcrm = 7, &
1752 cmds_precip = 8, &
1753 cmds_dayssincerain = 9, &
1754 cmds_tempcold1 = 10, &
1755 cmds_tempcold2 = 11, &
1756 cmds_tempcold3 = 12, &
1757 cmds_gddmin = 13, &
1758 cmds_gddmax = 14, &
1759 cmds_gdd1_0 = 15, &
1760 cmds_gdd2_0 = 16, &
1761 cmds_laiinitialevetr = 17, &
1762 cmds_laiinitialdectr = 18, &
1763 cmds_laiinitialgrass = 19, &
1764 cmds_porosity = 20, &
1765 cmds_albevetr = 21, &
1766 cmds_albdectr = 22, &
1767 cmds_albgrass = 23, &
1768 cmds_decidcap = 24, &
1769 cmds_snowfallcum = 25, &
1770 cmds_laievetr = 26, &
1771 cmds_laidectr = 27, &
1772 cmds_laigrass = 28, &
1773 cmds_snowalb = 29, &
1774 cmds_boratio = 30, & ! noontime Bowen ratio, added by TS
1775 cmds_a1anohm = 31, & ! a1 of AnOHM, added by TS
1776 cmds_a2anohm = 32, & ! a2 of AnOHM, added by TS
1777 cmds_a3anohm = 33 ! a3 of AnOHM, added by TS
1778
1779END MODULE colnamesmodeldailystate
1780
1781!-------------------------------------------------------------------------
1783
1784 IMPLICIT NONE
1785
1786 INTEGER :: ccc !Column counter
1787
1788 ! Column names and numbers must match the input files
1789
1790 !========== Columns for SUEWS_SiteSelect.txt ==========================
1791 ! Columns 1:97 are the same for SurfaceChar
1792 INTEGER :: c_grid = 1, &
1793 c_year = 2, &
1794 c_startdls = 3, &
1795 c_enddls = 4, &
1796 ! Site info
1797 c_lat = 5, &
1798 c_lng = 6, &
1799 c_tz = 7, &
1800 c_area = 8, &
1801 c_alt = 9, &
1802 c_z = 10, &
1803 ! Time info
1804 c_id = 11, &
1805 c_it = 12, &
1806 c_imin = 13, &
1807 ! Surface fractions
1808 c_frpaved = 14, &
1809 c_frbldgs = 15, &
1810 c_frevetr = 16, &
1811 c_frdectr = 17, &
1812 c_frgrass = 18, &
1813 c_frbsoil = 19, &
1814 c_frwater = 20, &
1815 ! Irrigated fractions
1816 c_irrpavedfrac = 21, &
1817 c_irrbldgsfrac = 22, &
1818 c_irrevetrfrac = 23, &
1819 c_irrdectrfrac = 24, &
1820 c_irrgrassfrac = 25, &
1821 c_irrbsoilfrac = 26, &
1822 c_irrwaterfrac = 27, &
1823 ! Height information
1824 c_hbldgs = 28, &
1825 c_hevetr = 29, &
1826 c_hdectr = 30, &
1827 c_z0m = 31, &
1828 c_zdm = 32, &
1829 c_faibldgs = 33, &
1830 c_faievetr = 34, &
1831 c_faidectr = 35, &
1832 ! Population
1833 c_popdensday = 36, &
1834 c_popdensnight = 37, &
1835 c_trafficrate_wd = 38, & ! Mean traffic rate in modelled area [veh km m-2 s-1] Weekday
1836 c_trafficrate_we = 39, & ! Mean traffic rate in modelled area [veh km m-2 s-1] Weekend
1837 c_qf0_beu_wd = 40, & ! Building energy use for modelled area [W m-2] - QUESTION: could change units?
1838 c_qf0_beu_we = 41, &
1839 ! Codes for different surfaces
1840 c_pavedcode = 42, & ! Links characteristics in SUEWS_NonVeg.txt
1841 c_bldgscode = 43, & ! Links characteristics in SUEWS_NonVeg.txt
1842 c_evetrcode = 44, & ! Links characteristics in SUEWS_Veg.txt
1843 c_dectrcode = 45, & ! Links characteristics in SUEWS_Veg.txt
1844 c_grasscode = 46, & ! Links characteristics in SUEWS_Veg.txt
1845 c_bsoilcode = 47, & ! Links characteristics in SUEWS_Veg.txt
1846 c_watercode = 48, & ! Links characteristics in SUEWS_Water.txt
1847 ! LUMPS info
1848 c_lumpsdr = 49, &
1849 c_lumpscover = 50, &
1850 c_lumpsmaxres = 51, &
1851 ! NARP info
1852 c_narptrans = 52, &
1853 ! Code for conductances
1854 c_condcode = 53, & ! Links characteristics in SUEWS_Conductance.txt
1855 ! Code for snow
1856 c_snowcode = 54, & ! Links characteristics in SUEWS_Snow.txt
1857 ! Codes for human impacts on energy, water and snow
1858 c_snowprofwd = 55, & ! Snow-clearing profile in SUEWS_Profile.txt (weekdays)
1859 c_snowprofwe = 56, & ! Snow-clearing profile in SUEWS_Profile.txt (weekends)
1860 c_qfcode = 57, & ! Links anthropogenic heat info in SUEWS_AnthropogenicEmission.txt
1861 c_irrcode = 58, & ! Links irrigation info in SUEWS_Irrigation.txt
1862 c_wprofmanuwd = 59, & ! Links to water-use profile in SUEWS_Profile.txt (manual irrigation, weekdays)
1863 c_wprofmanuwe = 60, & ! Links to water-use profile in SUEWS_Profile.txt (manual irrigation, weekends)
1864 c_wprofautowd = 61, & ! Links to water-use profile in SUEWS_Profile.txt (automatic irrigation, weekdays)
1865 c_wprofautowe = 62, & ! Links to water-use profile in SUEWS_Profile.txt (automatic irrigation, weekends)
1866 ! Flow information
1867 c_flowchange = 63, & ! Difference in input & output flows for water surface
1868 c_runofftowater = 64, & ! Fraction of above-ground runoff flowing to water surface
1869 c_pipecapacity = 65, & ! Pipe capacity [mm]
1870 ! Runoff (to 8 adjacent grids)
1871 c_gridconnection1of8 = 66, &
1872 c_fraction1of8 = 67, &
1873 c_gridconnection2of8 = 68, &
1874 c_fraction2of8 = 69, &
1875 c_gridconnection3of8 = 70, &
1876 c_fraction3of8 = 71, &
1877 c_gridconnection4of8 = 72, &
1878 c_fraction4of8 = 73, &
1879 c_gridconnection5of8 = 74, &
1880 c_fraction5of8 = 75, &
1881 c_gridconnection6of8 = 76, &
1882 c_fraction6of8 = 77, &
1883 c_gridconnection7of8 = 78, &
1884 c_fraction7of8 = 79, &
1885 c_gridconnection8of8 = 80, &
1886 c_fraction8of8 = 81, &
1887 ! Runoff within grid (for each surface type)
1888 c_wgpavedcode = 82, & ! Links to SUEWS_WaterDistibuteWithinGrid.txt
1889 c_wgbldgscode = 83, & ! Links to SUEWS_WaterDistibuteWithinGrid.txt
1890 c_wgevetrcode = 84, & ! Links to SUEWS_WaterDistibuteWithinGrid.txt
1891 c_wgdectrcode = 85, & ! Links to SUEWS_WaterDistibuteWithinGrid.txt
1892 c_wggrasscode = 86, & ! Links to SUEWS_WaterDistibuteWithinGrid.txt
1893 c_wgbsoilcode = 87, & ! Links to SUEWS_WaterDistibuteWithinGrid.txt
1894 c_wgwatercode = 88, & ! Links to SUEWS_WaterDistibuteWithinGrid.txt
1895 ! Additional info for ESTM
1896 c_areawall = 89 ! Wall surface fraction (Awall/Agridcell)
1897
1898 INTEGER, DIMENSION(3) :: c_fr_estmclass_paved = (/(ccc, ccc=90, 92, 1)/) ! Fraction of Paved surface with ESTM Class 1-3
1899 INTEGER, DIMENSION(3) :: c_code_estmclass_paved = (/(ccc, ccc=93, 95, 1)/) ! Code for Paved surface ESTM Class 1-3
1900 INTEGER, DIMENSION(5) :: c_fr_estmclass_bldgs = (/(ccc, ccc=96, 100, 1)/) ! Fraction of Bldgs surface with ESTM Class 1-5
1901 INTEGER, DIMENSION(5) :: c_code_estmclass_bldgs = (/(ccc, ccc=101, 105, 1)/) ! Code for Bldgs surface ESTM Class 1-5
1902
1903 !========== Columns for SUEWS_NonVeg.txt ==========================
1904 INTEGER :: ci_code = 1, &
1905 ci_albmin = 2, &
1906 ci_albmax = 3, &
1907 ci_emis = 4, &
1908 ci_stormin = 5, &
1909 ci_stormax = 6, &
1910 ci_wetthresh = 7, &
1911 ci_statelimit = 8, &
1912 ci_dreq = 9, &
1913 ci_drcoef1 = 10, &
1914 ci_drcoef2 = 11, &
1915 ci_soiltcode = 12, &
1916 ci_snowlimpat = 13, &
1917 ci_snowlimrem = 14, &
1918 ci_ohmcode_swet = 15, &
1919 ci_ohmcode_sdry = 16, &
1920 ci_ohmcode_wwet = 17, &
1921 ci_ohmcode_wdry = 18, &
1922 ci_ohmthresh_sw = 19, &
1923 ci_ohmthresh_wd = 20, &
1924 ci_estmcode = 21, & ! ESTM code for each surface (if 0 use codes in SiteSelect instead)
1925 ci_cpanohm = 22, & ! heat capacity, added by TS AnOHM
1926 ci_kkanohm = 23, & ! heat conductivity, added by TS AnOHM
1927 ci_chanohm = 24 ! bulk transfer coef., added by TS AnOHM
1928
1929 !========== Columns for SUEWS_Veg.txt ============================
1930 INTEGER :: cp_code = 1, &
1931 cp_albmin = 2, &
1932 cp_albmax = 3, &
1933 cp_emis = 4, &
1934 cp_stormin = 5, &
1935 cp_stormax = 6, &
1936 cp_wetthresh = 7, &
1937 cp_statelimit = 8, &
1938 cp_dreq = 9, &
1939 cp_drcoef1 = 10, &
1940 cp_drcoef2 = 11, &
1941 cp_soiltcode = 12, &
1942 cp_snowlimpat = 13, &
1943 cp_baset = 14, &
1944 cp_basete = 15, &
1945 cp_gddfull = 16, &
1946 cp_sddfull = 17, &
1947 cp_laimin = 18, &
1948 cp_laimax = 19, &
1949 cp_porositymin = 20, &
1950 cp_porositymax = 21, &
1951 cp_gsmax = 22, &
1952 cp_laieq = 23, &
1953 cp_leafgp1 = 24, &
1954 cp_leafgp2 = 25, &
1955 cp_leafop1 = 26, &
1956 cp_leafop2 = 27, &
1957 cp_ohmcode_swet = 28, &
1958 cp_ohmcode_sdry = 29, &
1959 cp_ohmcode_wwet = 30, &
1960 cp_ohmcode_wdry = 31, &
1961 cp_ohmthresh_sw = 32, &
1962 cp_ohmthresh_wd = 33, &
1963 cp_estmcode = 34, &
1964 cp_cpanohm = 35, & ! heat capacity, added by TS AnOHM
1965 cp_kkanohm = 36, & ! heat conductivity, added by TS AnOHM
1966 cp_chanohm = 37, & ! bulk transfer coef., added by TS AnOHM
1967 cp_biogenco2code = 38
1968
1969 !========== Columns for SUEWS_Water.txt ===============================
1970 INTEGER :: cw_code = 1, &
1971 cw_albmin = 2, &
1972 cw_albmax = 3, &
1973 cw_emis = 4, &
1974 cw_stormin = 5, &
1975 cw_stormax = 6, &
1976 cw_wetthresh = 7, &
1977 cw_statelimit = 8, &
1978 cw_waterdepth = 9, &
1979 cw_dreq = 10, &
1980 cw_drcoef1 = 11, &
1981 cw_drcoef2 = 12, &
1982 cw_ohmcode_swet = 13, &
1983 cw_ohmcode_sdry = 14, &
1984 cw_ohmcode_wwet = 15, &
1985 cw_ohmcode_wdry = 16, &
1986 cw_ohmthresh_sw = 17, &
1987 cw_ohmthresh_wd = 18, &
1988 cw_estmcode = 19, &
1989 cw_cpanohm = 20, & ! heat capacity, added by TS AnOHM
1990 cw_kkanohm = 21, & ! heat conductivity, added by TS AnOHM
1991 cw_chanohm = 22 ! bulk transfer coef., added by TS AnOHM
1992
1993 !========== Columns for SUEWS_Snow.txt ================================
1994 INTEGER :: cs_code = 1, &
1995 cs_snowrmfactor = 2, &
1996 cs_snowtmfactor = 3, &
1997 cs_snowalbmin = 4, &
1998 cs_snowalbmax = 5, &
1999 cs_snowemis = 6, &
2000 cs_snowtau_a = 7, &
2001 cs_snowtau_f = 8, &
2002 cs_snowplimalb = 9, &
2003 cs_snowsdmin = 10, &
2004 cs_snowsdmax = 11, &
2005 cs_snowtau_r = 12, &
2006 cs_snowcrwmin = 13, &
2007 cs_snowcrwmax = 14, &
2008 cs_snowplimsnow = 15, &
2009 cs_ohmcode_swet = 16, &
2010 cs_ohmcode_sdry = 17, &
2011 cs_ohmcode_wwet = 18, &
2012 cs_ohmcode_wdry = 19, &
2013 cs_ohmthresh_sw = 20, &
2014 cs_ohmthresh_wd = 21, &
2015 cs_estmcode = 22, &
2016 cs_cpanohm = 23, & ! heat capacity, added by TS
2017 cs_kkanohm = 24, & ! heat conductivity, added by TS
2018 cs_chanohm = 25 ! bulk transfer coef., added by TS
2019
2020 !========== Columns for SUEWS_Soil.txt ================================
2021 INTEGER :: cso_code = 1, &
2022 cso_soildepth = 2, &
2023 cso_soilstcap = 3, &
2024 cso_ksat = 4, &
2025 cso_soildens = 5, &
2026 cso_soilinfrate = 6, &
2027 cso_obssmdepth = 7, &
2028 cso_obssmmax = 8, &
2029 cso_obssnrfrac = 9
2030
2031 !========== Columns for SUEWS_Conductance.txt =========================
2032 INTEGER :: cc_code = 1, &
2033 cc_gsg1 = 2, &
2034 cc_gsg2 = 3, &
2035 cc_gsg3 = 4, &
2036 cc_gsg4 = 5, &
2037 cc_gsg5 = 6, &
2038 cc_gsg6 = 7, &
2039 cc_gsth = 8, &
2040 cc_gstl = 9, &
2041 cc_gss1 = 10, &
2042 cc_gss2 = 11, &
2043 cc_gskmax = 12, &
2044 cc_gsmodel = 13 !Options for surface conductance calculation (1 - Ja11, 2 - Wa16)
2045
2046 !========== Columns for SUEWS_OHMCoefficients.txt =====================
2047 INTEGER :: co_code = 1, &
2048 co_a1 = 2, &
2049 co_a2 = 3, &
2050 co_a3 = 4
2051
2052 !========== Columns for SUEWS_ESTMCoefficients.txt =====================! ! S.O. 04 Feb 2016
2053 INTEGER :: ce_code = 1, &
2054 ce_surf_thick1 = 2, & !Characteristics for 5x roof/surface layers
2055 ce_surf_k1 = 3, &
2056 ce_surf_rhocp1 = 4, &
2057 ce_surf_thick2 = 5, &
2058 ce_surf_k2 = 6, &
2059 ce_surf_rhocp2 = 7, &
2060 ce_surf_thick3 = 8, &
2061 ce_surf_k3 = 9, &
2062 ce_surf_rhocp3 = 10, &
2063 ce_surf_thick4 = 11, &
2064 ce_surf_k4 = 12, &
2065 ce_surf_rhocp4 = 13, &
2066 ce_surf_thick5 = 14, &
2067 ce_surf_k5 = 15, &
2068 ce_surf_rhocp5 = 16, &
2069 ce_wall_thick1 = 17, & ! Characteristics for 5x external wall layers (used for Bldgs surfaces only)
2070 ce_wall_k1 = 18, &
2071 ce_wall_rhocp1 = 19, &
2072 ce_wall_thick2 = 20, &
2073 ce_wall_k2 = 21, &
2074 ce_wall_rhocp2 = 22, &
2075 ce_wall_thick3 = 23, &
2076 ce_wall_k3 = 24, &
2077 ce_wall_rhocp3 = 25, &
2078 ce_wall_thick4 = 26, &
2079 ce_wall_k4 = 27, &
2080 ce_wall_rhocp4 = 28, &
2081 ce_wall_thick5 = 29, &
2082 ce_wall_k5 = 30, &
2083 ce_wall_rhocp5 = 31, &
2084 ce_internal_thick1 = 32, & ! Characteristics for 5x internal wall layers (used for Bldgs surfaces only)
2085 ce_internal_k1 = 33, &
2086 ce_internal_rhocp1 = 34, &
2087 ce_internal_thick2 = 35, &
2088 ce_internal_k2 = 36, &
2089 ce_internal_rhocp2 = 37, &
2090 ce_internal_thick3 = 38, &
2091 ce_internal_k3 = 39, &
2092 ce_internal_rhocp3 = 40, &
2093 ce_internal_thick4 = 41, &
2094 ce_internal_k4 = 42, &
2095 ce_internal_rhocp4 = 43, &
2096 ce_internal_thick5 = 44, &
2097 ce_internal_k5 = 45, &
2098 ce_internal_rhocp5 = 46, &
2099 ce_nroom = 47, &
2100 ce_alb_ibld = 48, &
2101 ce_em_ibld = 49, &
2102 ce_ch_iwall = 50, &
2103 ce_ch_iroof = 51, &
2104 ce_ch_ibld = 52
2105
2106 !========== Columns for SUEWS_AnthropogenicEmission.txt ===================
2107 INTEGER :: ca_code = 1, &
2108 ca_baset_hc = 2, &
2109 ca_qf_a1 = 3, & !Weekday
2110 ca_qf_b1 = 4, & !Weekday
2111 ca_qf_c1 = 5, & !Weekday
2112 ca_qf_a2 = 6, & !Weekend
2113 ca_qf_b2 = 7, & !Weekend
2114 ca_qf_c2 = 8, & !Weekend
2115 ca_ahmin_wd = 9, & !Weekday
2116 ca_ahmin_we = 10, & !Weekend
2117 ca_ahslopeheating_wd = 11, & !Weekday
2118 ca_ahslopeheating_we = 12, & !Weekend
2119 ca_ahslopecooling_wd = 13, & !Weekday
2120 ca_ahslopecooling_we = 14, & !Weekend
2121 ca_tcriticheating_wd = 15, & !Weekday
2122 ca_tcriticheating_we = 16, & !Weekend
2123 ca_tcriticcooling_wd = 17, & !Weekday
2124 ca_tcriticcooling_we = 18, & !Weekend
2125 ca_enprofwd = 19, & !Weekday
2126 ca_enprofwe = 20, & !Weekday
2127 ca_co2mwd = 21, & !Weekday
2128 ca_co2mwe = 22, & !Weekend
2129 ca_traffprofwd = 23, & !Weekday
2130 ca_traffprofwe = 24, & !Weekend
2131 ca_popprofwd = 25, & !Weekday
2132 ca_popprofwe = 26, & !Weekend
2133 ca_minqfmetab = 27, &
2134 ca_maxqfmetab = 28, &
2135 ca_minfcmetab = 29, &
2136 ca_maxfcmetab = 30, &
2137 ca_frpddwe = 31, &
2138 ca_frfossilfuel_heat = 32, &
2140 ca_ef_umolco2perj = 34, &
2141 ca_enef_v_jkm = 35, &
2142 ca_fcef_v_kgkmwd = 36, &
2143 ca_fcef_v_kgkmwe = 37, &
2144 ca_co2pointsource = 38, &
2145 ca_trafficunits = 39
2146
2147 !========== Columns for SUEWS_Irrigation.txt ==========================
2148
2149 INTEGER :: cir_code = 1, &
2150 cir_iestart = 2, &
2151 cir_ieend = 3, &
2152 cir_intwu = 4, &
2153 cir_faut = 5, &
2154 cir_h_maintain = 6, &
2155 cir_ie_a1 = 7, &
2156 cir_ie_a2 = 8, &
2157 cir_ie_a3 = 9, &
2158 cir_ie_m1 = 10, &
2159 cir_ie_m2 = 11, &
2160 cir_ie_m3 = 12, &
2161 cir_daywat1 = 13, &
2162 cir_daywat2 = 14, &
2163 cir_daywat3 = 15, &
2164 cir_daywat4 = 16, &
2165 cir_daywat5 = 17, &
2166 cir_daywat6 = 18, &
2167 cir_daywat7 = 19, &
2168 cir_daywatper1 = 20, &
2169 cir_daywatper2 = 21, &
2170 cir_daywatper3 = 22, &
2171 cir_daywatper4 = 23, &
2172 cir_daywatper5 = 24, &
2173 cir_daywatper6 = 25, &
2174 cir_daywatper7 = 26
2175 !========== Columns for SUEWS_Profile.txt =============================
2176
2177 INTEGER :: cc !Column counter
2178
2179 INTEGER :: cpr_code = 1
2180 INTEGER, DIMENSION(24) :: cpr_hours = (/(cc, cc=2, 25, 1)/) ! Hourly profile data
2181
2182 !========== Columns for SUEWS_WithinGridWaterDist.txt =================
2183
2184 INTEGER :: cwg_code = 1, &
2185 cwg_topaved = 2, &
2186 cwg_tobldgs = 3, &
2187 cwg_toevetr = 4, &
2188 cwg_todectr = 5, &
2189 cwg_tograss = 6, &
2190 cwg_tobsoil = 7, &
2191 cwg_towater = 8, &
2192 cwg_torunoff = 9, &
2193 cwg_tosoilstore = 10
2194
2195 !========== Columns for SUEWS_BiogenCO2.txt ===================
2196 INTEGER :: cb_code = 1, &
2197 cb_alpha = 2, &
2198 cb_beta = 3, &
2199 cb_theta = 4, &
2200 cb_alpha_enh = 5, &
2201 cb_beta_enh = 6, &
2202 cb_resp_a = 7, &
2203 cb_resp_b = 8, &
2204 cb_min_r = 9
2205
2206END MODULE colnamesinputfiles
2207
2208!----------------------------------------------------------------------------------------
2209
2210!----------------------------------------------------------------------------------
2212 ! Stores grid and datetime info
2213
2214 INTEGER :: gridid !Grid number (as specified in SUEWS_SiteSelect.txt)
2215 CHARACTER(LEN=10) :: gridid_text !Grid number as a text string
2216 CHARACTER(LEN=15) :: datetime ! YYYY DOY HH MM
2217
2218END MODULE wherewhen
2219
2220!----------------------------------------------------------------------------------
2222
2223 REAL(kind(1d0)), PARAMETER :: pi = 3.14159265359
2224 REAL(kind(1d0)), PARAMETER :: dtr = 0.0174532925, rtd = 57.2957795
2225
2226END MODULE mathconstants
2227
2228!----------------------------------------------------------------------------------
2230
2231 REAL(kind(1d0)), PARAMETER :: c2k = 273.15 !Celsius to Kelvin
2232 REAL(kind(1d0)), PARAMETER :: sbconst = 5.67051e-8 !Stefan Boltzmann constant [W m-2 K-4]
2233 REAL(kind(1d0)), PARAMETER :: jtoumolpar = 4.6 ! Convert PAR from W m-2 to umol m-2 s-1
2234 REAL(kind(1d0)), PARAMETER :: kdntopar = 0.46 ! Conversion from Kdn to PAR, originally from Tsubo and Walker (2005), used in Bellucco et al. (2017)
2235
2236END MODULE physconstants
real(kind(1d0)), dimension(maxnumberofgrids) decidcap_id_grids
real(kind(1d0)), dimension(nsurf) addwater
character(len=14 *ncolumnsdataoutsuews) headeruse
character(len=14 *ncolumnsdataoutsuews) unitsuse
real(kind(1d0)), dimension(12, maxnumberofgrids) hdd_id_grids
real(kind(1d0)), dimension(:, :, :), allocatable dataoutehc
integer, dimension(5) c_wall_thick4_bldgs
real(kind(1d0)), dimension(5, nsurfincsnow) zsurf_suewssurfs
integer, dimension(nvegsurf) c_gddfull
real(kind(1d0)), dimension(:), allocatable statelimit_wall
real(kind(1d0)), dimension(:, :), allocatable biogen_coeff
real(kind(1d0)) pormax_dec
real(kind(1d0)), dimension(nconns) gridtofrac
integer, dimension(5) c_internal_rhocp4_bldgs
real(kind(1d0)), dimension(nsurf) qn1_ind_nosnow
real(kind(1d0)), dimension(:), allocatable dqndt_grids
integer, parameter nsw
integer, parameter bldgsurf
real(kind(1d0)), dimension(:, :), allocatable modeldailystate
real(kind(1d0)), dimension(nsurf) snowpack
integer, dimension(nsurfincsnow) c_surf_thick5
real(kind(1d0)) a2
real(kind(1d0)), dimension(:, :), allocatable estmcoefficients_coeff
integer, dimension(nsurf) heig
integer, dimension(nsurf) c_kkanohm
integer, dimension(5) c_surf_k3_bldgs
integer, parameter ncolumnssoil
real(kind(1d0)), dimension(:, :, :), allocatable dataoutspartacus
real(kind(1d0)), dimension(:, :), allocatable tsfc_wall_grids
integer, parameter ncolumnssiteselect
real(kind(1d0)), dimension(:, :), allocatable soilstorecap_wall_grids
integer, dimension(5) c_wall_thick1_bldgs
real(kind(1d0)), dimension(:, :), allocatable dz_wall
real(kind(1d0)) tmin_id
real(kind(1d0)), dimension(nsurf) chanohm
real(kind(1d0)), dimension(:, :), allocatable snow_coeff
integer, dimension(nsurfincsnow) c_surf_rhocp2
integer, dimension(24) c_hrproftraffwd
real(kind(1d0)), dimension(nsurf) soilstorecap_surf
real(kind(1d0)), dimension(:, :), allocatable siteselect
real(kind(1d0)), dimension(0:23, 2) humactivity_24hr
real(kind(1d0)), dimension(:, :), allocatable anthropogenic_coeff
integer, dimension(nsurf) c_cpanohm
integer, dimension(nsurfincsnow) c_ohmcode_wwet
real(kind(1d0)), dimension(:, :), allocatable ts5mindata
character(len=20), dimension(ncolumnsnonveg) headernonveg_reqd
integer, dimension(5) c_ch_iwall_bldgs
integer, dimension(5) c_internal_rhocp1_bldgs
real(kind(1d0)), dimension(nsurf) freezmelt
integer, parameter cts_iy
real(kind(1d0)), dimension(:, :), allocatable wgwaterdist_coeff
integer, dimension(24) c_hrprofsnowcwe
real(kind(1d0)), dimension(:, :), allocatable soilstore_wall_grids
integer, dimension(5) c_wall_k1_bldgs
integer, dimension(nsurfincsnow) c_ohmthresh_sw
real(kind(1d0)), dimension(:), allocatable dailystatefirstopen
real(kind(1d0)), dimension(:, :), allocatable tin_surf_grids
real(kind(1d0)), dimension(nsurf) tsurf_ind_nosnow
integer, dimension(nsurfincsnow) c_surf_k1
integer, parameter ncolsestmdata
character(len=20), dimension(ncolumnsanthropogenic) headeranthropogenic_reqd
character(len=20), dimension(ncolumnsnonveg) headernonveg_file
real(kind(1d0)), dimension(1) waterdepth
integer, parameter conifsurf
integer, dimension(3) c_ie_a
integer, dimension(5) c_internal_thick3_bldgs
integer, dimension(nsurfincsnow) c_surf_thick4
character(len=20), dimension(ncolumnswgwaterdist) headerwgwaterdist_file
real(kind(1d0)), dimension(nsurf) smd_nsurf
real(kind(1d0)) albmin_grass
real(kind(1d0)), dimension(ncolumnsdataoutdebug) dataoutlinedebug
integer, parameter ccendir
real(kind(1d0)), dimension(:, :, :), allocatable cp_wall_grids
integer, dimension(5) c_internal_k3_bldgs
integer, parameter maxncols_cmod
real(kind(1d0)), dimension(:, :), allocatable emis_wall_grids
character(len=14 *ncolumnsdataoutsuews) headerusenosep
integer, dimension(3) c_surf_rhocp2_paved
real(kind(1d0)), dimension(:, :), allocatable metfordisagg
real(kind(1d0)), dimension(nsurf) statelimit_surf
integer, dimension(nvegsurf) c_sddfull
integer, dimension(nvegsurf) c_beta_bioco2
real(kind(1d0)), dimension(:, :), allocatable metforcingdata_grid
character(len=20), dimension(ncolumnswater) headerwater_reqd
real(kind(1d0)) ground_albedo_dir_mult_fact
real(kind(1d0)), dimension(ncolumnsdataoutsolweig - 5) dataoutlinesolweig
real(kind(1d0)), dimension(nsurf) changsnow
integer, parameter ccendpr
integer, dimension(nsurf) c_wgtorunoff
integer, dimension(nsurfincsnow) c_ohmcode_sdry
integer, dimension(nsurf) c_wgtograss
integer, parameter ccendw
integer, dimension(nsurfincsnow) c_a2_swet
real(kind(1d0)), dimension(nsurf) state_surf
integer, dimension(5) c_surf_k1_bldgs
real(kind(1d0)), dimension(nsurf) soildepth
integer, dimension(nsurf) c_wgtobldgs
real(kind(1d0)), dimension(nsurf) cpanohm
real(kind(1d0)), dimension(:), allocatable soilstorecap_wall
integer, dimension(nsurfincsnow) c_a1_wwet
real(kind(1d0)) porosity_id
real(kind(1d0)), dimension(nvegsurf) basete
real(kind(1d0)), dimension(:), allocatable tsfc_roof
real(kind(1d0)) narp_tz
integer, parameter ncolumnsconductance
integer, parameter cts_twall
integer, parameter ncolumnsohmcoefficients
integer, dimension(nvegsurf) c_gsmax
integer, dimension(nsurf) c_soilstcap
integer, dimension(nsurf) c_soildens
real(kind(1d0)), dimension(nsurf) snowdepth
integer, dimension(nsurfincsnow) c_a1_swet
integer, dimension(nsurfincsnow) c_ohmcode_swet
real(kind(1d0)), dimension(:), allocatable alb_roof
real(kind(1d0)), dimension(:, :, :), allocatable temp_surf_grids
real(kind(1d0)), dimension(nsurf) chang
integer, parameter ccendb
integer, dimension(nsurf) c_soildepth
integer, dimension(5) c_surf_thick3_bldgs
real(kind(1d0)), dimension(:, :, :), allocatable dataoutsolweig
real(kind(1d0)), parameter deg2rad
integer, dimension(nsurf) c_wgtoevetr
real(kind(1d0)), dimension(maxnumberofgrids) boanohmstart
integer, dimension(5) c_surf_rhocp2_bldgs
real(kind(1d0)), dimension(:), allocatable state_wall
real(kind(1d0)), dimension(0:23, 2) traffprof_24hr
integer n_vegetation_region_urban
integer, dimension(24) c_hrprofenusewe
real(kind(1d0)), dimension(nsurf+1) ohm_threshwd
real(kind(1d0)), dimension(0:23, 2) ahprof_24hr
integer, dimension(7) c_daywatper
real(kind(1d0)), dimension(:, :), allocatable tin_roof_grids
integer, dimension(5) c_surf_rhocp5_bldgs
real(kind(1d0)), dimension(nsurf) smd_nsurfout
real(kind(1d0)), dimension(:, :), allocatable building_frac_grids
integer, dimension(nsurf) c_soilinfrate
integer, dimension(5) c_ch_ibld_bldgs
real(kind(1d0)), dimension(:, :, :), allocatable temp_wall_grids
integer, dimension(5) c_surf_rhocp4_bldgs
integer, dimension(5) c_internal_thick1_bldgs
real(kind(1d0)), dimension(nvegsurf) beta_enh_bioco2
integer, dimension(24) c_hrprofwuautowd
integer, dimension(nvegsurf) c_laimax
real(kind(1d0)), dimension(:), allocatable estmfordisaggprev
integer, parameter ccendsn
character(len=20), dimension(ncolumnswater) headerwater_file
character(len=20), dimension(ncolumnssnow) headersnow_file
integer, dimension(nsurfincsnow) c_a2_sdry
integer, dimension(nsurf) c_statelimit
integer, dimension(3) c_ie_m
real(kind(1d0)), dimension(:, :), allocatable tin_wall_grids
real(kind(1d0)), dimension(nsurf+1, 4, 3) ohm_coef
integer, dimension(nvegsurf) c_alpha_bioco2
real(kind(1d0)), dimension(nsurf) stateold
integer, parameter nconns
real(kind(1d0)), dimension(:, :), allocatable temp_roof
integer, dimension(3) c_surf_k4_paved
real(kind(1d0)), dimension(nvegsurf) min_res_bioco2
real(kind(1d0)), dimension(:), allocatable wetthresh_wall
real(kind(1d0)), dimension(nvegsurf) lai_id
real(kind(1d0)) veg_ssa_lw
integer, parameter maxnumberofgrids
integer, parameter ncolumnsdataoutbl
real(kind(1d0)), dimension(:), allocatable state_roof
integer, parameter cts_it
integer, dimension(nsurf) c_drcoef2
real(kind(1d0)), dimension(:), allocatable dqnsdt_grids
integer, parameter ccenda
integer, dimension(5) c_ch_iroof_bldgs
integer, parameter cts_twall_w
integer, dimension(nsurf) c_ksat
real(kind(1d0)), dimension(:), allocatable narp_kdown_hr
character(len=20), dimension(ncolumnsveg) headerveg_file
real(kind(1d0)), dimension(nconns) gridto
real(kind(1d0)) air_ext_sw
real(kind(1d0)), dimension(ncolumnsdataoutsnow - 5) dataoutlinesnow
real(kind(1d0)), dimension(nvegsurf) baset
real(kind(1d0)), dimension(:, :), allocatable tsfc_roof_grids
real(kind(1d0)), dimension(:, :), allocatable dz_surf
integer, parameter ccendestmb
real(kind(1d0)), dimension(:), allocatable metfordisaggnext
integer, dimension(nsurf) c_obssmmax
integer, dimension(nvegsurf) c_leafgp2
integer, parameter cts_troad
real(kind(1d0)), dimension(nvegsurf) resp_b
real(kind(1d0)) narp_long
integer, dimension(nsurf) c_chanohm
integer, dimension(5) c_surf_thick2_bldgs
character(len=52 *ncolumnsdataoutsuews) longnmuse
integer, parameter ncolumnsmetforcingdata
real(kind(1d0)), dimension(nsurf) sfr_surf
real(kind(1d0)), dimension(maxnumberofgrids) a2anohm
real(kind(1d0)), dimension(maxnumberofgrids) albevetr_id_grids
real(kind(1d0)), dimension(:), allocatable qn_s_av_grids
integer, dimension(5) c_internal_rhocp2_bldgs
integer, dimension(:), allocatable nlayer_grids
real(kind(1d0)), dimension(nsurf) statefraction
real(kind(1d0)), dimension(4, nvegsurf) laipower
integer, dimension(5) c_wall_k3_bldgs
integer, parameter ncolumnsprofiles
real(kind(1d0)), dimension(:, :), allocatable alb_wall_grids
real(kind(1d0)), dimension(nvegsurf) resp_a
real(kind(1d0)), dimension(5, nsurfincsnow) rsurf_suewssurfs
real(kind(1d0)), dimension(ncolumnsdataoutsuews - 5) dataoutlinesuews
integer, dimension(5) c_wall_k5_bldgs
integer, dimension(nsurf) c_snowlimpat
integer, dimension(nsurfincsnow) c_ohmthresh_wd
real(kind(1d0)), dimension(nvegsurf) laimax
integer, dimension(nsurfincsnow) c_a3_wwet
real(kind(1d0)), dimension(0:23, 2) wuprofm_24hr
integer, dimension(5) c_surf_rhocp1_bldgs
real(kind(1d0)), dimension(:, :, :), allocatable cp_surf_grids
character(len=20), dimension(ncolumnsprofiles) headerprofiles_reqd
real(kind(1d0)), dimension(:), allocatable sfr_roof
real(kind(1d0)), dimension(:, :, :), allocatable dataoutsnow
integer, dimension(3) c_surf_k5_paved
integer, dimension(nsurf) c_stormin
real(kind(1d0)), dimension(nsurf) runoffsoil
character(len=4 *ncolumnsdataoutsuews) colnosuse
integer, dimension(7) c_daywat
real(kind(1d0)), dimension(nsurf) emis
real(kind(1d0)), dimension(:, :, :), allocatable wall_specular_frac_grids
real(kind(1d0)), dimension(nsurf) snowpackold
integer, dimension(5) c_wall_rhocp1_bldgs
character(len=20), dimension(ncolumnssnow) headersnow_reqd
real(kind(1d0)), dimension(:, :), allocatable alb_roof_grids
real(kind(1d0)), dimension(:, :, :), allocatable k_wall_grids
integer, parameter ccendgs
integer, parameter ncolumnswater
integer, parameter ncolumnsdataoutsuews
real(kind(1d0)), dimension(nvegsurf, maxnumberofgrids) sdd_id_grids
real(kind(1d0)), dimension(nvegsurf) gdd_id
integer, dimension(24) c_hrprofsnowcwd
real(kind(1d0)), dimension(maxnumberofgrids) tmin_id_grids
integer, parameter ccendsi
real(kind(1d0)), dimension(ncolumnsdataoutestm - 5) dataoutlineestm
real(kind(1d0)), dimension(nvegsurf, maxnumberofgrids) lai_id_grids
integer, parameter ccendo
real(kind(1d0)), dimension(:, :), allocatable emis_roof_grids
integer, dimension(:), allocatable grididmatrix0
character(len=14 *ncolumnsdataoutsuews) formatusenosep
integer, dimension(5) c_wall_rhocp3_bldgs
real(kind(1d0)) capmin_dec
integer, dimension(nsurfincsnow) c_a3_sdry
integer, parameter cts_id
real(kind(1d0)), dimension(maxnumberofgrids) tmax_id_grids
real(kind(1d0)), dimension(:), allocatable veg_ext
real(kind(1d0)) decidcap_id
integer, parameter ncolumnsanthropogenic
real(kind(1d0)), dimension(:), allocatable building_scale
real(kind(1d0)), dimension(:, :, :), allocatable temp_roof_grids
integer, dimension(:), allocatable usecolumnsdataout
real(kind(1d0)) tair_av
integer, parameter ncolumnsdataoutsolweig
integer, parameter ncolumnsdataoutestm
integer, dimension(5) c_surf_k2_bldgs
integer, dimension(nsurfincsnow) c_surf_k5
real(kind(1d0)), dimension(ncolumnsdataoutehc - 5) dataoutlineehc
real(kind(1d0)), dimension(nsurf) volswe
real(kind(1d0)), dimension(:), allocatable veg_contact_fraction
real(kind(1d0)), dimension(maxnumberofgrids) boanohmend
real(kind(1d0)) air_ssa_sw
real(kind(1d0)), dimension(:), allocatable soilstore_roof
integer, parameter ncolumnsveg
real(kind(1d0)), dimension(:), allocatable metfordisaggprev
real(kind(1d0)), dimension(nsurf) ev_snow
real(kind(1d0)), dimension(:, :, :), allocatable dataoutdebug
integer, dimension(nsurf) c_wgtowater
real(kind(1d0)), dimension(:, :, :), allocatable cp_roof_grids
real(kind(1d0)), dimension(nsurf) soilstore_surf
real(kind(1d0)), dimension(:, :), allocatable water_coeff
real(kind(1d0)), dimension(:, :), allocatable tsfc_surf_grids
integer, dimension(24) c_hrprofpopwe
real(kind(1d0)), dimension(maxnumberofgrids) lenday_id_grids
integer, dimension(nsurfincsnow) c_surf_thick3
integer, dimension(nsurf) cmod_snowfrac
real(kind(1d0)), dimension(:, :), allocatable sfr_wall_grids
integer, dimension(nvegsurf) laitype
integer, dimension(nsurf) cmds_snowdens
real(kind(1d0)), dimension(:, :), allocatable state_wall_grids
integer, parameter nlw
integer, dimension(nsurfincsnow) c_ohmcode_wdry
real(kind(1d0)), dimension(:, :), allocatable building_scale_grids
real(kind(1d0)), dimension(:, :, :), allocatable dz_surf_grids
integer, dimension(3) c_surf_k1_paved
real(kind(1d0)), dimension(:), allocatable height
integer, parameter maxncols_c
real(kind(1d0)), dimension(:, :), allocatable nonveg_coeff
integer, dimension(nsurf) cmod_snowwaterstate
integer, dimension(5) c_surf_k5_bldgs
real(kind(1d0)), dimension(5, nsurfincsnow) ksurf_suewssurfs
real(kind(1d0)) veg_ssa_sw
real(kind(1d0)) narp_alb_snow
real(kind(1d0)), dimension(:, :), allocatable cp_wall
integer, dimension(nsurf) c_wgtosoilstore
real(kind(1d0)), dimension(nsurf) tsurf_ind_snow
real(kind(1d0)), dimension(maxnumberofgrids) albgrass_id_grids
real(kind(1d0)), dimension(:), allocatable tair24hr
integer, dimension(nvegsurf) c_laimin
integer, dimension(3) c_surf_rhocp4_paved
integer, parameter ncolumnsdataoutbeers
character(len=20), dimension(ncolumnsohmcoefficients) headerohmcoefficients_reqd
real(kind(1d0)), dimension(nvegsurf) biogenco2code
real(kind(1d0)), dimension(nsurf) sathydraulicconduct
real(kind(1d0)) lenday_id
real(kind(1d0)) narp_lat
real(kind(1d0)) qn_s_av
real(kind(1d0)), dimension(6, nsurf) storedrainprm
real(kind(1d0)) air_ssa_lw
real(kind(1d0)), dimension(nsurf) rainonsnow
real(kind(1d0)), parameter rad2deg
real(kind(1d0)), dimension(:, :), allocatable soilstore_roof_grids
real(kind(1d0)) bulkalbedo
integer, dimension(nvegsurf) c_alpha_enh_bioco2
real(kind(1d0)), dimension(nsurf) kkanohm
real(kind(1d0)), dimension(nvegsurf) theta_bioco2
real(kind(1d0)), dimension(:, :), allocatable conductance_coeff
integer, dimension(24) c_hrprofpopwd
integer, parameter nspec
integer, parameter ncolumnsnonveg
real(kind(1d0)), dimension(nsurf+1, nsurf - 1) waterdist
real(kind(1d0)), dimension(nsurf) mw_indday
real(kind(1d0)), dimension(nsurf) kup_ind_nosnow
real(kind(1d0)), dimension(:), allocatable emis_roof
real(kind(1d0)), dimension(nsurf) kup_ind_snow
real(kind(1d0)), dimension(:), allocatable tsfc_surf
integer, parameter ncolumnswgwaterdist
integer, dimension(nsurfincsnow) c_surf_thick1
real(kind(1d0)), dimension(nsurf) soilstoreold
real(kind(1d0)) narp_emis_snow
integer, dimension(nsurf) c_wgtopaved
integer, dimension(5) c_internal_thick4_bldgs
integer, parameter cbendwg
real(kind(1d0)), dimension(nsurf) qm_freezstate
real(kind(1d0)), dimension(:, :), allocatable cp_surf
integer, dimension(nsurfincsnow) c_a3_wdry
integer, dimension(nsurf) cmod_snowdens
integer, dimension(24) c_hrprofwumanuwe
real(kind(1d0)), dimension(365) narp_g
real(kind(1d0)), dimension(nsurf+1) ohm_threshsw
integer, dimension(nvegsurf) c_min_res_bioco2
integer, dimension(nvegsurf) c_resp_b
real(kind(1d0)), dimension(nvegsurf) lai_id_prev
real(kind(1d0)), dimension(nsurf) tsurf_ind
real(kind(1d0)), dimension(:, :, :), allocatable k_roof_grids
character(len=20), dimension(ncolumnssoil) headersoil_file
real(kind(1d0)), dimension(nsurf) evap
integer, dimension(5) c_internal_rhocp5_bldgs
real(kind(1d0)), parameter sigma_sb
real(kind(1d0)), dimension(:, :, :), allocatable metforcingdata
integer, dimension(nsurf) c_albmin
integer, parameter ccendso
real(kind(1d0)), dimension(:, :), allocatable veg_contact_fraction_grids
integer, dimension(5) c_internal_k5_bldgs
integer, parameter ncolumnsdataoutspartacus
integer, parameter ccmod
real(kind(1d0)), dimension(9) wuday_id_prev
real(kind(1d0)), dimension(:, :), allocatable k_roof
character(len=20), dimension(ncolumnsirrigation) headerirrigation_reqd
integer, parameter ncolumnsdataoutrsl
character(len=3 *ncolumnsdataoutsuews) aggreguse
integer, parameter ccendestmm
character(len=20), dimension(ncolumnsanthropogenic) headeranthropogenic_file
integer, parameter cts_imin
real(kind(1d0)), dimension(nsurf) lup_ind_nosnow
real(kind(1d0)), dimension(:), allocatable wetthresh_roof
integer, dimension(nsurf) c_obssmdepth
real(kind(1d0)), dimension(:), allocatable soilstorecap_roof
real(kind(1d0)), dimension(:), allocatable veg_frac
real(kind(1d0)), dimension(:, :), allocatable k_surf
real(kind(1d0)) capmax_dec
real(kind(1d0)), dimension(maxnumberofgrids) a1anohm
real(kind(1d0)), dimension(nvegsurf) beta_bioco2
integer, dimension(24) c_hrproftraffwe
integer, dimension(5) c_wall_rhocp5_bldgs
real(kind(1d0)), dimension(nsurf) mw_ind
real(kind(1d0)), dimension(nsurf) qn1_ind_snow
real(kind(1d0)), dimension(5) datetimeline
integer, dimension(24) c_hrprofwumanuwd
real(kind(1d0)), dimension(ncolumnsdataoutrsl - 5+12) dataoutlinersl
integer, dimension(5) c_surf_thick5_bldgs
integer, dimension(5) c_wall_k2_bldgs
integer, dimension(nsurfincsnow) c_a3_swet
real(kind(1d0)), dimension(nsurf) addwaterrunoff
real(kind(1d0)), dimension(:, :), allocatable surfacechar
integer, dimension(nsurf) cmod_snowpack
real(kind(1d0)) albevetr_id
integer, parameter ivgrass
real(kind(1d0)), dimension(:, :), allocatable statelimit_wall_grids
real(kind(1d0)), dimension(nsurf) snowwater
real(kind(1d0)) narp_trans_site
integer, dimension(3) c_surf_thick4_paved
integer, dimension(nsurf) snowcoverforms
integer, dimension(nsurf) c_stormax
integer, dimension(nsurfincsnow) c_surf_rhocp3
real(kind(1d0)), dimension(:, :), allocatable wetthresh_roof_grids
integer, dimension(:), allocatable grididmatrix
real(kind(1d0)), dimension(nsurf) freezstatevol
real(kind(1d0)), dimension(0:23, 2) wuprofa_24hr
real(kind(1d0)), dimension(nvegsurf) gdd_id_prev
integer, dimension(nsurf) c_snowlimrem
real(kind(1d0)) xbo
real(kind(1d0)), dimension(ncolumnsdataoutspartacus) dataoutlinespartacus
character(len=14 *ncolumnsdataoutsuews) formatuse
integer, dimension(3) c_surf_rhocp1_paved
integer c_frfossilfuel_nonheat
integer, dimension(nvegsurf) c_baset
real(kind(1d0)), dimension(:, :), allocatable roof_albedo_dir_mult_fact
integer, dimension(nsurf) c_emis
real(kind(1d0)), dimension(:, :), allocatable soilstorecap_roof_grids
real(kind(1d0)) albmax_dectr
integer, dimension(nvegsurf) c_resp_a
integer, dimension(nsurfincsnow) c_surf_thick2
real(kind(1d0)), dimension(nvegsurf) sdd_id
integer, dimension(5) c_nroom_bldgs
real(kind(1d0)), dimension(nvegsurf) sddfull
integer, dimension(5) c_internal_k2_bldgs
integer, dimension(5) c_internal_k4_bldgs
integer, dimension(5) c_surf_k4_bldgs
real(kind(1d0)), dimension(nvegsurf) laimin
real(kind(1d0)) albmin_dectr
integer, parameter ncolumnsdataoutsnow
character(len=20), dimension(ncolumnsveg) headerveg_reqd
character(len=20), dimension(ncolumnsbiogen) headerbiogen_reqd
integer, dimension(24) c_hrprofhumactivitywe
character(len=20), dimension(ncolumnsohmcoefficients) headerohmcoefficients_file
real(kind(1d0)), dimension(:, :), allocatable estmfordisagg
real(kind(1d0)), dimension(maxnumberofgrids) porosity_id_grids
real(kind(1d0)), dimension(:), allocatable tin_surf
real(kind(1d0)), dimension(:), allocatable estmfordisaggnext
integer, parameter ncolumnsestmcoefficients
integer, parameter watersurf
real(kind(1d0)), dimension(:, :), allocatable profiles_coeff
real(kind(1d0)), dimension(:), allocatable tin_wall
integer, parameter grasssurf
integer, dimension(3) c_surf_thick1_paved
character(len=20), dimension(ncolumnsprofiles) headerprofiles_file
real(kind(1d0)), dimension(nvegsurf) alpha_enh_bioco2
character(len=20), dimension(ncolumnsconductance) headercond_reqd
real(kind(1d0)), dimension(:, :, :), allocatable dz_roof_grids
real(kind(1d0)), dimension(:), allocatable statelimit_roof
real(kind(1d0)), dimension(:), allocatable alb_wall
integer, parameter nsurfdonotreceivedrainage
real(kind(1d0)), dimension(:, :, :), allocatable roof_albedo_dir_mult_fact_grids
integer, dimension(nsurfincsnow) c_estmcode
real(kind(1d0)), dimension(9) wuday_id
real(kind(1d0)) albdectr_id
real(kind(1d0)), dimension(:, :, :), allocatable dataoutrsl
integer, parameter nvegsurf
real(kind(1d0)), dimension(:, :, :), allocatable dataoutsuews
integer, dimension(nsurf) cmod_soilstate
real(kind(1d0)), dimension(:, :), allocatable soil_coeff
real(kind(1d0)), dimension(:, :), allocatable wall_specular_frac
real(kind(1d0)) narp_year
real(kind(1d0)) qn_av
integer, dimension(nsurfincsnow) c_surf_k3
character(len=20), dimension(ncolumnsirrigation) headerirrigation_file
real(kind(1d0)), dimension(nsurf) lup_ind
real(kind(1d0)), dimension(:, :), allocatable height_grids
integer, dimension(nvegsurf) c_biogenco2code
real(kind(1d0)), dimension(nsurf) runoff
integer, parameter ccmds
real(kind(1d0)), dimension(maxnumberofgrids) albdectr_id_grids
integer, dimension(3) c_surf_rhocp5_paved
real(kind(1d0)), dimension(nsurf) rss_nsurf
integer, parameter ivdecid
real(kind(1d0)), dimension(:, :), allocatable veg_scale_grids
real(kind(1d0)) a3
real(kind(1d0)) veg_fsd_const
integer, dimension(5) c_surf_thick4_bldgs
integer, dimension(3) c_surf_thick2_paved
real(kind(1d0)), dimension(:, :), allocatable dz_roof
real(kind(1d0)), dimension(:, :, :), allocatable k_surf_grids
integer, parameter bsoilsurf
real(kind(1d0)) albmax_grass
real(kind(1d0)), dimension(nsurf) stateout
real(kind(1d0)) pormin_dec
real(kind(1d0)), dimension(:, :), allocatable temp_surf
integer, parameter ncolumnsdataoutdailystate
integer, dimension(5) c_surf_thick1_bldgs
real(kind(1d0)), dimension(9, maxnumberofgrids) wuday_id_grids
real(kind(1d0)), dimension(nsurf) snowdens
integer, parameter maxncols_cmds
real(kind(1d0)), dimension(nsurf) lup_ind_snow
integer, dimension(nsurfincsnow) c_surf_k2
integer, parameter ncolumnsdataoutehc
integer, dimension(3) c_surf_rhocp3_paved
integer, dimension(nsurfincsnow) c_surf_rhocp5
real(kind(1d0)), dimension(nsurf) deltaqi
integer, dimension(nsurf) c_wgtodectr
integer, parameter ncol
integer, dimension(5) c_internal_rhocp3_bldgs
integer, dimension(nsurf) c_soiltcode
real(kind(1d0)), dimension(:, :), allocatable ohmcoefficients_coeff
real(kind(1d0)), dimension(:), allocatable emis_wall
integer, dimension(nvegsurf) c_beta_enh_bioco2
integer, dimension(nvegsurf) c_porositymax
real(kind(1d0)), dimension(:), allocatable ts5mindata_ir
integer, parameter nsurf
integer, parameter pavsurf
integer, dimension(5) c_em_ibld_bldgs
real(kind(1d0)) dqnsdt
real(kind(1d0)) tmax_id
integer, dimension(3) c_surf_k3_paved
real(kind(1d0)), dimension(ncolumnsdataoutbeers - 5) dataoutlinebeers
integer, parameter cts_tsurf
integer, dimension(nvegsurf) c_theta_bioco2
real(kind(1d0)) albmax_evetr
character(len=20), dimension(ncolumnsbiogen) headerbiogen_file
character(len=20), dimension(ncolumnssiteselect) headersiteselect_file
integer, dimension(nvegsurf) c_porositymin
real(kind(1d0)), dimension(:, :), allocatable veg_ext_grids
integer, parameter ndays
real(kind(1d0)), dimension(:, :, :), allocatable dataoutbl
integer, parameter cts_twall_n
real(kind(1d0)), dimension(nsurf) wetthresh_surf
integer, dimension(nvegsurf) c_leafgp1
integer, dimension(3) c_surf_thick5_paved
integer, dimension(nsurfincsnow) c_surf_k4
real(kind(1d0)), dimension(:, :), allocatable cp_roof
real(kind(1d0)) a1
real(kind(1d0)), dimension(nsurf) alb
real(kind(1d0)), dimension(:, :), allocatable irrigation_coeff
real(kind(1d0)), dimension(nsurf) kup_ind
real(kind(1d0)), dimension(:), allocatable building_frac
integer, dimension(nsurf) c_obssnrfrac
integer, parameter ndepth
real(kind(1d0)), dimension(nsurf) qm_melt
integer, dimension(5) c_wall_thick5_bldgs
real(kind(1d0)), dimension(:, :, :), allocatable modeloutputdata
real(kind(1d0)), dimension(nsurf) runoffsnow
real(kind(1d0)), dimension(:, :), allocatable veg_frac_grids
integer, dimension(5) c_alb_ibld_bldgs
integer, dimension(24) c_hrprofwuautowe
integer, dimension(nsurf) cmod_state
character(len=20), dimension(ncolumnsconductance) headercond_file
integer, parameter ivconif
integer, dimension(3) c_surf_thick3_paved
real(kind(1d0)), dimension(:, :), allocatable state_roof_grids
integer, dimension(nsurfincsnow) c_surf_rhocp1
real(kind(1d0)), dimension(nsurf, maxnumberofgrids) icefrac_grids
real(kind(1d0)), dimension(nvegsurf) maxconductance
integer, dimension(24) c_hrprofhumactivitywd
real(kind(1d0)), dimension(:, :), allocatable statelimit_roof_grids
integer, parameter ncolumnsbiogen
real(kind(1d0)), dimension(:, :), allocatable sfr_roof_grids
integer, parameter excesssurf
integer, dimension(5) c_wall_rhocp4_bldgs
integer, dimension(nsurf) c_wgtobsoil
real(kind(1d0)), dimension(nsurf) qn1_ind
integer, dimension(nsurf) snowcalcswitch
character(len=20), dimension(ncolumnsestmcoefficients) headerestmcoefficients_reqd
integer, parameter cts_twall_e
integer, parameter ccendp
integer, dimension(nsurfincsnow) c_a1_wdry
real(kind(1d0)), dimension(0:23, 2) popprof_24hr
character(len=20), dimension(ncolumnssoil) headersoil_reqd
character(len=20), dimension(ncolumnsestmcoefficients) headerestmcoefficients_file
real(kind(1d0)), dimension(nvegsurf) gddfull
integer, dimension(nsurfincsnow) c_a2_wdry
integer, dimension(nvegsurf) c_laieq
integer, parameter cts_tiair
integer, parameter ncolumnsirrigation
real(kind(1d0)), dimension(:, :), allocatable temp_wall
real(kind(1d0)), dimension(:, :, :), allocatable dataoutdailystate
real(kind(1d0)), dimension(:, :, :), allocatable dataoutestm
real(kind(1d0)), dimension(:, :), allocatable veg_coeff
real(kind(1d0)) air_ext_lw
real(kind(1d0)), dimension(maxnumberofgrids) a3anohm
integer, dimension(5) c_wall_k4_bldgs
real(kind(1d0)), dimension(:, :, :), allocatable dz_wall_grids
integer, parameter ccendestmmp
real(kind(1d0)), dimension(:, :), allocatable veg_fsd_grids
real(kind(1d0)), dimension(ncolumnsdataoutdailystate - 5) dailystateline
real(kind(1d0)), dimension(nsurf) drain
real(kind(1d0)), dimension(:), allocatable tair_av_grids
integer, dimension(nsurfincsnow) c_a1_sdry
integer, dimension(nsurfincsnow) c_surf_rhocp4
real(kind(1d0)), dimension(:, :), allocatable k_wall
real(kind(1d0)), dimension(:, :, :), allocatable estmforcingdata
integer, dimension(nvegsurf) c_leafop1
real(kind(1d0)), dimension(nsurf) maxsnowvol
real(kind(1d0)), dimension(:), allocatable sfr_wall
real(kind(1d0)), dimension(nsurf) snowtosurf
integer, dimension(5) c_surf_rhocp3_bldgs
integer, dimension(nsurf) c_wetthresh
integer, parameter nlayer_max
real(kind(1d0)) dqndt
real(kind(1d0)), dimension(:, :, :), allocatable dataoutbeers
real(kind(1d0)), dimension(nsurf) snowpacklimit
character(len=20), dimension(ncolumnswgwaterdist) headerwgwaterdist_reqd
real(kind(1d0)), dimension(:), allocatable veg_scale
integer, dimension(5) c_internal_thick2_bldgs
real(kind(1d0)), dimension(nvegsurf, maxnumberofgrids) gdd_id_grids
integer, parameter maxlinesmet
integer, dimension(5) c_internal_k1_bldgs
integer, parameter ncolumnssnow
integer, dimension(nsurfincsnow) c_a2_wwet
real(kind(1d0)), dimension(12) hdd_id
real(kind(1d0)), dimension(:), allocatable qn_av_grids
real(kind(1d0)), dimension(:, :), allocatable wetthresh_wall_grids
integer, dimension(nvegsurf) c_leafop2
real(kind(1d0)), dimension(:), allocatable tin_roof
integer, parameter nsurfincsnow
real(kind(1d0)), dimension(:), allocatable soilstore_wall
integer, dimension(5) c_internal_thick5_bldgs
real(kind(1d0)), dimension(nsurf) freezstate
integer, dimension(24) c_hrprofenusewd
integer, dimension(nsurf) c_dreq
real(kind(1d0)) sw_dn_direct_frac
real(kind(1d0)), dimension(nsurf) snowinit
integer, dimension(nsurf) c_albmax
integer, parameter decidsurf
integer, dimension(5) c_wall_rhocp2_bldgs
real(kind(1d0)), dimension(nsurf) qm_rain
integer, parameter ncolumnsdataoutdebug
real(kind(1d0)) albgrass_id
integer, dimension(3) c_surf_k2_paved
integer, parameter ccendi
real(kind(1d0)), dimension(:), allocatable veg_fsd
real(kind(1d0)), dimension(nsurf) icefrac
integer, dimension(5) c_wall_thick2_bldgs
real(kind(1d0)), dimension(maxnumberofgrids) mahanohm
integer, dimension(nsurf) c_drcoef1
integer, parameter cts_twall_s
real(kind(1d0)) albmin_evetr
real(kind(1d0)), dimension(:), allocatable tsfc_wall
integer, dimension(nvegsurf) c_basete
real(kind(1d0)), dimension(nvegsurf) alpha_bioco2
integer, parameter cts_troof
real(kind(1d0)), dimension(nsurf) snowfrac
integer, dimension(5) c_wall_thick3_bldgs
real(kind(1d0)) veg_contact_fraction_const
integer, dimension(24) cpr_hours
integer, dimension(5) c_code_estmclass_bldgs
integer, dimension(3) c_code_estmclass_paved
integer, dimension(5) c_fr_estmclass_bldgs
integer, dimension(3) c_fr_estmclass_paved
real(kind(1d0)) emis_snow
character(len=150) fileout
character(len=150) filedscdestm
real(kind(1d0)) qf_sahp_ac
real(kind(1d0)) enprofwe
real(kind(1d0)) drainrt
real(kind(1d0)) buildenergyuse
integer netradiationmethod
real(kind(1d0)) qn1_snowfree
real(kind(1d0)) qf_sahp_base
integer resolutionfilesin
real(kind(1d0)) fc_build
real(kind(1d0)) absl
real(kind(1d0)) qn1_bup
real(kind(1d0)) lup
real(kind(1d0)) fc_traff
real(kind(1d0)) timezone
real(kind(1d0)) rainres
character(len=150) buildingsname
real(kind(1d0)) q2_gkg
character(len=20) filecode
real(kind(1d0)) minqfmetab
integer resolutionfilesinestm
real(kind(1d0)) trafficunits
real(kind(1d0)) heightgravity
integer multiplemetfiles
real(kind(1d0)) rainmaxres
real(kind(1d0)) alpha_qhqe
real(kind(1d0)) frfossilfuel_heat
real(kind(1d0)) transmax
integer ldown2d_out
real(kind(1d0)) qsanohm
real(kind(1d0)) co2pointsource
real(kind(1d0)) qsestm
character(len=150) fileoutputpath
real(kind(1d0)) avu10_ms
real(kind(1d0)) fcld_obs
real(kind(1d0)) qf_sahp_heat
real(kind(1d0)), dimension(5) multrainamongnupperi
real(kind(1d0)) ldown
real(kind(1d0)), dimension(2) fcef_v_kgkm
real(kind(1d0)) tsurf
real(kind(1d0)) fc_biogen
real(kind(1d0)) absk
real(kind(1d0)), dimension(2) qf0_beu
integer diagnosedisagg
character(len=150) cdsmname
integer, dimension(5) multrainamongn
real(kind(1d0)) transmin
character(len=150) fileestmts
real(kind(1d0)) lng
real(kind(1d0)), dimension(2) qf_a
real(kind(1d0)) qe
real(kind(1d0)) trans_site
real(kind(1d0)) ef_umolco2perj
integer inputmetformat
real(kind(1d0)) maxqfmetab
character(len=150) filedaily
character(len=90) progname
real(kind(1d0)) lai_obs
real(kind(1d0)) precip_hr
real(kind(1d0)) fc_photo
real(kind(1d0)) traffprofwd
real(kind(1d0)) ldown_obs
character(len=150) filestateinit
real(kind(1d0)) qf_obs
integer keeptstepfilesin
integer disaggmethodestm
real(kind(1d0)) enprofwd
real(kind(1d0)), dimension(2) ah_slope_heating
real(kind(1d0)) fc_point
integer resolutionfilesout
real(kind(1d0)) fc_respi
integer suppresswarnings
real(kind(1d0)) qf_build
character(len=150) fileout_tt
character(len=150) filechoices
real(kind(1d0)) snowfrac_obs
real(kind(1d0)) baset_hc
real(kind(1d0)) co2mwe
integer emissionsmethod
real(kind(1d0)) kdir
integer ldown_option
real(kind(1d0)) qf_metab
real(kind(1d0)) precip
real(kind(1d0)), dimension(2) ah_min
real(kind(1d0)) year
real(kind(1d0)), dimension(2) baset_heating
real(kind(1d0)) snow
real(kind(1d0)) qn1_s
integer multiplelayoutfiles
real(kind(1d0)) lat
real(kind(1d0)) popprofwe
real(kind(1d0)) wu_m3
real(kind(1d0)) qf_sahp
integer writeoutoption
real(kind(1d0)) e_mod
real(kind(1d0)) co2mwd
integer albedochoice
integer skipheadersiteinfo
real(kind(1d0)) tempveg
real(kind(1d0)), dimension(2) ah_slope_cooling
character(len=150) svfsuffix
real(kind(1d0)) press_hpa
integer outinterval
real(kind(1d0)) fc_anthro
real(kind(1d0)) h_mod
character(len=150) solweigpoiout
integer basetmethod
real(kind(1d0)), dimension(2) qf_c
real(kind(1d0)) qn1_obs
character(len=150) filemet
real(kind(1d0)) qs_obs
real(kind(1d0)) qh_obs
integer multipleinitfiles
integer waterusemethod
real(kind(1d0)) fc
real(kind(1d0)) avrh
real(kind(1d0)) maxfcmetab
real(kind(1d0)) qn1
integer keeptstepfilesout
integer storageheatmethod
real(kind(1d0)), dimension(2) trafficrate
character(len=150) svfpath
real(kind(1d0)) qf_traff
real(kind(1d0)) enef_v_jkm
character(len=150) fileinputpath
real(kind(1d0)) qh
real(kind(1d0)) fcld
real(kind(1d0)) avts
real(kind(1d0)), dimension(2) qf_b
integer kdown2d_out
character(len=150) filedscdmet
integer disaggmethod
character(len=150) tdsmname
real(kind(1d0)) kclear
integer solweig_ldown
integer multipleestmfiles
real(kind(1d0)) frpddwe
real(kind(1d0)) pres_kpa
real(kind(1d0)) kup
character(len=150) dsmpath
real(kind(1d0)) traffprofwe
real(kind(1d0)) raincover
integer solweigpoi_out
integer writedailystate
integer roughlenmommethod
real(kind(1d0)) zenith_deg
real(kind(1d0)) kdiff
character(len=150) estmout_tt
integer raindisaggmethod
integer diagnosedisaggestm
character(len=150) fileorigestm
real(kind(1d0)) avu1
real(kind(1d0)) popprofwd
real(kind(1d0)) temp_c
real(kind(1d0)) wdir
integer skipheadermet
real(kind(1d0)), dimension(2) popdensdaytime
real(kind(1d0)) xsmd
real(kind(1d0)) minfcmetab
real(kind(1d0)), dimension(2) baset_cooling
character(len=150) dsmname
real(kind(1d0)) alt
real(kind(1d0)) fc_metab
real(kind(1d0)) azimuth
real(kind(1d0)) avkdn
real(kind(1d0)) rainbucket
real(kind(1d0)) t2_c
real(kind(1d0)) popdensnighttime
character(len=150) fileorigmet
real(kind(1d0)) qh_r
real(kind(1d0)) qe_obs
integer outputformats
character(len=150) blout
real(kind(1d0)) frfossilfuel_nonheat
real(kind(1d0)) nan
real(kind(1d0)) pnan
real(kind(1d0)) notused
real(kind(1d0)) reall
character(len=90) smithfile
real(kind(1d0)) comp
real(kind(1d0)) molar_wat_vap
real(kind(1d0)) gas_ct_dry
real(kind(1d0)) epsil_gkg
real(kind(1d0)) epsil
real(kind(1d0)) gas_ct_wat
real(kind(1d0)) dry_gas
real(kind(1d0)) gas_ct_wv
real(kind(1d0)) molar
real(kind(1d0)) vegfraction
real(kind(1d0)) veg_fr
real(kind(1d0)) pavedfractionirrigated
real(kind(1d0)) faibldg
real(kind(1d0)) bldgh
real(kind(1d0)) evetreeh
real(kind(1d0)) nonwaterfraction
real(kind(1d0)) dectreeh
real(kind(1d0)) areazh
real(kind(1d0)) treeh
real(kind(1d0)) faievetree
real(kind(1d0)) areaunir
real(kind(1d0)) pervfraction
real(kind(1d0)) treefractionirrigated
real(kind(1d0)) faidectree
real(kind(1d0)) areair
real(kind(1d0)) faitree
real(kind(1d0)) impervfraction
real(kind(1d0)) grassfractionirrigated
integer nlinesirrigation
integer skippedlinesorig
integer readlinesmetdata
integer nlinesohmcoefficients
integer gridcounter
integer nlinessiteselect
integer nlinesprofiles
integer readblocksmetdata
integer nlinesestmdata
integer nlinesorigmetdata
integer numberofgrids
integer nlinesorigestmdata
integer nlineswgwaterdist
integer nlineswater
integer nlinesestmcoefficients
integer nlinesconductance
integer skippedlines
integer readlinesorigestmdatamax
integer nlinesbiogen
integer readlinesorigmetdata
integer readlinesorigmetdatamax
integer nlinesanthropogenic
integer readlinesorigestmdata
integer nlinesmetdata
integer skippedlinesorigestm
integer nlinesnonveg
integer readblocksorigmetdata
real(kind(1d0)) porosity0
real(kind(1d0)) snowwaterbldgsstate
real(kind(1d0)) snowpackbsoil
real(kind(1d0)) snowpackgrass
real(kind(1d0)) snowwatergrassstate
real(kind(1d0)) soilstoredectrstate
real(kind(1d0)) decidcap0
real(kind(1d0)) laiinitialgrass
real(kind(1d0)) albdectr0
real(kind(1d0)) soilstorepavedstate
real(kind(1d0)) snowpackdectr
real(kind(1d0)) laiinitialevetr
real(kind(1d0)) snowpackevetr
real(kind(1d0)) soilstorebldgsstate
real(kind(1d0)) snowwaterbsoilstate
real(kind(1d0)) soilstoregrassstate
real(kind(1d0)) snowwaterdectrstate
real(kind(1d0)) temp_c0
real(kind(1d0)) snowwaterpavedstate
real(kind(1d0)) albevetr0
real(kind(1d0)) laiinitialdectr
real(kind(1d0)) snowwaterwaterstate
real(kind(1d0)) albgrass0
real(kind(1d0)) snowpackwater
real(kind(1d0)) snowalb0
real(kind(1d0)) snowpackbldgs
real(kind(1d0)) soilstoreevetrstate
real(kind(1d0)) snowwaterevetrstate
real(kind(1d0)) gdd_2_0
real(kind(1d0)) soilstorebsoilstate
real(kind(1d0)) snowpackpaved
real(kind(1d0)) gdd_1_0
real(kind(1d0)), parameter dtr
real(kind(1d0)), parameter pi
real(kind(1d0)), parameter rtd
real(kind(1d0)) grav
real(kind(1d0)) zdm
real(kind(1e10)) z0v
real(kind(1d0)) z
real(kind(1d0)) z0m
real(kind(1d0)) zdm_in
real(kind(1d0)) zzd
real(kind(1d0)) z0m_in
real(kind(1d0)) s_pa
real(kind(1d0)) s_hpa
real(kind(1d0)) avcp
real(kind(1d0)) dens_dry
real(kind(1d0)) avdens
real(kind(1d0)) dq
real(kind(1d0)) psycice_hpa
real(kind(1d0)) es_hpa
real(kind(1d0)) psyc_hpa
real(kind(1d0)) ea_hpa
real(kind(1d0)) vpd_pa
real(kind(1d0)) waterdens
real(kind(1d0)) vpd_hpa
real(kind(1d0)) lv_j_kg
real(kind(1d0)) tlv
real(kind(1d0)) sice_hpa
real(kind(1d0)), parameter c2k
real(kind(1d0)), parameter jtoumolpar
real(kind(1d0)), parameter kdntopar
real(kind(1d0)), parameter sbconst
real(kind(1d0)) g1
real(kind(1d0)) th
real(kind(1d0)) tl
real(kind(1d0)) s2
real(kind(1d0)) tc
real(kind(1d0)) g3
real(kind(1d0)) s1
real(kind(1d0)) g4
real(kind(1d0)) tc2
real(kind(1d0)) g6
real(kind(1d0)) g2
real(kind(1d0)) kmax
real(kind(1d0)) g5
real(kind(1d0)) snowfallcum
real(kind(1d0)), dimension(0:23, 2) snowprof_24hr
real(kind(1d0)) lvs_j_kg
real(kind(1d0)) fwh
real(kind(1d0)) qn1_snow
real(kind(1d0)) snowlimpaved
real(kind(1d0)) snowalbmax
real(kind(1d0)) adjmeltfact
real(kind(1d0)) zf
real(kind(1d0)) radmeltfact
real(kind(1d0)) crwmax
real(kind(1d0)) qn1_nosnow
real(kind(1d0)) qmrain
real(kind(1d0)) tau_r
real(kind(1d0)) qmfreez
real(kind(1d0)) tempmeltfact
real(kind(1d0)) waterholdcapfrac
real(kind(1d0)) volday
real(kind(1d0)) qm
real(kind(1d0)) mwh
real(kind(1d0)), dimension(2) snowremoval
real(kind(1d0)) snowdensmin
real(kind(1d0)) snowlimbldg
real(kind(1d0)) snowalbmin
real(kind(1d0)) mwstore
real(kind(1d0)) preciplimitalb
real(kind(1d0)) snowdensmax
real(kind(1d0)) snowalb
real(kind(1d0)) tau_a
real(kind(1d0)) swe
real(kind(1d0)) tau_f
real(kind(1d0)) preciplimit
real(kind(1d0)) crwmin
integer snowfractionchoice
real(kind(1d0)) soilmoistcap
real(kind(1d0)) h
real(kind(1d0)), dimension(:), allocatable qeforcbl
real(kind(1d0)) runoffsoil_per_tstep
real(kind(1d0)), dimension(2) surplusevap
real(kind(1d0)) gl
real(kind(1d0)) irrfracgrass
real(kind(1d0)) irrfracbldgs
real(kind(1d0)) wu_grass
real(kind(1d0)) dr_per_interval
real(kind(1d0)) faut
integer stabilitymethod
real(kind(1d0)) ra
integer aerodynamicresistancemethod
real(kind(1d0)) zh
real(kind(1d0)) vsmd
real(kind(1d0)) surpluswaterbody
real(kind(1d0)) wu_evetr
real(kind(1d0)) sae
real(kind(1d0)) runoffpipes_m3
real(kind(1d0)) gsc
real(kind(1d0)) resistsurf
real(kind(1d0)) overuse
real(kind(1d0)) ustar
real(kind(1d0)) ext_wu
real(kind(1d0)) addveg
real(kind(1d0)) runoffagimpervious
real(kind(1d0)) st_per_interval
real(kind(1d0)) runoffagimpervious_m3
real(kind(1d0)) addpipes
real(kind(1d0)) ev_per_interval
real(kind(1d0)) runoffwaterbody_m3
real(kind(1d0)) runofftowater
real(kind(1d0)) fai
real(kind(1d0)) waterstorcap
real(kind(1d0)) runoff_per_tstep
real(kind(1d0)) int_wu
real(kind(1d0)) rb
real(kind(1d0)) numpm
real(kind(1d0)) ev_per_tstep
real(kind(1d0)) vdrc
real(kind(1d0)) rss
real(kind(1d0)), dimension(7) daywat
real(kind(1d0)) wuareatotal_m2
real(kind(1d0)) z0_gis
real(kind(1d0)) additionalwater
real(kind(1d0)) pin
real(kind(1d0)) wuareaevetr_m2
real(kind(1d0)) flowchange
real(kind(1d0)) gq
real(kind(1d0)) qe_per_interval
real(kind(1d0)) wuareagrass_m2
real(kind(1d0)) l_mod
real(kind(1d0)) gs
real(kind(1d0)) halftimestep
real(kind(1d0)) irrfracevetr
real(kind(1d0)) soildensity
real(kind(1d0)) state_per_tstep
real(kind(1d0)) smd
real(kind(1d0)) tlv_sub
real(kind(1d0)) pai
real(kind(1d0)) runoff_per_interval
real(kind(1d0)) chsnow_per_interval
real(kind(1d0)) tstep_real
real(kind(1d0)) soilrocks
real(kind(1d0)), dimension(:), allocatable qhforcbl
real(kind(1d0)), dimension(3) ie_a
real(kind(1d0)) smcap
real(kind(1d0)) psih
real(kind(1d0)) sdp
real(kind(1d0)) surfacearea_ha
real(kind(1d0)) irrfracdectr
real(kind(1d0)) addwaterbody
real(kind(1d0)) irrfracbsoil
real(kind(1d0)) pipecapacity
real(kind(1d0)) addimpervious
integer roughlenheatmethod
real(kind(1d0)) irrfracwater
real(kind(1d0)) ch_per_interval
real(kind(1d0)) rst
real(kind(1d0)) nperestm_real
real(kind(1d0)) runoffagveg_m3
real(kind(1d0)), dimension(7) daywatper
real(kind(1d0)) gdq
real(kind(1d0)) nsh_real
real(kind(1d0)) sp
real(kind(1d0)) qnm
real(kind(1d0)) qeph
real(kind(1d0)) qeout
real(kind(1d0)) tot_chang_per_tstep
real(kind(1d0)) ev
real(kind(1d0)) qe_per_tstep
real(kind(1d0)) nwstate_per_tstep
real(kind(1d0)) rasnow
real(kind(1d0)) irrfracpaved
real(kind(1d0)) drain_per_tstep
real(kind(1d0)) surf_chang_per_tstep
real(kind(1d0)) runoffwaterbody
real(kind(1d0)) wuareadectr_m2
real(kind(1d0)) p_mm
real(kind(1d0)) runoffsoil_per_interval
real(kind(1d0)) surfacearea
real(kind(1d0)), dimension(3) ie_m
real(kind(1d0)) npertstepin_real
real(kind(1d0)) soilstate
real(kind(1d0)) runoffagveg
real(kind(1d0)) internalwateruse_h
real(kind(1d0)) soildepthmeas
real(kind(1d0)) tstar
real(kind(1d0)) h_maintain
real(kind(1d0)) runoffpipes
real(kind(1d0)) di_dt
real(kind(1d0)) waterbodytype
real(kind(1d0)) wu_dectr
real(kind(1d0)) psim
real(kind(1d0)) gtemp
real(kind(1d0)) ipthreshold_mmhr
integer dt_since_start
integer id_prev_t
integer nofdaysthisyear
integer iy_prev_t
real(kind(1d0)) dectime
real(kind(1d0)) tstepcount
real(kind(1d0)) deltalai
real(kind(1d0)) vegphenlumps
character(len=10) gridid_text
character(len=15) datetime