SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
tridiag_ground.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 tridiag_ground(PA,PB,PC,PY,PX)
7 ! #########################################
8 !
9 !
10 !!**** *TRIDIAG_GROUND* - routine to solve a time implicit scheme
11 !!
12 !!
13 !! PURPOSE
14 !! -------
15 ! The purpose of this routine is to resolve the linear system:
16 !
17 ! A.X = Y
18 !
19 ! where A is a tridiagonal matrix, and X and Y two vertical vectors.
20 ! However, the computations are performed at the same time for all
21 ! the verticals where an inversion of the system is necessary.
22 ! This explain the dimansion of the input variables.
23 !
24 !!** METHOD
25 !! ------
26 !!
27 !! Then, the classical tridiagonal algorithm is used to invert the
28 !! implicit operator. Its matrix is given by:
29 !!
30 !! ( b(1) c(1) 0 0 0 0 0 0 )
31 !! ( a(2) b(2) c(2) 0 ... 0 0 0 0 )
32 !! ( 0 a(3) b(3) c(3) 0 0 0 0 )
33 !! .......................................................................
34 !! ( 0 ... 0 a(k) b(k) c(k) 0 ... 0 0 )
35 !! .......................................................................
36 !! ( 0 0 0 0 0 ... a(n-1) b(n-1) c(n-1))
37 !! ( 0 0 0 0 0 ... 0 a(n) b(n) )
38 !!
39 !!
40 !! All these computations are purely vertical and vectorizations are
41 !! easely achieved by processing all the verticals in parallel.
42 !!
43 !! EXTERNAL
44 !! --------
45 !!
46 !! NONE
47 !!
48 !! IMPLICIT ARGUMENTS
49 !! ------------------
50 !!
51 !! REFERENCE
52 !! ---------
53 !!
54 !! AUTHOR
55 !! ------
56 !! V. Masson
57 !!
58 !! MODIFICATIONS
59 !! -------------
60 !! Original May 13, 1998
61 !! Modified :
62 !! B. Decharme 08/12 Loop optimization
63 !! ---------------------------------------------------------------------
64 !
65 !* 0. DECLARATIONS
66 !
67 !
68 USE yomhook ,ONLY : lhook, dr_hook
69 USE parkind1 ,ONLY : jprb
70 !
71 IMPLICIT NONE
72 !
73 !
74 !* 0.1 declarations of arguments
75 !
76 REAL, DIMENSION(:,:), INTENT(IN) :: pa ! lower diag. elements of A matrix
77 REAL, DIMENSION(:,:), INTENT(IN) :: pb ! main diag. elements of A matrix
78 REAL, DIMENSION(:,:), INTENT(IN) :: pc ! upper diag. elements of A matrix
79 REAL, DIMENSION(:,:), INTENT(IN) :: py ! r.h.s. term
80 !
81 REAL, DIMENSION(:,:), INTENT(OUT) :: px ! solution of A.X = Y
82 !
83 !* 0.2 declarations of local variables
84 !
85 INTEGER :: ji ! number of point loop control
86 INTEGER :: jk ! vertical loop control
87 INTEGER :: ini ! number of point
88 INTEGER :: inl ! number of vertical levels
89 !
90 REAL, DIMENSION(SIZE(PA,1) ) :: zdet ! work array
91 REAL, DIMENSION(SIZE(PA,1),SIZE(PA,2)) :: zw ! work array
92 REAL(KIND=JPRB) :: zhook_handle
93 ! ---------------------------------------------------------------------------
94 !
95 IF (lhook) CALL dr_hook('TRIDIAG_GROUND',0,zhook_handle)
96 ini=SIZE(px,1)
97 inl=SIZE(px,2)
98 !
99 !* 1. levels going up
100 ! ---------------
101 !
102 !* 1.1 first level
103 ! -----------
104 !
105 zdet(:) = pb(:,1)
106 
107 px(:,1) = py(:,1) / zdet(:)
108 !
109 !* 1.2 other levels
110 ! ------------
111 !
112 DO jk=2,inl
113  DO ji=1,ini
114  zw(ji,jk) = pc(ji,jk-1)/zdet(ji)
115  zdet(ji) = pb(ji,jk ) - pa(ji,jk)*zw(ji,jk)
116  px(ji,jk) = ( py(ji,jk) - pa(ji,jk)*px(ji,jk-1) ) / zdet(ji)
117  END DO
118 END DO
119 !
120 !-------------------------------------------------------------------------------
121 !
122 !* 2. levels going down
123 ! -----------------
124 !
125 DO jk=inl-1,1,-1
126  DO ji=1,ini
127  px(ji,jk) = px(ji,jk) - zw(ji,jk+1)*px(ji,jk+1)
128  END DO
129 END DO
130 IF (lhook) CALL dr_hook('TRIDIAG_GROUND',1,zhook_handle)
131 !
132 !-------------------------------------------------------------------------------
133 !
134 END SUBROUTINE tridiag_ground
subroutine tridiag_ground(PA, PB, PC, PY, PX)