7ff69d02bc1e1573d8f657991c746fd3bb61b200
[platform/upstream/lapack.git] / SRC / zlag2c.f
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 *> \htmlonly
9 *> Download ZLAG2C + dependencies 
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlag2c.f"> 
11 *> [TGZ]</a> 
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlag2c.f"> 
13 *> [ZIP]</a> 
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlag2c.f"> 
15 *> [TXT]</a>
16 *> \endhtmlonly 
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE ZLAG2C( M, N, A, LDA, SA, LDSA, INFO )
22
23 *       .. Scalar Arguments ..
24 *       INTEGER            INFO, LDA, LDSA, M, N
25 *       ..
26 *       .. Array Arguments ..
27 *       COMPLEX            SA( LDSA, * )
28 *       COMPLEX*16         A( LDA, * )
29 *       ..
30 *  
31 *
32 *> \par Purpose:
33 *  =============
34 *>
35 *> \verbatim
36 *>
37 *> ZLAG2C converts a COMPLEX*16 matrix, SA, to a COMPLEX matrix, A.
38 *>
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.
42 *>
43 *> This is an auxiliary routine so there is no argument checking.
44 *> \endverbatim
45 *
46 *  Arguments:
47 *  ==========
48 *
49 *> \param[in] M
50 *> \verbatim
51 *>          M is INTEGER
52 *>          The number of lines of the matrix A.  M >= 0.
53 *> \endverbatim
54 *>
55 *> \param[in] N
56 *> \verbatim
57 *>          N is INTEGER
58 *>          The number of columns of the matrix A.  N >= 0.
59 *> \endverbatim
60 *>
61 *> \param[in] A
62 *> \verbatim
63 *>          A is COMPLEX*16 array, dimension (LDA,N)
64 *>          On entry, the M-by-N coefficient matrix A.
65 *> \endverbatim
66 *>
67 *> \param[in] LDA
68 *> \verbatim
69 *>          LDA is INTEGER
70 *>          The leading dimension of the array A.  LDA >= max(1,M).
71 *> \endverbatim
72 *>
73 *> \param[out] SA
74 *> \verbatim
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.
78 *> \endverbatim
79 *>
80 *> \param[in] LDSA
81 *> \verbatim
82 *>          LDSA is INTEGER
83 *>          The leading dimension of the array SA.  LDSA >= max(1,M).
84 *> \endverbatim
85 *>
86 *> \param[out] INFO
87 *> \verbatim
88 *>          INFO is INTEGER
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.
93 *> \endverbatim
94 *
95 *  Authors:
96 *  ========
97 *
98 *> \author Univ. of Tennessee 
99 *> \author Univ. of California Berkeley 
100 *> \author Univ. of Colorado Denver 
101 *> \author NAG Ltd. 
102 *
103 *> \date September 2012
104 *
105 *> \ingroup complex16OTHERauxiliary
106 *
107 *  =====================================================================
108       SUBROUTINE ZLAG2C( M, N, A, LDA, SA, LDSA, INFO )
109 *
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..--
113 *     September 2012
114 *
115 *     .. Scalar Arguments ..
116       INTEGER            INFO, LDA, LDSA, M, N
117 *     ..
118 *     .. Array Arguments ..
119       COMPLEX            SA( LDSA, * )
120       COMPLEX*16         A( LDA, * )
121 *     ..
122 *
123 *  =====================================================================
124 *
125 *     .. Local Scalars ..
126       INTEGER            I, J
127       DOUBLE PRECISION   RMAX
128 *     ..
129 *     .. Intrinsic Functions ..
130       INTRINSIC          DBLE, DIMAG
131 *     ..
132 *     .. External Functions ..
133       REAL               SLAMCH
134       EXTERNAL           SLAMCH
135 *     ..
136 *     .. Executable Statements ..
137 *
138       RMAX = SLAMCH( 'O' )
139       DO 20 J = 1, N
140          DO 10 I = 1, M
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
145                INFO = 1
146                GO TO 30
147             END IF
148             SA( I, J ) = A( I, J )
149    10    CONTINUE
150    20 CONTINUE
151       INFO = 0
152    30 CONTINUE
153       RETURN
154 *
155 *     End of ZLAG2C
156 *
157       END