STYLE: Remove trailing whitespace in Fortran files
[platform/upstream/lapack.git] / SRC / zlacp2.f
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 *> \htmlonly
9 *> Download ZLACP2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlacp2.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlacp2.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacp2.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE ZLACP2( 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 *       DOUBLE PRECISION   A( LDA, * )
29 *       COMPLEX*16         B( LDB, * )
30 *       ..
31 *
32 *
33 *> \par Purpose:
34 *  =============
35 *>
36 *> \verbatim
37 *>
38 *> ZLACP2 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 DOUBLE PRECISION 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*16 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 *> \date September 2012
101 *
102 *> \ingroup complex16OTHERauxiliary
103 *
104 *  =====================================================================
105       SUBROUTINE ZLACP2( UPLO, M, N, A, LDA, B, LDB )
106 *
107 *  -- LAPACK auxiliary routine (version 3.4.2) --
108 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
109 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
110 *     September 2012
111 *
112 *     .. Scalar Arguments ..
113       CHARACTER          UPLO
114       INTEGER            LDA, LDB, M, N
115 *     ..
116 *     .. Array Arguments ..
117       DOUBLE PRECISION   A( LDA, * )
118       COMPLEX*16         B( LDB, * )
119 *     ..
120 *
121 *  =====================================================================
122 *
123 *     .. Local Scalars ..
124       INTEGER            I, J
125 *     ..
126 *     .. External Functions ..
127       LOGICAL            LSAME
128       EXTERNAL           LSAME
129 *     ..
130 *     .. Intrinsic Functions ..
131       INTRINSIC          MIN
132 *     ..
133 *     .. Executable Statements ..
134 *
135       IF( LSAME( UPLO, 'U' ) ) THEN
136          DO 20 J = 1, N
137             DO 10 I = 1, MIN( J, M )
138                B( I, J ) = A( I, J )
139    10       CONTINUE
140    20    CONTINUE
141 *
142       ELSE IF( LSAME( UPLO, 'L' ) ) THEN
143          DO 40 J = 1, N
144             DO 30 I = J, M
145                B( I, J ) = A( I, J )
146    30       CONTINUE
147    40    CONTINUE
148 *
149       ELSE
150          DO 60 J = 1, N
151             DO 50 I = 1, M
152                B( I, J ) = A( I, J )
153    50       CONTINUE
154    60    CONTINUE
155       END IF
156 *
157       RETURN
158 *
159 *     End of ZLACP2
160 *
161       END