1       SUBROUTINE ZLAG2C( M, N, A, LDA, SA, LDSA, INFO )
 2 *
 3 *  -- LAPACK PROTOTYPE auxiliary routine (version 3.3.1) --
 4 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 5 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 6 *  -- April 2011                                                      --
 7 *
 8 *     ..
 9 *     .. Scalar Arguments ..
10       INTEGER            INFO, LDA, LDSA, M, N
11 *     ..
12 *     .. Array Arguments ..
13       COMPLEX            SA( LDSA, * )
14       COMPLEX*16         A( LDA, * )
15 *     ..
16 *
17 *  Purpose
18 *  =======
19 *
20 *  ZLAG2C converts a COMPLEX*16 matrix, SA, to a COMPLEX matrix, A.
21 *
22 *  RMAX is the overflow for the SINGLE PRECISION arithmetic
23 *  ZLAG2C checks that all the entries of A are between -RMAX and
24 *  RMAX. If not the convertion is aborted and a flag is raised.
25 *
26 *  This is an auxiliary routine so there is no argument checking.
27 *
28 *  Arguments
29 *  =========
30 *
31 *  M       (input) INTEGER
32 *          The number of lines of the matrix A.  M >= 0.
33 *
34 *  N       (input) INTEGER
35 *          The number of columns of the matrix A.  N >= 0.
36 *
37 *  A       (input) COMPLEX*16 array, dimension (LDA,N)
38 *          On entry, the M-by-N coefficient matrix A.
39 *
40 *  LDA     (input) INTEGER
41 *          The leading dimension of the array A.  LDA >= max(1,M).
42 *
43 *  SA      (output) COMPLEX array, dimension (LDSA,N)
44 *          On exit, if INFO=0, the M-by-N coefficient matrix SA; if
45 *          INFO>0, the content of SA is unspecified.
46 *
47 *  LDSA    (input) INTEGER
48 *          The leading dimension of the array SA.  LDSA >= max(1,M).
49 *
50 *  INFO    (output) INTEGER
51 *          = 0:  successful exit.
52 *          = 1:  an entry of the matrix A is greater than the SINGLE
53 *                PRECISION overflow threshold, in this case, the content
54 *                of SA in exit is unspecified.
55 *
56 *  =====================================================================
57 *
58 *     .. Local Scalars ..
59       INTEGER            I, J
60       DOUBLE PRECISION   RMAX
61 *     ..
62 *     .. Intrinsic Functions ..
63       INTRINSIC          DBLEDIMAG
64 *     ..
65 *     .. External Functions ..
66       REAL               SLAMCH
67       EXTERNAL           SLAMCH
68 *     ..
69 *     .. Executable Statements ..
70 *
71       RMAX = SLAMCH( 'O' )
72       DO 20 J = 1, N
73          DO 10 I = 1, M
74             IF( ( DBLE( A( I, J ) ).LT.-RMAX ) .OR.
75      $          ( DBLE( A( I, J ) ).GT.RMAX ) .OR.
76      $          ( DIMAG( A( I, J ) ).LT.-RMAX ) .OR.
77      $          ( DIMAG( A( I, J ) ).GT.RMAX ) ) THEN
78                INFO = 1
79                GO TO 30
80             END IF
81             SA( I, J ) = A( I, J )
82    10    CONTINUE
83    20 CONTINUE
84       INFO = 0
85    30 CONTINUE
86       RETURN
87 *
88 *     End of ZLAG2C
89 *
90       END