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