* -- LAPACK driver routine (version 3.3.0) --
* -- LAPACK is a software package provided by Univ. of Tennessee, --
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
-* November 2010
+* February 2011
+* @generated c
*
* .. Scalar Arguments ..
CHARACTER UPLO
* A = U * D * U**H, if UPLO = 'U', or
* A = L * D * L**H, if UPLO = 'L',
* where U (or L) is a product of permutation and unit upper (lower)
-* triangular matrices, and D is Hermitian and block diagonal with
+* triangular matrices, and D is Hermitian and block diagonal with
* 1-by-1 and 2-by-2 diagonal blocks. The factored form of A is then
* used to solve the system of equations A * X = B.
*
* The length of WORK. LWORK >= 1, and for best performance
* LWORK >= max(1,N*NB), where NB is the optimal blocksize for
* CHETRF.
+* for LWORK < N, TRS will be done with Level BLAS 2
+* for LWORK >= N, TRS will be done with Level BLAS 3
*
* If LWORK = -1, then a workspace query is assumed; the routine
* only calculates the optimal size of the WORK array, returns
* .. External Functions ..
LOGICAL LSAME
INTEGER ILAENV
- EXTERNAL ILAENV, LSAME
+ EXTERNAL LSAME, ILAENV
* ..
* .. External Subroutines ..
- EXTERNAL CHETRF, CHETRS2, XERBLA
+ EXTERNAL XERBLA, CHETRF, ZHETRS, CHETRS2
* ..
* .. Intrinsic Functions ..
INTRINSIC MAX
*
* Solve the system A*X = B, overwriting B with X.
*
- CALL CHETRS2( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, INFO )
+ IF ( LWORK.LT.N ) THEN
+*
+* Solve with TRS ( Use Level BLAS 2)
+*
+ CALL ZHETRS( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
+*
+ ELSE
+*
+* Solve with TRS2 ( Use Level BLAS 3)
+*
+ CALL CHETRS2( UPLO,N,NRHS,A,LDA,IPIV,B,LDB,WORK,INFO )
+*
+ END IF
*
END IF
*
SUBROUTINE CSYSV( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
$ LWORK, INFO )
*
-* -- LAPACK driver routine (version 3.2.2) --
+* -- LAPACK driver routine (version 3.3.0) --
* -- LAPACK is a software package provided by Univ. of Tennessee, --
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
-* June 2010
+* February 2011
+* @generated c
*
* .. Scalar Arguments ..
CHARACTER UPLO
* A = U * D * U**T, if UPLO = 'U', or
* A = L * D * L**T, if UPLO = 'L',
* where U (or L) is a product of permutation and unit upper (lower)
-* triangular matrices, and D is symmetric and block diagonal with
+* triangular matrices, and D is symmetric and block diagonal with
* 1-by-1 and 2-by-2 diagonal blocks. The factored form of A is then
* used to solve the system of equations A * X = B.
*
* The length of WORK. LWORK >= 1, and for best performance
* LWORK >= max(1,N*NB), where NB is the optimal blocksize for
* CSYTRF.
+* for LWORK < N, TRS will be done with Level BLAS 2
+* for LWORK >= N, TRS will be done with Level BLAS 3
*
* If LWORK = -1, then a workspace query is assumed; the routine
* only calculates the optimal size of the WORK array, returns
* .. External Functions ..
LOGICAL LSAME
INTEGER ILAENV
- EXTERNAL ILAENV, LSAME
+ EXTERNAL LSAME, ILAENV
* ..
* .. External Subroutines ..
- EXTERNAL CSYTRF, CSYTRS2, XERBLA
+ EXTERNAL XERBLA, CSYTRF, CSYTRS, CSYTRS2
* ..
* .. Intrinsic Functions ..
INTRINSIC MAX
*
* Solve the system A*X = B, overwriting B with X.
*
- CALL CSYTRS2( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, INFO )
+ IF ( LWORK.LT.N ) THEN
+*
+* Solve with TRS ( Use Level BLAS 2)
+*
+ CALL CSYTRS( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
+*
+ ELSE
+*
+* Solve with TRS2 ( Use Level BLAS 3)
+*
+ CALL CSYTRS2( UPLO,N,NRHS,A,LDA,IPIV,B,LDB,WORK,INFO )
+*
+ END IF
*
END IF
*
SUBROUTINE DSYSV( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
$ LWORK, INFO )
*
-* -- LAPACK driver routine (version 3.2.2) --
+* -- LAPACK driver routine (version 3.3.0) --
* -- LAPACK is a software package provided by Univ. of Tennessee, --
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
-* May 2010
+* February 2011
+* @generated d
*
* .. Scalar Arguments ..
CHARACTER UPLO
* The length of WORK. LWORK >= 1, and for best performance
* LWORK >= max(1,N*NB), where NB is the optimal blocksize for
* DSYTRF.
+* for LWORK < N, TRS will be done with Level BLAS 2
+* for LWORK >= N, TRS will be done with Level BLAS 3
*
* If LWORK = -1, then a workspace query is assumed; the routine
* only calculates the optimal size of the WORK array, returns
EXTERNAL LSAME, ILAENV
* ..
* .. External Subroutines ..
- EXTERNAL DSYTRF, DSYTRS2, XERBLA
+ EXTERNAL XERBLA, DSYTRF, DSYTRS, DSYTRS2
* ..
* .. Intrinsic Functions ..
INTRINSIC MAX
CALL DSYTRF( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
IF( INFO.EQ.0 ) THEN
*
-* Solve the system A*X = B, overwriting B with X.
+* Solve the system A*X = B, overwriting B with X.
*
- CALL DSYTRS2( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, INFO )
+ IF ( LWORK.LT.N ) THEN
+*
+* Solve with TRS ( Use Level BLAS 2)
+*
+ CALL DSYTRS( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
+*
+ ELSE
+*
+* Solve with TRS2 ( Use Level BLAS 3)
+*
+ CALL DSYTRS2( UPLO,N,NRHS,A,LDA,IPIV,B,LDB,WORK,INFO )
+*
+ END IF
*
END IF
*
SUBROUTINE SSYSV( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
$ LWORK, INFO )
*
-* -- LAPACK driver routine (version 3.2.2) --
+* -- LAPACK driver routine (version 3.3.0) --
* -- LAPACK is a software package provided by Univ. of Tennessee, --
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
-* May 2010
+* February 2011
+* @generated s
*
* .. Scalar Arguments ..
CHARACTER UPLO
* A = U * D * U**T, if UPLO = 'U', or
* A = L * D * L**T, if UPLO = 'L',
* where U (or L) is a product of permutation and unit upper (lower)
-* triangular matrices, and D is symmetric and block diagonal with
+* triangular matrices, and D is symmetric and block diagonal with
* 1-by-1 and 2-by-2 diagonal blocks. The factored form of A is then
* used to solve the system of equations A * X = B.
*
* The length of WORK. LWORK >= 1, and for best performance
* LWORK >= max(1,N*NB), where NB is the optimal blocksize for
* SSYTRF.
+* for LWORK < N, TRS will be done with Level BLAS 2
+* for LWORK >= N, TRS will be done with Level BLAS 3
*
* If LWORK = -1, then a workspace query is assumed; the routine
* only calculates the optimal size of the WORK array, returns
* .. External Functions ..
LOGICAL LSAME
INTEGER ILAENV
- EXTERNAL ILAENV, LSAME
+ EXTERNAL LSAME, ILAENV
* ..
* .. External Subroutines ..
- EXTERNAL SSYTRF, SSYTRS2, XERBLA
+ EXTERNAL XERBLA, SSYTRF, SSYTRS, SSYTRS2
* ..
* .. Intrinsic Functions ..
INTRINSIC MAX
*
* Solve the system A*X = B, overwriting B with X.
*
- CALL SSYTRS2( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, INFO )
+ IF ( LWORK.LT.N ) THEN
+*
+* Solve with TRS ( Use Level BLAS 2)
+*
+ CALL SSYTRS( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
+*
+ ELSE
+*
+* Solve with TRS2 ( Use Level BLAS 3)
+*
+ CALL SSYTRS2( UPLO,N,NRHS,A,LDA,IPIV,B,LDB,WORK,INFO )
+*
+ END IF
*
END IF
*
* -- LAPACK driver routine (version 3.3.0) --
* -- LAPACK is a software package provided by Univ. of Tennessee, --
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
-* November 2010
+* February 2011
+* @precisions normal z -> c
*
* .. Scalar Arguments ..
CHARACTER UPLO
* The length of WORK. LWORK >= 1, and for best performance
* LWORK >= max(1,N*NB), where NB is the optimal blocksize for
* ZHETRF.
+* for LWORK < N, TRS will be done with Level BLAS 2
+* for LWORK >= N, TRS will be done with Level BLAS 3
*
* If LWORK = -1, then a workspace query is assumed; the routine
* only calculates the optimal size of the WORK array, returns
EXTERNAL LSAME, ILAENV
* ..
* .. External Subroutines ..
- EXTERNAL XERBLA, ZHETRF, ZHETRS2
+ EXTERNAL XERBLA, ZHETRF, ZHETRS, ZHETRS2
* ..
* .. Intrinsic Functions ..
INTRINSIC MAX
*
* Solve the system A*X = B, overwriting B with X.
*
- CALL ZHETRS2( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, INFO )
+ IF ( LWORK.LT.N ) THEN
+*
+* Solve with TRS ( Use Level BLAS 2)
+*
+ CALL ZHETRS( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
+*
+ ELSE
+*
+* Solve with TRS2 ( Use Level BLAS 3)
+*
+ CALL ZHETRS2( UPLO,N,NRHS,A,LDA,IPIV,B,LDB,WORK,INFO )
+*
+ END IF
*
END IF
*
SUBROUTINE ZSYSV( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
$ LWORK, INFO )
*
-* -- LAPACK driver routine (version 3.2.2) --
+* -- LAPACK driver routine (version 3.3.0) --
* -- LAPACK is a software package provided by Univ. of Tennessee, --
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
-* June 2010
+* February 2011
+* @precisions normal z -> s d c
*
* .. Scalar Arguments ..
CHARACTER UPLO
* The length of WORK. LWORK >= 1, and for best performance
* LWORK >= max(1,N*NB), where NB is the optimal blocksize for
* ZSYTRF.
+* for LWORK < N, TRS will be done with Level BLAS 2
+* for LWORK >= N, TRS will be done with Level BLAS 3
*
* If LWORK = -1, then a workspace query is assumed; the routine
* only calculates the optimal size of the WORK array, returns
EXTERNAL LSAME, ILAENV
* ..
* .. External Subroutines ..
- EXTERNAL XERBLA, ZSYTRF, ZSYTRS2
+ EXTERNAL XERBLA, ZSYTRF, ZSYTRS, ZSYTRS2
* ..
* .. Intrinsic Functions ..
INTRINSIC MAX
*
* Solve the system A*X = B, overwriting B with X.
*
- CALL ZSYTRS2( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, INFO )
+ IF ( LWORK.LT.N ) THEN
+*
+* Solve with TRS ( Use Level BLAS 2)
+*
+ CALL ZSYTRS( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
+*
+ ELSE
+*
+* Solve with TRS2 ( Use Level BLAS 3)
+*
+ CALL ZSYTRS2( UPLO,N,NRHS,A,LDA,IPIV,B,LDB,WORK,INFO )
+*
+ END IF
*
END IF
*