Statistiques
| Révision :

root / src / lapack / double / dlacpy.f @ 8

Historique | Voir | Annoter | Télécharger (2,41 ko)

1 1 pfleura2
      SUBROUTINE DLACPY( UPLO, M, N, A, LDA, B, LDB )
2 1 pfleura2
*
3 1 pfleura2
*  -- LAPACK auxiliary routine (version 3.2) --
4 1 pfleura2
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
5 1 pfleura2
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 1 pfleura2
*     November 2006
7 1 pfleura2
*
8 1 pfleura2
*     .. Scalar Arguments ..
9 1 pfleura2
      CHARACTER          UPLO
10 1 pfleura2
      INTEGER            LDA, LDB, M, N
11 1 pfleura2
*     ..
12 1 pfleura2
*     .. Array Arguments ..
13 1 pfleura2
      DOUBLE PRECISION   A( LDA, * ), B( LDB, * )
14 1 pfleura2
*     ..
15 1 pfleura2
*
16 1 pfleura2
*  Purpose
17 1 pfleura2
*  =======
18 1 pfleura2
*
19 1 pfleura2
*  DLACPY copies all or part of a two-dimensional matrix A to another
20 1 pfleura2
*  matrix B.
21 1 pfleura2
*
22 1 pfleura2
*  Arguments
23 1 pfleura2
*  =========
24 1 pfleura2
*
25 1 pfleura2
*  UPLO    (input) CHARACTER*1
26 1 pfleura2
*          Specifies the part of the matrix A to be copied to B.
27 1 pfleura2
*          = 'U':      Upper triangular part
28 1 pfleura2
*          = 'L':      Lower triangular part
29 1 pfleura2
*          Otherwise:  All of the matrix A
30 1 pfleura2
*
31 1 pfleura2
*  M       (input) INTEGER
32 1 pfleura2
*          The number of rows of the matrix A.  M >= 0.
33 1 pfleura2
*
34 1 pfleura2
*  N       (input) INTEGER
35 1 pfleura2
*          The number of columns of the matrix A.  N >= 0.
36 1 pfleura2
*
37 1 pfleura2
*  A       (input) DOUBLE PRECISION array, dimension (LDA,N)
38 1 pfleura2
*          The m by n matrix A.  If UPLO = 'U', only the upper triangle
39 1 pfleura2
*          or trapezoid is accessed; if UPLO = 'L', only the lower
40 1 pfleura2
*          triangle or trapezoid is accessed.
41 1 pfleura2
*
42 1 pfleura2
*  LDA     (input) INTEGER
43 1 pfleura2
*          The leading dimension of the array A.  LDA >= max(1,M).
44 1 pfleura2
*
45 1 pfleura2
*  B       (output) DOUBLE PRECISION array, dimension (LDB,N)
46 1 pfleura2
*          On exit, B = A in the locations specified by UPLO.
47 1 pfleura2
*
48 1 pfleura2
*  LDB     (input) INTEGER
49 1 pfleura2
*          The leading dimension of the array B.  LDB >= max(1,M).
50 1 pfleura2
*
51 1 pfleura2
*  =====================================================================
52 1 pfleura2
*
53 1 pfleura2
*     .. Local Scalars ..
54 1 pfleura2
      INTEGER            I, J
55 1 pfleura2
*     ..
56 1 pfleura2
*     .. External Functions ..
57 1 pfleura2
      LOGICAL            LSAME
58 1 pfleura2
      EXTERNAL           LSAME
59 1 pfleura2
*     ..
60 1 pfleura2
*     .. Intrinsic Functions ..
61 1 pfleura2
      INTRINSIC          MIN
62 1 pfleura2
*     ..
63 1 pfleura2
*     .. Executable Statements ..
64 1 pfleura2
*
65 1 pfleura2
      IF( LSAME( UPLO, 'U' ) ) THEN
66 1 pfleura2
         DO 20 J = 1, N
67 1 pfleura2
            DO 10 I = 1, MIN( J, M )
68 1 pfleura2
               B( I, J ) = A( I, J )
69 1 pfleura2
   10       CONTINUE
70 1 pfleura2
   20    CONTINUE
71 1 pfleura2
      ELSE IF( LSAME( UPLO, 'L' ) ) THEN
72 1 pfleura2
         DO 40 J = 1, N
73 1 pfleura2
            DO 30 I = J, M
74 1 pfleura2
               B( I, J ) = A( I, J )
75 1 pfleura2
   30       CONTINUE
76 1 pfleura2
   40    CONTINUE
77 1 pfleura2
      ELSE
78 1 pfleura2
         DO 60 J = 1, N
79 1 pfleura2
            DO 50 I = 1, M
80 1 pfleura2
               B( I, J ) = A( I, J )
81 1 pfleura2
   50       CONTINUE
82 1 pfleura2
   60    CONTINUE
83 1 pfleura2
      END IF
84 1 pfleura2
      RETURN
85 1 pfleura2
*
86 1 pfleura2
*     End of DLACPY
87 1 pfleura2
*
88 1 pfleura2
      END