LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zlacp2.f
Go to the documentation of this file.
1*> \brief \b ZLACP2 copies all or part of a real two-dimensional array to a complex array.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZLACP2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlacp2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlacp2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacp2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZLACP2( UPLO, M, N, A, LDA, B, LDB )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER LDA, LDB, M, N
24* ..
25* .. Array Arguments ..
26* DOUBLE PRECISION A( LDA, * )
27* COMPLEX*16 B( LDB, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> ZLACP2 copies all or part of a real two-dimensional matrix A to a
37*> complex matrix B.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] UPLO
44*> \verbatim
45*> UPLO is CHARACTER*1
46*> Specifies the part of the matrix A to be copied to B.
47*> = 'U': Upper triangular part
48*> = 'L': Lower triangular part
49*> Otherwise: All of the matrix A
50*> \endverbatim
51*>
52*> \param[in] M
53*> \verbatim
54*> M is INTEGER
55*> The number of rows of the matrix A. M >= 0.
56*> \endverbatim
57*>
58*> \param[in] N
59*> \verbatim
60*> N is INTEGER
61*> The number of columns of the matrix A. N >= 0.
62*> \endverbatim
63*>
64*> \param[in] A
65*> \verbatim
66*> A is DOUBLE PRECISION array, dimension (LDA,N)
67*> The m by n matrix A. If UPLO = 'U', only the upper trapezium
68*> is accessed; if UPLO = 'L', only the lower trapezium is
69*> accessed.
70*> \endverbatim
71*>
72*> \param[in] LDA
73*> \verbatim
74*> LDA is INTEGER
75*> The leading dimension of the array A. LDA >= max(1,M).
76*> \endverbatim
77*>
78*> \param[out] B
79*> \verbatim
80*> B is COMPLEX*16 array, dimension (LDB,N)
81*> On exit, B = A in the locations specified by UPLO.
82*> \endverbatim
83*>
84*> \param[in] LDB
85*> \verbatim
86*> LDB is INTEGER
87*> The leading dimension of the array B. LDB >= max(1,M).
88*> \endverbatim
89*
90* Authors:
91* ========
92*
93*> \author Univ. of Tennessee
94*> \author Univ. of California Berkeley
95*> \author Univ. of Colorado Denver
96*> \author NAG Ltd.
97*
98*> \ingroup lacp2
99*
100* =====================================================================
101 SUBROUTINE zlacp2( UPLO, M, N, A, LDA, B, LDB )
102*
103* -- LAPACK auxiliary routine --
104* -- LAPACK is a software package provided by Univ. of Tennessee, --
105* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106*
107* .. Scalar Arguments ..
108 CHARACTER UPLO
109 INTEGER LDA, LDB, M, N
110* ..
111* .. Array Arguments ..
112 DOUBLE PRECISION A( LDA, * )
113 COMPLEX*16 B( LDB, * )
114* ..
115*
116* =====================================================================
117*
118* .. Local Scalars ..
119 INTEGER I, J
120* ..
121* .. External Functions ..
122 LOGICAL LSAME
123 EXTERNAL lsame
124* ..
125* .. Intrinsic Functions ..
126 INTRINSIC min
127* ..
128* .. Executable Statements ..
129*
130 IF( lsame( uplo, 'U' ) ) THEN
131 DO 20 j = 1, n
132 DO 10 i = 1, min( j, m )
133 b( i, j ) = a( i, j )
134 10 CONTINUE
135 20 CONTINUE
136*
137 ELSE IF( lsame( uplo, 'L' ) ) THEN
138 DO 40 j = 1, n
139 DO 30 i = j, m
140 b( i, j ) = a( i, j )
141 30 CONTINUE
142 40 CONTINUE
143*
144 ELSE
145 DO 60 j = 1, n
146 DO 50 i = 1, m
147 b( i, j ) = a( i, j )
148 50 CONTINUE
149 60 CONTINUE
150 END IF
151*
152 RETURN
153*
154* End of ZLACP2
155*
156 END
subroutine zlacp2(uplo, m, n, a, lda, b, ldb)
ZLACP2 copies all or part of a real two-dimensional array to a complex array.
Definition zlacp2.f:102