1 *> \brief \b ZLAG2C converts a complex double precision matrix to a complex single precision matrix.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZLAG2C + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlag2c.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlag2c.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlag2c.f">
21 * SUBROUTINE ZLAG2C( M, N, A, LDA, SA, LDSA, INFO )
23 * .. Scalar Arguments ..
24 * INTEGER INFO, LDA, LDSA, M, N
26 * .. Array Arguments ..
27 * COMPLEX SA( LDSA, * )
28 * COMPLEX*16 A( LDA, * )
37 *> ZLAG2C converts a COMPLEX*16 matrix, SA, to a COMPLEX matrix, A.
39 *> RMAX is the overflow for the SINGLE PRECISION arithmetic
40 *> ZLAG2C checks that all the entries of A are between -RMAX and
41 *> RMAX. If not the conversion is aborted and a flag is raised.
43 *> This is an auxiliary routine so there is no argument checking.
52 *> The number of lines of the matrix A. M >= 0.
58 *> The number of columns of the matrix A. N >= 0.
63 *> A is COMPLEX*16 array, dimension (LDA,N)
64 *> On entry, the M-by-N coefficient matrix A.
70 *> The leading dimension of the array A. LDA >= max(1,M).
75 *> SA is COMPLEX array, dimension (LDSA,N)
76 *> On exit, if INFO=0, the M-by-N coefficient matrix SA; if
77 *> INFO>0, the content of SA is unspecified.
83 *> The leading dimension of the array SA. LDSA >= max(1,M).
89 *> = 0: successful exit.
90 *> = 1: an entry of the matrix A is greater than the SINGLE
91 *> PRECISION overflow threshold, in this case, the content
92 *> of SA in exit is unspecified.
98 *> \author Univ. of Tennessee
99 *> \author Univ. of California Berkeley
100 *> \author Univ. of Colorado Denver
103 *> \date September 2012
105 *> \ingroup complex16OTHERauxiliary
107 * =====================================================================
108 SUBROUTINE ZLAG2C( M, N, A, LDA, SA, LDSA, INFO )
110 * -- LAPACK auxiliary routine (version 3.4.2) --
111 * -- LAPACK is a software package provided by Univ. of Tennessee, --
112 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
115 * .. Scalar Arguments ..
116 INTEGER INFO, LDA, LDSA, M, N
118 * .. Array Arguments ..
119 COMPLEX SA( LDSA, * )
120 COMPLEX*16 A( LDA, * )
123 * =====================================================================
125 * .. Local Scalars ..
127 DOUBLE PRECISION RMAX
129 * .. Intrinsic Functions ..
130 INTRINSIC DBLE, DIMAG
132 * .. External Functions ..
136 * .. Executable Statements ..
141 IF( ( DBLE( A( I, J ) ).LT.-RMAX ) .OR.
142 $ ( DBLE( A( I, J ) ).GT.RMAX ) .OR.
143 $ ( DIMAG( A( I, J ) ).LT.-RMAX ) .OR.
144 $ ( DIMAG( A( I, J ) ).GT.RMAX ) ) THEN
148 SA( I, J ) = A( I, J )