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