SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
solar_panel.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE solar_panel(PTSTEP, PTSUN, PRESIDENTIAL, &
7  pemit_lw_roof, pemit_lwdn_panel, plw_rad, &
8  pabs_sw_panel, pta, pn_floor, pfrac_panel,&
9  pemis_panel, palb_panel, peff_panel, &
10  pabs_lw_panel, ph_panel, prn_panel, &
11  pther_prodc_day, &
12  pther_prod_panel, pphot_prod_panel, &
13  pprod_panel, &
14  pther_prod_bld, pphot_prod_bld, &
15  pprod_bld )
16 ! ##########################################################################
17 !
18 !!**** *SOLAR_PANEL*
19 !!
20 !! PURPOSE
21 !! -------
22 !
23 ! Computes the energy budget of the solar panels.
24 !
25 !
26 !!** METHOD
27 ! ------
28 !
29 !
30 !! EXTERNAL
31 !! --------
32 !!
33 !!
34 !! IMPLICIT ARGUMENTS
35 !! ------------------
36 !!
37 !!
38 !! REFERENCE
39 !! ---------
40 !!
41 !!
42 !! AUTHOR
43 !! ------
44 !!
45 !! V. Masson * Meteo-France *
46 !!
47 !! MODIFICATIONS
48 !! -------------
49 !! Original 08/2013
50 !-------------------------------------------------------------------------------
51 !
52 !* 0. DECLARATIONS
53 ! ------------
54 !
55 USE modd_surf_par, ONLY : xundef
56 USE modd_csts, ONLY : xstefan
57 !
58 USE yomhook ,ONLY : lhook, dr_hook
59 USE parkind1 ,ONLY : jprb
60 !
61 IMPLICIT NONE
62 !
63 !* 0.1 declarations of arguments
64 !
65 !
66 REAL, INTENT(IN) :: ptstep ! time step (s)
67 REAL, DIMENSION(:), INTENT(IN) :: ptsun ! solar time (s since solar midnight)
68 REAL, DIMENSION(:), INTENT(IN) :: presidential ! Buildings Residential use fraction (-)
69 REAL, DIMENSION(:), INTENT(IN) :: pemit_lw_roof ! Upwards LW flux from roof (W/m2)
70 REAL, DIMENSION(:), INTENT(IN) :: pemit_lwdn_panel! Downwards LW flux from panel (W/m2)
71 REAL, DIMENSION(:), INTENT(IN) :: plw_rad ! Incoming Longwave radiation (W/m2)
72 REAL, DIMENSION(:), INTENT(IN) :: pabs_sw_panel ! Absorbed solar energy by the solar panel (W/m2)
73 REAL, DIMENSION(:), INTENT(IN) :: pta ! Air temperature (K)
74 REAL, DIMENSION(:), INTENT(IN) :: pn_floor ! number of floors (-)
75 REAL, DIMENSION(:), INTENT(IN) :: pfrac_panel ! fraction of solar panel on roofs (-)
76 REAL, DIMENSION(:), INTENT(IN) :: pemis_panel ! emissivity of solar panel (-)
77 REAL, DIMENSION(:), INTENT(IN) :: palb_panel ! albedo of solar panel (-)
78 REAL, DIMENSION(:), INTENT(IN) :: peff_panel ! efficiency of solar panel (-)
79 REAL, DIMENSION(:), INTENT(OUT) :: pabs_lw_panel ! Absorbed LW enerby by solar panel (W/m2)
80 REAL, DIMENSION(:), INTENT(OUT) :: ph_panel ! Sensible heat released by the solar panel (W/m2)
81 REAL, DIMENSION(:), INTENT(OUT) :: prn_panel ! Net radiation of the solar panel (W/m2)
82 REAL, DIMENSION(:), INTENT(INOUT)::pther_prodc_day ! Present day integrated thermal production of energy (J/m2 panel)
83 REAL, DIMENSION(:), INTENT(OUT) :: pther_prod_panel! Thermal Energy production of the solar panel (W/m2 panel)
84 REAL, DIMENSION(:), INTENT(OUT) :: pphot_prod_panel! Photovoltaic Energy production of the solar panel (W/m2 panel)
85 REAL, DIMENSION(:), INTENT(OUT) :: pprod_panel ! Averaged Energy production of the solar panel (W/m2 panel)
86 REAL, DIMENSION(:), INTENT(OUT) :: pther_prod_bld ! Thermal Energy production of the solar panel (W/m2 bld)
87 REAL, DIMENSION(:), INTENT(OUT) :: pphot_prod_bld ! Photovoltaic Energy production of the solar panel (W/m2 bld)
88 REAL, DIMENSION(:), INTENT(OUT) :: pprod_bld ! Averaged Energy production of the solar panel (W/m2 bld)
89 !
90 REAL(KIND=JPRB) :: zhook_handle
91 !
92 !* 0.2 declarations of parameters
93 !
94 ! coefficient to take into account irradiance to estimate surface temperature of panel
95 REAL, PARAMETER :: xkt = 0.05 ! (Km2/W)
96 !
97 ! coefficient to take into account optimum orientation of the solar panel
98 REAL, PARAMETER :: xft = 1.10 ! (-)
99 !
100 ! optimum panel temperature for photovoltaic production
101 REAL, PARAMETER :: xt_opt = 298.15 ! (K)
102 !
103 ! coefficient to take into account decrease of production for warm temperatures
104 REAL, PARAMETER :: xt_loss= 0.005 ! (K-1)
105 !
106 ! difference of temperature between cold and hot water
107 REAL, PARAMETER :: xwater_dt = 45. ! (K)
108 !
109 ! density of m2 of panel per m2 of floor necessary for hot water production
110 REAL, PARAMETER :: xther_floor= 1./30. ! (-)
111 !
112 ! Annual thermal production for an increase of 1K of the water temperature
113 REAL, PARAMETER :: xther_rate= 0.5 * 1.16*32. ! (kWh/year/m2 panel)
114 !
115 !! Maximum irradiance above which there is no more heating necessary (target temperature reached quickly)
116 !REAL, PARAMETER :: XTHER_IRR = 500. ! (W/m2)
117 ! Efficiency for thermal panels
118 REAL, PARAMETER :: xther_eff = 0.60 ! (-)
119 !
120 !
121 !
122 !
123 !* 0.3 declarations of local variables
124 !
125 REAL :: zther_daily_target ! daily target for thermal production (J/m2)
126 REAL, DIMENSION(SIZE(PTA)) :: zirradiance ! incoming solar radiation normal to the solar panel (W/m2)
127 REAL, DIMENSION(SIZE(PTA)) :: zts_panel ! Surface temperature of the upwards face of the solar panel (K)
128 REAL, DIMENSION(SIZE(PTA)) :: zlwu_panel ! Upwards longwave radiation from the solar panel (W/m2)
129 REAL, DIMENSION(SIZE(PTA)) :: zther_frac ! Fraction of thermal panels per m2 of roof (m2 panel/m2 bld)
130 REAL, DIMENSION(SIZE(PTA)) :: zphot_frac ! Fraction of photovoltaic panels per m2 of roof (m2 panel/m2 bld)
131 REAL, DIMENSION(SIZE(PTA)) :: zther_prodc_day ! guess of daily production by thermal panels (J/m2)
132 !
133 !-------------------------------------------------------------------------------
134 IF (lhook) CALL dr_hook('SOLAR_PANEL',0,zhook_handle)
135 !-------------------------------------------------------------------------------
136 !
137 !* 0.4 Default values for output variables
138 ! -----------------------------------
139 !
140 pabs_lw_panel = xundef ! Absorbed LW enerby by solar panel (W/m2)
141 ph_panel = xundef ! Sensible heat released by the solar panel (W/m2)
142 prn_panel = xundef ! Net radiation of the solar panel (W/m2)
143 pther_prod_panel= xundef ! Thermal Energy production of the solar panel (W/m2)
144 pphot_prod_panel= xundef ! Photovoltaic Energy production of the solar panel (W/m2)
145 pprod_panel = xundef ! Averaged Energy production of the solar panel (W/m2)
146 pther_prod_bld = 0. ! Thermal Energy production of the solar panel (W/m2)
147 pphot_prod_bld = 0. ! Photovoltaic Energy production of the solar panel (W/m2)
148 pprod_bld = 0. ! Averaged Energy production of the solar panel (W/m2)
149 !
150 !-------------------------------------------------------------------------------
151 !
152 !* 1. Initializations
153 ! ---------------
154 !
155 !* 1.1 Checks hour for daily thermal production reset
156 ! ----------------------------------------------
157 !
158 !* energy reset between midnight and 1AM.
159 WHERE (ptsun(:)>=0. .AND. ptsun(:)<=3600.) pther_prodc_day(:) = 0.
160 !
161 !
162 !* 1.2 Daily target production for thermal panels
163 ! ------------------------------------------
164 !
165 zther_daily_target = (2.*xther_rate) * xwater_dt * (1000. / 365. * 3600. ) ! (J/m2)
166 ! the factor 2 is to remove the assumption of cloudy days in the annual mean production
167 !
168 !-------------------------------------------------------------------------------
169 !* Note that computations are done only where solar panels are present
170 WHERE (pfrac_panel(:)>0.)
171 !-------------------------------------------------------------------------------
172 !
173 !* 2. Irradiance on panel
174 ! -------------------
175 !
176  zirradiance(:) = xft * pabs_sw_panel(:) / (1.-palb_panel(:) )
177 !
178 !-------------------------------------------------------------------------------
179 !
180 !* 3. Solar panel temperature
181 ! -----------------------
182 !
183  zts_panel(:) = pta(:) + xkt * zirradiance(:)
184 !
185 !-------------------------------------------------------------------------------
186 !
187 !* 4. Upwards solar panel LW radiation
188 ! --------------------------------
189 !
190  zlwu_panel(:) = pemis_panel(:) * xstefan * zts_panel(:)**4 &
191  + (1.-pemis_panel(:)) * plw_rad(:)
192 !
193 !-------------------------------------------------------------------------------
194 !
195 !* 5. Solar panel LW budget
196 ! ---------------------
197 !
198  pabs_lw_panel(:)= plw_rad(:) + pemit_lw_roof(:) - pemit_lwdn_panel(:) - zlwu_panel(:)
199 !
200 !-------------------------------------------------------------------------------
201 !
202 !* 6. Solar panel Net radiation
203 ! -------------------------
204 !
205  prn_panel(:) = pabs_sw_panel(:) + pabs_lw_panel(:)
206 !
207 !-------------------------------------------------------------------------------
208 !
209 !* 7. Fraction of panel surface types
210 ! -------------------------------
211 !
212 !* 7.1 Panel dedicated to thermal production of hot water
213 ! --------------------------------------------------
214 !
215  zther_frac(:) = min( xther_floor * pn_floor(:) * presidential(:), pfrac_panel(:) ) ! (m2 thermal panel / m2 roof)
216 !
217 !* 7.2 Photovoltaic panel
218 ! ------------------
219 !
220  zphot_frac(:) = pfrac_panel(:) - zther_frac(:) ! (m2 photovoltaic panel / m2 roof)
221 !
222 !-------------------------------------------------------------------------------
223 !
224 !* 8. Thermal Production of hot water (W/m2 thermal panel)
225 ! -------------------------------
226 !
227 !* 8.1 Instantaneous production
228 ! ------------------------
229 !
230  pther_prod_panel(:)= xther_eff * zirradiance(:) ! (W/m2)
231 ! PTHER_PROD_PANEL(:) = XTHER_RATE * XWATER_DT * (1000. / 24. / 365.)
232 !
233 !* 8.2 Integrated daily production
234 ! ---------------------------
235 !
236  zther_prodc_day(:) = pther_prodc_day(:) + ptstep * pther_prod_panel(:) ! (J/m2)
237 !
238 !* 8.3 Daily production limited by daily target
239 ! ----------------------------------------
240 !
241  zther_prodc_day(:) = min( zther_prodc_day(:) , zther_daily_target )
242 !
243 !* 8.4 Instantaneous production taking into account target limit if reached
244 ! --------------------------------------------------------------------
245 !
246  pther_prod_panel(:)= ( zther_prodc_day(:) - pther_prodc_day(:) ) / ptstep
247 !
248 !* 8.5 Updates daily production
249 ! ------------------------
250 !
251  pther_prodc_day(:) = zther_prodc_day(:)
252 
253 !-------------------------------------------------------------------------------
254 !
255 !* 9. Photovoltaic Production (W/m2 photovoltaic panel)
256 ! -----------------------
257 !
258  pphot_prod_panel(:) = peff_panel(:) * zirradiance(:) * min(1.,1.-xt_loss*(zts_panel(:)-xt_opt))
259 !
260 !-------------------------------------------------------------------------------
261 !
262 !* 10. Averaged Production (W/m2 panel)
263 ! -------------------
264 !
265  pprod_panel(:) = pther_prod_panel(:) * (zther_frac(:) / pfrac_panel(:)) &
266  + pphot_prod_panel(:) * (zphot_frac(:) / pfrac_panel(:))
267 !
268 !-------------------------------------------------------------------------------
269 !
270 !* 11. Sensible heat flux (W/m2 panel)
271 ! ------------------
272 !
273  ph_panel(:) = prn_panel(:) - pprod_panel(:)
274 !
275 !-------------------------------------------------------------------------------
276 !
277 !* 12. Productions per building (W/m2 bld)
278 ! ------------------------
279 !
280  pther_prod_bld(:) = pther_prod_panel(:) * zther_frac(:)
281  pphot_prod_bld(:) = pphot_prod_panel(:) * zphot_frac(:)
282  pprod_bld(:) = pther_prod_bld(:) + pphot_prod_panel(:)
283 !
284 !-------------------------------------------------------------------------------
285 END WHERE
286 !-------------------------------------------------------------------------------
287 !
288 !-------------------------------------------------------------------------------
289 IF (lhook) CALL dr_hook('SOLAR_PANEL',1,zhook_handle)
290 !-------------------------------------------------------------------------------
291 !
292 END SUBROUTINE solar_panel
subroutine solar_panel(PTSTEP, PTSUN, PRESIDENTIAL, PEMIT_LW_ROOF, PEMIT_LWDN_PANEL, PLW_RAD, PABS_SW_PANEL, PTA, PN_FLOOR, PFRAC_PANEL, PEMIS_PANEL, PALB_PANEL, PEFF_PANEL, PABS_LW_PANEL, PH_PANEL, PRN_PANEL, PTHER_PRODC_DAY, PTHER_PROD_PANEL, PPHOT_PROD_PANEL, PPROD_PANEL, PTHER_PROD_BLD, PPHOT_PROD_BLD, PPROD_BLD)
Definition: solar_panel.F90:6