SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
layer_e_budget_get_coef.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 layer_e_budget_get_coef(PT, PTSTEP, PIMPL, PHC, PTC, PD, PA, PB, PC, PY)
7 ! ##########################################################################
8 !
9 !!**** *LAYER_E_BUDGET_GET_COEF*
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 ! Computes the evoultion of building floor temperatures
15 !
16 !
17 !!** METHOD
18 ! ------
19 !
20 ! 6 : equations for evolution of Ts_floor
21 ! *************************************************************
22 !
23 ! dTf_k(t) / dt = 1/(df_k*Cf_k) * (- 2*Kf_k-1*(Tf_k-Tf_k-1)/(df_k-1 +df_k)
24 ! - 2*Kf_k *(Tf_k-Tf_k+1)/(df_k+1 +df_k) )
25 !
26 ! dTf_1(t) / dt = 1/(df_1*Cf_1) * (- 2*Kw_1*(Tw_1-Tw_2)/(dw_1 +dw_2))
27 !
28 ! with
29 !
30 ! K*_k = (d*_k+ d*_k+1)/(d*_k/k*_k+ d*_k+1/k*_k+1)
31 !
32 !
33 ! The system is implicited (or semi-implicited).
34 !
35 ! ZIMPL=1 ---> implicit system
36 ! ZIMPL=0.5 ---> semi-implicit system
37 ! ZIMPL=0 ---> explicit system
38 !
39 !
40 !
41 !
42 !! EXTERNAL
43 !! --------
44 !!
45 !!
46 !! IMPLICIT ARGUMENTS
47 !! ------------------
48 !!
49 !! MODD_CST
50 !!
51 !!
52 !! REFERENCE
53 !! ---------
54 !!
55 !!
56 !! AUTHOR
57 !! ------
58 !!
59 !! G. Pigeon * Meteo-France *
60 !!
61 !! MODIFICATIONS
62 !! -------------
63 !! Original 15/04/09
64 !! 08/10 (G. Pigeon) computation of residual of energy balance
65 !! modification of the limit condition for
66 !! the deep temp. from the deep road temp.
67 !! to zero flux condition. idem for sfce T
68 !-------------------------------------------------------------------------------
69 !
70 !* 0. DECLARATIONS
71 ! ------------
72 !
73 USE yomhook ,ONLY : lhook, dr_hook
74 USE parkind1 ,ONLY : jprb
75 !
76 IMPLICIT NONE
77 !
78 !* 0.1 declarations of arguments
79 !
80 REAL, DIMENSION(:,:), INTENT(IN) :: pt ! floor layers temperatures
81 REAL, INTENT(IN) :: ptstep ! time step
82 REAL, DIMENSION(:,:), INTENT(IN) :: phc ! heat capacity for road layers
83 REAL, DIMENSION(:,:), INTENT(IN) :: ptc ! thermal conductivity for road layers
84 REAL, DIMENSION(:,:), INTENT(IN) :: pd ! depth of road layers
85 REAL, DIMENSION(:,:), INTENT(OUT) :: pa
86 REAL, DIMENSION(:,:), INTENT(OUT) :: pb
87 REAL, DIMENSION(:,:), INTENT(OUT) :: pc
88 REAL, DIMENSION(:,:), INTENT(OUT) :: py
89 REAL, INTENT(IN) :: pimpl ! implicitation coefficient
90 !
91 !* 0.2 declarations of local variables
92 !
93 REAL :: zimpl ! implicit coefficient
94 REAL :: zexpl ! explicit coefficient
95 !
96 ! mean thermal conductivity over distance between 2 layers
97 REAL, DIMENSION(SIZE(PT,1),SIZE(PT,2)) :: zmtc_o_d
98 ! thermal capacity times layer depth
99 REAL, DIMENSION(SIZE(PT,1),SIZE(PT,2)) :: zhc_d
100 !
101 INTEGER :: ilayer ! number of floor layers
102 INTEGER :: jlayer ! loop counter
103 INTEGER :: jj ! loop counter
104 REAL(KIND=JPRB) :: zhook_handle
105 !-------------------------------------------------------------------------------
106 IF (lhook) CALL dr_hook('LAYER_E_BUDGET_GET_COEF',0,zhook_handle)
107 !
108 !* 1. layer thermal properties
109 ! ------------------------
110 !
111 zimpl = pimpl
112 zexpl = 1. - pimpl
113 !
114 ilayer = SIZE(pt,2)
115 zmtc_o_d(:,:) = 0.
116 !
117 DO jlayer=1,ilayer-1
118  DO jj=1,SIZE(pt,1)
119  zmtc_o_d(jj,jlayer) = 2./( pd(jj,jlayer)/ptc(jj,jlayer) + pd(jj,jlayer+1)/ptc(jj,jlayer+1) )
120  zhc_d(jj,jlayer) = phc(jj,jlayer) * pd(jj,jlayer)
121  ENDDO
122 END DO
123 !
124 DO jj=1,SIZE(pt,1)
125  zhc_d(jj,ilayer) = phc(jj,ilayer) * pd(jj,ilayer)
126 ENDDO
127 !
128 !-------------------------------------------------------------------------------
129 !
130 !* 3. Surface layer coefficients
131 ! ------------------------------
132 !
133 ! no implication for Ts and use of flux from BEM or BLD_E_BUDGET
134 DO jlayer = 1, ilayer
135  DO jj = 1, SIZE(pt,1)
136  !
137  IF ( jlayer == 1 ) THEN
138  pa(jj,jlayer) = 0.
139  ELSE
140  pa(jj,jlayer) = - zimpl * zmtc_o_d(jj,jlayer-1)
141  ENDIF
142  !
143  IF ( jlayer == ilayer ) THEN
144  pc(jj,jlayer) = 0.
145  ELSE
146  pc(jj,jlayer) = - zimpl * zmtc_o_d(jj,jlayer)
147  ENDIF
148  !
149  pb(jj,jlayer) = zhc_d(jj,jlayer)/ptstep
150  py(jj,jlayer) = zhc_d(jj,jlayer)/ptstep * pt(jj,jlayer)
151  !
152  IF ( jlayer .GT. 1.) THEN
153  pb(jj,jlayer) = pb(jj,jlayer) + zimpl * zmtc_o_d(jj,jlayer-1)
154  py(jj,jlayer) = py(jj,jlayer) + zexpl * zmtc_o_d(jj,jlayer-1) * ( pt(jj,jlayer-1) - pt(jj,jlayer) )
155  ENDIF
156  !
157  IF ( jlayer .LT. ilayer) THEN
158  pb(jj,jlayer) = pb(jj,jlayer) + zimpl * zmtc_o_d(jj,jlayer)
159  py(jj,jlayer) = py(jj,jlayer) + zexpl * zmtc_o_d(jj,jlayer) * ( pt(jj,jlayer+1) - pt(jj,jlayer) )
160  ENDIF
161  !
162  ENDDO
163  !
164 ENDDO
165 !
166 IF (lhook) CALL dr_hook('LAYER_E_BUDGET_GET_COEF',1,zhook_handle)
167 !-------------------------------------------------------------------------------
168 END SUBROUTINE layer_e_budget_get_coef
subroutine layer_e_budget_get_coef(PT, PTSTEP, PIMPL, PHC, PTC, PD, PA, PB, PC, PY)