STYLE: Remove trailing whitespace in Fortran files
[platform/upstream/lapack.git] / SRC / dpttrs.f
1 *> \brief \b DPTTRS
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DPTTRS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dpttrs.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dpttrs.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dpttrs.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE DPTTRS( N, NRHS, D, E, B, LDB, INFO )
22 *
23 *       .. Scalar Arguments ..
24 *       INTEGER            INFO, LDB, N, NRHS
25 *       ..
26 *       .. Array Arguments ..
27 *       DOUBLE PRECISION   B( LDB, * ), D( * ), E( * )
28 *       ..
29 *
30 *
31 *> \par Purpose:
32 *  =============
33 *>
34 *> \verbatim
35 *>
36 *> DPTTRS solves a tridiagonal system of the form
37 *>    A * X = B
38 *> using the L*D*L**T factorization of A computed by DPTTRF.  D is a
39 *> diagonal matrix specified in the vector D, L is a unit bidiagonal
40 *> matrix whose subdiagonal is specified in the vector E, and X and B
41 *> are N by NRHS matrices.
42 *> \endverbatim
43 *
44 *  Arguments:
45 *  ==========
46 *
47 *> \param[in] N
48 *> \verbatim
49 *>          N is INTEGER
50 *>          The order of the tridiagonal matrix A.  N >= 0.
51 *> \endverbatim
52 *>
53 *> \param[in] NRHS
54 *> \verbatim
55 *>          NRHS is INTEGER
56 *>          The number of right hand sides, i.e., the number of columns
57 *>          of the matrix B.  NRHS >= 0.
58 *> \endverbatim
59 *>
60 *> \param[in] D
61 *> \verbatim
62 *>          D is DOUBLE PRECISION array, dimension (N)
63 *>          The n diagonal elements of the diagonal matrix D from the
64 *>          L*D*L**T factorization of A.
65 *> \endverbatim
66 *>
67 *> \param[in] E
68 *> \verbatim
69 *>          E is DOUBLE PRECISION array, dimension (N-1)
70 *>          The (n-1) subdiagonal elements of the unit bidiagonal factor
71 *>          L from the L*D*L**T factorization of A.  E can also be regarded
72 *>          as the superdiagonal of the unit bidiagonal factor U from the
73 *>          factorization A = U**T*D*U.
74 *> \endverbatim
75 *>
76 *> \param[in,out] B
77 *> \verbatim
78 *>          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
79 *>          On entry, the right hand side vectors B for the system of
80 *>          linear equations.
81 *>          On exit, the solution vectors, X.
82 *> \endverbatim
83 *>
84 *> \param[in] LDB
85 *> \verbatim
86 *>          LDB is INTEGER
87 *>          The leading dimension of the array B.  LDB >= max(1,N).
88 *> \endverbatim
89 *>
90 *> \param[out] INFO
91 *> \verbatim
92 *>          INFO is INTEGER
93 *>          = 0: successful exit
94 *>          < 0: if INFO = -k, the k-th argument had an illegal value
95 *> \endverbatim
96 *
97 *  Authors:
98 *  ========
99 *
100 *> \author Univ. of Tennessee
101 *> \author Univ. of California Berkeley
102 *> \author Univ. of Colorado Denver
103 *> \author NAG Ltd.
104 *
105 *> \date September 2012
106 *
107 *> \ingroup doublePTcomputational
108 *
109 *  =====================================================================
110       SUBROUTINE DPTTRS( N, NRHS, D, E, B, LDB, INFO )
111 *
112 *  -- LAPACK computational routine (version 3.4.2) --
113 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
114 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
115 *     September 2012
116 *
117 *     .. Scalar Arguments ..
118       INTEGER            INFO, LDB, N, NRHS
119 *     ..
120 *     .. Array Arguments ..
121       DOUBLE PRECISION   B( LDB, * ), D( * ), E( * )
122 *     ..
123 *
124 *  =====================================================================
125 *
126 *     .. Local Scalars ..
127       INTEGER            J, JB, NB
128 *     ..
129 *     .. External Functions ..
130       INTEGER            ILAENV
131       EXTERNAL           ILAENV
132 *     ..
133 *     .. External Subroutines ..
134       EXTERNAL           DPTTS2, XERBLA
135 *     ..
136 *     .. Intrinsic Functions ..
137       INTRINSIC          MAX, MIN
138 *     ..
139 *     .. Executable Statements ..
140 *
141 *     Test the input arguments.
142 *
143       INFO = 0
144       IF( N.LT.0 ) THEN
145          INFO = -1
146       ELSE IF( NRHS.LT.0 ) THEN
147          INFO = -2
148       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
149          INFO = -6
150       END IF
151       IF( INFO.NE.0 ) THEN
152          CALL XERBLA( 'DPTTRS', -INFO )
153          RETURN
154       END IF
155 *
156 *     Quick return if possible
157 *
158       IF( N.EQ.0 .OR. NRHS.EQ.0 )
159      $   RETURN
160 *
161 *     Determine the number of right-hand sides to solve at a time.
162 *
163       IF( NRHS.EQ.1 ) THEN
164          NB = 1
165       ELSE
166          NB = MAX( 1, ILAENV( 1, 'DPTTRS', ' ', N, NRHS, -1, -1 ) )
167       END IF
168 *
169       IF( NB.GE.NRHS ) THEN
170          CALL DPTTS2( N, NRHS, D, E, B, LDB )
171       ELSE
172          DO 10 J = 1, NRHS, NB
173             JB = MIN( NRHS-J+1, NB )
174             CALL DPTTS2( N, JB, D, E, B( 1, J ), LDB )
175    10    CONTINUE
176       END IF
177 *
178       RETURN
179 *
180 *     End of DPTTRS
181 *
182       END