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