SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
tridiag_ground_snowcro.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.
6 !
8 !
9 SUBROUTINE tridiag_ground_snowcro_1d(PA,PB,PC,PY,PX,KNLVLS_USE,KDIFLOOP)
10 REAL, DIMENSION(:,:), INTENT(IN) :: pa ! lower diag. elements of A matrix
11 REAL, DIMENSION(:,:), INTENT(IN) :: pb ! main diag. elements of A matrix
12 REAL, DIMENSION(:,:), INTENT(IN) :: pc ! upper diag. elements of A matrix
13 REAL, DIMENSION(:,:), INTENT(IN) :: py ! r.h.s. term
14 !
15 REAL, DIMENSION(:,:), INTENT(OUT) :: px ! solution of A.X = Y
16 !
17 INTEGER, DIMENSION(:), INTENT(IN) :: knlvls_use ! number of effective layers
18 !
19 INTEGER, INTENT(IN) :: kdifloop ! shift in control loops: 0 or 1
20 END SUBROUTINE tridiag_ground_snowcro_1d
21 !
22 SUBROUTINE tridiag_ground_snowcro_2d(PA,PB,PC,PY,PX,KNLVLS_USE,KDIFLOOP)
23 REAL, DIMENSION(:,:,:), INTENT(IN) :: pa ! lower diag. elements of A matrix
24 REAL, DIMENSION(:,:,:), INTENT(IN) :: pb ! main diag. elements of A matrix
25 REAL, DIMENSION(:,:,:), INTENT(IN) :: pc ! upper diag. elements of A matrix
26 REAL, DIMENSION(:,:,:), INTENT(IN) :: py ! r.h.s. term
27 !
28 REAL, DIMENSION(:,:,:), INTENT(OUT) :: px ! solution of A.X = Y
29 !
30 INTEGER, DIMENSION(:,:), INTENT(IN) :: knlvls_use ! number of effective layers
31 !
32 INTEGER, INTENT(IN) :: kdifloop ! shift in control loops: 0 or 1
33 END SUBROUTINE tridiag_ground_snowcro_2d
34 !
35 END INTERFACE tridiag_ground_snowcro
36 !
38 !
39 !###################################################################
40  SUBROUTINE tridiag_ground_snowcro_1d(PA,PB,PC,PY,PX,KNLVLS_USE,KDIFLOOP)
41 ! #########################################
42 !
43 !
44 !!**** *TRIDIAG_GROUND* - routine to solve a time implicit scheme
45 !!
46 !!
47 !! PURPOSE
48 !! -------
49 ! The purpose of this routine is to resolve the linear system:
50 !
51 ! A.X = Y
52 !
53 ! where A is a tridiagonal matrix, and X and Y two vertical vectors.
54 ! However, the computations are performed at the same time for all
55 ! the verticals where an inversion of the system is necessary.
56 ! This explain the dimansion of the input variables.
57 !
58 !!** METHOD
59 !! ------
60 !!
61 !! Then, the classical tridiagonal algorithm is used to invert the
62 !! implicit operator. Its matrix is given by:
63 !!
64 !! ( b(1) c(1) 0 0 0 0 0 0 )
65 !! ( a(2) b(2) c(2) 0 ... 0 0 0 0 )
66 !! ( 0 a(3) b(3) c(3) 0 0 0 0 )
67 !! .......................................................................
68 !! ( 0 ... 0 a(k) b(k) c(k) 0 ... 0 0 )
69 !! .......................................................................
70 !! ( 0 0 0 0 0 ... a(n-1) b(n-1) c(n-1))
71 !! ( 0 0 0 0 0 ... 0 a(n) b(n) )
72 !!
73 !!
74 !! All these computations are purely vertical and vectorizations are
75 !! easely achieved by processing all the verticals in parallel.
76 !!
77 !! EXTERNAL
78 !! --------
79 !!
80 !! NONE
81 !!
82 !! IMPLICIT ARGUMENTS
83 !! ------------------
84 !!
85 !! REFERENCE
86 !! ---------
87 !!
88 !! AUTHOR
89 !! ------
90 !! V. Masson
91 !!
92 !! MODIFICATIONS
93 !! -------------
94 !! Original May 13, 1998
95 !! 05/2011: Brun Special treatment to tackle the variable number
96 !! of snow layers
97 !! In case of second call, a shift of 1 snow layer
98 !! is applied in the control loops.
99 !! ---------------------------------------------------------------------
100 !
101 !* 0. DECLARATIONS
102 !
103 USE yomhook , ONLY : lhook, dr_hook
104 USE parkind1, ONLY : jprb
105 !
106 IMPLICIT NONE
107 !
108 !* 0.1 declarations of arguments
109 !
110 REAL, DIMENSION(:,:), INTENT(IN) :: pa ! lower diag. elements of A matrix
111 REAL, DIMENSION(:,:), INTENT(IN) :: pb ! main diag. elements of A matrix
112 REAL, DIMENSION(:,:), INTENT(IN) :: pc ! upper diag. elements of A matrix
113 REAL, DIMENSION(:,:), INTENT(IN) :: py ! r.h.s. term
114 !
115 REAL, DIMENSION(:,:), INTENT(OUT) :: px ! solution of A.X = Y
116 !
117 INTEGER, DIMENSION(:), INTENT(IN) :: knlvls_use ! number of effective layers
118 !
119 INTEGER, INTENT(IN) :: kdifloop ! shift in control loops: 0 or 1
120 !
121 !* 0.2 declarations of local variables
122 !
123 REAL, DIMENSION(SIZE(PA,1),SIZE(PA,2)) :: zw ! work array
124 REAL, DIMENSION(SIZE(PA,1) ) :: zdet ! work array
125 !
126 !
127 INTEGER :: jl, jj ! vertical loop control
128 INTEGER :: inl ! number of vertical levels
129 !
130 REAL(KIND=JPRB) :: zhook_handle
131 ! ---------------------------------------------------------------------------
132 !
133 IF (lhook) CALL dr_hook('TRIDIAG_GROUND_SNOWCRO_1D',0,zhook_handle)
134 !
135 inl = SIZE(px,2)
136 !
137 !* 1. levels going up
138 ! ---------------
139 !
140 !* 1.1 first level
141 ! -----------
142 !
143 zdet(:) = pb(:,1)
144 !
145 px(:,1) = py(:,1) / zdet(:)
146 !
147 !* 1.2 other levels
148 ! ------------
149 !
150 DO jl = 2,inl
151  !
152  DO jj = 1,SIZE(px,1)
153  !
154  IF ( jl<=knlvls_use(jj)-kdifloop ) THEN
155  !
156  zw(jj,jl) = pc(jj,jl-1)/zdet(jj)
157  zdet(jj) = pb(jj,jl ) - pa(jj,jl)*zw(jj,jl)
158  !
159  px(jj,jl) = ( py(jj,jl) - pa(jj,jl)*px(jj,jl-1) ) / zdet(jj)
160  !
161  ENDIF
162  !
163  ENDDO
164  !
165 END DO
166 !
167 !-------------------------------------------------------------------------------
168 !
169 !* 2. levels going down
170 ! -----------------
171 !
172 DO jl = inl-1,1,-1
173  !
174  DO jj = 1,SIZE(px,1)
175  !
176  IF ( jl<=knlvls_use(jj)-1-kdifloop ) THEN
177  !
178  px(jj,jl) = px(jj,jl) - zw(jj,jl+1)*px(jj,jl+1)
179  !
180  ENDIF
181  !
182  ENDDO
183  !
184 END DO
185 !
186 IF (lhook) CALL dr_hook('TRIDIAG_GROUND_SNOWCRO_1D',1,zhook_handle)
187 !
188 !-------------------------------------------------------------------------------
189 !
190 END SUBROUTINE tridiag_ground_snowcro_1d
191 !
192 !###################################################################
193  SUBROUTINE tridiag_ground_snowcro_2d(PA,PB,PC,PY,PX,KNLVLS_USE,KDIFLOOP)
194 ! #########################################
195 !
196 !
197 !!**** *TRIDIAG_GROUND* - routine to solve a time implicit scheme
198 !!
199 !!
200 !! PURPOSE
201 !! -------
202 ! The purpose of this routine is to resolve the linear system:
203 !
204 ! A.X = Y
205 !
206 ! where A is a tridiagonal matrix, and X and Y two vertical vectors.
207 ! However, the computations are performed at the same time for all
208 ! the verticals where an inversion of the system is necessary.
209 ! This explain the dimansion of the input variables.
210 !
211 !!** METHOD
212 !! ------
213 !!
214 !! Then, the classical tridiagonal algorithm is used to invert the
215 !! implicit operator. Its matrix is given by:
216 !!
217 !! ( b(1) c(1) 0 0 0 0 0 0 )
218 !! ( a(2) b(2) c(2) 0 ... 0 0 0 0 )
219 !! ( 0 a(3) b(3) c(3) 0 0 0 0 )
220 !! .......................................................................
221 !! ( 0 ... 0 a(k) b(k) c(k) 0 ... 0 0 )
222 !! .......................................................................
223 !! ( 0 0 0 0 0 ... a(n-1) b(n-1) c(n-1))
224 !! ( 0 0 0 0 0 ... 0 a(n) b(n) )
225 !!
226 !!
227 !! All these computations are purely vertical and vectorizations are
228 !! easely achieved by processing all the verticals in parallel.
229 !!
230 !! EXTERNAL
231 !! --------
232 !!
233 !! NONE
234 !!
235 !! IMPLICIT ARGUMENTS
236 !! ------------------
237 !!
238 !! REFERENCE
239 !! ---------
240 !!
241 !! AUTHOR
242 !! ------
243 !! V. Masson
244 !!
245 !! MODIFICATIONS
246 !! -------------
247 !! Original May 13, 1998
248 !! 05/2011: Brun Special treatment to tackle the variable number
249 !! of snow layers
250 !! In case of second call, a shift of 1 snow layer
251 !! is applied in the control loops.
252 !! ---------------------------------------------------------------------
253 !
254 !* 0. DECLARATIONS
255 !
256 USE yomhook , ONLY : lhook, dr_hook
257 USE parkind1, ONLY : jprb
258 !
259 IMPLICIT NONE
260 !
261 !* 0.1 declarations of arguments
262 !
263 REAL, DIMENSION(:,:,:), INTENT(IN) :: pa ! lower diag. elements of A matrix
264 REAL, DIMENSION(:,:,:), INTENT(IN) :: pb ! main diag. elements of A matrix
265 REAL, DIMENSION(:,:,:), INTENT(IN) :: pc ! upper diag. elements of A matrix
266 REAL, DIMENSION(:,:,:), INTENT(IN) :: py ! r.h.s. term
267 !
268 REAL, DIMENSION(:,:,:), INTENT(OUT) :: px ! solution of A.X = Y
269 !
270 INTEGER, DIMENSION(:,:), INTENT(IN) :: knlvls_use ! number of effective layers
271 !
272 INTEGER, INTENT(IN) :: kdifloop ! shift in control loops: 0 or 1
273 !
274 !* 0.2 declarations of local variables
275 !
276 REAL, DIMENSION(SIZE(PA,2)) :: zw ! work array
277 REAL :: zdet ! work array
278 !
279 !
280 INTEGER :: jl, jj, jb ! vertical loop control
281 INTEGER :: inl, inb ! number of vertical levels
282 !
283 REAL(KIND=JPRB) :: zhook_handle
284 ! ---------------------------------------------------------------------------
285 !
286 IF (lhook) CALL dr_hook('TRIDIAG_GROUND_SNOWCRO_2D',0,zhook_handle)
287 !
288 inl = SIZE(px,2)
289 inb = SIZE(px,3)
290 !
291 !* 1. levels going up
292 ! ---------------
293 !
294 !* 1.1 first level
295 ! -----------
296 !
297 DO jb = 1,inb
298  !
299  DO jj = 1,SIZE(px,1)
300  !
301  zdet = pb(jj,1,jb)
302  !
303  px(jj,1,jb) = py(jj,1,jb) / zdet
304  !
305  !* 1.2 other levels
306  ! ------------
307  !
308  DO jl = 2,inl
309  !
310  IF ( jl<=knlvls_use(jj,jb)-kdifloop ) THEN
311  !
312  zw(jl) = pc(jj,jl-1,jb) /zdet
313  zdet = pb(jj,jl ,jb) - pa(jj,jl,jb) * zw(jl)
314  !
315  px(jj,jl,jb) = ( py(jj,jl,jb) - pa(jj,jl,jb) * px(jj,jl-1,jb) ) / zdet
316  !
317  ENDIF
318  !
319  ENDDO
320  !
321  !-------------------------------------------------------------------------------
322  !
323  !* 2. levels going down
324  ! -----------------
325  !
326  DO jl = inl-1,1,-1
327  !
328  IF ( jl<=knlvls_use(jj,jb)-1-kdifloop ) THEN
329  !
330  px(jj,jl,jb) = px(jj,jl,jb) - zw(jl+1) * px(jj,jl+1,jb)
331  !
332  ENDIF
333  !
334  ENDDO
335  !
336  END DO
337  !
338 ENDDO
339 !
340 IF (lhook) CALL dr_hook('TRIDIAG_GROUND_SNOWCRO_2D',1,zhook_handle)
341 !
342 !-------------------------------------------------------------------------------
343 !
344 END SUBROUTINE tridiag_ground_snowcro_2d
subroutine tridiag_ground_snowcro_1d(PA, PB, PC, PY, PX, KNLVLS_USE, KDIFLOOP)
subroutine tridiag_ground_snowcro_2d(PA, PB, PC, PY, PX, KNLVLS_USE, KDIFLOOP)