SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
bld_occ_calendar.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_occ_calendar(KYEAR, KMONTH, KDAY, PTSUN, PRESIDENTIAL, PTCOOL_TARGET_IN, PTHEAT_TARGET_IN, &
7  pqin_in, pdt_res, pdt_off, pqin_frac, ptcool_target, ptheat_target, pqin)
8 !#####################################################################################
9 !! **** BLD_OCC_CALENDAR *
10 !!
11 !! PURPOSE
12 !! -------
13 !! BLD_OCC_CALENDAR defines the parameters relevant for BEM (TCOOL_TARGET, THEAT_TARGET and QIN)
14 !! depending on the building use type (hence the DOW and local French TOD) * based on MUSCADE scenarii *
15 !!
16 !! AUTHOR
17 !! ------
18 !! C. de Munck *Météo-France*
19 !!
20 !! MODIFICATIONS
21 !! -------------
22 !! Original 02/2013
23 !
24 USE modd_csts, ONLY : xtt
25 !
26 USE modi_day_of_week
27 !
28 USE yomhook ,ONLY : lhook, dr_hook
29 USE parkind1 ,ONLY : jprb
30 !
31 IMPLICIT NONE
32 !
33 !! 1. declaration of arguments
34 !
35 INTEGER,INTENT(IN) :: kyear ! current year (UTC)
36 INTEGER,INTENT(IN) :: kmonth ! current month (UTC)
37 INTEGER,INTENT(IN) :: kday ! current day (UTC)
38 REAL, DIMENSION(:) , INTENT(IN) :: ptsun ! current solar time (s, UTC)
39 !
40 REAL, DIMENSION(:) , INTENT(IN) :: presidential ! Residential use fraction
41 REAL, DIMENSION(:) , INTENT(IN) :: ptcool_target_in ! Cooling setpoint of HVAC system [K] input
42 REAL, DIMENSION(:) , INTENT(IN) :: ptheat_target_in ! Heating setpoint of HVAC system [K] input
43 REAL, DIMENSION(:) , INTENT(IN) :: pqin_in ! Internal heat gains [W m-2(floor)] input
44 REAL, INTENT(IN) :: pdt_res ! Target temperature change when unoccupied (K) (residential buildings)
45 REAL, INTENT(IN) :: pdt_off ! Target temperature change when unoccupied (K) (offices and commercial buildings)
46 REAL, INTENT(IN) :: pqin_frac ! Fraction of internal gains when unoccupied (-)
47 !
48 REAL, DIMENSION(:) , INTENT(OUT) :: ptcool_target ! Cooling setpoint of HVAC system [K]
49 REAL, DIMENSION(:) , INTENT(OUT) :: ptheat_target ! Heating setpoint of HVAC system [K]
50 REAL, DIMENSION(:) , INTENT(OUT) :: pqin ! Internal heat gains [W m-2(floor)]
51 !
52 !! 2. declaration of local variables
53 !
54  CHARACTER(LEN = 6) :: ctime ! Local time scheme (winter or summer time)
55 INTEGER :: jdow ! day of week
56 INTEGER :: jj
57 !
58 REAL, DIMENSION(SIZE(PQIN)) :: ztod_beg ! first Time Of Day that building unoccupied (UTC, s)
59 REAL, DIMENSION(SIZE(PQIN)) :: ztod_end ! last Time Of Day that building unoccupied (UTC, s)
60 REAL, DIMENSION(SIZE(PQIN)) :: zdt ! Target temperature change when unoccupied (K)
61 
62 REAL(KIND=JPRB) :: ztodook_handle
63 !
64 IF (lhook) CALL dr_hook('BLD_OCC_CALENDAR',0,ztodook_handle)
65 !
66 !--------------------------------------------------------------------------------------
67 ! 3. determine the day of the week and the local time scheme in France
68 !--------------------------------------------------------------------------------------
69 !
70  CALL day_of_week(kyear, kmonth, kday, jdow)
71 !
72  ctime = 'WINTER'
73 IF (kmonth >= 4 .AND. kmonth <= 10) ctime = 'SUMMER'
74 !
75 !--------------------------------------------------------------------------------------
76 ! 4. initialisation of parameters
77 !--------------------------------------------------------------------------------------
78 !
79 ! Parameters assigned to the occupied values - read in namelist via BATI.csv :
80 !
81 ptheat_target(:) = ptheat_target_in(:)
82 !
83 ptcool_target(:) = ptcool_target_in(:)
84 !
85 pqin(:) = pqin_in(:)
86 !
87 ztod_beg(:) = 0.
88 ztod_end(:) = 0.
89 !
90 !--------------------------------------------------------------------------------------
91 ! 5. computes beginning and end of unoccupied calendar based on building USE TYPE
92 !--------------------------------------------------------------------------------------
93 !
94 DO jj =1,SIZE(ptsun)
95 !
96  IF (presidential(jj) > 0.5) THEN ! RESIDENTIAL
97  !
98  IF (jdow >= 2 .AND. jdow <=6) THEN ! week days
99  ztod_beg(jj) = 9. * 3600. ! 9 UTC - WINTER time
100  ztod_end(jj) = 17. * 3600. ! 17 UTC - WINTER time
101  END IF
102  zdt(jj) = pdt_res
103  !
104  ELSE
105  !
106  IF (jdow >= 2 .AND. jdow <=7) THEN ! week days
107  ztod_beg(jj) = 17. * 3600. ! 17 UTC
108  ztod_end(jj) = 7. * 3600. ! 7 UTC
109  ELSE ! week-end
110  ztod_beg(jj) = 0. * 3600. ! 0 UTC
111  ztod_end(jj) = 24. * 3600. ! 24 UTC
112  END IF
113  zdt(jj) = pdt_off
114  !
115  END IF
116 ! adjustment of unoccupied TOD based on time scheme
117  IF (ctime == 'SUMMER') THEN
118  ztod_beg(jj) = ztod_beg(jj) - 3600.
119  ztod_end(jj) = ztod_end(jj) - 3600.
120  END IF
121 !
122 ENDDO
123 !
124 !--------------------------------------------------------------------------------------
125 ! 6. modulate BEM input values for unoccupied building calendar
126 !--------------------------------------------------------------------------------------
127 !
128 DO jj =1,SIZE(ptsun)
129 !
130  IF (( (ztod_beg(jj) < ztod_end(jj)) .AND. (ptsun(jj) > ztod_beg(jj) .AND. ptsun(jj) < ztod_end(jj)) ) &
131  .OR. &
132  ( (ztod_beg(jj) > ztod_end(jj)) .AND. ((ptsun(jj) > 0 .AND. ptsun(jj) < ztod_end(jj)) .OR. &
133  (ptsun(jj) > ztod_beg(jj) .AND. ptsun(jj) < 24 * 3600.)))) THEN
134  !
135  ptheat_target(jj) = ptheat_target_in(jj) - zdt(jj)
136  ptcool_target(jj) = ptcool_target_in(jj) + zdt(jj)
137  pqin(jj) = pqin_frac * pqin(jj)
138  ENDIF
139 !
140 ENDDO
141 !
142 !--------------------------------------------------------------------------------------
143 !
144 IF (lhook) CALL dr_hook('BLD_OCC_CALENDAR',1,ztodook_handle)
145 !
146 END SUBROUTINE bld_occ_calendar
subroutine day_of_week(DATE, MONTH, YEAR, DOW)
subroutine bld_occ_calendar(KYEAR, KMONTH, KDAY, PTSUN, PRESIDENTIAL, PTCOOL_TARGET_IN, PTHEAT_TARGET_IN, PQIN_IN, PDT_RES, PDT_OFF, PQIN_FRAC, PTCOOL_TARGET, PTHEAT_TARGET, PQIN)