SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
window_shading.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 window_shading(PSHGC, PSHGC_SH, O_SHADE, PALB_WALL, &
7  pabs_win, pabs_winsh, palb_win, ptran_win )
8 ! #############################################################
9 !
10 !
11 !
12 !!**** *WINDOW_SHADING*
13 !!
14 !! PURPOSE
15 !! -------
16 !
17 ! Computes the radiative properties of the window in case of shading
18 ! devices active
19 !
20 !
21 !!** METHOD
22 !! ------
23 !!
24 !! apply radiative properties coming from namelist input (SHGC_SH)
25 !!
26 !! EXTERNAL
27 !! --------
28 !!
29 !!
30 !! IMPLICIT ARGUMENTS
31 !! ------------------
32 !!
33 !! MODD_CST
34 !!
35 !!
36 !! REFERENCE
37 !! ---------
38 !!
39 !! EnergyPlus Engineering Reference V7, 2012, p. 217.
40 !!
41 !! AUTHOR
42 !! ------
43 !!
44 !! B. Bueno * Meteo-France *
45 !!
46 !! MODIFICATIONS
47 !! -------------
48 !! Original 11/10
49 !! G. Pigeon 09/12 code reorganization to take into account propertie
50 !! from window
51 !-------------------------------------------------------------------------------
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 !
57 REAL, DIMENSION(:), INTENT(IN) :: pshgc !Window solar heat gain coefficient
58 REAL, DIMENSION(:), INTENT(IN) :: pshgc_sh !Window + shading solar heat gain coefficient
59 LOGICAL, DIMENSION(:), INTENT(IN) :: o_shade !use of shadings TRUE -> shadings ;
60  !FALSE -> no shading
61 REAL, DIMENSION(:), INTENT(IN) :: palb_wall !albedo of the wall
62 REAL, DIMENSION(:), INTENT(IN) :: pabs_win !Window absorptivity
63 REAL, DIMENSION(:), INTENT(OUT) :: pabs_winsh!Window absorptivity after shading
64 REAL, DIMENSION(:), INTENT(OUT) :: palb_win !Albedo of the ensemble window + shading
65 REAL, DIMENSION(:), INTENT(INOUT) :: ptran_win !Window transmitivity
66 !
67 !local variables
68 REAL(KIND=JPRB) :: zhook_handle
69 !
70 IF (lhook) CALL dr_hook('WINDOW_SHADING',0,zhook_handle)
71 !
72 WHERE(o_shade)
73  ptran_win(:) = pshgc_sh(:)
74  pabs_winsh(:) = ptran_win(:) * pabs_win(:)
75  palb_win(:) = palb_wall(:)
76 ELSE WHERE
77  ptran_win(:) = ptran_win(:)
78  pabs_winsh(:) = pabs_win(:)
79  palb_win(:) = 1. - pabs_win(:) - ptran_win(:)
80 END WHERE
81 !
82 WHERE ((pabs_winsh(:) + ptran_win(:) + palb_win) > 1.)
83  palb_win(:) = 1. - pabs_winsh(:) - ptran_win(:)
84 END WHERE
85 !
86 IF (lhook) CALL dr_hook('WINDOW_SHADING',1,zhook_handle)
87 !
88 END SUBROUTINE window_shading
subroutine window_shading(PSHGC, PSHGC_SH, O_SHADE, PALB_WALL, PABS_WIN, PABS_WINSH, PALB_WIN, PTRAN_WIN)