001:       SUBROUTINE SLASWP( N, A, LDA, K1, K2, IPIV, INCX )
002: *
003: *  -- LAPACK auxiliary routine (version 3.2) --
004: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
005: *     November 2006
006: *
007: *     .. Scalar Arguments ..
008:       INTEGER            INCX, K1, K2, LDA, N
009: *     ..
010: *     .. Array Arguments ..
011:       INTEGER            IPIV( * )
012:       REAL               A( LDA, * )
013: *     ..
014: *
015: *  Purpose
016: *  =======
017: *
018: *  SLASWP performs a series of row interchanges on the matrix A.
019: *  One row interchange is initiated for each of rows K1 through K2 of A.
020: *
021: *  Arguments
022: *  =========
023: *
024: *  N       (input) INTEGER
025: *          The number of columns of the matrix A.
026: *
027: *  A       (input/output) REAL array, dimension (LDA,N)
028: *          On entry, the matrix of column dimension N to which the row
029: *          interchanges will be applied.
030: *          On exit, the permuted matrix.
031: *
032: *  LDA     (input) INTEGER
033: *          The leading dimension of the array A.
034: *
035: *  K1      (input) INTEGER
036: *          The first element of IPIV for which a row interchange will
037: *          be done.
038: *
039: *  K2      (input) INTEGER
040: *          The last element of IPIV for which a row interchange will
041: *          be done.
042: *
043: *  IPIV    (input) INTEGER array, dimension (K2*abs(INCX))
044: *          The vector of pivot indices.  Only the elements in positions
045: *          K1 through K2 of IPIV are accessed.
046: *          IPIV(K) = L implies rows K and L are to be interchanged.
047: *
048: *  INCX    (input) INTEGER
049: *          The increment between successive values of IPIV.  If IPIV
050: *          is negative, the pivots are applied in reverse order.
051: *
052: *  Further Details
053: *  ===============
054: *
055: *  Modified by
056: *   R. C. Whaley, Computer Science Dept., Univ. of Tenn., Knoxville, USA
057: *
058: * =====================================================================
059: *
060: *     .. Local Scalars ..
061:       INTEGER            I, I1, I2, INC, IP, IX, IX0, J, K, N32
062:       REAL               TEMP
063: *     ..
064: *     .. Executable Statements ..
065: *
066: *     Interchange row I with row IPIV(I) for each of rows K1 through K2.
067: *
068:       IF( INCX.GT.0 ) THEN
069:          IX0 = K1
070:          I1 = K1
071:          I2 = K2
072:          INC = 1
073:       ELSE IF( INCX.LT.0 ) THEN
074:          IX0 = 1 + ( 1-K2 )*INCX
075:          I1 = K2
076:          I2 = K1
077:          INC = -1
078:       ELSE
079:          RETURN
080:       END IF
081: *
082:       N32 = ( N / 32 )*32
083:       IF( N32.NE.0 ) THEN
084:          DO 30 J = 1, N32, 32
085:             IX = IX0
086:             DO 20 I = I1, I2, INC
087:                IP = IPIV( IX )
088:                IF( IP.NE.I ) THEN
089:                   DO 10 K = J, J + 31
090:                      TEMP = A( I, K )
091:                      A( I, K ) = A( IP, K )
092:                      A( IP, K ) = TEMP
093:    10             CONTINUE
094:                END IF
095:                IX = IX + INCX
096:    20       CONTINUE
097:    30    CONTINUE
098:       END IF
099:       IF( N32.NE.N ) THEN
100:          N32 = N32 + 1
101:          IX = IX0
102:          DO 50 I = I1, I2, INC
103:             IP = IPIV( IX )
104:             IF( IP.NE.I ) THEN
105:                DO 40 K = N32, N
106:                   TEMP = A( I, K )
107:                   A( I, K ) = A( IP, K )
108:                   A( IP, K ) = TEMP
109:    40          CONTINUE
110:             END IF
111:             IX = IX + INCX
112:    50    CONTINUE
113:       END IF
114: *
115:       RETURN
116: *
117: *     End of SLASWP
118: *
119:       END
120: