LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlat2s.f
Go to the documentation of this file.
1*> \brief \b DLAT2S converts a double-precision triangular matrix to a single-precision triangular matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLAT2S + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlat2s.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlat2s.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlat2s.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLAT2S( UPLO, N, A, LDA, SA, LDSA, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDA, LDSA, N
24* ..
25* .. Array Arguments ..
26* REAL SA( LDSA, * )
27* DOUBLE PRECISION A( LDA, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> DLAT2S converts a DOUBLE PRECISION triangular matrix, SA, to a SINGLE
37*> PRECISION triangular matrix, A.
38*>
39*> RMAX is the overflow for the SINGLE PRECISION arithmetic
40*> DLAS2S 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] UPLO
50*> \verbatim
51*> UPLO is CHARACTER*1
52*> = 'U': A is upper triangular;
53*> = 'L': A is lower triangular.
54*> \endverbatim
55*>
56*> \param[in] N
57*> \verbatim
58*> N is INTEGER
59*> The number of rows and columns of the matrix A. N >= 0.
60*> \endverbatim
61*>
62*> \param[in] A
63*> \verbatim
64*> A is DOUBLE PRECISION array, dimension (LDA,N)
65*> On entry, the N-by-N triangular coefficient matrix A.
66*> \endverbatim
67*>
68*> \param[in] LDA
69*> \verbatim
70*> LDA is INTEGER
71*> The leading dimension of the array A. LDA >= max(1,N).
72*> \endverbatim
73*>
74*> \param[out] SA
75*> \verbatim
76*> SA is REAL array, dimension (LDSA,N)
77*> Only the UPLO part of SA is referenced. On exit, if INFO=0,
78*> the N-by-N coefficient matrix SA; if INFO>0, the content of
79*> the UPLO part of SA is unspecified.
80*> \endverbatim
81*>
82*> \param[in] LDSA
83*> \verbatim
84*> LDSA is INTEGER
85*> The leading dimension of the array SA. LDSA >= max(1,M).
86*> \endverbatim
87*>
88*> \param[out] INFO
89*> \verbatim
90*> INFO is INTEGER
91*> = 0: successful exit.
92*> = 1: an entry of the matrix A is greater than the SINGLE
93*> PRECISION overflow threshold, in this case, the content
94*> of the UPLO part of SA in exit is unspecified.
95*> \endverbatim
96*
97* Authors:
98* ========
99*
100*> \author Univ. of Tennessee
101*> \author Univ. of California Berkeley
102*> \author Univ. of Colorado Denver
103*> \author NAG Ltd.
104*
105*> \ingroup _lat2_
106*
107* =====================================================================
108 SUBROUTINE dlat2s( UPLO, N, A, LDA, SA, LDSA, INFO )
109*
110* -- LAPACK auxiliary routine --
111* -- LAPACK is a software package provided by Univ. of Tennessee, --
112* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
113*
114* .. Scalar Arguments ..
115 CHARACTER UPLO
116 INTEGER INFO, LDA, LDSA, N
117* ..
118* .. Array Arguments ..
119 REAL SA( LDSA, * )
120 DOUBLE PRECISION A( LDA, * )
121* ..
122*
123* =====================================================================
124*
125* .. Local Scalars ..
126 INTEGER I, J
127 DOUBLE PRECISION RMAX
128 LOGICAL UPPER
129* ..
130* .. External Functions ..
131 REAL SLAMCH
132 LOGICAL LSAME
133 EXTERNAL slamch, lsame
134* ..
135* .. Intrinsic Functions ..
136 INTRINSIC real
137* ..
138* .. Executable Statements ..
139*
140 rmax = slamch( 'O' )
141 upper = lsame( uplo, 'U' )
142 IF( upper ) THEN
143 DO 20 j = 1, n
144 DO 10 i = 1, j
145 IF( ( a( i, j ).LT.-rmax ) .OR. ( a( i, j ).GT.rmax ) )
146 $ THEN
147 info = 1
148 GO TO 50
149 END IF
150 sa( i, j ) = real( a( i, j ) )
151 10 CONTINUE
152 20 CONTINUE
153 ELSE
154 DO 40 j = 1, n
155 DO 30 i = j, n
156 IF( ( a( i, j ).LT.-rmax ) .OR. ( a( i, j ).GT.rmax ) )
157 $ THEN
158 info = 1
159 GO TO 50
160 END IF
161 sa( i, j ) = real( a( i, j ) )
162 30 CONTINUE
163 40 CONTINUE
164 END IF
165 50 CONTINUE
166*
167 RETURN
168*
169* End of DLAT2S
170*
171 END
subroutine dlat2s(uplo, n, a, lda, sa, ldsa, info)
DLAT2S converts a double-precision triangular matrix to a single-precision triangular matrix.
Definition dlat2s.f:109