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