Contents


NAME

     blas_dsortv - sorts a real (double precision)  vector  X  in
     increasing  or  decreasing  order using quick sort algorithm
     and overwrite P with the permutation vector

SYNOPSIS

     SUBROUTINE BLAS_DSORTV (SORT, N, X, INCX, P, INCP)

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

     SUBROUTINE BLAS_DSORTV_64 (SORT, N, X, INCX, P, INCP)

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

  F95 INTERFACE
     SUBROUTINE SORTV (X [, SORT] [, P])

     USE SUNPERF

     SUBROUTINE SORTV_64 (X [, SORT] [, P])

     USE SUNPERF

     SORTV covers the functionality of SORT

ARGUMENTS

     SORT (input) INTEGER, indicating sort directions
               SORT = 0, descending
               SORT = 1, ascending
               SORT = other value, error
               SORT is default to 1 for F95 INTERFACE

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

     X (input/output) REAL*8((N-1)*|INCX|+1), the array to be
               sorted
               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, change the sorting direction defined by
               SORT. That is
               If SORT = 0, let SORT = 1, INCX = |INCX|;
               If SORT = 1, let SORT = 0, INCX = |INCX|.

     P (output) INTEGER((N-1)*|INCP|+1), the permutation (index)
               vector recording the details of  the  interchanges
               of  the  elements of X during sorting. That is X =
               P*X. In this implementation, P contains the  index
               of sorted X.

     INCP (input) INTEGER, increment fpr P
               INCP must not be zero. INCP could be negative.  If
               INCP < 0, store P(i) in reverse order. 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)).

SEE ALSO

     blas_dsort(3P), blas_dpermute(3P)