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

NAME

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

SYNOPSIS

10       SUBROUTINE SSYTRF( 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           REAL           A( LDA, * ), WORK( * )
19

PURPOSE

21       SSYTRF 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) REAL 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) REAL array, dimension (MAX(1,LWORK))
63               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
64
65       LWORK   (input) INTEGER
66               The  length of WORK.  LWORK >=1.  For best performance LWORK >=
67               N*NB, where NB is the block size returned by ILAENV.  If  LWORK
68               =  -1, then a workspace query is assumed; the routine only cal‐
69               culates the optimal size of the WORK array, returns this  value
70               as  the  first  entry  of  the WORK array, and no error message
71               related to LWORK is issued by XERBLA.
72
73       INFO    (output) INTEGER
74               = 0:  successful exit
75               < 0:  if INFO = -i, the i-th argument had an illegal value
76               > 0:  if INFO = i, D(i,i) is exactly zero.   The  factorization
77               has  been completed, but the block diagonal matrix D is exactly
78               singular, and division by zero will occur  if  it  is  used  to
79               solve a system of equations.
80

FURTHER DETAILS

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