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