1DSYTRF(1)                LAPACK routine (version 3.2)                DSYTRF(1)
2
3
4

NAME

6       DSYTRF  - computes the factorization of a real symmetric matrix A using
7       the Bunch-Kaufman diagonal pivoting method
8

SYNOPSIS

10       SUBROUTINE DSYTRF( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
11
12           CHARACTER      UPLO
13
14           INTEGER        INFO, LDA, LWORK, N
15
16           INTEGER        IPIV( * )
17
18           DOUBLE         PRECISION A( LDA, * ), WORK( * )
19

PURPOSE

21       DSYTRF computes the factorization of a real symmetric  matrix  A  using
22       the Bunch-Kaufman diagonal pivoting method.  The form of the factoriza‐
23       tion is
24          A = U*D*U**T  or  A = L*D*L**T
25       where U (or L) is a product of permutation and unit upper (lower)  tri‐
26       angular matrices, and D is symmetric and block diagonal with 1-by-1 and
27       2-by-2 diagonal blocks.
28       This is the blocked version of the algorithm, calling Level 3 BLAS.
29

ARGUMENTS

31       UPLO    (input) CHARACTER*1
32               = 'U':  Upper triangle of A is stored;
33               = 'L':  Lower triangle of A is stored.
34
35       N       (input) INTEGER
36               The order of the matrix A.  N >= 0.
37
38       A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
39               On entry, the symmetric matrix A.  If UPLO = 'U',  the  leading
40               N-by-N upper triangular part of A contains the upper triangular
41               part of the matrix A, and the strictly lower triangular part of
42               A  is  not referenced.  If UPLO = 'L', the leading N-by-N lower
43               triangular part of A contains the lower triangular part of  the
44               matrix  A,  and  the strictly upper triangular part of A is not
45               referenced.  On exit, the block diagonal matrix D and the  mul‐
46               tipliers  used  to obtain the factor U or L (see below for fur‐
47               ther details).
48
49       LDA     (input) INTEGER
50               The leading dimension of the array A.  LDA >= max(1,N).
51
52       IPIV    (output) INTEGER array, dimension (N)
53               Details of the interchanges and the block structure of  D.   If
54               IPIV(k)  >  0,  then rows and columns k and IPIV(k) were inter‐
55               changed and D(k,k) is a 1-by-1 diagonal block.  If UPLO  =  'U'
56               and  IPIV(k)  =  IPIV(k-1)  <  0, then rows and columns k-1 and
57               -IPIV(k) were interchanged and D(k-1:k,k-1:k) is a 2-by-2 diag‐
58               onal  block.   If  UPLO = 'L' and IPIV(k) = IPIV(k+1) < 0, then
59               rows  and  columns  k+1  and  -IPIV(k)  were  interchanged  and
60               D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
61
62       WORK       (workspace/output)   DOUBLE   PRECISION   array,   dimension
63       (MAX(1,LWORK))
64               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
65
66       LWORK   (input) INTEGER
67               The length of WORK.  LWORK >=1.  For best performance LWORK  >=
68               N*NB,  where NB is the block size returned by ILAENV.  If LWORK
69               = -1, then a workspace query is assumed; the routine only  cal‐
70               culates  the optimal size of the WORK array, returns this value
71               as the first entry of the WORK  array,  and  no  error  message
72               related to LWORK is issued by XERBLA.
73
74       INFO    (output) INTEGER
75               = 0:  successful exit
76               < 0:  if INFO = -i, the i-th argument had an illegal value
77               >  0:   if INFO = i, D(i,i) is exactly zero.  The factorization
78               has been completed, but the block diagonal matrix D is  exactly
79               singular,  and  division  by  zero  will occur if it is used to
80               solve a system of equations.
81

FURTHER DETAILS

83       If UPLO = 'U', then A = U*D*U', where
84          U = P(n)*U(n)* ... *P(k)U(k)* ...,
85       i.e., U is a product of terms P(k)*U(k), where k decreases from n to  1
86       in  steps  of  1 or 2, and D is a block diagonal matrix with 1-by-1 and
87       2-by-2 diagonal blocks D(k).  P(k) is a permutation matrix  as  defined
88       by  IPIV(k),  and  U(k) is a unit upper triangular matrix, such that if
89       the diagonal block D(k) is of order s (s = 1 or 2), then
90                  (   I    v    0   )   k-s
91          U(k) =  (   0    I    0   )   s
92                  (   0    0    I   )   n-k
93                     k-s   s   n-k
94       If s = 1, D(k) overwrites A(k,k), and v overwrites A(1:k-1,k).  If s  =
95       2,  the  upper  triangle  of  D(k) overwrites A(k-1,k-1), A(k-1,k), and
96       A(k,k), and v overwrites A(1:k-2,k-1:k).
97       If UPLO = 'L', then A = L*D*L', where
98          L = P(1)*L(1)* ... *P(k)*L(k)* ...,
99       i.e., L is a product of terms P(k)*L(k), where k increases from 1 to  n
100       in  steps  of  1 or 2, and D is a block diagonal matrix with 1-by-1 and
101       2-by-2 diagonal blocks D(k).  P(k) is a permutation matrix  as  defined
102       by  IPIV(k),  and  L(k) is a unit lower triangular matrix, such that if
103       the diagonal block D(k) is of order s (s = 1 or 2), then
104                  (   I    0     0   )  k-1
105          L(k) =  (   0    I     0   )  s
106                  (   0    v     I   )  n-k-s+1
107                     k-1   s  n-k-s+1
108       If s = 1, D(k) overwrites A(k,k), and v overwrites A(k+1:n,k).  If s  =
109       2,  the  lower  triangle  of  D(k)  overwrites  A(k,k),  A(k+1,k),  and
110       A(k+1,k+1), and v overwrites A(k+2:n,k:k+1).
111
112
113
114 LAPACK routine (version 3.2)    November 2008                       DSYTRF(1)
Impressum