SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
bld_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 bld_e_budget( OTI_EVOL, PTSTEP, PBLD, PWALL_O_HOR, &
7  prhoa, pt_roof, pt_wall, pti_bld, pts_floor )
8 ! ##########################################################################
9 !
10 !!**** *BLD_E_BUDGET*
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 ! Computes the evoultion of the temperature of inside building air
16 
17 !
18 !!** METHOD
19 ! ------
20 !
21 ! The resistance term between the surfaces and the room is given
22 ! by a standard value, which mimics both the convection
23 ! and the radiative interactions in the room.
24 ! This explains the very low resistance. It is used to compute
25 ! the evolution of the surfaces only.
26 ! This resistance value is 0.123 Km/W (typical for inside surfaces).
27 ! (ENVIRONMENTAL SCIENCE IN BUILDING, 3rd Edition, Randall McMullan,
28 ! THE MACMILLAN PRESS Limited).
29 !
30 !
31 !
32 ! On the contrary, the evolution of the air temperature is mainly
33 ! governed by the convection (considering the low radiative absorption
34 ! of the air itself).
35 ! In order to have a simple formulation, a diurnal cycle is assumed,
36 ! with a force restore formulation.
37 !
38 ! The floor temperature is fixed
39 !
40 !! EXTERNAL
41 !! --------
42 !!
43 !!
44 !! IMPLICIT ARGUMENTS
45 !! ------------------
46 !!
47 !! MODD_CST
48 !!
49 !!
50 !! REFERENCE
51 !! ---------
52 !!
53 !!
54 !! AUTHOR
55 !! ------
56 !!
57 !! V. Masson * Meteo-France *
58 !!
59 !! MODIFICATIONS
60 !! -------------
61 !! Original 24/08/00
62 !
63 !-------------------------------------------------------------------------------
64 !
65 !* 0. DECLARATIONS
66 ! ------------
67 !
68 USE modd_csts,ONLY : xtt, xcpd, xday
69 USE modd_surf_par,ONLY : xundef
70 !
71 USE yomhook ,ONLY : lhook, dr_hook
72 USE parkind1 ,ONLY : jprb
73 !
74 IMPLICIT NONE
75 !
76 !* 0.1 declarations of arguments
77 !
78 LOGICAL, INTENT(IN) :: oti_evol ! true --> internal temp. of
79 ! ! of buildings evolves
80 ! ! false--> it is fixed
81 REAL, INTENT(IN) :: ptstep ! time step
82 REAL, DIMENSION(:), INTENT(IN) :: pbld ! building fraction
83 REAL, DIMENSION(:), INTENT(IN) :: pwall_o_hor ! wall surf. / hor. surf.
84 REAL, DIMENSION(:), INTENT(IN) :: prhoa ! air density
85  ! at the lowest level
86 REAL, DIMENSION(:,:), INTENT(IN) :: pt_roof ! roof layers temperatures
87 REAL, DIMENSION(:,:), INTENT(IN) :: pt_wall ! wall layers temperatures
88 REAL, DIMENSION(:), INTENT(INOUT):: pti_bld ! building air temperature
89  ! computed with its equation evolution
90 REAL, DIMENSION(:), INTENT(IN) :: pts_floor ! floor surface temperature
91 !
92 !* 0.2 declarations of local variables
93 !
94 !
95 REAL :: ztau ! temporal filter period
96 !
97 INTEGER :: iroof ! number of roof layers
98 INTEGER :: iwall ! number of wall layers
99 REAL(KIND=JPRB) :: zhook_handle
100 !-------------------------------------------------------------------------------
101 IF (lhook) CALL dr_hook('BLD_E_BUDGET',0,zhook_handle)
102 !
103 !* 1. initializations
104 ! ---------------
105 !
106 iroof = SIZE(pt_roof,2)
107 iwall = SIZE(pt_wall,2)
108 !
109 !!! 27/01/2012 passé dans TEB
110 !! PTS_FLOOR(:)= 19. + XTT
111 !!! 27/01/2012 passé dans TEB
112 !
113 !* 2. no evolution of interior temperature if OTI_EVOL=.FALSE.
114 ! --------------------------------------------------------
115 !
116 IF (.NOT. oti_evol .AND. lhook) CALL dr_hook('BLD_E_BUDGET',1,zhook_handle)
117 IF (.NOT. oti_evol) RETURN
118 !
119 !* 3. evolution of the internal temperature
120 ! -------------------------------------
121 !
122 ztau = xday
123 !
124 WHERE (pbld(:) .GT. 0.)
125  pti_bld(:) = pti_bld(:) * (ztau-ptstep)/ztau &
126  + ( pt_roof(:,iroof) * pbld(:) &
127  + pt_wall(:,iwall) * pwall_o_hor(:) &
128  + pts_floor(:) * pbld(:) ) &
129  / ( 2. * pbld(:) + pwall_o_hor(:) ) * ptstep / ztau
130 ELSEWHERE
131  pti_bld(:) = pts_floor(:)
132 ENDWHERE
133 !
134 !
135 !* 5. internal temperature set to a minimum value (heating)
136 ! -----------------------------------------------------
137 !
138 pti_bld(:) = max( pti_bld(:) , pts_floor(:) )
139 !
140 IF (lhook) CALL dr_hook('BLD_E_BUDGET',1,zhook_handle)
141 !-------------------------------------------------------------------------------
142 END SUBROUTINE bld_e_budget
subroutine bld_e_budget(OTI_EVOL, PTSTEP, PBLD, PWALL_O_HOR, PRHOA, PT_ROOF, PT_WALL, PTI_BLD, PTS_FLOOR)
Definition: bld_e_budget.F90:6