SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_diag_cumul_tebn.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 ! ############################
7 ! ############################
8 !
9 !!**** *MODD_DIAG_CUMUL_TEB - declaration of cumulated surface parameters for TEB scheme
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!
15 !!** IMPLICIT ARGUMENTS
16 !! ------------------
17 !! None
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !! AUTHOR
23 !! ------
24 !! C de Munck *Meteo France*
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 19/02/2013
29 !
30 !
31 !* 0. DECLARATIONS
32 ! ------------
33 !
34 !
35 !
36 USE yomhook ,ONLY : lhook, dr_hook
37 USE parkind1 ,ONLY : jprb
38 !
39 IMPLICIT NONE
40 
41 !TYPE DIAG_CUMUL_TEB_OPTIONS_t
42 !------------------------------------------------------------------------------
43 !
44 ! LOGICAL :: LTEB_CUM ! flag for cumulated terms of teb scheme
45 !
46 !------------------------------------------------------------------------------
47 !END TYPE DIAG_CUMUL_TEB_OPTIONS_t
48 !
50 !------------------------------------------------------------------------------
51 !* miscellaneous variables
52 !
53  REAL, POINTER, DIMENSION(:) :: XRUNOFFC_TOWN ! cumulateda ggregated water runoff for town (kg/m2 town/s)
54  REAL, POINTER, DIMENSION(:) :: XRUNOFFC_GARDEN ! cumulated water runoff for green areas (kg/m2 garden/s)
55  REAL, POINTER, DIMENSION(:) :: XRUNOFFC_ROAD ! cumulated water runoff for roads (kg/m2 road/s)
56  REAL, POINTER, DIMENSION(:) :: XRUNOFFC_ROOF ! cumulated aggregated water runoff for roofs (kg/m2 roof/s)
57  REAL, POINTER, DIMENSION(:) :: XRUNOFFC_STRLROOF ! cumulated water runoff for structural roofs (kg/m2 structural roof/s)
58  REAL, POINTER, DIMENSION(:) :: XRUNOFFC_GREENROOF ! cumulated water runoff for greenroof (kg/m2 greenroof/s)
59  REAL, POINTER, DIMENSION(:) :: XDRAINC_GREENROOF ! cumulated water vertical drainage for greenroof (kg/m2 greenroof/s)
60  REAL, POINTER, DIMENSION(:) :: XDRAINC_GARDEN ! cumulated water vertical drainage for gardens (kg/m2 garden/s)
61  REAL, POINTER, DIMENSION(:) :: XIRRIGC_GREENROOF ! cumulated water supply from summer irrigation (kg/m2 greenroof/s)
62  REAL, POINTER, DIMENSION(:) :: XIRRIGC_GARDEN ! cumulated water supply from summer irrigation (kg/m2 garden/s)
63  REAL, POINTER, DIMENSION(:) :: XIRRIGC_ROAD ! cumulated water supply from summer irrigation (kg/m2 road/s)
64  !
65  REAL, POINTER, DIMENSION(:) :: XHVACC_COOL ! cumulated en. consump. of the cooling system [W m-2(bld)]
66  REAL, POINTER, DIMENSION(:) :: XHVACC_HEAT ! cumulated en. consump. of the heating system [W m-2(bld)]
67  REAL, POINTER, DIMENSION(:) :: XTHER_PROD_BLDC ! cumulated en. product. of thermal solar panels [W m-2(bld)]
68  REAL, POINTER, DIMENSION(:) :: XPHOT_PROD_BLDC ! cumulated en. product. of photovoltaic solar panels [W m-2(bld)]
69 !
70 !------------------------------------------------------------------------------
71 END TYPE diag_cumul_teb_1p_t
72 
74  !
75  TYPE(diag_cumul_teb_1p_t), POINTER :: ALP(:) => NULL()
76  TYPE(diag_cumul_teb_1p_t), POINTER :: CUR => NULL()
77  !
78 END TYPE diag_cumul_teb_t
79 
80 
81 
82 
83  CONTAINS
84 !
85 !------------------------------------------------------------------------------
86 !
87 !------------------------------------------------------------------------------
88 !
89 !
90 
91 
92 
93 !
94 SUBROUTINE diag_cumul_teb_goto_patch(YDIAG_CUMUL_TEB,KTO_PATCH)
95 TYPE(diag_cumul_teb_t), INTENT(INOUT) :: ydiag_cumul_teb
96 INTEGER, INTENT(IN) :: kto_patch
97 REAL(KIND=JPRB) :: zhook_handle
98 !
99 ! Current patch is set to patch KTO_PATCH
100 IF (lhook) CALL dr_hook('MODD_DIAG_CUMUL_TEB_N:DIAG_CUMUL_TEB_GOTO_PATCH',0,zhook_handle)
101 
102 ydiag_cumul_teb%CUR => ydiag_cumul_teb%ALP(kto_patch)
103 
104 IF (lhook) CALL dr_hook('MODD_DIAG_CUMUL_TEB_N:DIAG_CUMUL_TEB_GOTO_PATCH',1,zhook_handle)
105 
106 END SUBROUTINE diag_cumul_teb_goto_patch
107 !
108 !------------------------------------------------------------------------------
109 !
110 SUBROUTINE diag_cumul_teb_init(YDIAG_CUMUL_TEB,KPATCH)
111 TYPE(diag_cumul_teb_t), INTENT(INOUT) :: ydiag_cumul_teb
112 INTEGER, INTENT(IN) :: kpatch
113 INTEGER :: jp
114 REAL(KIND=JPRB) :: zhook_handle
115 IF (lhook) CALL dr_hook("MODD_DIAG_CUMUL_TEB_N:DIAG_CUMUL_TEB_INIT",0,zhook_handle)
116  ALLOCATE(ydiag_cumul_teb%ALP(kpatch))
117  ydiag_cumul_teb%CUR => ydiag_cumul_teb%ALP(1)
118 DO jp=1,kpatch
119  nullify(ydiag_cumul_teb%ALP(jp)%XRUNOFFC_TOWN)
120  nullify(ydiag_cumul_teb%ALP(jp)%XRUNOFFC_GARDEN)
121  nullify(ydiag_cumul_teb%ALP(jp)%XRUNOFFC_ROAD)
122  nullify(ydiag_cumul_teb%ALP(jp)%XRUNOFFC_ROOF)
123  nullify(ydiag_cumul_teb%ALP(jp)%XRUNOFFC_STRLROOF)
124  nullify(ydiag_cumul_teb%ALP(jp)%XRUNOFFC_GREENROOF)
125  nullify(ydiag_cumul_teb%ALP(jp)%XDRAINC_GREENROOF)
126  nullify(ydiag_cumul_teb%ALP(jp)%XDRAINC_GARDEN)
127  nullify(ydiag_cumul_teb%ALP(jp)%XIRRIGC_GREENROOF)
128  nullify(ydiag_cumul_teb%ALP(jp)%XIRRIGC_GARDEN)
129  nullify(ydiag_cumul_teb%ALP(jp)%XIRRIGC_ROAD)
130  nullify(ydiag_cumul_teb%ALP(jp)%XHVACC_COOL)
131  nullify(ydiag_cumul_teb%ALP(jp)%XHVACC_HEAT)
132  nullify(ydiag_cumul_teb%ALP(jp)%XTHER_PROD_BLDC)
133  nullify(ydiag_cumul_teb%ALP(jp)%XPHOT_PROD_BLDC)
134 ENDDO
135 IF (lhook) CALL dr_hook("MODD_DIAG_CUMUL_TEB_N:DIAG_CUMUL_TEB_INIT",1,zhook_handle)
136 END SUBROUTINE diag_cumul_teb_init
137 !
138 !------------------------------------------------------------------------------
139 !
140 !
141 !------------------------------------------------------------------------------
142 
143 END MODULE modd_diag_cumul_teb_n
subroutine diag_cumul_teb_goto_patch(YDIAG_CUMUL_TEB, KTO_PATCH)
subroutine diag_cumul_teb_init(YDIAG_CUMUL_TEB, KPATCH)