SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
layer_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 layer_e_budget( PT, PTSTEP, PIMPL, PHC, PTC, PD, PA, PB, PC, PY, PDQS )
7 ! ##########################################################################
8 !
9 !!**** *FLOOR_LAYER_E_BUDGET*
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 modi_tridiag_ground
74 !
75 USE yomhook ,ONLY : lhook, dr_hook
76 USE parkind1 ,ONLY : jprb
77 !
78 IMPLICIT NONE
79 !
80 !* 0.1 declarations of arguments
81 !
82 REAL, DIMENSION(:,:), INTENT(INOUT) :: pt ! floor layers temperatures
83 REAL, INTENT(IN) :: ptstep ! time step
84 REAL, DIMENSION(:,:), INTENT(IN) :: phc ! heat capacity for road layers
85 REAL, DIMENSION(:,:), INTENT(IN) :: ptc ! thermal conductivity for
86  !road layers
87 REAL, DIMENSION(:,:), INTENT(IN) :: pd ! depth of road layers
88 REAL, DIMENSION(:,:), INTENT(IN) :: pa
89 REAL, DIMENSION(:,:), INTENT(IN) :: pb
90 REAL, DIMENSION(:,:), INTENT(IN) :: pc
91 REAL, DIMENSION(:,:), INTENT(IN) :: py
92 REAL, DIMENSION(:), INTENT(OUT) :: pdqs
93 REAL, INTENT(IN) :: pimpl ! implicitation coefficient
94 !
95 !* 0.2 declarations of local variables
96 !
97 !
98 REAL :: zimpl ! implicit coefficient
99 REAL :: zexpl ! explicit coefficient
100 !
101 REAL, DIMENSION(SIZE(PT,1),SIZE(PT,2)) :: zx ! solution
102 !
103 REAL, DIMENSION(SIZE(PT,1)) :: zei ! internal energy of floor at t
104 REAL, DIMENSION(SIZE(PT,1)) :: zpei ! internal energy of floor at time t+
105 !
106 INTEGER :: ilayer ! number of floor layers
107 INTEGER :: jlayer ! loop counter
108 INTEGER :: jj ! loop counter
109 REAL(KIND=JPRB) :: zhook_handle
110 !-------------------------------------------------------------------------------
111 IF (lhook) CALL dr_hook('LAYER_E_BUDGET',0,zhook_handle)
112 !
113 ilayer = SIZE(pt,2)
114 !
115 zimpl = pimpl
116 zexpl = 1.-pimpl
117 !
118 !-------------------------------------------------------------------------------
119 !
120 !* 1. Preliminaries : internal energy of floor at the current time step
121 ! -----------------------------------------------------------------
122 !
123 zei(:) = 0.
124 DO jlayer=1,ilayer
125  DO jj=1,SIZE(pt,1)
126  zei(jj)=zei(jj) + ( phc(jj,jlayer)*pd(jj,jlayer)*pt(jj,jlayer) )
127  ENDDO
128 END DO
129 !
130 !-------------------------------------------------------------------------------
131 !
132 !* 2. Tri-diagonal system resolution
133 ! ------------------------------
134 !
135  CALL tridiag_ground(pa,pb,pc,py,zx)
136 !
137 DO jlayer=1,ilayer
138  pt(:,jlayer) = zx(:,jlayer)
139 END DO
140 !
141 !* 3. heat storage inside floor and flux toward the floor
142 ! ---------------------------------------------------
143 !
144 ! 3.1 internal energy of the floor at the next time step
145 ! --------------------------------------------------
146 !
147 zpei(:) = 0.0
148 DO jlayer=1,ilayer
149  DO jj=1,SIZE(pt,1)
150  zpei(jj) = zpei(jj)+ ( phc(jj,jlayer)*pd(jj,jlayer)*pt(jj,jlayer) )
151  ENDDO
152 END DO
153 !
154 ! 3.2 heat storage flux inside floor
155 ! ------------------------------
156 !
157 pdqs(:)=(zpei(:)-zei(:))/ptstep
158 !
159 IF (lhook) CALL dr_hook('LAYER_E_BUDGET',1,zhook_handle)
160 !-------------------------------------------------------------------------------
161 END SUBROUTINE layer_e_budget
subroutine tridiag_ground(PA, PB, PC, PY, PX)
subroutine layer_e_budget(PT, PTSTEP, PIMPL, PHC, PTC, PD, PA, PB, PC, PY, PDQS)