ffc79b3cf25c3744bc0c8a4cab52b9de2d7cf7c4
[platform/upstream/lapack.git] / SRC / dptsv.f
1 *> \brief <b> DPTSV computes the solution to system of linear equations A * X = B for PT matrices</b>
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at 
6 *            http://www.netlib.org/lapack/explore-html/ 
7 *
8 *> \htmlonly
9 *> Download DPTSV + dependencies 
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dptsv.f"> 
11 *> [TGZ]</a> 
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dptsv.f"> 
13 *> [ZIP]</a> 
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dptsv.f"> 
15 *> [TXT]</a>
16 *> \endhtmlonly 
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE DPTSV( 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 *> DPTSV computes the solution to a real system of linear equations
37 *> A*X = B, where A is an N-by-N symmetric positive definite tridiagonal
38 *> matrix, and X and B are N-by-NRHS matrices.
39 *>
40 *> A is factored as A = L*D*L**T, and the factored form of A is then
41 *> used to solve the system of equations.
42 *> \endverbatim
43 *
44 *  Arguments:
45 *  ==========
46 *
47 *> \param[in] N
48 *> \verbatim
49 *>          N is INTEGER
50 *>          The order of the 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,out] D
61 *> \verbatim
62 *>          D is DOUBLE PRECISION array, dimension (N)
63 *>          On entry, the n diagonal elements of the tridiagonal matrix
64 *>          A.  On exit, the n diagonal elements of the diagonal matrix
65 *>          D from the factorization A = L*D*L**T.
66 *> \endverbatim
67 *>
68 *> \param[in,out] E
69 *> \verbatim
70 *>          E is DOUBLE PRECISION array, dimension (N-1)
71 *>          On entry, the (n-1) subdiagonal elements of the tridiagonal
72 *>          matrix A.  On exit, the (n-1) subdiagonal elements of the
73 *>          unit bidiagonal factor L from the L*D*L**T factorization of
74 *>          A.  (E can also be regarded as the superdiagonal of the unit
75 *>          bidiagonal factor U from the U**T*D*U factorization of A.)
76 *> \endverbatim
77 *>
78 *> \param[in,out] B
79 *> \verbatim
80 *>          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
81 *>          On entry, the N-by-NRHS right hand side matrix B.
82 *>          On exit, if INFO = 0, the N-by-NRHS solution matrix X.
83 *> \endverbatim
84 *>
85 *> \param[in] LDB
86 *> \verbatim
87 *>          LDB is INTEGER
88 *>          The leading dimension of the array B.  LDB >= max(1,N).
89 *> \endverbatim
90 *>
91 *> \param[out] INFO
92 *> \verbatim
93 *>          INFO is INTEGER
94 *>          = 0:  successful exit
95 *>          < 0:  if INFO = -i, the i-th argument had an illegal value
96 *>          > 0:  if INFO = i, the leading minor of order i is not
97 *>                positive definite, and the solution has not been
98 *>                computed.  The factorization has not been completed
99 *>                unless i = N.
100 *> \endverbatim
101 *
102 *  Authors:
103 *  ========
104 *
105 *> \author Univ. of Tennessee 
106 *> \author Univ. of California Berkeley 
107 *> \author Univ. of Colorado Denver 
108 *> \author NAG Ltd. 
109 *
110 *> \date September 2012
111 *
112 *> \ingroup doublePTsolve
113 *
114 *  =====================================================================
115       SUBROUTINE DPTSV( N, NRHS, D, E, B, LDB, INFO )
116 *
117 *  -- LAPACK driver routine (version 3.4.2) --
118 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
119 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
120 *     September 2012
121 *
122 *     .. Scalar Arguments ..
123       INTEGER            INFO, LDB, N, NRHS
124 *     ..
125 *     .. Array Arguments ..
126       DOUBLE PRECISION   B( LDB, * ), D( * ), E( * )
127 *     ..
128 *
129 *  =====================================================================
130 *
131 *     .. External Subroutines ..
132       EXTERNAL           DPTTRF, DPTTRS, XERBLA
133 *     ..
134 *     .. Intrinsic Functions ..
135       INTRINSIC          MAX
136 *     ..
137 *     .. Executable Statements ..
138 *
139 *     Test the input parameters.
140 *
141       INFO = 0
142       IF( N.LT.0 ) THEN
143          INFO = -1
144       ELSE IF( NRHS.LT.0 ) THEN
145          INFO = -2
146       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
147          INFO = -6
148       END IF
149       IF( INFO.NE.0 ) THEN
150          CALL XERBLA( 'DPTSV ', -INFO )
151          RETURN
152       END IF
153 *
154 *     Compute the L*D*L**T (or U**T*D*U) factorization of A.
155 *
156       CALL DPTTRF( N, D, E, INFO )
157       IF( INFO.EQ.0 ) THEN
158 *
159 *        Solve the system A*X = B, overwriting B with X.
160 *
161          CALL DPTTRS( N, NRHS, D, E, B, LDB, INFO )
162       END IF
163       RETURN
164 *
165 *     End of DPTSV
166 *
167       END