Contents


NAME

     blas_spermute - permutes a real array in terms of the permu-
     tation vector P, output by dsortv

SYNOPSIS

     SUBROUTINE BLAS_SPERMUTE (N, P, INCP, X, INCX)

     INTEGER N
     INTEGER P(*)
     INTEGER INCP
     REAL X(*)
     INTEGER INCX

     SUBROUTINE BLAS_SPERMUTE_64 (N, P, INCP, X, INCX)

     INTEGER*8 N
     INTEGER*8 P(*)
     INTEGER*8 INCP
     REAL X(*)
     INTEGER*8  INCX

  F95 INTERFACE
     SUBROUTINE PERMUTE (X, P)

     USE SUNPERF

     SUBROUTINE PERMUTE_64 (X, P)

     USE SUNPERF

ARGUMENTS

     N (input) INTEGER, the number of elements to be permuted in X
               If  N  <= 1, the subroutine returns without trying
               to permute X.

     P (input) INTEGER((N-1)*|INCP|+1), the permutation (index)
               vector defined follows  the  same  conventions  as
               that  for  DTYPE  SORTV. It records the details of
               the interchanges of the elements of X during sort-
               ing. That is X = P*X. In current implementation, P
               contains the index of sorted X.

     INCP  (input) INTEGER, increment for P
               INCP must not be zero. INCP could be negative.  If
               INCP  < 0, the permutation is applied in the oppo-
               site direction.  That is
               If INCP > 0,
                 if INCX > 0,
                   sorted X((i-1)*INCX+1) = X(P((i-1)*INCP+1)),
                 if INCX < 0,
                   sorted X((N-i)*|INCX|+1) = X(P((i-1)*INCP+1));
               If INCP < 0,
                 if INCX > 0,
                   sorted X((i-1)*INCX+1) = X(P((N-i)*|INCP|+1)).
                 if INCX < 0,
                   sorted X((N-i)*|INCX|+1)
                        = X(P((N-i)*|INCP|+1)).

     X (input/output) REAL(KIND)((N-1)*|INCX|+1), the array to be
               permuted. Minimum size (N-1)*|INCX|+1 is required

     INCX  (input) INTEGER, increment for X
               INCX must not be zero. INCX could be negative.  If
               INCX < 0, X will be permuted in a reverse way (see
               the description for INCP above).

SEE ALSO

     blas_ssortv(3P), blas_ssort(3P)