001:       SUBROUTINE SORGTR( UPLO, N, A, LDA, TAU, WORK, LWORK, INFO )
002: *
003: *  -- LAPACK routine (version 3.2) --
004: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
005: *     November 2006
006: *
007: *     .. Scalar Arguments ..
008:       CHARACTER          UPLO
009:       INTEGER            INFO, LDA, LWORK, N
010: *     ..
011: *     .. Array Arguments ..
012:       REAL               A( LDA, * ), TAU( * ), WORK( * )
013: *     ..
014: *
015: *  Purpose
016: *  =======
017: *
018: *  SORGTR generates a real orthogonal matrix Q which is defined as the
019: *  product of n-1 elementary reflectors of order N, as returned by
020: *  SSYTRD:
021: *
022: *  if UPLO = 'U', Q = H(n-1) . . . H(2) H(1),
023: *
024: *  if UPLO = 'L', Q = H(1) H(2) . . . H(n-1).
025: *
026: *  Arguments
027: *  =========
028: *
029: *  UPLO    (input) CHARACTER*1
030: *          = 'U': Upper triangle of A contains elementary reflectors
031: *                 from SSYTRD;
032: *          = 'L': Lower triangle of A contains elementary reflectors
033: *                 from SSYTRD.
034: *
035: *  N       (input) INTEGER
036: *          The order of the matrix Q. N >= 0.
037: *
038: *  A       (input/output) REAL array, dimension (LDA,N)
039: *          On entry, the vectors which define the elementary reflectors,
040: *          as returned by SSYTRD.
041: *          On exit, the N-by-N orthogonal matrix Q.
042: *
043: *  LDA     (input) INTEGER
044: *          The leading dimension of the array A. LDA >= max(1,N).
045: *
046: *  TAU     (input) REAL array, dimension (N-1)
047: *          TAU(i) must contain the scalar factor of the elementary
048: *          reflector H(i), as returned by SSYTRD.
049: *
050: *  WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
051: *          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
052: *
053: *  LWORK   (input) INTEGER
054: *          The dimension of the array WORK. LWORK >= max(1,N-1).
055: *          For optimum performance LWORK >= (N-1)*NB, where NB is
056: *          the optimal blocksize.
057: *
058: *          If LWORK = -1, then a workspace query is assumed; the routine
059: *          only calculates the optimal size of the WORK array, returns
060: *          this value as the first entry of the WORK array, and no error
061: *          message related to LWORK is issued by XERBLA.
062: *
063: *  INFO    (output) INTEGER
064: *          = 0:  successful exit
065: *          < 0:  if INFO = -i, the i-th argument had an illegal value
066: *
067: *  =====================================================================
068: *
069: *     .. Parameters ..
070:       REAL               ZERO, ONE
071:       PARAMETER          ( ZERO = 0.0E+0, ONE = 1.0E+0 )
072: *     ..
073: *     .. Local Scalars ..
074:       LOGICAL            LQUERY, UPPER
075:       INTEGER            I, IINFO, J, LWKOPT, NB
076: *     ..
077: *     .. External Functions ..
078:       LOGICAL            LSAME
079:       INTEGER            ILAENV
080:       EXTERNAL           ILAENV, LSAME
081: *     ..
082: *     .. External Subroutines ..
083:       EXTERNAL           SORGQL, SORGQR, XERBLA
084: *     ..
085: *     .. Intrinsic Functions ..
086:       INTRINSIC          MAX
087: *     ..
088: *     .. Executable Statements ..
089: *
090: *     Test the input arguments
091: *
092:       INFO = 0
093:       LQUERY = ( LWORK.EQ.-1 )
094:       UPPER = LSAME( UPLO, 'U' )
095:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
096:          INFO = -1
097:       ELSE IF( N.LT.0 ) THEN
098:          INFO = -2
099:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
100:          INFO = -4
101:       ELSE IF( LWORK.LT.MAX( 1, N-1 ) .AND. .NOT.LQUERY ) THEN
102:          INFO = -7
103:       END IF
104: *
105:       IF( INFO.EQ.0 ) THEN
106:          IF ( UPPER ) THEN
107:            NB = ILAENV( 1, 'SORGQL', ' ', N-1, N-1, N-1, -1 )
108:          ELSE
109:            NB = ILAENV( 1, 'SORGQR', ' ', N-1, N-1, N-1, -1 )
110:          END IF
111:          LWKOPT = MAX( 1, N-1 )*NB
112:          WORK( 1 ) = LWKOPT
113:       END IF
114: *    
115:       IF( INFO.NE.0 ) THEN
116:          CALL XERBLA( 'SORGTR', -INFO )
117:          RETURN
118:       ELSE IF( LQUERY ) THEN
119:          RETURN
120:       END IF
121: *
122: *     Quick return if possible
123: *
124:       IF( N.EQ.0 ) THEN
125:          WORK( 1 ) = 1
126:          RETURN
127:       END IF
128: *
129:       IF( UPPER ) THEN
130: *
131: *        Q was determined by a call to SSYTRD with UPLO = 'U'
132: *
133: *        Shift the vectors which define the elementary reflectors one
134: *        column to the left, and set the last row and column of Q to
135: *        those of the unit matrix
136: *
137:          DO 20 J = 1, N - 1
138:             DO 10 I = 1, J - 1
139:                A( I, J ) = A( I, J+1 )
140:    10       CONTINUE
141:             A( N, J ) = ZERO
142:    20    CONTINUE
143:          DO 30 I = 1, N - 1
144:             A( I, N ) = ZERO
145:    30    CONTINUE
146:          A( N, N ) = ONE
147: *
148: *        Generate Q(1:n-1,1:n-1)
149: *
150:          CALL SORGQL( N-1, N-1, N-1, A, LDA, TAU, WORK, LWORK, IINFO )
151: *
152:       ELSE
153: *
154: *        Q was determined by a call to SSYTRD with UPLO = 'L'.
155: *
156: *        Shift the vectors which define the elementary reflectors one
157: *        column to the right, and set the first row and column of Q to
158: *        those of the unit matrix
159: *
160:          DO 50 J = N, 2, -1
161:             A( 1, J ) = ZERO
162:             DO 40 I = J + 1, N
163:                A( I, J ) = A( I, J-1 )
164:    40       CONTINUE
165:    50    CONTINUE
166:          A( 1, 1 ) = ONE
167:          DO 60 I = 2, N
168:             A( I, 1 ) = ZERO
169:    60    CONTINUE
170:          IF( N.GT.1 ) THEN
171: *
172: *           Generate Q(2:n,2:n)
173: *
174:             CALL SORGQR( N-1, N-1, N-1, A( 2, 2 ), LDA, TAU, WORK,
175:      $                   LWORK, IINFO )
176:          END IF
177:       END IF
178:       WORK( 1 ) = LWKOPT
179:       RETURN
180: *
181: *     End of SORGTR
182: *
183:       END
184: