SURFEX v8.1
General documentation of Surfex
floor_layer_e_budget.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 floor_layer_e_budget(B, PTSTEP, PFLX_BLD_FL, PDQS_FL, PIMB_FL, PRADHT_IN, &
7  PRAD_WL_FL, PRAD_RF_FL, PRAD_WIN_FL, PLOAD_FL, &
8  PRAD_FL_MA, PCONV_FL_BLD )
9 ! ##########################################################################
10 !
11 !!**** *FLOOR_LAYER_E_BUDGET*
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 ! Computes the evoultion of building floor temperatures
17 !
18 !
19 !!** METHOD
20 ! ------
21 !
22 ! 6 : equations for evolution of Ts_floor
23 ! *************************************************************
24 !
25 ! dTf_k(t) / dt = 1/(df_k*Cf_k) * (- 2*Kf_k-1*(Tf_k-Tf_k-1)/(df_k-1 +df_k)
26 ! - 2*Kf_k *(Tf_k-Tf_k+1)/(df_k+1 +df_k) )
27 !
28 ! dTf_1(t) / dt = 1/(df_1*Cf_1) * (- 2*Kw_1*(Tw_1-Tw_2)/(dw_1 +dw_2))
29 !
30 ! with
31 !
32 ! K*_k = (d*_k+ d*_k+1)/(d*_k/k*_k+ d*_k+1/k*_k+1)
33 !
34 !
35 ! The system is implicited (or semi-implicited).
36 !
37 ! ZIMPL=1 ---> implicit system
38 ! ZIMPL=0.5 ---> semi-implicit system
39 ! ZIMPL=0 ---> explicit system
40 !
41 !
42 !
43 !
44 !! EXTERNAL
45 !! --------
46 !!
47 !!
48 !! IMPLICIT ARGUMENTS
49 !! ------------------
50 !!
51 !! MODD_CST
52 !!
53 !!
54 !! REFERENCE
55 !! ---------
56 !!
57 !!
58 !! AUTHOR
59 !! ------
60 !!
61 !! G. Pigeon * Meteo-France *
62 !!
63 !! MODIFICATIONS
64 !! -------------
65 !! Original 15/04/09
66 !! G. Pigeon 08/10 computation of residual of energy balance
67 !! modification of the limit condition for
68 !! the deep temp. from the deep road temp.
69 !! to zero flux condition. idem for sfce T
70 !! G. Pigeon 11/11 split in 2 for floor and mass to be flux conservative
71 !! G. Pigeon 09/12 modif of conv. coef + implicitation of the exchange
72 !-------------------------------------------------------------------------------
73 !
74 !* 0. DECLARATIONS
75 ! ------------
76 !
77 USE modd_bem_n, ONLY : bem_t
78 !
79 USE modi_layer_e_budget_get_coef
80 USE modi_layer_e_budget
81 USE mode_conv_doe
82 !
83 USE yomhook ,ONLY : lhook, dr_hook
84 USE parkind1 ,ONLY : jprb
85 !
86 IMPLICIT NONE
87 !
88 !* 0.1 declarations of arguments
89 !
90 TYPE(bem_t), INTENT(INOUT) :: B
91 !
92 REAL, INTENT(IN) :: PTSTEP ! time step
93 REAL, DIMENSION(:), INTENT(OUT) :: PFLX_BLD_FL !flux from building to floor
94 REAL, DIMENSION(:), INTENT(OUT) :: PDQS_FL !heat storage inside the floor
95 REAL, DIMENSION(:), INTENT(OUT) :: PIMB_FL !floor energy residual imbalance for verification
96 REAL, DIMENSION(:), INTENT(IN) :: PRADHT_IN ! Indoor radiant heat transfer coefficient
97  ! [W K-1 m-2]
98 REAL, DIMENSION(:), INTENT(IN) :: PRAD_RF_FL ! rad. fluxes from roof to floor[W m-2(roof)]
99 REAL, DIMENSION(:), INTENT(IN) :: PRAD_WL_FL ! rad. fluxes from wall to floor[W m-2(wall)]
100 REAL, DIMENSION(:), INTENT(IN) :: PRAD_WIN_FL ! rad. fluxes from win to floor[W m-2(win)]
101 REAL, DIMENSION(:), INTENT(IN) :: PLOAD_FL ! solar and internal load to the floor
102 REAL, DIMENSION(:), INTENT(OUT) :: PRAD_FL_MA ! rad. fluxes from floor to mass [W m-2(floor)]
103 REAL, DIMENSION(:), INTENT(OUT) :: PCONV_FL_BLD ! conv. fluxes from floor to bld [W m-2(floor)]
104 !
105 !* 0.2 declarations of local variables
106 !
107 !
108 REAL :: ZIMPL=1.0 ! implicit coefficient
109 REAL :: ZEXPL=0.0 ! explicit coefficient
110 !
111 REAL, DIMENSION(SIZE(B%XT_FLOOR,1),SIZE(B%XT_FLOOR,2)) :: ZA,& ! lower diag.
112  ZB,& ! main diag.
113  ZC,& ! upper diag.
114  ZY ! r.h.s.
115 !
116 REAL, DIMENSION(SIZE(B%XT_FLOOR,1)) :: ZTS_FL ! surf. floor temp. used for rad. exchanges
117 REAL, DIMENSION(SIZE(B%XT_FLOOR,1)) :: ZTS_FL_CONV ! surf. floor temp. used for conv exchanges
118  ! used during calculation
119 REAL, DIMENSION(SIZE(B%XT_FLOOR,1)) :: ZCHTC_IN_FL ! Indoor floor convec heat transfer coefficient
120  ! [W K-1 m-2(bld)]
121 
122 REAL(KIND=JPRB) :: ZHOOK_HANDLE
123 INTEGER :: JJ
124 !-------------------------------------------------------------------------------
125 IF (lhook) CALL dr_hook('FLOOR_LAYER_E_BUDGET',0,zhook_handle)
126 !
127 ! *Convection heat transfer coefficients [W m-2 K-1]
128 ! From EP Engineering Reference
129 zchtc_in_fl(:) = chtc_up_doe(b%XT_FLOOR(:,1), b%XTI_BLD(:))
130 DO jj=1,SIZE(zchtc_in_fl)
131  zchtc_in_fl(jj) = max(1., zchtc_in_fl(jj))
132 ENDDO
133 
134 
135 !
136  CALL layer_e_budget_get_coef( b%XT_FLOOR, ptstep, zimpl, b%XHC_FLOOR, b%XTC_FLOOR, b%XD_FLOOR, &
137  za, zb, zc, zy )
138 !
139 zts_fl(:) = b%XT_FLOOR(:,1)
140 
141 zb(:,1) = zb(:,1) + zimpl * (zchtc_in_fl(:)*4./3. + pradht_in(:) * b%XF_FLOOR_MASS(:))
142 
143 
144 zy(:,1) = zy(:,1) &
145  + zchtc_in_fl(:) * (b%XTI_BLD(:) - 1./3. * b%XT_FLOOR(:, 1) * (4* zexpl -1)) &
146  + b%XF_FLOOR_WIN (:) * prad_win_fl(:) + b%XF_FLOOR_WALL (:) * prad_wl_fl(:) &
147  + b%XF_FLOOR_ROOF (:) * prad_rf_fl(:) &
148  + pradht_in(:) * b%XF_FLOOR_MASS (:) * (b%XT_MASS(:,1) - zexpl * b%XT_FLOOR(:,1)) &
149  + pload_fl(:)
150 !
151  CALL layer_e_budget( b%XT_FLOOR, ptstep, zimpl, b%XHC_FLOOR, b%XTC_FLOOR, b%XD_FLOOR, &
152  za, zb, zc, zy, pdqs_fl )
153 !
154 !* floor surface temperature used in the implicit formulation
155 ! ----------------------------------------------------------
156 zts_fl_conv(:) = 4./3. * zimpl * b%XT_FLOOR(:,1) + 1./3. * zts_fl(:) * (4 * zexpl - 1.)
157 zts_fl(:) = zexpl * zts_fl(:) + zimpl * b%XT_FLOOR(:,1)
158 !
159 !* fluxes with mass and indoor air
160 ! ----------------------------------------------------------
161 prad_fl_ma(:) = pradht_in(:) * (zts_fl(:) - b%XT_MASS(:,1))
162 pconv_fl_bld(:) = zchtc_in_fl(:) * (zts_fl_conv(:) - b%XTI_BLD (:))
163 !
164 !* Flux between floor and indoor surfaces and air
165 ! ------------------------------------------------
166 pflx_bld_fl(:) = - pconv_fl_bld(:) + b%XF_FLOOR_WIN (:) * prad_win_fl(:) &
167  + b%XF_FLOOR_WALL (:) * prad_wl_fl(:) + b%XF_FLOOR_ROOF (:) * prad_rf_fl(:) &
168  + pradht_in(:) * b%XF_FLOOR_MASS(:) * (b%XT_MASS(:,1) - zts_fl(:)) &
169  + pload_fl(:)
170 !
171 !* Floor residual energy imbalance for verification
172 ! ------------------------------------------------
173 pimb_fl(:) = pflx_bld_fl(:) - pdqs_fl(:)
174 !
175 IF (lhook) CALL dr_hook('FLOOR_LAYER_E_BUDGET',1,zhook_handle)
176 !-------------------------------------------------------------------------------
177 END SUBROUTINE floor_layer_e_budget
integer, parameter jprb
Definition: parkind1.F90:32
subroutine layer_e_budget(PT, PTSTEP, PIMPL, PHC, PTC, PD, PA, PB, PC, PY, PDQS)
logical lhook
Definition: yomhook.F90:15
subroutine floor_layer_e_budget(B, PTSTEP, PFLX_BLD_FL, PDQS_FL, PIMB_FL, PRADHT_IN, PRAD_WL_FL, PRAD_RF_FL, PRAD_WIN_FL, PLOAD_FL, PRAD_FL_MA, PCONV_FL_BLD)
subroutine layer_e_budget_get_coef(PT, PTSTEP, PIMPL, PHC, PTC, PD, PA, PB, PC, PY)