diff --git a/src/msspec/spec/fortran/phd_ce_noso_nosp_nosym/lapack_axb.f b/src/msspec/spec/fortran/phd_ce_noso_nosp_nosym/lapack_axb.f
new file mode 100644
index 0000000..8019303
--- /dev/null
+++ b/src/msspec/spec/fortran/phd_ce_noso_nosp_nosym/lapack_axb.f
@@ -0,0 +1,5123 @@
+C
+C=======================================================================
+C
+C LAPACK Ax=b subroutines
+C
+C=======================================================================
+C
+C (version 3.6.1) June 2016
+C
+C=======================================================================
+C
+*> \brief \b ZGETRS
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+*> \htmlonly
+*> Download ZGETRS + dependencies
+*>
+*> [TGZ]
+*>
+*> [ZIP]
+*>
+*> [TXT]
+*> \endhtmlonly
+*
+* Definition:
+* ===========
+*
+* SUBROUTINE ZGETRS( TRANS, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
+*
+* .. Scalar Arguments ..
+* CHARACTER TRANS
+* INTEGER INFO, LDA, LDB, N, NRHS
+* ..
+* .. Array Arguments ..
+* INTEGER IPIV( * )
+* COMPLEX*16 A( LDA, * ), B( LDB, * )
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ZGETRS solves a system of linear equations
+*> A * X = B, A**T * X = B, or A**H * X = B
+*> with a general N-by-N matrix A using the LU factorization computed
+*> by ZGETRF.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] TRANS
+*> \verbatim
+*> TRANS is CHARACTER*1
+*> Specifies the form of the system of equations:
+*> = 'N': A * X = B (No transpose)
+*> = 'T': A**T * X = B (Transpose)
+*> = 'C': A**H * X = B (Conjugate transpose)
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The order of the matrix A. N >= 0.
+*> \endverbatim
+*>
+*> \param[in] NRHS
+*> \verbatim
+*> NRHS is INTEGER
+*> The number of right hand sides, i.e., the number of columns
+*> of the matrix B. NRHS >= 0.
+*> \endverbatim
+*>
+*> \param[in] A
+*> \verbatim
+*> A is COMPLEX*16 array, dimension (LDA,N)
+*> The factors L and U from the factorization A = P*L*U
+*> as computed by ZGETRF.
+*> \endverbatim
+*>
+*> \param[in] LDA
+*> \verbatim
+*> LDA is INTEGER
+*> The leading dimension of the array A. LDA >= max(1,N).
+*> \endverbatim
+*>
+*> \param[in] IPIV
+*> \verbatim
+*> IPIV is INTEGER array, dimension (N)
+*> The pivot indices from ZGETRF; for 1<=i<=N, row i of the
+*> matrix was interchanged with row IPIV(i).
+*> \endverbatim
+*>
+*> \param[in,out] B
+*> \verbatim
+*> B is COMPLEX*16 array, dimension (LDB,NRHS)
+*> On entry, the right hand side matrix B.
+*> On exit, the solution matrix X.
+*> \endverbatim
+*>
+*> \param[in] LDB
+*> \verbatim
+*> LDB is INTEGER
+*> The leading dimension of the array B. LDB >= max(1,N).
+*> \endverbatim
+*>
+*> \param[out] INFO
+*> \verbatim
+*> INFO is INTEGER
+*> = 0: successful exit
+*> < 0: if INFO = -i, the i-th argument had an illegal value
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup complex16GEcomputational
+*
+* =====================================================================
+ SUBROUTINE ZGETRS( TRANS, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
+*
+* -- LAPACK computational routine (version 3.4.0) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2011
+*
+* .. Scalar Arguments ..
+ CHARACTER TRANS
+ INTEGER INFO, LDA, LDB, N, NRHS
+* ..
+* .. Array Arguments ..
+ INTEGER IPIV( * )
+ COMPLEX*16 A( LDA, * ), B( LDB, * )
+* ..
+*
+* =====================================================================
+*
+* .. Parameters ..
+ COMPLEX*16 ONE
+ PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ) )
+* ..
+* .. Local Scalars ..
+ LOGICAL NOTRAN
+* ..
+* .. External Functions ..
+ LOGICAL LSAME
+ EXTERNAL LSAME
+* ..
+* .. External Subroutines ..
+ EXTERNAL XERBLA, ZLASWP, ZTRSM
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC MAX
+* ..
+* .. Executable Statements ..
+*
+* Test the input parameters.
+*
+ INFO = 0
+ NOTRAN = LSAME( TRANS, 'N' )
+ IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'T' ) .AND. .NOT.
+ $ LSAME( TRANS, 'C' ) ) THEN
+ INFO = -1
+ ELSE IF( N.LT.0 ) THEN
+ INFO = -2
+ ELSE IF( NRHS.LT.0 ) THEN
+ INFO = -3
+ ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
+ INFO = -5
+ ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
+ INFO = -8
+ END IF
+ IF( INFO.NE.0 ) THEN
+ CALL XERBLA( 'ZGETRS', -INFO )
+ RETURN
+ END IF
+*
+* Quick return if possible
+*
+ IF( N.EQ.0 .OR. NRHS.EQ.0 )
+ $ RETURN
+*
+ IF( NOTRAN ) THEN
+*
+* Solve A * X = B.
+*
+* Apply row interchanges to the right hand sides.
+*
+ CALL ZLASWP( NRHS, B, LDB, 1, N, IPIV, 1 )
+*
+* Solve L*X = B, overwriting B with X.
+*
+ CALL ZTRSM( 'Left', 'Lower', 'No transpose', 'Unit', N, NRHS,
+ $ ONE, A, LDA, B, LDB )
+*
+* Solve U*X = B, overwriting B with X.
+*
+ CALL ZTRSM( 'Left', 'Upper', 'No transpose', 'Non-unit', N,
+ $ NRHS, ONE, A, LDA, B, LDB )
+ ELSE
+*
+* Solve A**T * X = B or A**H * X = B.
+*
+* Solve U**T *X = B or U**H *X = B, overwriting B with X.
+*
+ CALL ZTRSM( 'Left', 'Upper', TRANS, 'Non-unit', N, NRHS, ONE,
+ $ A, LDA, B, LDB )
+*
+* Solve L**T *X = B, or L**H *X = B overwriting B with X.
+*
+ CALL ZTRSM( 'Left', 'Lower', TRANS, 'Unit', N, NRHS, ONE, A,
+ $ LDA, B, LDB )
+*
+* Apply row interchanges to the solution vectors.
+*
+ CALL ZLASWP( NRHS, B, LDB, 1, N, IPIV, -1 )
+ END IF
+*
+ RETURN
+*
+* End of ZGETRS
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b IEEECK
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+*> \htmlonly
+*> Download IEEECK + dependencies
+*>
+*> [TGZ]
+*>
+*> [ZIP]
+*>
+*> [TXT]
+*> \endhtmlonly
+*
+* Definition:
+* ===========
+*
+* INTEGER FUNCTION IEEECK( ISPEC, ZERO, ONE )
+*
+* .. Scalar Arguments ..
+* INTEGER ISPEC
+* REAL ONE, ZERO
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> IEEECK is called from the ILAENV to verify that Infinity and
+*> possibly NaN arithmetic is safe (i.e. will not trap).
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] ISPEC
+*> \verbatim
+*> ISPEC is INTEGER
+*> Specifies whether to test just for inifinity arithmetic
+*> or whether to test for infinity and NaN arithmetic.
+*> = 0: Verify infinity arithmetic only.
+*> = 1: Verify infinity and NaN arithmetic.
+*> \endverbatim
+*>
+*> \param[in] ZERO
+*> \verbatim
+*> ZERO is REAL
+*> Must contain the value 0.0
+*> This is passed to prevent the compiler from optimizing
+*> away this code.
+*> \endverbatim
+*>
+*> \param[in] ONE
+*> \verbatim
+*> ONE is REAL
+*> Must contain the value 1.0
+*> This is passed to prevent the compiler from optimizing
+*> away this code.
+*>
+*> RETURN VALUE: INTEGER
+*> = 0: Arithmetic failed to produce the correct answers
+*> = 1: Arithmetic produced the correct answers
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup auxOTHERauxiliary
+*
+* =====================================================================
+ INTEGER FUNCTION IEEECK( ISPEC, ZERO, ONE )
+*
+* -- LAPACK auxiliary routine (version 3.4.0) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2011
+*
+* .. Scalar Arguments ..
+ INTEGER ISPEC
+ REAL ONE, ZERO
+* ..
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ REAL NAN1, NAN2, NAN3, NAN4, NAN5, NAN6, NEGINF,
+ $ NEGZRO, NEWZRO, POSINF
+* ..
+* .. Executable Statements ..
+ IEEECK = 1
+*
+ POSINF = ONE / ZERO
+ IF( POSINF.LE.ONE ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ NEGINF = -ONE / ZERO
+ IF( NEGINF.GE.ZERO ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ NEGZRO = ONE / ( NEGINF+ONE )
+ IF( NEGZRO.NE.ZERO ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ NEGINF = ONE / NEGZRO
+ IF( NEGINF.GE.ZERO ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ NEWZRO = NEGZRO + ZERO
+ IF( NEWZRO.NE.ZERO ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ POSINF = ONE / NEWZRO
+ IF( POSINF.LE.ONE ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ NEGINF = NEGINF*POSINF
+ IF( NEGINF.GE.ZERO ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ POSINF = POSINF*POSINF
+ IF( POSINF.LE.ONE ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+*
+*
+*
+* Return if we were only asked to check infinity arithmetic
+*
+ IF( ISPEC.EQ.0 )
+ $ RETURN
+*
+ NAN1 = POSINF + NEGINF
+*
+ NAN2 = POSINF / NEGINF
+*
+ NAN3 = POSINF / POSINF
+*
+ NAN4 = POSINF*ZERO
+*
+ NAN5 = NEGINF*NEGZRO
+*
+ NAN6 = NAN5*ZERO
+*
+ IF( NAN1.EQ.NAN1 ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ IF( NAN2.EQ.NAN2 ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ IF( NAN3.EQ.NAN3 ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ IF( NAN4.EQ.NAN4 ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ IF( NAN5.EQ.NAN5 ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ IF( NAN6.EQ.NAN6 ) THEN
+ IEEECK = 0
+ RETURN
+ END IF
+*
+ RETURN
+ END
+C
+C======================================================================
+C
+*> \brief \b ILAENV
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+*> \htmlonly
+*> Download ILAENV + dependencies
+*>
+*> [TGZ]
+*>
+*> [ZIP]
+*>
+*> [TXT]
+*> \endhtmlonly
+*
+* Definition:
+* ===========
+*
+* INTEGER FUNCTION ILAENV( ISPEC, NAME, OPTS, N1, N2, N3, N4 )
+*
+* .. Scalar Arguments ..
+* CHARACTER*( * ) NAME, OPTS
+* INTEGER ISPEC, N1, N2, N3, N4
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ILAENV is called from the LAPACK routines to choose problem-dependent
+*> parameters for the local environment. See ISPEC for a description of
+*> the parameters.
+*>
+*> ILAENV returns an INTEGER
+*> if ILAENV >= 0: ILAENV returns the value of the parameter specified by ISPEC
+*> if ILAENV < 0: if ILAENV = -k, the k-th argument had an illegal value.
+*>
+*> This version provides a set of parameters which should give good,
+*> but not optimal, performance on many of the currently available
+*> computers. Users are encouraged to modify this subroutine to set
+*> the tuning parameters for their particular machine using the option
+*> and problem size information in the arguments.
+*>
+*> This routine will not function correctly if it is converted to all
+*> lower case. Converting it to all upper case is allowed.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] ISPEC
+*> \verbatim
+*> ISPEC is INTEGER
+*> Specifies the parameter to be returned as the value of
+*> ILAENV.
+*> = 1: the optimal blocksize; if this value is 1, an unblocked
+*> algorithm will give the best performance.
+*> = 2: the minimum block size for which the block routine
+*> should be used; if the usable block size is less than
+*> this value, an unblocked routine should be used.
+*> = 3: the crossover point (in a block routine, for N less
+*> than this value, an unblocked routine should be used)
+*> = 4: the number of shifts, used in the nonsymmetric
+*> eigenvalue routines (DEPRECATED)
+*> = 5: the minimum column dimension for blocking to be used;
+*> rectangular blocks must have dimension at least k by m,
+*> where k is given by ILAENV(2,...) and m by ILAENV(5,...)
+*> = 6: the crossover point for the SVD (when reducing an m by n
+*> matrix to bidiagonal form, if max(m,n)/min(m,n) exceeds
+*> this value, a QR factorization is used first to reduce
+*> the matrix to a triangular form.)
+*> = 7: the number of processors
+*> = 8: the crossover point for the multishift QR method
+*> for nonsymmetric eigenvalue problems (DEPRECATED)
+*> = 9: maximum size of the subproblems at the bottom of the
+*> computation tree in the divide-and-conquer algorithm
+*> (used by xGELSD and xGESDD)
+*> =10: ieee NaN arithmetic can be trusted not to trap
+*> =11: infinity arithmetic can be trusted not to trap
+*> 12 <= ISPEC <= 16:
+*> xHSEQR or related subroutines,
+*> see IPARMQ for detailed explanation
+*> \endverbatim
+*>
+*> \param[in] NAME
+*> \verbatim
+*> NAME is CHARACTER*(*)
+*> The name of the calling subroutine, in either upper case or
+*> lower case.
+*> \endverbatim
+*>
+*> \param[in] OPTS
+*> \verbatim
+*> OPTS is CHARACTER*(*)
+*> The character options to the subroutine NAME, concatenated
+*> into a single character string. For example, UPLO = 'U',
+*> TRANS = 'T', and DIAG = 'N' for a triangular routine would
+*> be specified as OPTS = 'UTN'.
+*> \endverbatim
+*>
+*> \param[in] N1
+*> \verbatim
+*> N1 is INTEGER
+*> \endverbatim
+*>
+*> \param[in] N2
+*> \verbatim
+*> N2 is INTEGER
+*> \endverbatim
+*>
+*> \param[in] N3
+*> \verbatim
+*> N3 is INTEGER
+*> \endverbatim
+*>
+*> \param[in] N4
+*> \verbatim
+*> N4 is INTEGER
+*> Problem dimensions for the subroutine NAME; these may not all
+*> be required.
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date June 2016
+*
+*> \ingroup auxOTHERauxiliary
+*
+*> \par Further Details:
+* =====================
+*>
+*> \verbatim
+*>
+*> The following conventions have been used when calling ILAENV from the
+*> LAPACK routines:
+*> 1) OPTS is a concatenation of all of the character options to
+*> subroutine NAME, in the same order that they appear in the
+*> argument list for NAME, even if they are not used in determining
+*> the value of the parameter specified by ISPEC.
+*> 2) The problem dimensions N1, N2, N3, N4 are specified in the order
+*> that they appear in the argument list for NAME. N1 is used
+*> first, N2 second, and so on, and unused problem dimensions are
+*> passed a value of -1.
+*> 3) The parameter value returned by ILAENV is checked for validity in
+*> the calling subroutine. For example, ILAENV is used to retrieve
+*> the optimal blocksize for STRTRI as follows:
+*>
+*> NB = ILAENV( 1, 'STRTRI', UPLO // DIAG, N, -1, -1, -1 )
+*> IF( NB.LE.1 ) NB = MAX( 1, N )
+*> \endverbatim
+*>
+* =====================================================================
+ INTEGER FUNCTION ILAENV( ISPEC, NAME, OPTS, N1, N2, N3, N4 )
+*
+* -- LAPACK auxiliary routine (version 3.6.1) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* June 2016
+*
+* .. Scalar Arguments ..
+ CHARACTER*( * ) NAME, OPTS
+ INTEGER ISPEC, N1, N2, N3, N4
+* ..
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ INTEGER I, IC, IZ, NB, NBMIN, NX
+ LOGICAL CNAME, SNAME
+ CHARACTER C1*1, C2*2, C4*2, C3*3, SUBNAM*6
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC CHAR, ICHAR, INT, MIN, REAL
+* ..
+* .. External Functions ..
+ INTEGER IEEECK, IPARMQ
+ EXTERNAL IEEECK, IPARMQ
+* ..
+* .. Executable Statements ..
+*
+ GO TO ( 10, 10, 10, 80, 90, 100, 110, 120,
+ $ 130, 140, 150, 160, 160, 160, 160, 160 )ISPEC
+*
+* Invalid value for ISPEC
+*
+ ILAENV = -1
+ RETURN
+*
+ 10 CONTINUE
+*
+* Convert NAME to upper case if the first character is lower case.
+*
+ ILAENV = 1
+ SUBNAM = NAME
+ IC = ICHAR( SUBNAM( 1: 1 ) )
+ IZ = ICHAR( 'Z' )
+ IF( IZ.EQ.90 .OR. IZ.EQ.122 ) THEN
+*
+* ASCII character set
+*
+ IF( IC.GE.97 .AND. IC.LE.122 ) THEN
+ SUBNAM( 1: 1 ) = CHAR( IC-32 )
+ DO 20 I = 2, 6
+ IC = ICHAR( SUBNAM( I: I ) )
+ IF( IC.GE.97 .AND. IC.LE.122 )
+ $ SUBNAM( I: I ) = CHAR( IC-32 )
+ 20 CONTINUE
+ END IF
+*
+ ELSE IF( IZ.EQ.233 .OR. IZ.EQ.169 ) THEN
+*
+* EBCDIC character set
+*
+ IF( ( IC.GE.129 .AND. IC.LE.137 ) .OR.
+ $ ( IC.GE.145 .AND. IC.LE.153 ) .OR.
+ $ ( IC.GE.162 .AND. IC.LE.169 ) ) THEN
+ SUBNAM( 1: 1 ) = CHAR( IC+64 )
+ DO 30 I = 2, 6
+ IC = ICHAR( SUBNAM( I: I ) )
+ IF( ( IC.GE.129 .AND. IC.LE.137 ) .OR.
+ $ ( IC.GE.145 .AND. IC.LE.153 ) .OR.
+ $ ( IC.GE.162 .AND. IC.LE.169 ) )SUBNAM( I:
+ $ I ) = CHAR( IC+64 )
+ 30 CONTINUE
+ END IF
+*
+ ELSE IF( IZ.EQ.218 .OR. IZ.EQ.250 ) THEN
+*
+* Prime machines: ASCII+128
+*
+ IF( IC.GE.225 .AND. IC.LE.250 ) THEN
+ SUBNAM( 1: 1 ) = CHAR( IC-32 )
+ DO 40 I = 2, 6
+ IC = ICHAR( SUBNAM( I: I ) )
+ IF( IC.GE.225 .AND. IC.LE.250 )
+ $ SUBNAM( I: I ) = CHAR( IC-32 )
+ 40 CONTINUE
+ END IF
+ END IF
+*
+ C1 = SUBNAM( 1: 1 )
+ SNAME = C1.EQ.'S' .OR. C1.EQ.'D'
+ CNAME = C1.EQ.'C' .OR. C1.EQ.'Z'
+ IF( .NOT.( CNAME .OR. SNAME ) )
+ $ RETURN
+ C2 = SUBNAM( 2: 3 )
+ C3 = SUBNAM( 4: 6 )
+ C4 = C3( 2: 3 )
+*
+ GO TO ( 50, 60, 70 )ISPEC
+*
+ 50 CONTINUE
+*
+* ISPEC = 1: block size
+*
+* In these examples, separate code is provided for setting NB for
+* real and complex. We assume that NB will take the same value in
+* single or double precision.
+*
+ NB = 1
+*
+ IF( C2.EQ.'GE' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ ELSE IF( C3.EQ.'QRF' .OR. C3.EQ.'RQF' .OR. C3.EQ.'LQF' .OR.
+ $ C3.EQ.'QLF' ) THEN
+ IF( SNAME ) THEN
+ NB = 32
+ ELSE
+ NB = 32
+ END IF
+ ELSE IF( C3.EQ.'HRD' ) THEN
+ IF( SNAME ) THEN
+ NB = 32
+ ELSE
+ NB = 32
+ END IF
+ ELSE IF( C3.EQ.'BRD' ) THEN
+ IF( SNAME ) THEN
+ NB = 32
+ ELSE
+ NB = 32
+ END IF
+ ELSE IF( C3.EQ.'TRI' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'PO' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'SY' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ ELSE IF( SNAME .AND. C3.EQ.'TRD' ) THEN
+ NB = 32
+ ELSE IF( SNAME .AND. C3.EQ.'GST' ) THEN
+ NB = 64
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'HE' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ NB = 64
+ ELSE IF( C3.EQ.'TRD' ) THEN
+ NB = 32
+ ELSE IF( C3.EQ.'GST' ) THEN
+ NB = 64
+ END IF
+ ELSE IF( SNAME .AND. C2.EQ.'OR' ) THEN
+ IF( C3( 1: 1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR. C4.EQ.
+ $ 'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR. C4.EQ.'BR' )
+ $ THEN
+ NB = 32
+ END IF
+ ELSE IF( C3( 1: 1 ).EQ.'M' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR. C4.EQ.
+ $ 'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR. C4.EQ.'BR' )
+ $ THEN
+ NB = 32
+ END IF
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'UN' ) THEN
+ IF( C3( 1: 1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR. C4.EQ.
+ $ 'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR. C4.EQ.'BR' )
+ $ THEN
+ NB = 32
+ END IF
+ ELSE IF( C3( 1: 1 ).EQ.'M' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR. C4.EQ.
+ $ 'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR. C4.EQ.'BR' )
+ $ THEN
+ NB = 32
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'GB' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ IF( N4.LE.64 ) THEN
+ NB = 1
+ ELSE
+ NB = 32
+ END IF
+ ELSE
+ IF( N4.LE.64 ) THEN
+ NB = 1
+ ELSE
+ NB = 32
+ END IF
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'PB' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ IF( N2.LE.64 ) THEN
+ NB = 1
+ ELSE
+ NB = 32
+ END IF
+ ELSE
+ IF( N2.LE.64 ) THEN
+ NB = 1
+ ELSE
+ NB = 32
+ END IF
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'TR' ) THEN
+ IF( C3.EQ.'TRI' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ ELSE IF ( C3.EQ.'EVC' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'LA' ) THEN
+ IF( C3.EQ.'UUM' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ END IF
+ ELSE IF( SNAME .AND. C2.EQ.'ST' ) THEN
+ IF( C3.EQ.'EBZ' ) THEN
+ NB = 1
+ END IF
+ ELSE IF( C2.EQ.'GG' ) THEN
+ NB = 32
+ IF( C3.EQ.'HD3' ) THEN
+ IF( SNAME ) THEN
+ NB = 32
+ ELSE
+ NB = 32
+ END IF
+ END IF
+ END IF
+ ILAENV = NB
+ RETURN
+*
+ 60 CONTINUE
+*
+* ISPEC = 2: minimum block size
+*
+ NBMIN = 2
+ IF( C2.EQ.'GE' ) THEN
+ IF( C3.EQ.'QRF' .OR. C3.EQ.'RQF' .OR. C3.EQ.'LQF' .OR. C3.EQ.
+ $ 'QLF' ) THEN
+ IF( SNAME ) THEN
+ NBMIN = 2
+ ELSE
+ NBMIN = 2
+ END IF
+ ELSE IF( C3.EQ.'HRD' ) THEN
+ IF( SNAME ) THEN
+ NBMIN = 2
+ ELSE
+ NBMIN = 2
+ END IF
+ ELSE IF( C3.EQ.'BRD' ) THEN
+ IF( SNAME ) THEN
+ NBMIN = 2
+ ELSE
+ NBMIN = 2
+ END IF
+ ELSE IF( C3.EQ.'TRI' ) THEN
+ IF( SNAME ) THEN
+ NBMIN = 2
+ ELSE
+ NBMIN = 2
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'SY' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ NBMIN = 8
+ ELSE
+ NBMIN = 8
+ END IF
+ ELSE IF( SNAME .AND. C3.EQ.'TRD' ) THEN
+ NBMIN = 2
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'HE' ) THEN
+ IF( C3.EQ.'TRD' ) THEN
+ NBMIN = 2
+ END IF
+ ELSE IF( SNAME .AND. C2.EQ.'OR' ) THEN
+ IF( C3( 1: 1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR. C4.EQ.
+ $ 'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR. C4.EQ.'BR' )
+ $ THEN
+ NBMIN = 2
+ END IF
+ ELSE IF( C3( 1: 1 ).EQ.'M' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR. C4.EQ.
+ $ 'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR. C4.EQ.'BR' )
+ $ THEN
+ NBMIN = 2
+ END IF
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'UN' ) THEN
+ IF( C3( 1: 1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR. C4.EQ.
+ $ 'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR. C4.EQ.'BR' )
+ $ THEN
+ NBMIN = 2
+ END IF
+ ELSE IF( C3( 1: 1 ).EQ.'M' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR. C4.EQ.
+ $ 'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR. C4.EQ.'BR' )
+ $ THEN
+ NBMIN = 2
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'GG' ) THEN
+ NBMIN = 2
+ IF( C3.EQ.'HD3' ) THEN
+ NBMIN = 2
+ END IF
+ END IF
+ ILAENV = NBMIN
+ RETURN
+*
+ 70 CONTINUE
+*
+* ISPEC = 3: crossover point
+*
+ NX = 0
+ IF( C2.EQ.'GE' ) THEN
+ IF( C3.EQ.'QRF' .OR. C3.EQ.'RQF' .OR. C3.EQ.'LQF' .OR. C3.EQ.
+ $ 'QLF' ) THEN
+ IF( SNAME ) THEN
+ NX = 128
+ ELSE
+ NX = 128
+ END IF
+ ELSE IF( C3.EQ.'HRD' ) THEN
+ IF( SNAME ) THEN
+ NX = 128
+ ELSE
+ NX = 128
+ END IF
+ ELSE IF( C3.EQ.'BRD' ) THEN
+ IF( SNAME ) THEN
+ NX = 128
+ ELSE
+ NX = 128
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'SY' ) THEN
+ IF( SNAME .AND. C3.EQ.'TRD' ) THEN
+ NX = 32
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'HE' ) THEN
+ IF( C3.EQ.'TRD' ) THEN
+ NX = 32
+ END IF
+ ELSE IF( SNAME .AND. C2.EQ.'OR' ) THEN
+ IF( C3( 1: 1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR. C4.EQ.
+ $ 'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR. C4.EQ.'BR' )
+ $ THEN
+ NX = 128
+ END IF
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'UN' ) THEN
+ IF( C3( 1: 1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR. C4.EQ.
+ $ 'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR. C4.EQ.'BR' )
+ $ THEN
+ NX = 128
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'GG' ) THEN
+ NX = 128
+ IF( C3.EQ.'HD3' ) THEN
+ NX = 128
+ END IF
+ END IF
+ ILAENV = NX
+ RETURN
+*
+ 80 CONTINUE
+*
+* ISPEC = 4: number of shifts (used by xHSEQR)
+*
+ ILAENV = 6
+ RETURN
+*
+ 90 CONTINUE
+*
+* ISPEC = 5: minimum column dimension (not used)
+*
+ ILAENV = 2
+ RETURN
+*
+ 100 CONTINUE
+*
+* ISPEC = 6: crossover point for SVD (used by xGELSS and xGESVD)
+*
+ ILAENV = INT( REAL( MIN( N1, N2 ) )*1.6E0 )
+ RETURN
+*
+ 110 CONTINUE
+*
+* ISPEC = 7: number of processors (not used)
+*
+ ILAENV = 1
+ RETURN
+*
+ 120 CONTINUE
+*
+* ISPEC = 8: crossover point for multishift (used by xHSEQR)
+*
+ ILAENV = 50
+ RETURN
+*
+ 130 CONTINUE
+*
+* ISPEC = 9: maximum size of the subproblems at the bottom of the
+* computation tree in the divide-and-conquer algorithm
+* (used by xGELSD and xGESDD)
+*
+ ILAENV = 25
+ RETURN
+*
+ 140 CONTINUE
+*
+* ISPEC = 10: ieee NaN arithmetic can be trusted not to trap
+*
+* ILAENV = 0
+ ILAENV = 1
+ IF( ILAENV.EQ.1 ) THEN
+ ILAENV = IEEECK( 1, 0.0, 1.0 )
+ END IF
+ RETURN
+*
+ 150 CONTINUE
+*
+* ISPEC = 11: infinity arithmetic can be trusted not to trap
+*
+* ILAENV = 0
+ ILAENV = 1
+ IF( ILAENV.EQ.1 ) THEN
+ ILAENV = IEEECK( 0, 0.0, 1.0 )
+ END IF
+ RETURN
+*
+ 160 CONTINUE
+*
+* 12 <= ISPEC <= 16: xHSEQR or related subroutines.
+*
+ ILAENV = IPARMQ( ISPEC, NAME, OPTS, N1, N2, N3, N4 )
+ RETURN
+*
+* End of ILAENV
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b LSAME
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition:
+* ===========
+*
+* LOGICAL FUNCTION LSAME(CA,CB)
+*
+* .. Scalar Arguments ..
+* CHARACTER CA,CB
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> LSAME returns .TRUE. if CA is the same letter as CB regardless of
+*> case.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] CA
+*> \verbatim
+*> CA is CHARACTER*1
+*> \endverbatim
+*>
+*> \param[in] CB
+*> \verbatim
+*> CB is CHARACTER*1
+*> CA and CB specify the single characters to be compared.
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup aux_blas
+*
+* =====================================================================
+ LOGICAL FUNCTION LSAME(CA,CB)
+*
+* -- Reference BLAS level1 routine (version 3.1) --
+* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2011
+*
+* .. Scalar Arguments ..
+ CHARACTER CA,CB
+* ..
+*
+* =====================================================================
+*
+* .. Intrinsic Functions ..
+ INTRINSIC ICHAR
+* ..
+* .. Local Scalars ..
+ INTEGER INTA,INTB,ZCODE
+* ..
+*
+* Test if the characters are equal
+*
+ LSAME = CA .EQ. CB
+ IF (LSAME) RETURN
+*
+* Now test for equivalence if both characters are alphabetic.
+*
+ ZCODE = ICHAR('Z')
+*
+* Use 'Z' rather than 'A' so that ASCII can be detected on Prime
+* machines, on which ICHAR returns a value with bit 8 set.
+* ICHAR('A') on Prime machines returns 193 which is the same as
+* ICHAR('A') on an EBCDIC machine.
+*
+ INTA = ICHAR(CA)
+ INTB = ICHAR(CB)
+*
+ IF (ZCODE.EQ.90 .OR. ZCODE.EQ.122) THEN
+*
+* ASCII is assumed - ZCODE is the ASCII code of either lower or
+* upper case 'Z'.
+*
+ IF (INTA.GE.97 .AND. INTA.LE.122) INTA = INTA - 32
+ IF (INTB.GE.97 .AND. INTB.LE.122) INTB = INTB - 32
+*
+ ELSE IF (ZCODE.EQ.233 .OR. ZCODE.EQ.169) THEN
+*
+* EBCDIC is assumed - ZCODE is the EBCDIC code of either lower or
+* upper case 'Z'.
+*
+ IF (INTA.GE.129 .AND. INTA.LE.137 .OR.
+ + INTA.GE.145 .AND. INTA.LE.153 .OR.
+ + INTA.GE.162 .AND. INTA.LE.169) INTA = INTA + 64
+ IF (INTB.GE.129 .AND. INTB.LE.137 .OR.
+ + INTB.GE.145 .AND. INTB.LE.153 .OR.
+ + INTB.GE.162 .AND. INTB.LE.169) INTB = INTB + 64
+*
+ ELSE IF (ZCODE.EQ.218 .OR. ZCODE.EQ.250) THEN
+*
+* ASCII is assumed, on Prime machines - ZCODE is the ASCII code
+* plus 128 of either lower or upper case 'Z'.
+*
+ IF (INTA.GE.225 .AND. INTA.LE.250) INTA = INTA - 32
+ IF (INTB.GE.225 .AND. INTB.LE.250) INTB = INTB - 32
+ END IF
+ LSAME = INTA .EQ. INTB
+*
+* RETURN
+*
+* End of LSAME
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b ZGETF2 computes the LU factorization of a general m-by-n matrix using partial pivoting with row interchanges (unblocked algorithm).
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+*> \htmlonly
+*> Download ZGETF2 + dependencies
+*>
+*> [TGZ]
+*>
+*> [ZIP]
+*>
+*> [TXT]
+*> \endhtmlonly
+*
+* Definition:
+* ===========
+*
+* SUBROUTINE ZGETF2( M, N, A, LDA, IPIV, INFO )
+*
+* .. Scalar Arguments ..
+* INTEGER INFO, LDA, M, N
+* ..
+* .. Array Arguments ..
+* INTEGER IPIV( * )
+* COMPLEX*16 A( LDA, * )
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ZGETF2 computes an LU factorization of a general m-by-n matrix A
+*> using partial pivoting with row interchanges.
+*>
+*> The factorization has the form
+*> A = P * L * U
+*> where P is a permutation matrix, L is lower triangular with unit
+*> diagonal elements (lower trapezoidal if m > n), and U is upper
+*> triangular (upper trapezoidal if m < n).
+*>
+*> This is the right-looking Level 2 BLAS version of the algorithm.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] M
+*> \verbatim
+*> M is INTEGER
+*> The number of rows of the matrix A. M >= 0.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The number of columns of the matrix A. N >= 0.
+*> \endverbatim
+*>
+*> \param[in,out] A
+*> \verbatim
+*> A is COMPLEX*16 array, dimension (LDA,N)
+*> On entry, the m by n matrix to be factored.
+*> On exit, the factors L and U from the factorization
+*> A = P*L*U; the unit diagonal elements of L are not stored.
+*> \endverbatim
+*>
+*> \param[in] LDA
+*> \verbatim
+*> LDA is INTEGER
+*> The leading dimension of the array A. LDA >= max(1,M).
+*> \endverbatim
+*>
+*> \param[out] IPIV
+*> \verbatim
+*> IPIV is INTEGER array, dimension (min(M,N))
+*> The pivot indices; for 1 <= i <= min(M,N), row i of the
+*> matrix was interchanged with row IPIV(i).
+*> \endverbatim
+*>
+*> \param[out] INFO
+*> \verbatim
+*> INFO is INTEGER
+*> = 0: successful exit
+*> < 0: if INFO = -k, the k-th argument had an illegal value
+*> > 0: if INFO = k, U(k,k) is exactly zero. The factorization
+*> has been completed, but the factor U is exactly
+*> singular, and division by zero will occur if it is used
+*> to solve a system of equations.
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date September 2012
+*
+*> \ingroup complex16GEcomputational
+*
+* =====================================================================
+ SUBROUTINE ZGETF2( M, N, A, LDA, IPIV, INFO )
+*
+* -- LAPACK computational routine (version 3.4.2) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* September 2012
+*
+* .. Scalar Arguments ..
+ INTEGER INFO, LDA, M, N
+* ..
+* .. Array Arguments ..
+ INTEGER IPIV( * )
+ COMPLEX*16 A( LDA, * )
+* ..
+*
+* =====================================================================
+*
+* .. Parameters ..
+ COMPLEX*16 ONE, ZERO
+ PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ),
+ $ ZERO = ( 0.0D+0, 0.0D+0 ) )
+* ..
+* .. Local Scalars ..
+ DOUBLE PRECISION SFMIN
+ INTEGER I, J, JP
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMCH
+ INTEGER IZAMAX
+ EXTERNAL DLAMCH, IZAMAX
+* ..
+* .. External Subroutines ..
+ EXTERNAL XERBLA, ZGERU, ZSCAL, ZSWAP
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC MAX, MIN
+* ..
+* .. Executable Statements ..
+*
+* Test the input parameters.
+*
+ INFO = 0
+ IF( M.LT.0 ) THEN
+ INFO = -1
+ ELSE IF( N.LT.0 ) THEN
+ INFO = -2
+ ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
+ INFO = -4
+ END IF
+ IF( INFO.NE.0 ) THEN
+ CALL XERBLA( 'ZGETF2', -INFO )
+ RETURN
+ END IF
+*
+* Quick return if possible
+*
+ IF( M.EQ.0 .OR. N.EQ.0 )
+ $ RETURN
+*
+* Compute machine safe minimum
+*
+ SFMIN = DLAMCH('S')
+*
+ DO 10 J = 1, MIN( M, N )
+*
+* Find pivot and test for singularity.
+*
+ JP = J - 1 + IZAMAX( M-J+1, A( J, J ), 1 )
+ IPIV( J ) = JP
+ IF( A( JP, J ).NE.ZERO ) THEN
+*
+* Apply the interchange to columns 1:N.
+*
+ IF( JP.NE.J )
+ $ CALL ZSWAP( N, A( J, 1 ), LDA, A( JP, 1 ), LDA )
+*
+* Compute elements J+1:M of J-th column.
+*
+ IF( J.LT.M ) THEN
+ IF( ABS(A( J, J )) .GE. SFMIN ) THEN
+ CALL ZSCAL( M-J, ONE / A( J, J ), A( J+1, J ), 1 )
+ ELSE
+ DO 20 I = 1, M-J
+ A( J+I, J ) = A( J+I, J ) / A( J, J )
+ 20 CONTINUE
+ END IF
+ END IF
+*
+ ELSE IF( INFO.EQ.0 ) THEN
+*
+ INFO = J
+ END IF
+*
+ IF( J.LT.MIN( M, N ) ) THEN
+*
+* Update trailing submatrix.
+*
+ CALL ZGERU( M-J, N-J, -ONE, A( J+1, J ), 1, A( J, J+1 ),
+ $ LDA, A( J+1, J+1 ), LDA )
+ END IF
+ 10 CONTINUE
+ RETURN
+*
+* End of ZGETF2
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b ZGETRF
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+*> \htmlonly
+*> Download ZGETRF + dependencies
+*>
+*> [TGZ]
+*>
+*> [ZIP]
+*>
+*> [TXT]
+*> \endhtmlonly
+*
+* Definition:
+* ===========
+*
+* SUBROUTINE ZGETRF( M, N, A, LDA, IPIV, INFO )
+*
+* .. Scalar Arguments ..
+* INTEGER INFO, LDA, M, N
+* ..
+* .. Array Arguments ..
+* INTEGER IPIV( * )
+* COMPLEX*16 A( LDA, * )
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ZGETRF computes an LU factorization of a general M-by-N matrix A
+*> using partial pivoting with row interchanges.
+*>
+*> The factorization has the form
+*> A = P * L * U
+*> where P is a permutation matrix, L is lower triangular with unit
+*> diagonal elements (lower trapezoidal if m > n), and U is upper
+*> triangular (upper trapezoidal if m < n).
+*>
+*> This is the right-looking Level 3 BLAS version of the algorithm.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] M
+*> \verbatim
+*> M is INTEGER
+*> The number of rows of the matrix A. M >= 0.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The number of columns of the matrix A. N >= 0.
+*> \endverbatim
+*>
+*> \param[in,out] A
+*> \verbatim
+*> A is COMPLEX*16 array, dimension (LDA,N)
+*> On entry, the M-by-N matrix to be factored.
+*> On exit, the factors L and U from the factorization
+*> A = P*L*U; the unit diagonal elements of L are not stored.
+*> \endverbatim
+*>
+*> \param[in] LDA
+*> \verbatim
+*> LDA is INTEGER
+*> The leading dimension of the array A. LDA >= max(1,M).
+*> \endverbatim
+*>
+*> \param[out] IPIV
+*> \verbatim
+*> IPIV is INTEGER array, dimension (min(M,N))
+*> The pivot indices; for 1 <= i <= min(M,N), row i of the
+*> matrix was interchanged with row IPIV(i).
+*> \endverbatim
+*>
+*> \param[out] INFO
+*> \verbatim
+*> INFO is INTEGER
+*> = 0: successful exit
+*> < 0: if INFO = -i, the i-th argument had an illegal value
+*> > 0: if INFO = i, U(i,i) is exactly zero. The factorization
+*> has been completed, but the factor U is exactly
+*> singular, and division by zero will occur if it is used
+*> to solve a system of equations.
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2015
+*
+*> \ingroup complex16GEcomputational
+*
+* =====================================================================
+ SUBROUTINE ZGETRF( M, N, A, LDA, IPIV, INFO )
+*
+* -- LAPACK computational routine (version 3.6.0) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2015
+*
+* .. Scalar Arguments ..
+ INTEGER INFO, LDA, M, N
+* ..
+* .. Array Arguments ..
+ INTEGER IPIV( * )
+ COMPLEX*16 A( LDA, * )
+* ..
+*
+* =====================================================================
+*
+* .. Parameters ..
+ COMPLEX*16 ONE
+ PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ) )
+* ..
+* .. Local Scalars ..
+ INTEGER I, IINFO, J, JB, NB
+* ..
+* .. External Subroutines ..
+ EXTERNAL XERBLA, ZGEMM, ZGETRF2, ZLASWP, ZTRSM
+* ..
+* .. External Functions ..
+ INTEGER ILAENV
+ EXTERNAL ILAENV
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC MAX, MIN
+* ..
+* .. Executable Statements ..
+*
+* Test the input parameters.
+*
+ INFO = 0
+ IF( M.LT.0 ) THEN
+ INFO = -1
+ ELSE IF( N.LT.0 ) THEN
+ INFO = -2
+ ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
+ INFO = -4
+ END IF
+ IF( INFO.NE.0 ) THEN
+ CALL XERBLA( 'ZGETRF', -INFO )
+ RETURN
+ END IF
+*
+* Quick return if possible
+*
+ IF( M.EQ.0 .OR. N.EQ.0 )
+ $ RETURN
+*
+* Determine the block size for this environment.
+*
+ NB = ILAENV( 1, 'ZGETRF', ' ', M, N, -1, -1 )
+ IF( NB.LE.1 .OR. NB.GE.MIN( M, N ) ) THEN
+*
+* Use unblocked code.
+*
+ CALL ZGETRF2( M, N, A, LDA, IPIV, INFO )
+ ELSE
+*
+* Use blocked code.
+*
+ DO 20 J = 1, MIN( M, N ), NB
+ JB = MIN( MIN( M, N )-J+1, NB )
+*
+* Factor diagonal and subdiagonal blocks and test for exact
+* singularity.
+*
+ CALL ZGETRF2( M-J+1, JB, A( J, J ), LDA, IPIV( J ), IINFO )
+*
+* Adjust INFO and the pivot indices.
+*
+ IF( INFO.EQ.0 .AND. IINFO.GT.0 )
+ $ INFO = IINFO + J - 1
+ DO 10 I = J, MIN( M, J+JB-1 )
+ IPIV( I ) = J - 1 + IPIV( I )
+ 10 CONTINUE
+*
+* Apply interchanges to columns 1:J-1.
+*
+ CALL ZLASWP( J-1, A, LDA, J, J+JB-1, IPIV, 1 )
+*
+ IF( J+JB.LE.N ) THEN
+*
+* Apply interchanges to columns J+JB:N.
+*
+ CALL ZLASWP( N-J-JB+1, A( 1, J+JB ), LDA, J, J+JB-1,
+ $ IPIV, 1 )
+*
+* Compute block row of U.
+*
+ CALL ZTRSM( 'Left', 'Lower', 'No transpose', 'Unit', JB,
+ $ N-J-JB+1, ONE, A( J, J ), LDA, A( J, J+JB ),
+ $ LDA )
+ IF( J+JB.LE.M ) THEN
+*
+* Update trailing submatrix.
+*
+ CALL ZGEMM( 'No transpose', 'No transpose', M-J-JB+1,
+ $ N-J-JB+1, JB, -ONE, A( J+JB, J ), LDA,
+ $ A( J, J+JB ), LDA, ONE, A( J+JB, J+JB ),
+ $ LDA )
+ END IF
+ END IF
+ 20 CONTINUE
+ END IF
+ RETURN
+*
+* End of ZGETRF
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b ZGETRF2
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition:
+* ===========
+*
+* RECURSIVE SUBROUTINE ZGETRF2( M, N, A, LDA, IPIV, INFO )
+*
+* .. Scalar Arguments ..
+* INTEGER INFO, LDA, M, N
+* ..
+* .. Array Arguments ..
+* INTEGER IPIV( * )
+* COMPLEX*16 A( LDA, * )
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ZGETRF2 computes an LU factorization of a general M-by-N matrix A
+*> using partial pivoting with row interchanges.
+*>
+*> The factorization has the form
+*> A = P * L * U
+*> where P is a permutation matrix, L is lower triangular with unit
+*> diagonal elements (lower trapezoidal if m > n), and U is upper
+*> triangular (upper trapezoidal if m < n).
+*>
+*> This is the recursive version of the algorithm. It divides
+*> the matrix into four submatrices:
+*>
+*> [ A11 | A12 ] where A11 is n1 by n1 and A22 is n2 by n2
+*> A = [ -----|----- ] with n1 = min(m,n)/2
+*> [ A21 | A22 ] n2 = n-n1
+*>
+*> [ A11 ]
+*> The subroutine calls itself to factor [ --- ],
+*> [ A12 ]
+*> [ A12 ]
+*> do the swaps on [ --- ], solve A12, update A22,
+*> [ A22 ]
+*>
+*> then calls itself to factor A22 and do the swaps on A21.
+*>
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] M
+*> \verbatim
+*> M is INTEGER
+*> The number of rows of the matrix A. M >= 0.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The number of columns of the matrix A. N >= 0.
+*> \endverbatim
+*>
+*> \param[in,out] A
+*> \verbatim
+*> A is COMPLEX*16 array, dimension (LDA,N)
+*> On entry, the M-by-N matrix to be factored.
+*> On exit, the factors L and U from the factorization
+*> A = P*L*U; the unit diagonal elements of L are not stored.
+*> \endverbatim
+*>
+*> \param[in] LDA
+*> \verbatim
+*> LDA is INTEGER
+*> The leading dimension of the array A. LDA >= max(1,M).
+*> \endverbatim
+*>
+*> \param[out] IPIV
+*> \verbatim
+*> IPIV is INTEGER array, dimension (min(M,N))
+*> The pivot indices; for 1 <= i <= min(M,N), row i of the
+*> matrix was interchanged with row IPIV(i).
+*> \endverbatim
+*>
+*> \param[out] INFO
+*> \verbatim
+*> INFO is INTEGER
+*> = 0: successful exit
+*> < 0: if INFO = -i, the i-th argument had an illegal value
+*> > 0: if INFO = i, U(i,i) is exactly zero. The factorization
+*> has been completed, but the factor U is exactly
+*> singular, and division by zero will occur if it is used
+*> to solve a system of equations.
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date June 2016
+*
+*> \ingroup complex16GEcomputational
+*
+* =====================================================================
+ RECURSIVE SUBROUTINE ZGETRF2( M, N, A, LDA, IPIV, INFO )
+*
+* -- LAPACK computational routine (version 3.6.1) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* June 2016
+*
+* .. Scalar Arguments ..
+ INTEGER INFO, LDA, M, N
+* ..
+* .. Array Arguments ..
+ INTEGER IPIV( * )
+ COMPLEX*16 A( LDA, * )
+* ..
+*
+* =====================================================================
+*
+* .. Parameters ..
+ COMPLEX*16 ONE, ZERO
+ PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ),
+ $ ZERO = ( 0.0D+0, 0.0D+0 ) )
+* ..
+* .. Local Scalars ..
+ DOUBLE PRECISION SFMIN
+ COMPLEX*16 TEMP
+ INTEGER I, IINFO, N1, N2
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMCH
+ INTEGER IZAMAX
+ EXTERNAL DLAMCH, IZAMAX
+* ..
+* .. External Subroutines ..
+ EXTERNAL ZGEMM, ZSCAL, ZLASWP, ZTRSM, XERBLA
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC MAX, MIN
+* ..
+* .. Executable Statements ..
+*
+* Test the input parameters
+*
+ INFO = 0
+ IF( M.LT.0 ) THEN
+ INFO = -1
+ ELSE IF( N.LT.0 ) THEN
+ INFO = -2
+ ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
+ INFO = -4
+ END IF
+ IF( INFO.NE.0 ) THEN
+ CALL XERBLA( 'ZGETRF2', -INFO )
+ RETURN
+ END IF
+*
+* Quick return if possible
+*
+ IF( M.EQ.0 .OR. N.EQ.0 )
+ $ RETURN
+
+ IF ( M.EQ.1 ) THEN
+*
+* Use unblocked code for one row case
+* Just need to handle IPIV and INFO
+*
+ IPIV( 1 ) = 1
+ IF ( A(1,1).EQ.ZERO )
+ $ INFO = 1
+*
+ ELSE IF( N.EQ.1 ) THEN
+*
+* Use unblocked code for one column case
+*
+*
+* Compute machine safe minimum
+*
+ SFMIN = DLAMCH('S')
+*
+* Find pivot and test for singularity
+*
+ I = IZAMAX( M, A( 1, 1 ), 1 )
+ IPIV( 1 ) = I
+ IF( A( I, 1 ).NE.ZERO ) THEN
+*
+* Apply the interchange
+*
+ IF( I.NE.1 ) THEN
+ TEMP = A( 1, 1 )
+ A( 1, 1 ) = A( I, 1 )
+ A( I, 1 ) = TEMP
+ END IF
+*
+* Compute elements 2:M of the column
+*
+ IF( ABS(A( 1, 1 )) .GE. SFMIN ) THEN
+ CALL ZSCAL( M-1, ONE / A( 1, 1 ), A( 2, 1 ), 1 )
+ ELSE
+ DO 10 I = 1, M-1
+ A( 1+I, 1 ) = A( 1+I, 1 ) / A( 1, 1 )
+ 10 CONTINUE
+ END IF
+*
+ ELSE
+ INFO = 1
+ END IF
+
+ ELSE
+*
+* Use recursive code
+*
+ N1 = MIN( M, N ) / 2
+ N2 = N-N1
+*
+* [ A11 ]
+* Factor [ --- ]
+* [ A21 ]
+*
+ CALL ZGETRF2( M, N1, A, LDA, IPIV, IINFO )
+
+ IF ( INFO.EQ.0 .AND. IINFO.GT.0 )
+ $ INFO = IINFO
+*
+* [ A12 ]
+* Apply interchanges to [ --- ]
+* [ A22 ]
+*
+ CALL ZLASWP( N2, A( 1, N1+1 ), LDA, 1, N1, IPIV, 1 )
+*
+* Solve A12
+*
+ CALL ZTRSM( 'L', 'L', 'N', 'U', N1, N2, ONE, A, LDA,
+ $ A( 1, N1+1 ), LDA )
+*
+* Update A22
+*
+ CALL ZGEMM( 'N', 'N', M-N1, N2, N1, -ONE, A( N1+1, 1 ), LDA,
+ $ A( 1, N1+1 ), LDA, ONE, A( N1+1, N1+1 ), LDA )
+*
+* Factor A22
+*
+ CALL ZGETRF2( M-N1, N2, A( N1+1, N1+1 ), LDA, IPIV( N1+1 ),
+ $ IINFO )
+*
+* Adjust INFO and the pivot indices
+*
+ IF ( INFO.EQ.0 .AND. IINFO.GT.0 )
+ $ INFO = IINFO + N1
+ DO 20 I = N1+1, MIN( M, N )
+ IPIV( I ) = IPIV( I ) + N1
+ 20 CONTINUE
+*
+* Apply interchanges to A21
+*
+ CALL ZLASWP( N1, A( 1, 1 ), LDA, N1+1, MIN( M, N), IPIV, 1 )
+*
+ END IF
+ RETURN
+*
+* End of ZGETRF2
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b ZLASWP performs a series of row interchanges on a general rectangular matrix.
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+*> \htmlonly
+*> Download ZLASWP + dependencies
+*>
+*> [TGZ]
+*>
+*> [ZIP]
+*>
+*> [TXT]
+*> \endhtmlonly
+*
+* Definition:
+* ===========
+*
+* SUBROUTINE ZLASWP( N, A, LDA, K1, K2, IPIV, INCX )
+*
+* .. Scalar Arguments ..
+* INTEGER INCX, K1, K2, LDA, N
+* ..
+* .. Array Arguments ..
+* INTEGER IPIV( * )
+* COMPLEX*16 A( LDA, * )
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ZLASWP performs a series of row interchanges on the matrix A.
+*> One row interchange is initiated for each of rows K1 through K2 of A.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The number of columns of the matrix A.
+*> \endverbatim
+*>
+*> \param[in,out] A
+*> \verbatim
+*> A is COMPLEX*16 array, dimension (LDA,N)
+*> On entry, the matrix of column dimension N to which the row
+*> interchanges will be applied.
+*> On exit, the permuted matrix.
+*> \endverbatim
+*>
+*> \param[in] LDA
+*> \verbatim
+*> LDA is INTEGER
+*> The leading dimension of the array A.
+*> \endverbatim
+*>
+*> \param[in] K1
+*> \verbatim
+*> K1 is INTEGER
+*> The first element of IPIV for which a row interchange will
+*> be done.
+*> \endverbatim
+*>
+*> \param[in] K2
+*> \verbatim
+*> K2 is INTEGER
+*> The last element of IPIV for which a row interchange will
+*> be done.
+*> \endverbatim
+*>
+*> \param[in] IPIV
+*> \verbatim
+*> IPIV is INTEGER array, dimension (K2*abs(INCX))
+*> The vector of pivot indices. Only the elements in positions
+*> K1 through K2 of IPIV are accessed.
+*> IPIV(K) = L implies rows K and L are to be interchanged.
+*> \endverbatim
+*>
+*> \param[in] INCX
+*> \verbatim
+*> INCX is INTEGER
+*> The increment between successive values of IPIV. If IPIV
+*> is negative, the pivots are applied in reverse order.
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date September 2012
+*
+*> \ingroup complex16OTHERauxiliary
+*
+*> \par Further Details:
+* =====================
+*>
+*> \verbatim
+*>
+*> Modified by
+*> R. C. Whaley, Computer Science Dept., Univ. of Tenn., Knoxville, USA
+*> \endverbatim
+*>
+* =====================================================================
+ SUBROUTINE ZLASWP( N, A, LDA, K1, K2, IPIV, INCX )
+*
+* -- LAPACK auxiliary routine (version 3.4.2) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* September 2012
+*
+* .. Scalar Arguments ..
+ INTEGER INCX, K1, K2, LDA, N
+* ..
+* .. Array Arguments ..
+ INTEGER IPIV( * )
+ COMPLEX*16 A( LDA, * )
+* ..
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ INTEGER I, I1, I2, INC, IP, IX, IX0, J, K, N32
+ COMPLEX*16 TEMP
+* ..
+* .. Executable Statements ..
+*
+* Interchange row I with row IPIV(I) for each of rows K1 through K2.
+*
+ IF( INCX.GT.0 ) THEN
+ IX0 = K1
+ I1 = K1
+ I2 = K2
+ INC = 1
+ ELSE IF( INCX.LT.0 ) THEN
+ IX0 = 1 + ( 1-K2 )*INCX
+ I1 = K2
+ I2 = K1
+ INC = -1
+ ELSE
+ RETURN
+ END IF
+*
+ N32 = ( N / 32 )*32
+ IF( N32.NE.0 ) THEN
+ DO 30 J = 1, N32, 32
+ IX = IX0
+ DO 20 I = I1, I2, INC
+ IP = IPIV( IX )
+ IF( IP.NE.I ) THEN
+ DO 10 K = J, J + 31
+ TEMP = A( I, K )
+ A( I, K ) = A( IP, K )
+ A( IP, K ) = TEMP
+ 10 CONTINUE
+ END IF
+ IX = IX + INCX
+ 20 CONTINUE
+ 30 CONTINUE
+ END IF
+ IF( N32.NE.N ) THEN
+ N32 = N32 + 1
+ IX = IX0
+ DO 50 I = I1, I2, INC
+ IP = IPIV( IX )
+ IF( IP.NE.I ) THEN
+ DO 40 K = N32, N
+ TEMP = A( I, K )
+ A( I, K ) = A( IP, K )
+ A( IP, K ) = TEMP
+ 40 CONTINUE
+ END IF
+ IX = IX + INCX
+ 50 CONTINUE
+ END IF
+*
+ RETURN
+*
+* End of ZLASWP
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b XERBLA
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+*> \htmlonly
+*> Download XERBLA + dependencies
+*>
+*> [TGZ]
+*>
+*> [ZIP]
+*>
+*> [TXT]
+*> \endhtmlonly
+*
+* Definition:
+* ===========
+*
+* SUBROUTINE XERBLA( SRNAME, INFO )
+*
+* .. Scalar Arguments ..
+* CHARACTER*(*) SRNAME
+* INTEGER INFO
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> XERBLA is an error handler for the LAPACK routines.
+*> It is called by an LAPACK routine if an input parameter has an
+*> invalid value. A message is printed and execution stops.
+*>
+*> Installers may consider modifying the STOP statement in order to
+*> call system-specific exception-handling facilities.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] SRNAME
+*> \verbatim
+*> SRNAME is CHARACTER*(*)
+*> The name of the routine which called XERBLA.
+*> \endverbatim
+*>
+*> \param[in] INFO
+*> \verbatim
+*> INFO is INTEGER
+*> The position of the invalid parameter in the parameter list
+*> of the calling routine.
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup auxOTHERauxiliary
+*
+* =====================================================================
+ SUBROUTINE XERBLA( SRNAME, INFO )
+*
+* -- LAPACK auxiliary routine (version 3.4.0) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2011
+*
+* .. Scalar Arguments ..
+ CHARACTER*(*) SRNAME
+ INTEGER INFO
+* ..
+*
+* =====================================================================
+*
+* .. Intrinsic Functions ..
+ INTRINSIC LEN_TRIM
+* ..
+* .. Executable Statements ..
+*
+ WRITE( *, FMT = 9999 )SRNAME( 1:LEN_TRIM( SRNAME ) ), INFO
+*
+ STOP
+*
+ 9999 FORMAT( ' ** On entry to ', A, ' parameter number ', I2, ' had ',
+ $ 'an illegal value' )
+*
+* End of XERBLA
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b ZGEMM
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition:
+* ===========
+*
+* SUBROUTINE ZGEMM(TRANSA,TRANSB,M,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
+*
+* .. Scalar Arguments ..
+* COMPLEX*16 ALPHA,BETA
+* INTEGER K,LDA,LDB,LDC,M,N
+* CHARACTER TRANSA,TRANSB
+* ..
+* .. Array Arguments ..
+* COMPLEX*16 A(LDA,*),B(LDB,*),C(LDC,*)
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ZGEMM performs one of the matrix-matrix operations
+*>
+*> C := alpha*op( A )*op( B ) + beta*C,
+*>
+*> where op( X ) is one of
+*>
+*> op( X ) = X or op( X ) = X**T or op( X ) = X**H,
+*>
+*> alpha and beta are scalars, and A, B and C are matrices, with op( A )
+*> an m by k matrix, op( B ) a k by n matrix and C an m by n matrix.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] TRANSA
+*> \verbatim
+*> TRANSA is CHARACTER*1
+*> On entry, TRANSA specifies the form of op( A ) to be used in
+*> the matrix multiplication as follows:
+*>
+*> TRANSA = 'N' or 'n', op( A ) = A.
+*>
+*> TRANSA = 'T' or 't', op( A ) = A**T.
+*>
+*> TRANSA = 'C' or 'c', op( A ) = A**H.
+*> \endverbatim
+*>
+*> \param[in] TRANSB
+*> \verbatim
+*> TRANSB is CHARACTER*1
+*> On entry, TRANSB specifies the form of op( B ) to be used in
+*> the matrix multiplication as follows:
+*>
+*> TRANSB = 'N' or 'n', op( B ) = B.
+*>
+*> TRANSB = 'T' or 't', op( B ) = B**T.
+*>
+*> TRANSB = 'C' or 'c', op( B ) = B**H.
+*> \endverbatim
+*>
+*> \param[in] M
+*> \verbatim
+*> M is INTEGER
+*> On entry, M specifies the number of rows of the matrix
+*> op( A ) and of the matrix C. M must be at least zero.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> On entry, N specifies the number of columns of the matrix
+*> op( B ) and the number of columns of the matrix C. N must be
+*> at least zero.
+*> \endverbatim
+*>
+*> \param[in] K
+*> \verbatim
+*> K is INTEGER
+*> On entry, K specifies the number of columns of the matrix
+*> op( A ) and the number of rows of the matrix op( B ). K must
+*> be at least zero.
+*> \endverbatim
+*>
+*> \param[in] ALPHA
+*> \verbatim
+*> ALPHA is COMPLEX*16
+*> On entry, ALPHA specifies the scalar alpha.
+*> \endverbatim
+*>
+*> \param[in] A
+*> \verbatim
+*> A is COMPLEX*16 array of DIMENSION ( LDA, ka ), where ka is
+*> k when TRANSA = 'N' or 'n', and is m otherwise.
+*> Before entry with TRANSA = 'N' or 'n', the leading m by k
+*> part of the array A must contain the matrix A, otherwise
+*> the leading k by m part of the array A must contain the
+*> matrix A.
+*> \endverbatim
+*>
+*> \param[in] LDA
+*> \verbatim
+*> LDA is INTEGER
+*> On entry, LDA specifies the first dimension of A as declared
+*> in the calling (sub) program. When TRANSA = 'N' or 'n' then
+*> LDA must be at least max( 1, m ), otherwise LDA must be at
+*> least max( 1, k ).
+*> \endverbatim
+*>
+*> \param[in] B
+*> \verbatim
+*> B is COMPLEX*16 array of DIMENSION ( LDB, kb ), where kb is
+*> n when TRANSB = 'N' or 'n', and is k otherwise.
+*> Before entry with TRANSB = 'N' or 'n', the leading k by n
+*> part of the array B must contain the matrix B, otherwise
+*> the leading n by k part of the array B must contain the
+*> matrix B.
+*> \endverbatim
+*>
+*> \param[in] LDB
+*> \verbatim
+*> LDB is INTEGER
+*> On entry, LDB specifies the first dimension of B as declared
+*> in the calling (sub) program. When TRANSB = 'N' or 'n' then
+*> LDB must be at least max( 1, k ), otherwise LDB must be at
+*> least max( 1, n ).
+*> \endverbatim
+*>
+*> \param[in] BETA
+*> \verbatim
+*> BETA is COMPLEX*16
+*> On entry, BETA specifies the scalar beta. When BETA is
+*> supplied as zero then C need not be set on input.
+*> \endverbatim
+*>
+*> \param[in,out] C
+*> \verbatim
+*> C is COMPLEX*16 array of DIMENSION ( LDC, n ).
+*> Before entry, the leading m by n part of the array C must
+*> contain the matrix C, except when beta is zero, in which
+*> case C need not be set on entry.
+*> On exit, the array C is overwritten by the m by n matrix
+*> ( alpha*op( A )*op( B ) + beta*C ).
+*> \endverbatim
+*>
+*> \param[in] LDC
+*> \verbatim
+*> LDC is INTEGER
+*> On entry, LDC specifies the first dimension of C as declared
+*> in the calling (sub) program. LDC must be at least
+*> max( 1, m ).
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2015
+*
+*> \ingroup complex16_blas_level3
+*
+*> \par Further Details:
+* =====================
+*>
+*> \verbatim
+*>
+*> Level 3 Blas routine.
+*>
+*> -- Written on 8-February-1989.
+*> Jack Dongarra, Argonne National Laboratory.
+*> Iain Duff, AERE Harwell.
+*> Jeremy Du Croz, Numerical Algorithms Group Ltd.
+*> Sven Hammarling, Numerical Algorithms Group Ltd.
+*> \endverbatim
+*>
+* =====================================================================
+ SUBROUTINE ZGEMM(TRANSA,TRANSB,M,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
+*
+* -- Reference BLAS level3 routine (version 3.6.0) --
+* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2015
+*
+* .. Scalar Arguments ..
+ COMPLEX*16 ALPHA,BETA
+ INTEGER K,LDA,LDB,LDC,M,N
+ CHARACTER TRANSA,TRANSB
+* ..
+* .. Array Arguments ..
+ COMPLEX*16 A(LDA,*),B(LDB,*),C(LDC,*)
+* ..
+*
+* =====================================================================
+*
+* .. External Functions ..
+ LOGICAL LSAME
+ EXTERNAL LSAME
+* ..
+* .. External Subroutines ..
+ EXTERNAL XERBLA
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC DCONJG,MAX
+* ..
+* .. Local Scalars ..
+ COMPLEX*16 TEMP
+ INTEGER I,INFO,J,L,NCOLA,NROWA,NROWB
+ LOGICAL CONJA,CONJB,NOTA,NOTB
+* ..
+* .. Parameters ..
+ COMPLEX*16 ONE
+ PARAMETER (ONE= (1.0D+0,0.0D+0))
+ COMPLEX*16 ZERO
+ PARAMETER (ZERO= (0.0D+0,0.0D+0))
+* ..
+*
+* Set NOTA and NOTB as true if A and B respectively are not
+* conjugated or transposed, set CONJA and CONJB as true if A and
+* B respectively are to be transposed but not conjugated and set
+* NROWA, NCOLA and NROWB as the number of rows and columns of A
+* and the number of rows of B respectively.
+*
+ NOTA = LSAME(TRANSA,'N')
+ NOTB = LSAME(TRANSB,'N')
+ CONJA = LSAME(TRANSA,'C')
+ CONJB = LSAME(TRANSB,'C')
+ IF (NOTA) THEN
+ NROWA = M
+ NCOLA = K
+ ELSE
+ NROWA = K
+ NCOLA = M
+ END IF
+ IF (NOTB) THEN
+ NROWB = K
+ ELSE
+ NROWB = N
+ END IF
+*
+* Test the input parameters.
+*
+ INFO = 0
+ IF ((.NOT.NOTA) .AND. (.NOT.CONJA) .AND.
+ + (.NOT.LSAME(TRANSA,'T'))) THEN
+ INFO = 1
+ ELSE IF ((.NOT.NOTB) .AND. (.NOT.CONJB) .AND.
+ + (.NOT.LSAME(TRANSB,'T'))) THEN
+ INFO = 2
+ ELSE IF (M.LT.0) THEN
+ INFO = 3
+ ELSE IF (N.LT.0) THEN
+ INFO = 4
+ ELSE IF (K.LT.0) THEN
+ INFO = 5
+ ELSE IF (LDA.LT.MAX(1,NROWA)) THEN
+ INFO = 8
+ ELSE IF (LDB.LT.MAX(1,NROWB)) THEN
+ INFO = 10
+ ELSE IF (LDC.LT.MAX(1,M)) THEN
+ INFO = 13
+ END IF
+ IF (INFO.NE.0) THEN
+ CALL XERBLA('ZGEMM ',INFO)
+ RETURN
+ END IF
+*
+* Quick return if possible.
+*
+ IF ((M.EQ.0) .OR. (N.EQ.0) .OR.
+ + (((ALPHA.EQ.ZERO).OR. (K.EQ.0)).AND. (BETA.EQ.ONE))) RETURN
+*
+* And when alpha.eq.zero.
+*
+ IF (ALPHA.EQ.ZERO) THEN
+ IF (BETA.EQ.ZERO) THEN
+ DO 20 J = 1,N
+ DO 10 I = 1,M
+ C(I,J) = ZERO
+ 10 CONTINUE
+ 20 CONTINUE
+ ELSE
+ DO 40 J = 1,N
+ DO 30 I = 1,M
+ C(I,J) = BETA*C(I,J)
+ 30 CONTINUE
+ 40 CONTINUE
+ END IF
+ RETURN
+ END IF
+*
+* Start the operations.
+*
+ IF (NOTB) THEN
+ IF (NOTA) THEN
+*
+* Form C := alpha*A*B + beta*C.
+*
+ DO 90 J = 1,N
+ IF (BETA.EQ.ZERO) THEN
+ DO 50 I = 1,M
+ C(I,J) = ZERO
+ 50 CONTINUE
+ ELSE IF (BETA.NE.ONE) THEN
+ DO 60 I = 1,M
+ C(I,J) = BETA*C(I,J)
+ 60 CONTINUE
+ END IF
+ DO 80 L = 1,K
+ TEMP = ALPHA*B(L,J)
+ DO 70 I = 1,M
+ C(I,J) = C(I,J) + TEMP*A(I,L)
+ 70 CONTINUE
+ 80 CONTINUE
+ 90 CONTINUE
+ ELSE IF (CONJA) THEN
+*
+* Form C := alpha*A**H*B + beta*C.
+*
+ DO 120 J = 1,N
+ DO 110 I = 1,M
+ TEMP = ZERO
+ DO 100 L = 1,K
+ TEMP = TEMP + DCONJG(A(L,I))*B(L,J)
+ 100 CONTINUE
+ IF (BETA.EQ.ZERO) THEN
+ C(I,J) = ALPHA*TEMP
+ ELSE
+ C(I,J) = ALPHA*TEMP + BETA*C(I,J)
+ END IF
+ 110 CONTINUE
+ 120 CONTINUE
+ ELSE
+*
+* Form C := alpha*A**T*B + beta*C
+*
+ DO 150 J = 1,N
+ DO 140 I = 1,M
+ TEMP = ZERO
+ DO 130 L = 1,K
+ TEMP = TEMP + A(L,I)*B(L,J)
+ 130 CONTINUE
+ IF (BETA.EQ.ZERO) THEN
+ C(I,J) = ALPHA*TEMP
+ ELSE
+ C(I,J) = ALPHA*TEMP + BETA*C(I,J)
+ END IF
+ 140 CONTINUE
+ 150 CONTINUE
+ END IF
+ ELSE IF (NOTA) THEN
+ IF (CONJB) THEN
+*
+* Form C := alpha*A*B**H + beta*C.
+*
+ DO 200 J = 1,N
+ IF (BETA.EQ.ZERO) THEN
+ DO 160 I = 1,M
+ C(I,J) = ZERO
+ 160 CONTINUE
+ ELSE IF (BETA.NE.ONE) THEN
+ DO 170 I = 1,M
+ C(I,J) = BETA*C(I,J)
+ 170 CONTINUE
+ END IF
+ DO 190 L = 1,K
+ TEMP = ALPHA*DCONJG(B(J,L))
+ DO 180 I = 1,M
+ C(I,J) = C(I,J) + TEMP*A(I,L)
+ 180 CONTINUE
+ 190 CONTINUE
+ 200 CONTINUE
+ ELSE
+*
+* Form C := alpha*A*B**T + beta*C
+*
+ DO 250 J = 1,N
+ IF (BETA.EQ.ZERO) THEN
+ DO 210 I = 1,M
+ C(I,J) = ZERO
+ 210 CONTINUE
+ ELSE IF (BETA.NE.ONE) THEN
+ DO 220 I = 1,M
+ C(I,J) = BETA*C(I,J)
+ 220 CONTINUE
+ END IF
+ DO 240 L = 1,K
+ TEMP = ALPHA*B(J,L)
+ DO 230 I = 1,M
+ C(I,J) = C(I,J) + TEMP*A(I,L)
+ 230 CONTINUE
+ 240 CONTINUE
+ 250 CONTINUE
+ END IF
+ ELSE IF (CONJA) THEN
+ IF (CONJB) THEN
+*
+* Form C := alpha*A**H*B**H + beta*C.
+*
+ DO 280 J = 1,N
+ DO 270 I = 1,M
+ TEMP = ZERO
+ DO 260 L = 1,K
+ TEMP = TEMP + DCONJG(A(L,I))*DCONJG(B(J,L))
+ 260 CONTINUE
+ IF (BETA.EQ.ZERO) THEN
+ C(I,J) = ALPHA*TEMP
+ ELSE
+ C(I,J) = ALPHA*TEMP + BETA*C(I,J)
+ END IF
+ 270 CONTINUE
+ 280 CONTINUE
+ ELSE
+*
+* Form C := alpha*A**H*B**T + beta*C
+*
+ DO 310 J = 1,N
+ DO 300 I = 1,M
+ TEMP = ZERO
+ DO 290 L = 1,K
+ TEMP = TEMP + DCONJG(A(L,I))*B(J,L)
+ 290 CONTINUE
+ IF (BETA.EQ.ZERO) THEN
+ C(I,J) = ALPHA*TEMP
+ ELSE
+ C(I,J) = ALPHA*TEMP + BETA*C(I,J)
+ END IF
+ 300 CONTINUE
+ 310 CONTINUE
+ END IF
+ ELSE
+ IF (CONJB) THEN
+*
+* Form C := alpha*A**T*B**H + beta*C
+*
+ DO 340 J = 1,N
+ DO 330 I = 1,M
+ TEMP = ZERO
+ DO 320 L = 1,K
+ TEMP = TEMP + A(L,I)*DCONJG(B(J,L))
+ 320 CONTINUE
+ IF (BETA.EQ.ZERO) THEN
+ C(I,J) = ALPHA*TEMP
+ ELSE
+ C(I,J) = ALPHA*TEMP + BETA*C(I,J)
+ END IF
+ 330 CONTINUE
+ 340 CONTINUE
+ ELSE
+*
+* Form C := alpha*A**T*B**T + beta*C
+*
+ DO 370 J = 1,N
+ DO 360 I = 1,M
+ TEMP = ZERO
+ DO 350 L = 1,K
+ TEMP = TEMP + A(L,I)*B(J,L)
+ 350 CONTINUE
+ IF (BETA.EQ.ZERO) THEN
+ C(I,J) = ALPHA*TEMP
+ ELSE
+ C(I,J) = ALPHA*TEMP + BETA*C(I,J)
+ END IF
+ 360 CONTINUE
+ 370 CONTINUE
+ END IF
+ END IF
+*
+ RETURN
+*
+* End of ZGEMM .
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b ZGERU
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition:
+* ===========
+*
+* SUBROUTINE ZGERU(M,N,ALPHA,X,INCX,Y,INCY,A,LDA)
+*
+* .. Scalar Arguments ..
+* COMPLEX*16 ALPHA
+* INTEGER INCX,INCY,LDA,M,N
+* ..
+* .. Array Arguments ..
+* COMPLEX*16 A(LDA,*),X(*),Y(*)
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ZGERU performs the rank 1 operation
+*>
+*> A := alpha*x*y**T + A,
+*>
+*> where alpha is a scalar, x is an m element vector, y is an n element
+*> vector and A is an m by n matrix.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] M
+*> \verbatim
+*> M is INTEGER
+*> On entry, M specifies the number of rows of the matrix A.
+*> M must be at least zero.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> On entry, N specifies the number of columns of the matrix A.
+*> N must be at least zero.
+*> \endverbatim
+*>
+*> \param[in] ALPHA
+*> \verbatim
+*> ALPHA is COMPLEX*16
+*> On entry, ALPHA specifies the scalar alpha.
+*> \endverbatim
+*>
+*> \param[in] X
+*> \verbatim
+*> X is COMPLEX*16 array of dimension at least
+*> ( 1 + ( m - 1 )*abs( INCX ) ).
+*> Before entry, the incremented array X must contain the m
+*> element vector x.
+*> \endverbatim
+*>
+*> \param[in] INCX
+*> \verbatim
+*> INCX is INTEGER
+*> On entry, INCX specifies the increment for the elements of
+*> X. INCX must not be zero.
+*> \endverbatim
+*>
+*> \param[in] Y
+*> \verbatim
+*> Y is COMPLEX*16 array of dimension at least
+*> ( 1 + ( n - 1 )*abs( INCY ) ).
+*> Before entry, the incremented array Y must contain the n
+*> element vector y.
+*> \endverbatim
+*>
+*> \param[in] INCY
+*> \verbatim
+*> INCY is INTEGER
+*> On entry, INCY specifies the increment for the elements of
+*> Y. INCY must not be zero.
+*> \endverbatim
+*>
+*> \param[in,out] A
+*> \verbatim
+*> A is COMPLEX*16 array of DIMENSION ( LDA, n ).
+*> Before entry, the leading m by n part of the array A must
+*> contain the matrix of coefficients. On exit, A is
+*> overwritten by the updated matrix.
+*> \endverbatim
+*>
+*> \param[in] LDA
+*> \verbatim
+*> LDA is INTEGER
+*> On entry, LDA specifies the first dimension of A as declared
+*> in the calling (sub) program. LDA must be at least
+*> max( 1, m ).
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup complex16_blas_level2
+*
+*> \par Further Details:
+* =====================
+*>
+*> \verbatim
+*>
+*> Level 2 Blas routine.
+*>
+*> -- Written on 22-October-1986.
+*> Jack Dongarra, Argonne National Lab.
+*> Jeremy Du Croz, Nag Central Office.
+*> Sven Hammarling, Nag Central Office.
+*> Richard Hanson, Sandia National Labs.
+*> \endverbatim
+*>
+* =====================================================================
+ SUBROUTINE ZGERU(M,N,ALPHA,X,INCX,Y,INCY,A,LDA)
+*
+* -- Reference BLAS level2 routine (version 3.4.0) --
+* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2011
+*
+* .. Scalar Arguments ..
+ COMPLEX*16 ALPHA
+ INTEGER INCX,INCY,LDA,M,N
+* ..
+* .. Array Arguments ..
+ COMPLEX*16 A(LDA,*),X(*),Y(*)
+* ..
+*
+* =====================================================================
+*
+* .. Parameters ..
+ COMPLEX*16 ZERO
+ PARAMETER (ZERO= (0.0D+0,0.0D+0))
+* ..
+* .. Local Scalars ..
+ COMPLEX*16 TEMP
+ INTEGER I,INFO,IX,J,JY,KX
+* ..
+* .. External Subroutines ..
+ EXTERNAL XERBLA
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC MAX
+* ..
+*
+* Test the input parameters.
+*
+ INFO = 0
+ IF (M.LT.0) THEN
+ INFO = 1
+ ELSE IF (N.LT.0) THEN
+ INFO = 2
+ ELSE IF (INCX.EQ.0) THEN
+ INFO = 5
+ ELSE IF (INCY.EQ.0) THEN
+ INFO = 7
+ ELSE IF (LDA.LT.MAX(1,M)) THEN
+ INFO = 9
+ END IF
+ IF (INFO.NE.0) THEN
+ CALL XERBLA('ZGERU ',INFO)
+ RETURN
+ END IF
+*
+* Quick return if possible.
+*
+ IF ((M.EQ.0) .OR. (N.EQ.0) .OR. (ALPHA.EQ.ZERO)) RETURN
+*
+* Start the operations. In this version the elements of A are
+* accessed sequentially with one pass through A.
+*
+ IF (INCY.GT.0) THEN
+ JY = 1
+ ELSE
+ JY = 1 - (N-1)*INCY
+ END IF
+ IF (INCX.EQ.1) THEN
+ DO 20 J = 1,N
+ IF (Y(JY).NE.ZERO) THEN
+ TEMP = ALPHA*Y(JY)
+ DO 10 I = 1,M
+ A(I,J) = A(I,J) + X(I)*TEMP
+ 10 CONTINUE
+ END IF
+ JY = JY + INCY
+ 20 CONTINUE
+ ELSE
+ IF (INCX.GT.0) THEN
+ KX = 1
+ ELSE
+ KX = 1 - (M-1)*INCX
+ END IF
+ DO 40 J = 1,N
+ IF (Y(JY).NE.ZERO) THEN
+ TEMP = ALPHA*Y(JY)
+ IX = KX
+ DO 30 I = 1,M
+ A(I,J) = A(I,J) + X(IX)*TEMP
+ IX = IX + INCX
+ 30 CONTINUE
+ END IF
+ JY = JY + INCY
+ 40 CONTINUE
+ END IF
+*
+ RETURN
+*
+* End of ZGERU .
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b ZSCAL
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition:
+* ===========
+*
+* SUBROUTINE ZSCAL(N,ZA,ZX,INCX)
+*
+* .. Scalar Arguments ..
+* COMPLEX*16 ZA
+* INTEGER INCX,N
+* ..
+* .. Array Arguments ..
+* COMPLEX*16 ZX(*)
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ZSCAL scales a vector by a constant.
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup complex16_blas_level1
+*
+*> \par Further Details:
+* =====================
+*>
+*> \verbatim
+*>
+*> jack dongarra, 3/11/78.
+*> modified 3/93 to return if incx .le. 0.
+*> modified 12/3/93, array(1) declarations changed to array(*)
+*> \endverbatim
+*>
+* =====================================================================
+ SUBROUTINE ZSCAL(N,ZA,ZX,INCX)
+*
+* -- Reference BLAS level1 routine (version 3.4.0) --
+* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2011
+*
+* .. Scalar Arguments ..
+ COMPLEX*16 ZA
+ INTEGER INCX,N
+* ..
+* .. Array Arguments ..
+ COMPLEX*16 ZX(*)
+* ..
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ INTEGER I,NINCX
+* ..
+ IF (N.LE.0 .OR. INCX.LE.0) RETURN
+ IF (INCX.EQ.1) THEN
+*
+* code for increment equal to 1
+*
+ DO I = 1,N
+ ZX(I) = ZA*ZX(I)
+ END DO
+ ELSE
+*
+* code for increment not equal to 1
+*
+ NINCX = N*INCX
+ DO I = 1,NINCX,INCX
+ ZX(I) = ZA*ZX(I)
+ END DO
+ END IF
+ RETURN
+ END
+C
+C======================================================================
+C
+*> \brief \b ZSWAP
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition:
+* ===========
+*
+* SUBROUTINE ZSWAP(N,ZX,INCX,ZY,INCY)
+*
+* .. Scalar Arguments ..
+* INTEGER INCX,INCY,N
+* ..
+* .. Array Arguments ..
+* COMPLEX*16 ZX(*),ZY(*)
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ZSWAP interchanges two vectors.
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup complex16_blas_level1
+*
+*> \par Further Details:
+* =====================
+*>
+*> \verbatim
+*>
+*> jack dongarra, 3/11/78.
+*> modified 12/3/93, array(1) declarations changed to array(*)
+*> \endverbatim
+*>
+* =====================================================================
+ SUBROUTINE ZSWAP(N,ZX,INCX,ZY,INCY)
+*
+* -- Reference BLAS level1 routine (version 3.4.0) --
+* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2011
+*
+* .. Scalar Arguments ..
+ INTEGER INCX,INCY,N
+* ..
+* .. Array Arguments ..
+ COMPLEX*16 ZX(*),ZY(*)
+* ..
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ COMPLEX*16 ZTEMP
+ INTEGER I,IX,IY
+* ..
+ IF (N.LE.0) RETURN
+ IF (INCX.EQ.1 .AND. INCY.EQ.1) THEN
+*
+* code for both increments equal to 1
+ DO I = 1,N
+ ZTEMP = ZX(I)
+ ZX(I) = ZY(I)
+ ZY(I) = ZTEMP
+ END DO
+ ELSE
+*
+* code for unequal increments or equal increments not equal
+* to 1
+*
+ IX = 1
+ IY = 1
+ IF (INCX.LT.0) IX = (-N+1)*INCX + 1
+ IF (INCY.LT.0) IY = (-N+1)*INCY + 1
+ DO I = 1,N
+ ZTEMP = ZX(IX)
+ ZX(IX) = ZY(IY)
+ ZY(IY) = ZTEMP
+ IX = IX + INCX
+ IY = IY + INCY
+ END DO
+ END IF
+ RETURN
+ END
+C
+C======================================================================
+C
+*> \brief \b ZTRSM
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition:
+* ===========
+*
+* SUBROUTINE ZTRSM(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB)
+*
+* .. Scalar Arguments ..
+* COMPLEX*16 ALPHA
+* INTEGER LDA,LDB,M,N
+* CHARACTER DIAG,SIDE,TRANSA,UPLO
+* ..
+* .. Array Arguments ..
+* COMPLEX*16 A(LDA,*),B(LDB,*)
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> ZTRSM solves one of the matrix equations
+*>
+*> op( A )*X = alpha*B, or X*op( A ) = alpha*B,
+*>
+*> where alpha is a scalar, X and B are m by n matrices, A is a unit, or
+*> non-unit, upper or lower triangular matrix and op( A ) is one of
+*>
+*> op( A ) = A or op( A ) = A**T or op( A ) = A**H.
+*>
+*> The matrix X is overwritten on B.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] SIDE
+*> \verbatim
+*> SIDE is CHARACTER*1
+*> On entry, SIDE specifies whether op( A ) appears on the left
+*> or right of X as follows:
+*>
+*> SIDE = 'L' or 'l' op( A )*X = alpha*B.
+*>
+*> SIDE = 'R' or 'r' X*op( A ) = alpha*B.
+*> \endverbatim
+*>
+*> \param[in] UPLO
+*> \verbatim
+*> UPLO is CHARACTER*1
+*> On entry, UPLO specifies whether the matrix A is an upper or
+*> lower triangular matrix as follows:
+*>
+*> UPLO = 'U' or 'u' A is an upper triangular matrix.
+*>
+*> UPLO = 'L' or 'l' A is a lower triangular matrix.
+*> \endverbatim
+*>
+*> \param[in] TRANSA
+*> \verbatim
+*> TRANSA is CHARACTER*1
+*> On entry, TRANSA specifies the form of op( A ) to be used in
+*> the matrix multiplication as follows:
+*>
+*> TRANSA = 'N' or 'n' op( A ) = A.
+*>
+*> TRANSA = 'T' or 't' op( A ) = A**T.
+*>
+*> TRANSA = 'C' or 'c' op( A ) = A**H.
+*> \endverbatim
+*>
+*> \param[in] DIAG
+*> \verbatim
+*> DIAG is CHARACTER*1
+*> On entry, DIAG specifies whether or not A is unit triangular
+*> as follows:
+*>
+*> DIAG = 'U' or 'u' A is assumed to be unit triangular.
+*>
+*> DIAG = 'N' or 'n' A is not assumed to be unit
+*> triangular.
+*> \endverbatim
+*>
+*> \param[in] M
+*> \verbatim
+*> M is INTEGER
+*> On entry, M specifies the number of rows of B. M must be at
+*> least zero.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> On entry, N specifies the number of columns of B. N must be
+*> at least zero.
+*> \endverbatim
+*>
+*> \param[in] ALPHA
+*> \verbatim
+*> ALPHA is COMPLEX*16
+*> On entry, ALPHA specifies the scalar alpha. When alpha is
+*> zero then A is not referenced and B need not be set before
+*> entry.
+*> \endverbatim
+*>
+*> \param[in] A
+*> \verbatim
+*> A is COMPLEX*16 array of DIMENSION ( LDA, k ),
+*> where k is m when SIDE = 'L' or 'l'
+*> and k is n when SIDE = 'R' or 'r'.
+*> Before entry with UPLO = 'U' or 'u', the leading k by k
+*> upper triangular part of the array A must contain the upper
+*> triangular matrix and the strictly lower triangular part of
+*> A is not referenced.
+*> Before entry with UPLO = 'L' or 'l', the leading k by k
+*> lower triangular part of the array A must contain the lower
+*> triangular matrix and the strictly upper triangular part of
+*> A is not referenced.
+*> Note that when DIAG = 'U' or 'u', the diagonal elements of
+*> A are not referenced either, but are assumed to be unity.
+*> \endverbatim
+*>
+*> \param[in] LDA
+*> \verbatim
+*> LDA is INTEGER
+*> On entry, LDA specifies the first dimension of A as declared
+*> in the calling (sub) program. When SIDE = 'L' or 'l' then
+*> LDA must be at least max( 1, m ), when SIDE = 'R' or 'r'
+*> then LDA must be at least max( 1, n ).
+*> \endverbatim
+*>
+*> \param[in,out] B
+*> \verbatim
+*> B is COMPLEX*16 array of DIMENSION ( LDB, n ).
+*> Before entry, the leading m by n part of the array B must
+*> contain the right-hand side matrix B, and on exit is
+*> overwritten by the solution matrix X.
+*> \endverbatim
+*>
+*> \param[in] LDB
+*> \verbatim
+*> LDB is INTEGER
+*> On entry, LDB specifies the first dimension of B as declared
+*> in the calling (sub) program. LDB must be at least
+*> max( 1, m ).
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup complex16_blas_level3
+*
+*> \par Further Details:
+* =====================
+*>
+*> \verbatim
+*>
+*> Level 3 Blas routine.
+*>
+*> -- Written on 8-February-1989.
+*> Jack Dongarra, Argonne National Laboratory.
+*> Iain Duff, AERE Harwell.
+*> Jeremy Du Croz, Numerical Algorithms Group Ltd.
+*> Sven Hammarling, Numerical Algorithms Group Ltd.
+*> \endverbatim
+*>
+* =====================================================================
+ SUBROUTINE ZTRSM(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB)
+*
+* -- Reference BLAS level3 routine (version 3.4.0) --
+* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2011
+*
+* .. Scalar Arguments ..
+ COMPLEX*16 ALPHA
+ INTEGER LDA,LDB,M,N
+ CHARACTER DIAG,SIDE,TRANSA,UPLO
+* ..
+* .. Array Arguments ..
+ COMPLEX*16 A(LDA,*),B(LDB,*)
+* ..
+*
+* =====================================================================
+*
+* .. External Functions ..
+ LOGICAL LSAME
+ EXTERNAL LSAME
+* ..
+* .. External Subroutines ..
+ EXTERNAL XERBLA
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC DCONJG,MAX
+* ..
+* .. Local Scalars ..
+ COMPLEX*16 TEMP
+ INTEGER I,INFO,J,K,NROWA
+ LOGICAL LSIDE,NOCONJ,NOUNIT,UPPER
+* ..
+* .. Parameters ..
+ COMPLEX*16 ONE
+ PARAMETER (ONE= (1.0D+0,0.0D+0))
+ COMPLEX*16 ZERO
+ PARAMETER (ZERO= (0.0D+0,0.0D+0))
+* ..
+*
+* Test the input parameters.
+*
+ LSIDE = LSAME(SIDE,'L')
+ IF (LSIDE) THEN
+ NROWA = M
+ ELSE
+ NROWA = N
+ END IF
+ NOCONJ = LSAME(TRANSA,'T')
+ NOUNIT = LSAME(DIAG,'N')
+ UPPER = LSAME(UPLO,'U')
+*
+ INFO = 0
+ IF ((.NOT.LSIDE) .AND. (.NOT.LSAME(SIDE,'R'))) THEN
+ INFO = 1
+ ELSE IF ((.NOT.UPPER) .AND. (.NOT.LSAME(UPLO,'L'))) THEN
+ INFO = 2
+ ELSE IF ((.NOT.LSAME(TRANSA,'N')) .AND.
+ + (.NOT.LSAME(TRANSA,'T')) .AND.
+ + (.NOT.LSAME(TRANSA,'C'))) THEN
+ INFO = 3
+ ELSE IF ((.NOT.LSAME(DIAG,'U')) .AND. (.NOT.LSAME(DIAG,'N'))) THEN
+ INFO = 4
+ ELSE IF (M.LT.0) THEN
+ INFO = 5
+ ELSE IF (N.LT.0) THEN
+ INFO = 6
+ ELSE IF (LDA.LT.MAX(1,NROWA)) THEN
+ INFO = 9
+ ELSE IF (LDB.LT.MAX(1,M)) THEN
+ INFO = 11
+ END IF
+ IF (INFO.NE.0) THEN
+ CALL XERBLA('ZTRSM ',INFO)
+ RETURN
+ END IF
+*
+* Quick return if possible.
+*
+ IF (M.EQ.0 .OR. N.EQ.0) RETURN
+*
+* And when alpha.eq.zero.
+*
+ IF (ALPHA.EQ.ZERO) THEN
+ DO 20 J = 1,N
+ DO 10 I = 1,M
+ B(I,J) = ZERO
+ 10 CONTINUE
+ 20 CONTINUE
+ RETURN
+ END IF
+*
+* Start the operations.
+*
+ IF (LSIDE) THEN
+ IF (LSAME(TRANSA,'N')) THEN
+*
+* Form B := alpha*inv( A )*B.
+*
+ IF (UPPER) THEN
+ DO 60 J = 1,N
+ IF (ALPHA.NE.ONE) THEN
+ DO 30 I = 1,M
+ B(I,J) = ALPHA*B(I,J)
+ 30 CONTINUE
+ END IF
+ DO 50 K = M,1,-1
+ IF (B(K,J).NE.ZERO) THEN
+ IF (NOUNIT) B(K,J) = B(K,J)/A(K,K)
+ DO 40 I = 1,K - 1
+ B(I,J) = B(I,J) - B(K,J)*A(I,K)
+ 40 CONTINUE
+ END IF
+ 50 CONTINUE
+ 60 CONTINUE
+ ELSE
+ DO 100 J = 1,N
+ IF (ALPHA.NE.ONE) THEN
+ DO 70 I = 1,M
+ B(I,J) = ALPHA*B(I,J)
+ 70 CONTINUE
+ END IF
+ DO 90 K = 1,M
+ IF (B(K,J).NE.ZERO) THEN
+ IF (NOUNIT) B(K,J) = B(K,J)/A(K,K)
+ DO 80 I = K + 1,M
+ B(I,J) = B(I,J) - B(K,J)*A(I,K)
+ 80 CONTINUE
+ END IF
+ 90 CONTINUE
+ 100 CONTINUE
+ END IF
+ ELSE
+*
+* Form B := alpha*inv( A**T )*B
+* or B := alpha*inv( A**H )*B.
+*
+ IF (UPPER) THEN
+ DO 140 J = 1,N
+ DO 130 I = 1,M
+ TEMP = ALPHA*B(I,J)
+ IF (NOCONJ) THEN
+ DO 110 K = 1,I - 1
+ TEMP = TEMP - A(K,I)*B(K,J)
+ 110 CONTINUE
+ IF (NOUNIT) TEMP = TEMP/A(I,I)
+ ELSE
+ DO 120 K = 1,I - 1
+ TEMP = TEMP - DCONJG(A(K,I))*B(K,J)
+ 120 CONTINUE
+ IF (NOUNIT) TEMP = TEMP/DCONJG(A(I,I))
+ END IF
+ B(I,J) = TEMP
+ 130 CONTINUE
+ 140 CONTINUE
+ ELSE
+ DO 180 J = 1,N
+ DO 170 I = M,1,-1
+ TEMP = ALPHA*B(I,J)
+ IF (NOCONJ) THEN
+ DO 150 K = I + 1,M
+ TEMP = TEMP - A(K,I)*B(K,J)
+ 150 CONTINUE
+ IF (NOUNIT) TEMP = TEMP/A(I,I)
+ ELSE
+ DO 160 K = I + 1,M
+ TEMP = TEMP - DCONJG(A(K,I))*B(K,J)
+ 160 CONTINUE
+ IF (NOUNIT) TEMP = TEMP/DCONJG(A(I,I))
+ END IF
+ B(I,J) = TEMP
+ 170 CONTINUE
+ 180 CONTINUE
+ END IF
+ END IF
+ ELSE
+ IF (LSAME(TRANSA,'N')) THEN
+*
+* Form B := alpha*B*inv( A ).
+*
+ IF (UPPER) THEN
+ DO 230 J = 1,N
+ IF (ALPHA.NE.ONE) THEN
+ DO 190 I = 1,M
+ B(I,J) = ALPHA*B(I,J)
+ 190 CONTINUE
+ END IF
+ DO 210 K = 1,J - 1
+ IF (A(K,J).NE.ZERO) THEN
+ DO 200 I = 1,M
+ B(I,J) = B(I,J) - A(K,J)*B(I,K)
+ 200 CONTINUE
+ END IF
+ 210 CONTINUE
+ IF (NOUNIT) THEN
+ TEMP = ONE/A(J,J)
+ DO 220 I = 1,M
+ B(I,J) = TEMP*B(I,J)
+ 220 CONTINUE
+ END IF
+ 230 CONTINUE
+ ELSE
+ DO 280 J = N,1,-1
+ IF (ALPHA.NE.ONE) THEN
+ DO 240 I = 1,M
+ B(I,J) = ALPHA*B(I,J)
+ 240 CONTINUE
+ END IF
+ DO 260 K = J + 1,N
+ IF (A(K,J).NE.ZERO) THEN
+ DO 250 I = 1,M
+ B(I,J) = B(I,J) - A(K,J)*B(I,K)
+ 250 CONTINUE
+ END IF
+ 260 CONTINUE
+ IF (NOUNIT) THEN
+ TEMP = ONE/A(J,J)
+ DO 270 I = 1,M
+ B(I,J) = TEMP*B(I,J)
+ 270 CONTINUE
+ END IF
+ 280 CONTINUE
+ END IF
+ ELSE
+*
+* Form B := alpha*B*inv( A**T )
+* or B := alpha*B*inv( A**H ).
+*
+ IF (UPPER) THEN
+ DO 330 K = N,1,-1
+ IF (NOUNIT) THEN
+ IF (NOCONJ) THEN
+ TEMP = ONE/A(K,K)
+ ELSE
+ TEMP = ONE/DCONJG(A(K,K))
+ END IF
+ DO 290 I = 1,M
+ B(I,K) = TEMP*B(I,K)
+ 290 CONTINUE
+ END IF
+ DO 310 J = 1,K - 1
+ IF (A(J,K).NE.ZERO) THEN
+ IF (NOCONJ) THEN
+ TEMP = A(J,K)
+ ELSE
+ TEMP = DCONJG(A(J,K))
+ END IF
+ DO 300 I = 1,M
+ B(I,J) = B(I,J) - TEMP*B(I,K)
+ 300 CONTINUE
+ END IF
+ 310 CONTINUE
+ IF (ALPHA.NE.ONE) THEN
+ DO 320 I = 1,M
+ B(I,K) = ALPHA*B(I,K)
+ 320 CONTINUE
+ END IF
+ 330 CONTINUE
+ ELSE
+ DO 380 K = 1,N
+ IF (NOUNIT) THEN
+ IF (NOCONJ) THEN
+ TEMP = ONE/A(K,K)
+ ELSE
+ TEMP = ONE/DCONJG(A(K,K))
+ END IF
+ DO 340 I = 1,M
+ B(I,K) = TEMP*B(I,K)
+ 340 CONTINUE
+ END IF
+ DO 360 J = K + 1,N
+ IF (A(J,K).NE.ZERO) THEN
+ IF (NOCONJ) THEN
+ TEMP = A(J,K)
+ ELSE
+ TEMP = DCONJG(A(J,K))
+ END IF
+ DO 350 I = 1,M
+ B(I,J) = B(I,J) - TEMP*B(I,K)
+ 350 CONTINUE
+ END IF
+ 360 CONTINUE
+ IF (ALPHA.NE.ONE) THEN
+ DO 370 I = 1,M
+ B(I,K) = ALPHA*B(I,K)
+ 370 CONTINUE
+ END IF
+ 380 CONTINUE
+ END IF
+ END IF
+ END IF
+*
+ RETURN
+*
+* End of ZTRSM .
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b DLAMCH
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition:
+* ===========
+*
+* DOUBLE PRECISION FUNCTION DLAMCH( CMACH )
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> DLAMCH determines double precision machine parameters.
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] CMACH
+*> \verbatim
+*> Specifies the value to be returned by DLAMCH:
+*> = 'E' or 'e', DLAMCH := eps
+*> = 'S' or 's , DLAMCH := sfmin
+*> = 'B' or 'b', DLAMCH := base
+*> = 'P' or 'p', DLAMCH := eps*base
+*> = 'N' or 'n', DLAMCH := t
+*> = 'R' or 'r', DLAMCH := rnd
+*> = 'M' or 'm', DLAMCH := emin
+*> = 'U' or 'u', DLAMCH := rmin
+*> = 'L' or 'l', DLAMCH := emax
+*> = 'O' or 'o', DLAMCH := rmax
+*> where
+*> eps = relative machine precision
+*> sfmin = safe minimum, such that 1/sfmin does not overflow
+*> base = base of the machine
+*> prec = eps*base
+*> t = number of (base) digits in the mantissa
+*> rnd = 1.0 when rounding occurs in addition, 0.0 otherwise
+*> emin = minimum exponent before (gradual) underflow
+*> rmin = underflow threshold - base**(emin-1)
+*> emax = largest exponent before overflow
+*> rmax = overflow threshold - (base**emax)*(1-eps)
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2015
+*
+*> \ingroup auxOTHERauxiliary
+*
+* =====================================================================
+ DOUBLE PRECISION FUNCTION DLAMCH( CMACH )
+*
+* -- LAPACK auxiliary routine (version 3.6.0) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2015
+*
+* .. Scalar Arguments ..
+ CHARACTER CMACH
+* ..
+*
+* =====================================================================
+*
+* .. Parameters ..
+ DOUBLE PRECISION ONE, ZERO
+ PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
+* ..
+* .. Local Scalars ..
+ DOUBLE PRECISION RND, EPS, SFMIN, SMALL, RMACH
+* ..
+* .. External Functions ..
+ LOGICAL LSAME
+ EXTERNAL LSAME
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC DIGITS, EPSILON, HUGE, MAXEXPONENT,
+ $ MINEXPONENT, RADIX, TINY
+* ..
+* .. Executable Statements ..
+*
+*
+* Assume rounding, not chopping. Always.
+*
+ RND = ONE
+*
+ IF( ONE.EQ.RND ) THEN
+ EPS = EPSILON(ZERO) * 0.5
+ ELSE
+ EPS = EPSILON(ZERO)
+ END IF
+*
+ IF( LSAME( CMACH, 'E' ) ) THEN
+ RMACH = EPS
+ ELSE IF( LSAME( CMACH, 'S' ) ) THEN
+ SFMIN = TINY(ZERO)
+ SMALL = ONE / HUGE(ZERO)
+ IF( SMALL.GE.SFMIN ) THEN
+*
+* Use SMALL plus a bit, to avoid the possibility of rounding
+* causing overflow when computing 1/sfmin.
+*
+ SFMIN = SMALL*( ONE+EPS )
+ END IF
+ RMACH = SFMIN
+ ELSE IF( LSAME( CMACH, 'B' ) ) THEN
+ RMACH = RADIX(ZERO)
+ ELSE IF( LSAME( CMACH, 'P' ) ) THEN
+ RMACH = EPS * RADIX(ZERO)
+ ELSE IF( LSAME( CMACH, 'N' ) ) THEN
+ RMACH = DIGITS(ZERO)
+ ELSE IF( LSAME( CMACH, 'R' ) ) THEN
+ RMACH = RND
+ ELSE IF( LSAME( CMACH, 'M' ) ) THEN
+ RMACH = MINEXPONENT(ZERO)
+ ELSE IF( LSAME( CMACH, 'U' ) ) THEN
+ RMACH = tiny(zero)
+ ELSE IF( LSAME( CMACH, 'L' ) ) THEN
+ RMACH = MAXEXPONENT(ZERO)
+ ELSE IF( LSAME( CMACH, 'O' ) ) THEN
+ RMACH = HUGE(ZERO)
+ ELSE
+ RMACH = ZERO
+ END IF
+*
+ DLAMCH = RMACH
+ RETURN
+*
+* End of DLAMCH
+*
+ END
+C
+C======================================================================
+C
+*
+************************************************************************
+*
+*> \brief \b DLAMC1
+*> \details
+*> \b Purpose:
+*> \verbatim
+*> DLAMC1 determines the machine parameters given by BETA, T, RND, and
+*> IEEE1.
+*> \endverbatim
+*>
+*> \param[out] BETA
+*> \verbatim
+*> The base of the machine.
+*> \endverbatim
+*>
+*> \param[out] T
+*> \verbatim
+*> The number of ( BETA ) digits in the mantissa.
+*> \endverbatim
+*>
+*> \param[out] RND
+*> \verbatim
+*> Specifies whether proper rounding ( RND = .TRUE. ) or
+*> chopping ( RND = .FALSE. ) occurs in addition. This may not
+*> be a reliable guide to the way in which the machine performs
+*> its arithmetic.
+*> \endverbatim
+*>
+*> \param[out] IEEE1
+*> \verbatim
+*> Specifies whether rounding appears to be done in the IEEE
+*> 'round to nearest' style.
+*> \endverbatim
+*> \author LAPACK is a software package provided by Univ. of Tennessee, Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..
+*> \date April 2012
+*> \ingroup auxOTHERauxiliary
+*>
+*> \details \b Further \b Details
+*> \verbatim
+*>
+*> The routine is based on the routine ENVRON by Malcolm and
+*> incorporates suggestions by Gentleman and Marovich. See
+*>
+*> Malcolm M. A. (1972) Algorithms to reveal properties of
+*> floating-point arithmetic. Comms. of the ACM, 15, 949-951.
+*>
+*> Gentleman W. M. and Marovich S. B. (1974) More on algorithms
+*> that reveal properties of floating point arithmetic units.
+*> Comms. of the ACM, 17, 276-277.
+*> \endverbatim
+*>
+ SUBROUTINE DLAMC1( BETA, T, RND, IEEE1 )
+*
+* -- LAPACK auxiliary routine (version 3.4.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2010
+*
+* .. Scalar Arguments ..
+ LOGICAL IEEE1, RND
+ INTEGER BETA, T
+* ..
+* =====================================================================
+*
+* .. Local Scalars ..
+ LOGICAL FIRST, LIEEE1, LRND
+ INTEGER LBETA, LT
+ DOUBLE PRECISION A, B, C, F, ONE, QTR, SAVEC, T1, T2
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMC3
+ EXTERNAL DLAMC3
+* ..
+* .. Save statement ..
+ SAVE FIRST, LIEEE1, LBETA, LRND, LT
+* ..
+* .. Data statements ..
+ DATA FIRST / .TRUE. /
+* ..
+* .. Executable Statements ..
+*
+ IF( FIRST ) THEN
+ ONE = 1
+*
+* LBETA, LIEEE1, LT and LRND are the local values of BETA,
+* IEEE1, T and RND.
+*
+* Throughout this routine we use the function DLAMC3 to ensure
+* that relevant values are stored and not held in registers, or
+* are not affected by optimizers.
+*
+* Compute a = 2.0**m with the smallest positive integer m such
+* that
+*
+* fl( a + 1.0 ) = a.
+*
+ A = 1
+ C = 1
+*
+*+ WHILE( C.EQ.ONE )LOOP
+ 10 CONTINUE
+ IF( C.EQ.ONE ) THEN
+ A = 2*A
+ C = DLAMC3( A, ONE )
+ C = DLAMC3( C, -A )
+ GO TO 10
+ END IF
+*+ END WHILE
+*
+* Now compute b = 2.0**m with the smallest positive integer m
+* such that
+*
+* fl( a + b ) .gt. a.
+*
+ B = 1
+ C = DLAMC3( A, B )
+*
+*+ WHILE( C.EQ.A )LOOP
+ 20 CONTINUE
+ IF( C.EQ.A ) THEN
+ B = 2*B
+ C = DLAMC3( A, B )
+ GO TO 20
+ END IF
+*+ END WHILE
+*
+* Now compute the base. a and c are neighbouring floating point
+* numbers in the interval ( beta**t, beta**( t + 1 ) ) and so
+* their difference is beta. Adding 0.25 to c is to ensure that it
+* is truncated to beta and not ( beta - 1 ).
+*
+ QTR = ONE / 4
+ SAVEC = C
+ C = DLAMC3( C, -A )
+ LBETA = C + QTR
+*
+* Now determine whether rounding or chopping occurs, by adding a
+* bit less than beta/2 and a bit more than beta/2 to a.
+*
+ B = LBETA
+ F = DLAMC3( B / 2, -B / 100 )
+ C = DLAMC3( F, A )
+ IF( C.EQ.A ) THEN
+ LRND = .TRUE.
+ ELSE
+ LRND = .FALSE.
+ END IF
+ F = DLAMC3( B / 2, B / 100 )
+ C = DLAMC3( F, A )
+ IF( ( LRND ) .AND. ( C.EQ.A ) )
+ $ LRND = .FALSE.
+*
+* Try and decide whether rounding is done in the IEEE 'round to
+* nearest' style. B/2 is half a unit in the last place of the two
+* numbers A and SAVEC. Furthermore, A is even, i.e. has last bit
+* zero, and SAVEC is odd. Thus adding B/2 to A should not change
+* A, but adding B/2 to SAVEC should change SAVEC.
+*
+ T1 = DLAMC3( B / 2, A )
+ T2 = DLAMC3( B / 2, SAVEC )
+ LIEEE1 = ( T1.EQ.A ) .AND. ( T2.GT.SAVEC ) .AND. LRND
+*
+* Now find the mantissa, t. It should be the integer part of
+* log to the base beta of a, however it is safer to determine t
+* by powering. So we find t as the smallest positive integer for
+* which
+*
+* fl( beta**t + 1.0 ) = 1.0.
+*
+ LT = 0
+ A = 1
+ C = 1
+*
+*+ WHILE( C.EQ.ONE )LOOP
+ 30 CONTINUE
+ IF( C.EQ.ONE ) THEN
+ LT = LT + 1
+ A = A*LBETA
+ C = DLAMC3( A, ONE )
+ C = DLAMC3( C, -A )
+ GO TO 30
+ END IF
+*+ END WHILE
+*
+ END IF
+*
+ BETA = LBETA
+ T = LT
+ RND = LRND
+ IEEE1 = LIEEE1
+ FIRST = .FALSE.
+ RETURN
+*
+* End of DLAMC1
+*
+ END
+C
+C======================================================================
+C
+*
+************************************************************************
+*
+*> \brief \b DLAMC2
+*> \details
+*> \b Purpose:
+*> \verbatim
+*> DLAMC2 determines the machine parameters specified in its argument
+*> list.
+*> \endverbatim
+*> \author LAPACK is a software package provided by Univ. of Tennessee, Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..
+*> \date April 2012
+*> \ingroup auxOTHERauxiliary
+*>
+*> \param[out] BETA
+*> \verbatim
+*> The base of the machine.
+*> \endverbatim
+*>
+*> \param[out] T
+*> \verbatim
+*> The number of ( BETA ) digits in the mantissa.
+*> \endverbatim
+*>
+*> \param[out] RND
+*> \verbatim
+*> Specifies whether proper rounding ( RND = .TRUE. ) or
+*> chopping ( RND = .FALSE. ) occurs in addition. This may not
+*> be a reliable guide to the way in which the machine performs
+*> its arithmetic.
+*> \endverbatim
+*>
+*> \param[out] EPS
+*> \verbatim
+*> The smallest positive number such that
+*> fl( 1.0 - EPS ) .LT. 1.0,
+*> where fl denotes the computed value.
+*> \endverbatim
+*>
+*> \param[out] EMIN
+*> \verbatim
+*> The minimum exponent before (gradual) underflow occurs.
+*> \endverbatim
+*>
+*> \param[out] RMIN
+*> \verbatim
+*> The smallest normalized number for the machine, given by
+*> BASE**( EMIN - 1 ), where BASE is the floating point value
+*> of BETA.
+*> \endverbatim
+*>
+*> \param[out] EMAX
+*> \verbatim
+*> The maximum exponent before overflow occurs.
+*> \endverbatim
+*>
+*> \param[out] RMAX
+*> \verbatim
+*> The largest positive number for the machine, given by
+*> BASE**EMAX * ( 1 - EPS ), where BASE is the floating point
+*> value of BETA.
+*> \endverbatim
+*>
+*> \details \b Further \b Details
+*> \verbatim
+*>
+*> The computation of EPS is based on a routine PARANOIA by
+*> W. Kahan of the University of California at Berkeley.
+*> \endverbatim
+ SUBROUTINE DLAMC2( BETA, T, RND, EPS, EMIN, RMIN, EMAX, RMAX )
+*
+* -- LAPACK auxiliary routine (version 3.4.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2010
+*
+* .. Scalar Arguments ..
+ LOGICAL RND
+ INTEGER BETA, EMAX, EMIN, T
+ DOUBLE PRECISION EPS, RMAX, RMIN
+* ..
+* =====================================================================
+*
+* .. Local Scalars ..
+ LOGICAL FIRST, IEEE, IWARN, LIEEE1, LRND
+ INTEGER GNMIN, GPMIN, I, LBETA, LEMAX, LEMIN, LT,
+ $ NGNMIN, NGPMIN
+ DOUBLE PRECISION A, B, C, HALF, LEPS, LRMAX, LRMIN, ONE, RBASE,
+ $ SIXTH, SMALL, THIRD, TWO, ZERO
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMC3
+ EXTERNAL DLAMC3
+* ..
+* .. External Subroutines ..
+ EXTERNAL DLAMC1, DLAMC4, DLAMC5
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC ABS, MAX, MIN
+* ..
+* .. Save statement ..
+ SAVE FIRST, IWARN, LBETA, LEMAX, LEMIN, LEPS, LRMAX,
+ $ LRMIN, LT
+* ..
+* .. Data statements ..
+ DATA FIRST / .TRUE. / , IWARN / .FALSE. /
+* ..
+* .. Executable Statements ..
+*
+ IF( FIRST ) THEN
+ ZERO = 0
+ ONE = 1
+ TWO = 2
+*
+* LBETA, LT, LRND, LEPS, LEMIN and LRMIN are the local values of
+* BETA, T, RND, EPS, EMIN and RMIN.
+*
+* Throughout this routine we use the function DLAMC3 to ensure
+* that relevant values are stored and not held in registers, or
+* are not affected by optimizers.
+*
+* DLAMC1 returns the parameters LBETA, LT, LRND and LIEEE1.
+*
+ CALL DLAMC1( LBETA, LT, LRND, LIEEE1 )
+*
+* Start to find EPS.
+*
+ B = LBETA
+ A = B**( -LT )
+ LEPS = A
+*
+* Try some tricks to see whether or not this is the correct EPS.
+*
+ B = TWO / 3
+ HALF = ONE / 2
+ SIXTH = DLAMC3( B, -HALF )
+ THIRD = DLAMC3( SIXTH, SIXTH )
+ B = DLAMC3( THIRD, -HALF )
+ B = DLAMC3( B, SIXTH )
+ B = ABS( B )
+ IF( B.LT.LEPS )
+ $ B = LEPS
+*
+ LEPS = 1
+*
+*+ WHILE( ( LEPS.GT.B ).AND.( B.GT.ZERO ) )LOOP
+ 10 CONTINUE
+ IF( ( LEPS.GT.B ) .AND. ( B.GT.ZERO ) ) THEN
+ LEPS = B
+ C = DLAMC3( HALF*LEPS, ( TWO**5 )*( LEPS**2 ) )
+ C = DLAMC3( HALF, -C )
+ B = DLAMC3( HALF, C )
+ C = DLAMC3( HALF, -B )
+ B = DLAMC3( HALF, C )
+ GO TO 10
+ END IF
+*+ END WHILE
+*
+ IF( A.LT.LEPS )
+ $ LEPS = A
+*
+* Computation of EPS complete.
+*
+* Now find EMIN. Let A = + or - 1, and + or - (1 + BASE**(-3)).
+* Keep dividing A by BETA until (gradual) underflow occurs. This
+* is detected when we cannot recover the previous A.
+*
+ RBASE = ONE / LBETA
+ SMALL = ONE
+ DO 20 I = 1, 3
+ SMALL = DLAMC3( SMALL*RBASE, ZERO )
+ 20 CONTINUE
+ A = DLAMC3( ONE, SMALL )
+ CALL DLAMC4( NGPMIN, ONE, LBETA )
+ CALL DLAMC4( NGNMIN, -ONE, LBETA )
+ CALL DLAMC4( GPMIN, A, LBETA )
+ CALL DLAMC4( GNMIN, -A, LBETA )
+ IEEE = .FALSE.
+*
+ IF( ( NGPMIN.EQ.NGNMIN ) .AND. ( GPMIN.EQ.GNMIN ) ) THEN
+ IF( NGPMIN.EQ.GPMIN ) THEN
+ LEMIN = NGPMIN
+* ( Non twos-complement machines, no gradual underflow;
+* e.g., VAX )
+ ELSE IF( ( GPMIN-NGPMIN ).EQ.3 ) THEN
+ LEMIN = NGPMIN - 1 + LT
+ IEEE = .TRUE.
+* ( Non twos-complement machines, with gradual underflow;
+* e.g., IEEE standard followers )
+ ELSE
+ LEMIN = MIN( NGPMIN, GPMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+*
+ ELSE IF( ( NGPMIN.EQ.GPMIN ) .AND. ( NGNMIN.EQ.GNMIN ) ) THEN
+ IF( ABS( NGPMIN-NGNMIN ).EQ.1 ) THEN
+ LEMIN = MAX( NGPMIN, NGNMIN )
+* ( Twos-complement machines, no gradual underflow;
+* e.g., CYBER 205 )
+ ELSE
+ LEMIN = MIN( NGPMIN, NGNMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+*
+ ELSE IF( ( ABS( NGPMIN-NGNMIN ).EQ.1 ) .AND.
+ $ ( GPMIN.EQ.GNMIN ) ) THEN
+ IF( ( GPMIN-MIN( NGPMIN, NGNMIN ) ).EQ.3 ) THEN
+ LEMIN = MAX( NGPMIN, NGNMIN ) - 1 + LT
+* ( Twos-complement machines with gradual underflow;
+* no known machine )
+ ELSE
+ LEMIN = MIN( NGPMIN, NGNMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+*
+ ELSE
+ LEMIN = MIN( NGPMIN, NGNMIN, GPMIN, GNMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+ FIRST = .FALSE.
+***
+* Comment out this if block if EMIN is ok
+ IF( IWARN ) THEN
+ FIRST = .TRUE.
+ WRITE( 6, FMT = 9999 )LEMIN
+ END IF
+***
+*
+* Assume IEEE arithmetic if we found denormalised numbers above,
+* or if arithmetic seems to round in the IEEE style, determined
+* in routine DLAMC1. A true IEEE machine should have both things
+* true; however, faulty machines may have one or the other.
+*
+ IEEE = IEEE .OR. LIEEE1
+*
+* Compute RMIN by successive division by BETA. We could compute
+* RMIN as BASE**( EMIN - 1 ), but some machines underflow during
+* this computation.
+*
+ LRMIN = 1
+ DO 30 I = 1, 1 - LEMIN
+ LRMIN = DLAMC3( LRMIN*RBASE, ZERO )
+ 30 CONTINUE
+*
+* Finally, call DLAMC5 to compute EMAX and RMAX.
+*
+ CALL DLAMC5( LBETA, LT, LEMIN, IEEE, LEMAX, LRMAX )
+ END IF
+*
+ BETA = LBETA
+ T = LT
+ RND = LRND
+ EPS = LEPS
+ EMIN = LEMIN
+ RMIN = LRMIN
+ EMAX = LEMAX
+ RMAX = LRMAX
+*
+ RETURN
+*
+ 9999 FORMAT( / / ' WARNING. The value EMIN may be incorrect:-',
+ $ ' EMIN = ', I8, /
+ $ ' If, after inspection, the value EMIN looks',
+ $ ' acceptable please comment out ',
+ $ / ' the IF block as marked within the code of routine',
+ $ ' DLAMC2,', / ' otherwise supply EMIN explicitly.', / )
+*
+* End of DLAMC2
+*
+ END
+*
+************************************************************************
+*
+*> \brief \b DLAMC3
+*> \details
+*> \b Purpose:
+*> \verbatim
+*> DLAMC3 is intended to force A and B to be stored prior to doing
+*> the addition of A and B , for use in situations where optimizers
+*> might hold one of these in a register.
+*> \endverbatim
+*>
+*> \param[in] A
+*>
+*> \param[in] B
+*> \verbatim
+*> The values A and B.
+*> \endverbatim
+
+ DOUBLE PRECISION FUNCTION DLAMC3( A, B )
+*
+* -- LAPACK auxiliary routine (version 3.4.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2010
+*
+* .. Scalar Arguments ..
+ DOUBLE PRECISION A, B
+* ..
+* =====================================================================
+*
+* .. Executable Statements ..
+*
+ DLAMC3 = A + B
+*
+ RETURN
+*
+* End of DLAMC3
+*
+ END
+C
+C======================================================================
+C
+*
+************************************************************************
+*
+*> \brief \b DLAMC4
+*> \details
+*> \b Purpose:
+*> \verbatim
+*> DLAMC4 is a service routine for DLAMC2.
+*> \endverbatim
+*>
+*> \param[out] EMIN
+*> \verbatim
+*> The minimum exponent before (gradual) underflow, computed by
+*> setting A = START and dividing by BASE until the previous A
+*> can not be recovered.
+*> \endverbatim
+*>
+*> \param[in] START
+*> \verbatim
+*> The starting point for determining EMIN.
+*> \endverbatim
+*>
+*> \param[in] BASE
+*> \verbatim
+*> The base of the machine.
+*> \endverbatim
+*>
+ SUBROUTINE DLAMC4( EMIN, START, BASE )
+*
+* -- LAPACK auxiliary routine (version 3.4.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2010
+*
+* .. Scalar Arguments ..
+ INTEGER BASE, EMIN
+ DOUBLE PRECISION START
+* ..
+* =====================================================================
+*
+* .. Local Scalars ..
+ INTEGER I
+ DOUBLE PRECISION A, B1, B2, C1, C2, D1, D2, ONE, RBASE, ZERO
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMC3
+ EXTERNAL DLAMC3
+* ..
+* .. Executable Statements ..
+*
+ A = START
+ ONE = 1
+ RBASE = ONE / BASE
+ ZERO = 0
+ EMIN = 1
+ B1 = DLAMC3( A*RBASE, ZERO )
+ C1 = A
+ C2 = A
+ D1 = A
+ D2 = A
+*+ WHILE( ( C1.EQ.A ).AND.( C2.EQ.A ).AND.
+* $ ( D1.EQ.A ).AND.( D2.EQ.A ) )LOOP
+ 10 CONTINUE
+ IF( ( C1.EQ.A ) .AND. ( C2.EQ.A ) .AND. ( D1.EQ.A ) .AND.
+ $ ( D2.EQ.A ) ) THEN
+ EMIN = EMIN - 1
+ A = B1
+ B1 = DLAMC3( A / BASE, ZERO )
+ C1 = DLAMC3( B1*BASE, ZERO )
+ D1 = ZERO
+ DO 20 I = 1, BASE
+ D1 = D1 + B1
+ 20 CONTINUE
+ B2 = DLAMC3( A*RBASE, ZERO )
+ C2 = DLAMC3( B2 / RBASE, ZERO )
+ D2 = ZERO
+ DO 30 I = 1, BASE
+ D2 = D2 + B2
+ 30 CONTINUE
+ GO TO 10
+ END IF
+*+ END WHILE
+*
+ RETURN
+*
+* End of DLAMC4
+*
+ END
+C
+C======================================================================
+C
+*
+************************************************************************
+*
+*> \brief \b DLAMC5
+*> \details
+*> \b Purpose:
+*> \verbatim
+*> DLAMC5 attempts to compute RMAX, the largest machine floating-point
+*> number, without overflow. It assumes that EMAX + abs(EMIN) sum
+*> approximately to a power of 2. It will fail on machines where this
+*> assumption does not hold, for example, the Cyber 205 (EMIN = -28625,
+*> EMAX = 28718). It will also fail if the value supplied for EMIN is
+*> too large (i.e. too close to zero), probably with overflow.
+*> \endverbatim
+*>
+*> \param[in] BETA
+*> \verbatim
+*> The base of floating-point arithmetic.
+*> \endverbatim
+*>
+*> \param[in] P
+*> \verbatim
+*> The number of base BETA digits in the mantissa of a
+*> floating-point value.
+*> \endverbatim
+*>
+*> \param[in] EMIN
+*> \verbatim
+*> The minimum exponent before (gradual) underflow.
+*> \endverbatim
+*>
+*> \param[in] IEEE
+*> \verbatim
+*> A logical flag specifying whether or not the arithmetic
+*> system is thought to comply with the IEEE standard.
+*> \endverbatim
+*>
+*> \param[out] EMAX
+*> \verbatim
+*> The largest exponent before overflow
+*> \endverbatim
+*>
+*> \param[out] RMAX
+*> \verbatim
+*> The largest machine floating-point number.
+*> \endverbatim
+*>
+ SUBROUTINE DLAMC5( BETA, P, EMIN, IEEE, EMAX, RMAX )
+*
+* -- LAPACK auxiliary routine (version 3.4.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2010
+*
+* .. Scalar Arguments ..
+ LOGICAL IEEE
+ INTEGER BETA, EMAX, EMIN, P
+ DOUBLE PRECISION RMAX
+* ..
+* =====================================================================
+*
+* .. Parameters ..
+ DOUBLE PRECISION ZERO, ONE
+ PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0 )
+* ..
+* .. Local Scalars ..
+ INTEGER EXBITS, EXPSUM, I, LEXP, NBITS, TRY, UEXP
+ DOUBLE PRECISION OLDY, RECBAS, Y, Z
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMC3
+ EXTERNAL DLAMC3
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC MOD
+* ..
+* .. Executable Statements ..
+*
+* First compute LEXP and UEXP, two powers of 2 that bound
+* abs(EMIN). We then assume that EMAX + abs(EMIN) will sum
+* approximately to the bound that is closest to abs(EMIN).
+* (EMAX is the exponent of the required number RMAX).
+*
+ LEXP = 1
+ EXBITS = 1
+ 10 CONTINUE
+ TRY = LEXP*2
+ IF( TRY.LE.( -EMIN ) ) THEN
+ LEXP = TRY
+ EXBITS = EXBITS + 1
+ GO TO 10
+ END IF
+ IF( LEXP.EQ.-EMIN ) THEN
+ UEXP = LEXP
+ ELSE
+ UEXP = TRY
+ EXBITS = EXBITS + 1
+ END IF
+*
+* Now -LEXP is less than or equal to EMIN, and -UEXP is greater
+* than or equal to EMIN. EXBITS is the number of bits needed to
+* store the exponent.
+*
+ IF( ( UEXP+EMIN ).GT.( -LEXP-EMIN ) ) THEN
+ EXPSUM = 2*LEXP
+ ELSE
+ EXPSUM = 2*UEXP
+ END IF
+*
+* EXPSUM is the exponent range, approximately equal to
+* EMAX - EMIN + 1 .
+*
+ EMAX = EXPSUM + EMIN - 1
+ NBITS = 1 + EXBITS + P
+*
+* NBITS is the total number of bits needed to store a
+* floating-point number.
+*
+ IF( ( MOD( NBITS, 2 ).EQ.1 ) .AND. ( BETA.EQ.2 ) ) THEN
+*
+* Either there are an odd number of bits used to store a
+* floating-point number, which is unlikely, or some bits are
+* not used in the representation of numbers, which is possible,
+* (e.g. Cray machines) or the mantissa has an implicit bit,
+* (e.g. IEEE machines, Dec Vax machines), which is perhaps the
+* most likely. We have to assume the last alternative.
+* If this is true, then we need to reduce EMAX by one because
+* there must be some way of representing zero in an implicit-bit
+* system. On machines like Cray, we are reducing EMAX by one
+* unnecessarily.
+*
+ EMAX = EMAX - 1
+ END IF
+*
+ IF( IEEE ) THEN
+*
+* Assume we are on an IEEE machine which reserves one exponent
+* for infinity and NaN.
+*
+ EMAX = EMAX - 1
+ END IF
+*
+* Now create RMAX, the largest machine number, which should
+* be equal to (1.0 - BETA**(-P)) * BETA**EMAX .
+*
+* First compute 1.0 - BETA**(-P), being careful that the
+* result is less than 1.0 .
+*
+ RECBAS = ONE / BETA
+ Z = BETA - ONE
+ Y = ZERO
+ DO 20 I = 1, P
+ Z = Z*RECBAS
+ IF( Y.LT.ONE )
+ $ OLDY = Y
+ Y = DLAMC3( Y, Z )
+ 20 CONTINUE
+ IF( Y.GE.ONE )
+ $ Y = OLDY
+*
+* Now multiply by BETA**EMAX to get RMAX.
+*
+ DO 30 I = 1, EMAX
+ Y = DLAMC3( Y*BETA, ZERO )
+ 30 CONTINUE
+*
+ RMAX = Y
+ RETURN
+*
+* End of DLAMC5
+*
+ END
+*> \brief \b IPARMQ
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+*> \htmlonly
+*> Download IPARMQ + dependencies
+*>
+*> [TGZ]
+*>
+*> [ZIP]
+*>
+*> [TXT]
+*> \endhtmlonly
+*
+* Definition:
+* ===========
+*
+* INTEGER FUNCTION IPARMQ( ISPEC, NAME, OPTS, N, ILO, IHI, LWORK )
+*
+* .. Scalar Arguments ..
+* INTEGER IHI, ILO, ISPEC, LWORK, N
+* CHARACTER NAME*( * ), OPTS*( * )
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> This program sets problem and machine dependent parameters
+*> useful for xHSEQR and related subroutines for eigenvalue
+*> problems. It is called whenever
+*> IPARMQ is called with 12 <= ISPEC <= 16
+*> \endverbatim
+*
+* Arguments:
+* ==========
+*
+*> \param[in] ISPEC
+*> \verbatim
+*> ISPEC is integer scalar
+*> ISPEC specifies which tunable parameter IPARMQ should
+*> return.
+*>
+*> ISPEC=12: (INMIN) Matrices of order nmin or less
+*> are sent directly to xLAHQR, the implicit
+*> double shift QR algorithm. NMIN must be
+*> at least 11.
+*>
+*> ISPEC=13: (INWIN) Size of the deflation window.
+*> This is best set greater than or equal to
+*> the number of simultaneous shifts NS.
+*> Larger matrices benefit from larger deflation
+*> windows.
+*>
+*> ISPEC=14: (INIBL) Determines when to stop nibbling and
+*> invest in an (expensive) multi-shift QR sweep.
+*> If the aggressive early deflation subroutine
+*> finds LD converged eigenvalues from an order
+*> NW deflation window and LD.GT.(NW*NIBBLE)/100,
+*> then the next QR sweep is skipped and early
+*> deflation is applied immediately to the
+*> remaining active diagonal block. Setting
+*> IPARMQ(ISPEC=14) = 0 causes TTQRE to skip a
+*> multi-shift QR sweep whenever early deflation
+*> finds a converged eigenvalue. Setting
+*> IPARMQ(ISPEC=14) greater than or equal to 100
+*> prevents TTQRE from skipping a multi-shift
+*> QR sweep.
+*>
+*> ISPEC=15: (NSHFTS) The number of simultaneous shifts in
+*> a multi-shift QR iteration.
+*>
+*> ISPEC=16: (IACC22) IPARMQ is set to 0, 1 or 2 with the
+*> following meanings.
+*> 0: During the multi-shift QR/QZ sweep,
+*> blocked eigenvalue reordering, blocked
+*> Hessenberg-triangular reduction,
+*> reflections and/or rotations are not
+*> accumulated when updating the
+*> far-from-diagonal matrix entries.
+*> 1: During the multi-shift QR/QZ sweep,
+*> blocked eigenvalue reordering, blocked
+*> Hessenberg-triangular reduction,
+*> reflections and/or rotations are
+*> accumulated, and matrix-matrix
+*> multiplication is used to update the
+*> far-from-diagonal matrix entries.
+*> 2: During the multi-shift QR/QZ sweep,
+*> blocked eigenvalue reordering, blocked
+*> Hessenberg-triangular reduction,
+*> reflections and/or rotations are
+*> accumulated, and 2-by-2 block structure
+*> is exploited during matrix-matrix
+*> multiplies.
+*> (If xTRMM is slower than xGEMM, then
+*> IPARMQ(ISPEC=16)=1 may be more efficient than
+*> IPARMQ(ISPEC=16)=2 despite the greater level of
+*> arithmetic work implied by the latter choice.)
+*> \endverbatim
+*>
+*> \param[in] NAME
+*> \verbatim
+*> NAME is character string
+*> Name of the calling subroutine
+*> \endverbatim
+*>
+*> \param[in] OPTS
+*> \verbatim
+*> OPTS is character string
+*> This is a concatenation of the string arguments to
+*> TTQRE.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is integer scalar
+*> N is the order of the Hessenberg matrix H.
+*> \endverbatim
+*>
+*> \param[in] ILO
+*> \verbatim
+*> ILO is INTEGER
+*> \endverbatim
+*>
+*> \param[in] IHI
+*> \verbatim
+*> IHI is INTEGER
+*> It is assumed that H is already upper triangular
+*> in rows and columns 1:ILO-1 and IHI+1:N.
+*> \endverbatim
+*>
+*> \param[in] LWORK
+*> \verbatim
+*> LWORK is integer scalar
+*> The amount of workspace available.
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2015
+*
+*> \ingroup auxOTHERauxiliary
+*
+*> \par Further Details:
+* =====================
+*>
+*> \verbatim
+*>
+*> Little is known about how best to choose these parameters.
+*> It is possible to use different values of the parameters
+*> for each of CHSEQR, DHSEQR, SHSEQR and ZHSEQR.
+*>
+*> It is probably best to choose different parameters for
+*> different matrices and different parameters at different
+*> times during the iteration, but this has not been
+*> implemented --- yet.
+*>
+*>
+*> The best choices of most of the parameters depend
+*> in an ill-understood way on the relative execution
+*> rate of xLAQR3 and xLAQR5 and on the nature of each
+*> particular eigenvalue problem. Experiment may be the
+*> only practical way to determine which choices are most
+*> effective.
+*>
+*> Following is a list of default values supplied by IPARMQ.
+*> These defaults may be adjusted in order to attain better
+*> performance in any particular computational environment.
+*>
+*> IPARMQ(ISPEC=12) The xLAHQR vs xLAQR0 crossover point.
+*> Default: 75. (Must be at least 11.)
+*>
+*> IPARMQ(ISPEC=13) Recommended deflation window size.
+*> This depends on ILO, IHI and NS, the
+*> number of simultaneous shifts returned
+*> by IPARMQ(ISPEC=15). The default for
+*> (IHI-ILO+1).LE.500 is NS. The default
+*> for (IHI-ILO+1).GT.500 is 3*NS/2.
+*>
+*> IPARMQ(ISPEC=14) Nibble crossover point. Default: 14.
+*>
+*> IPARMQ(ISPEC=15) Number of simultaneous shifts, NS.
+*> a multi-shift QR iteration.
+*>
+*> If IHI-ILO+1 is ...
+*>
+*> greater than ...but less ... the
+*> or equal to ... than default is
+*>
+*> 0 30 NS = 2+
+*> 30 60 NS = 4+
+*> 60 150 NS = 10
+*> 150 590 NS = **
+*> 590 3000 NS = 64
+*> 3000 6000 NS = 128
+*> 6000 infinity NS = 256
+*>
+*> (+) By default matrices of this order are
+*> passed to the implicit double shift routine
+*> xLAHQR. See IPARMQ(ISPEC=12) above. These
+*> values of NS are used only in case of a rare
+*> xLAHQR failure.
+*>
+*> (**) The asterisks (**) indicate an ad-hoc
+*> function increasing from 10 to 64.
+*>
+*> IPARMQ(ISPEC=16) Select structured matrix multiply.
+*> (See ISPEC=16 above for details.)
+*> Default: 3.
+*> \endverbatim
+*>
+* =====================================================================
+ INTEGER FUNCTION IPARMQ( ISPEC, NAME, OPTS, N, ILO, IHI, LWORK )
+*
+* -- LAPACK auxiliary routine (version 3.6.0) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2015
+*
+* .. Scalar Arguments ..
+ INTEGER IHI, ILO, ISPEC, LWORK, N
+ CHARACTER NAME*( * ), OPTS*( * )
+*
+* ================================================================
+* .. Parameters ..
+ INTEGER INMIN, INWIN, INIBL, ISHFTS, IACC22
+ PARAMETER ( INMIN = 12, INWIN = 13, INIBL = 14,
+ $ ISHFTS = 15, IACC22 = 16 )
+ INTEGER NMIN, K22MIN, KACMIN, NIBBLE, KNWSWP
+ PARAMETER ( NMIN = 75, K22MIN = 14, KACMIN = 14,
+ $ NIBBLE = 14, KNWSWP = 500 )
+ REAL TWO
+ PARAMETER ( TWO = 2.0 )
+* ..
+* .. Local Scalars ..
+ INTEGER NH, NS
+ INTEGER I, IC, IZ
+ CHARACTER SUBNAM*6
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC LOG, MAX, MOD, NINT, REAL
+* ..
+* .. Executable Statements ..
+ IF( ( ISPEC.EQ.ISHFTS ) .OR. ( ISPEC.EQ.INWIN ) .OR.
+ $ ( ISPEC.EQ.IACC22 ) ) THEN
+*
+* ==== Set the number simultaneous shifts ====
+*
+ NH = IHI - ILO + 1
+ NS = 2
+ IF( NH.GE.30 )
+ $ NS = 4
+ IF( NH.GE.60 )
+ $ NS = 10
+ IF( NH.GE.150 )
+ $ NS = MAX( 10, NH / NINT( LOG( REAL( NH ) ) / LOG( TWO ) ) )
+ IF( NH.GE.590 )
+ $ NS = 64
+ IF( NH.GE.3000 )
+ $ NS = 128
+ IF( NH.GE.6000 )
+ $ NS = 256
+ NS = MAX( 2, NS-MOD( NS, 2 ) )
+ END IF
+*
+ IF( ISPEC.EQ.INMIN ) THEN
+*
+*
+* ===== Matrices of order smaller than NMIN get sent
+* . to xLAHQR, the classic double shift algorithm.
+* . This must be at least 11. ====
+*
+ IPARMQ = NMIN
+*
+ ELSE IF( ISPEC.EQ.INIBL ) THEN
+*
+* ==== INIBL: skip a multi-shift qr iteration and
+* . whenever aggressive early deflation finds
+* . at least (NIBBLE*(window size)/100) deflations. ====
+*
+ IPARMQ = NIBBLE
+*
+ ELSE IF( ISPEC.EQ.ISHFTS ) THEN
+*
+* ==== NSHFTS: The number of simultaneous shifts =====
+*
+ IPARMQ = NS
+*
+ ELSE IF( ISPEC.EQ.INWIN ) THEN
+*
+* ==== NW: deflation window size. ====
+*
+ IF( NH.LE.KNWSWP ) THEN
+ IPARMQ = NS
+ ELSE
+ IPARMQ = 3*NS / 2
+ END IF
+*
+ ELSE IF( ISPEC.EQ.IACC22 ) THEN
+*
+* ==== IACC22: Whether to accumulate reflections
+* . before updating the far-from-diagonal elements
+* . and whether to use 2-by-2 block structure while
+* . doing it. A small amount of work could be saved
+* . by making this choice dependent also upon the
+* . NH=IHI-ILO+1.
+*
+*
+* Convert NAME to upper case if the first character is lower case.
+*
+ IPARMQ = 0
+ SUBNAM = NAME
+ IC = ICHAR( SUBNAM( 1: 1 ) )
+ IZ = ICHAR( 'Z' )
+ IF( IZ.EQ.90 .OR. IZ.EQ.122 ) THEN
+*
+* ASCII character set
+*
+ IF( IC.GE.97 .AND. IC.LE.122 ) THEN
+ SUBNAM( 1: 1 ) = CHAR( IC-32 )
+ DO I = 2, 6
+ IC = ICHAR( SUBNAM( I: I ) )
+ IF( IC.GE.97 .AND. IC.LE.122 )
+ $ SUBNAM( I: I ) = CHAR( IC-32 )
+ END DO
+ END IF
+*
+ ELSE IF( IZ.EQ.233 .OR. IZ.EQ.169 ) THEN
+*
+* EBCDIC character set
+*
+ IF( ( IC.GE.129 .AND. IC.LE.137 ) .OR.
+ $ ( IC.GE.145 .AND. IC.LE.153 ) .OR.
+ $ ( IC.GE.162 .AND. IC.LE.169 ) ) THEN
+ SUBNAM( 1: 1 ) = CHAR( IC+64 )
+ DO I = 2, 6
+ IC = ICHAR( SUBNAM( I: I ) )
+ IF( ( IC.GE.129 .AND. IC.LE.137 ) .OR.
+ $ ( IC.GE.145 .AND. IC.LE.153 ) .OR.
+ $ ( IC.GE.162 .AND. IC.LE.169 ) )SUBNAM( I:
+ $ I ) = CHAR( IC+64 )
+ END DO
+ END IF
+*
+ ELSE IF( IZ.EQ.218 .OR. IZ.EQ.250 ) THEN
+*
+* Prime machines: ASCII+128
+*
+ IF( IC.GE.225 .AND. IC.LE.250 ) THEN
+ SUBNAM( 1: 1 ) = CHAR( IC-32 )
+ DO I = 2, 6
+ IC = ICHAR( SUBNAM( I: I ) )
+ IF( IC.GE.225 .AND. IC.LE.250 )
+ $ SUBNAM( I: I ) = CHAR( IC-32 )
+ END DO
+ END IF
+ END IF
+*
+ IF( SUBNAM( 2:6 ).EQ.'GGHRD' .OR.
+ $ SUBNAM( 2:6 ).EQ.'GGHD3' ) THEN
+ IPARMQ = 1
+ IF( NH.GE.K22MIN )
+ $ IPARMQ = 2
+ ELSE IF ( SUBNAM( 4:6 ).EQ.'EXC' ) THEN
+ IF( NH.GE.KACMIN )
+ $ IPARMQ = 1
+ IF( NH.GE.K22MIN )
+ $ IPARMQ = 2
+ ELSE IF ( SUBNAM( 2:6 ).EQ.'HSEQR' .OR.
+ $ SUBNAM( 2:5 ).EQ.'LAQR' ) THEN
+ IF( NS.GE.KACMIN )
+ $ IPARMQ = 1
+ IF( NS.GE.K22MIN )
+ $ IPARMQ = 2
+ END IF
+*
+ ELSE
+* ===== invalid value of ispec =====
+ IPARMQ = -1
+*
+ END IF
+*
+* ==== End of IPARMQ ====
+*
+ END
+C
+C======================================================================
+C
+*> \brief \b IZAMAX
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition:
+* ===========
+*
+* INTEGER FUNCTION IZAMAX(N,ZX,INCX)
+*
+* .. Scalar Arguments ..
+* INTEGER INCX,N
+* ..
+* .. Array Arguments ..
+* COMPLEX*16 ZX(*)
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> IZAMAX finds the index of the first element having maximum |Re(.)| + |Im(.)|
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2015
+*
+*> \ingroup aux_blas
+*
+*> \par Further Details:
+* =====================
+*>
+*> \verbatim
+*>
+*> jack dongarra, 1/15/85.
+*> modified 3/93 to return if incx .le. 0.
+*> modified 12/3/93, array(1) declarations changed to array(*)
+*> \endverbatim
+*>
+* =====================================================================
+ INTEGER FUNCTION IZAMAX(N,ZX,INCX)
+*
+* -- Reference BLAS level1 routine (version 3.6.0) --
+* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2015
+*
+* .. Scalar Arguments ..
+ INTEGER INCX,N
+* ..
+* .. Array Arguments ..
+ COMPLEX*16 ZX(*)
+* ..
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ DOUBLE PRECISION DMAX
+ INTEGER I,IX
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DCABS1
+ EXTERNAL DCABS1
+* ..
+ IZAMAX = 0
+ IF (N.LT.1 .OR. INCX.LE.0) RETURN
+ IZAMAX = 1
+ IF (N.EQ.1) RETURN
+ IF (INCX.EQ.1) THEN
+*
+* code for increment equal to 1
+*
+ DMAX = DCABS1(ZX(1))
+ DO I = 2,N
+ IF (DCABS1(ZX(I)).GT.DMAX) THEN
+ IZAMAX = I
+ DMAX = DCABS1(ZX(I))
+ END IF
+ END DO
+ ELSE
+*
+* code for increment not equal to 1
+*
+ IX = 1
+ DMAX = DCABS1(ZX(1))
+ IX = IX + INCX
+ DO I = 2,N
+ IF (DCABS1(ZX(IX)).GT.DMAX) THEN
+ IZAMAX = I
+ DMAX = DCABS1(ZX(IX))
+ END IF
+ IX = IX + INCX
+ END DO
+ END IF
+ RETURN
+ END
+C
+C=======================================================================
+C
+*> \brief \b DCABS1
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition:
+* ===========
+*
+* DOUBLE PRECISION FUNCTION DCABS1(Z)
+*
+* .. Scalar Arguments ..
+* COMPLEX*16 Z
+* ..
+* ..
+*
+*
+*> \par Purpose:
+* =============
+*>
+*> \verbatim
+*>
+*> DCABS1 computes |Re(.)| + |Im(.)| of a double complex number
+*> \endverbatim
+*
+* Authors:
+* ========
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2015
+*
+*> \ingroup double_blas_level1
+*
+* =====================================================================
+ DOUBLE PRECISION FUNCTION DCABS1(Z)
+*
+* -- Reference BLAS level1 routine (version 3.6.0) --
+* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2015
+*
+* .. Scalar Arguments ..
+ COMPLEX*16 Z
+* ..
+* ..
+* =====================================================================
+*
+* .. Intrinsic Functions ..
+ INTRINSIC ABS,DBLE,DIMAG
+*
+ DCABS1 = ABS(DBLE(Z)) + ABS(DIMAG(Z))
+ RETURN
+ END
+C
+