LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zlag2c.f
Go to the documentation of this file.
1*> \brief \b ZLAG2C converts a complex double precision matrix to a complex single precision matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZLAG2C + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlag2c.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlag2c.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlag2c.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZLAG2C( M, N, A, LDA, SA, LDSA, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, LDA, LDSA, M, N
23* ..
24* .. Array Arguments ..
25* COMPLEX SA( LDSA, * )
26* COMPLEX*16 A( LDA, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> ZLAG2C converts a COMPLEX*16 matrix, SA, to a COMPLEX matrix, A.
36*>
37*> RMAX is the overflow for the SINGLE PRECISION arithmetic
38*> ZLAG2C checks that all the entries of A are between -RMAX and
39*> RMAX. If not the conversion is aborted and a flag is raised.
40*>
41*> This is an auxiliary routine so there is no argument checking.
42*> \endverbatim
43*
44* Arguments:
45* ==========
46*
47*> \param[in] M
48*> \verbatim
49*> M is INTEGER
50*> The number of lines of the matrix A. M >= 0.
51*> \endverbatim
52*>
53*> \param[in] N
54*> \verbatim
55*> N is INTEGER
56*> The number of columns of the matrix A. N >= 0.
57*> \endverbatim
58*>
59*> \param[in] A
60*> \verbatim
61*> A is COMPLEX*16 array, dimension (LDA,N)
62*> On entry, the M-by-N coefficient matrix A.
63*> \endverbatim
64*>
65*> \param[in] LDA
66*> \verbatim
67*> LDA is INTEGER
68*> The leading dimension of the array A. LDA >= max(1,M).
69*> \endverbatim
70*>
71*> \param[out] SA
72*> \verbatim
73*> SA is COMPLEX array, dimension (LDSA,N)
74*> On exit, if INFO=0, the M-by-N coefficient matrix SA; if
75*> INFO>0, the content of SA is unspecified.
76*> \endverbatim
77*>
78*> \param[in] LDSA
79*> \verbatim
80*> LDSA is INTEGER
81*> The leading dimension of the array SA. LDSA >= max(1,M).
82*> \endverbatim
83*>
84*> \param[out] INFO
85*> \verbatim
86*> INFO is INTEGER
87*> = 0: successful exit.
88*> = 1: an entry of the matrix A is greater than the SINGLE
89*> PRECISION overflow threshold, in this case, the content
90*> of SA in exit is unspecified.
91*> \endverbatim
92*
93* Authors:
94* ========
95*
96*> \author Univ. of Tennessee
97*> \author Univ. of California Berkeley
98*> \author Univ. of Colorado Denver
99*> \author NAG Ltd.
100*
101*> \ingroup _lag2_
102*
103* =====================================================================
104 SUBROUTINE zlag2c( M, N, A, LDA, SA, LDSA, INFO )
105*
106* -- LAPACK auxiliary routine --
107* -- LAPACK is a software package provided by Univ. of Tennessee, --
108* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
109*
110* .. Scalar Arguments ..
111 INTEGER INFO, LDA, LDSA, M, N
112* ..
113* .. Array Arguments ..
114 COMPLEX SA( LDSA, * )
115 COMPLEX*16 A( LDA, * )
116* ..
117*
118* =====================================================================
119*
120* .. Local Scalars ..
121 INTEGER I, J
122 DOUBLE PRECISION RMAX
123* ..
124* .. Intrinsic Functions ..
125 INTRINSIC dble, dimag, cmplx
126* ..
127* .. External Functions ..
128 REAL SLAMCH
129 EXTERNAL slamch
130* ..
131* .. Executable Statements ..
132*
133 rmax = slamch( 'O' )
134 DO 20 j = 1, n
135 DO 10 i = 1, m
136 IF( ( dble( a( i, j ) ).LT.-rmax ) .OR.
137 $ ( dble( a( i, j ) ).GT.rmax ) .OR.
138 $ ( dimag( a( i, j ) ).LT.-rmax ) .OR.
139 $ ( dimag( a( i, j ) ).GT.rmax ) ) THEN
140 info = 1
141 GO TO 30
142 END IF
143 sa( i, j ) = cmplx( a( i, j ) )
144 10 CONTINUE
145 20 CONTINUE
146 info = 0
147 30 CONTINUE
148 RETURN
149*
150* End of ZLAG2C
151*
152 END
subroutine zlag2c(m, n, a, lda, sa, ldsa, info)
ZLAG2C converts a complex double precision matrix to a complex single precision matrix.
Definition zlag2c.f:105