The SORTI and qsorti routines

Fortran version:

Fortran-90 generic routine SORTI() for I/O API-3.2:: compiler selects the appropriate type-specific form depending upon the number and types of the INTEGER, INTEGER*8 or REAL key-lists. Note that the SORTIN*( N[8], M[8], INDX[8], CLIST ) forms do the sort on the basis of the first M or M8 characters in the strings in the CLIST array and ignore the remainder of each table-entry.

For I/O API Versions 3.1 and before, the generic form SORTI(), SORTIC8(), the SORTL*() and the SORTINC*() are not available.

    SUBROUTINE SORTI( N,      INDX,  LIST1[, ... ] )
    SUBROUTINE SORTI( N,      INDX,  CLIST )
    SUBROUTINE SORTI( N8,     INDX8, CLIST )
    SUBROUTINE SORTI( N,  M,  INDX,  CLIST )
    SUBROUTINE SORTI( N8, M8, INDX,  CLIST )

Type-specific forms:

    SUBROUTINE SORTIC(   N,      INDX,  CLIST )
    SUBROUTINE SORTIC4(  N,      INDX,  CLIST )
    SUBROUTINE SORTIC8(  N8,     INDX8, CLIST )
    SUBROUTINE SORTINC4( N,  M,  INDX,  CLIST )
    SUBROUTINE SORTINC8( N8, M8, INDX8, CLIST )

    SUBROUTINE SORTI1( N, INDX, ILIST1 )
    SUBROUTINE SORTI2( N, INDX, ILIST1, ILIST2 )
    SUBROUTINE SORTI3( N, INDX, ILIST1, ILIST2, ILIST3 )
    SUBROUTINE SORTI4( N, INDX, ILIST1, ILIST2, ILIST3, ILIST4 )

    SUBROUTINE SORTL1( N, INDX, LLIST1 )
    SUBROUTINE SORTL2( N, INDX, LLIST1, LLIST2 )
    SUBROUTINE SORTL3( N, INDX, LLIST1, LLIST2, LLIST3 )
    SUBROUTINE SORTL4( N, INDX, LLIST1, LLIST2, LLIST3, LLIST4 )

    SUBROUTINE SORTR1( N, INDX, RLIST1 )
    SUBROUTINE SORTR2( N, INDX, RLIST1, RLIST2 )
    SUBROUTINE SORTR3( N, INDX, RLIST1, RLIST2, RLIST3 )
    SUBROUTINE SORTR4( N, INDX, RLIST1, RLIST2, RLIST3, RLIST4 )

        INTEGER  , INTENT(IN   ) :: N           !  table size
        INTEGER*8, INTENT(IN   ) :: N8          !  table size (for SORT*8() )
        INTEGER  , INTENT(IN   ) :: M           !  significant number of columns in table
        INTEGER*8, INTENT(IN   ) :: M8          !  significant number of columns in table
        INTEGER  , INTENT(INOUT) :: INDX ( N )  !  Fortran-subscript 1...N string-table to be sorted
        INTEGER*8, INTENT(INOUT) :: INDX8( N )  !  Fortran-subscript 1...N string-table to be sorted

        CHARACTER*(*), INTENT(IN   ) :: CLIST     !  table of key strings

        INTEGER  , INTENT(IN   ) :: ILIST1( N ) !  table of first  key-tuple components
        INTEGER  , INTENT(IN   ) :: ILIST2( N ) !  table of second key-tuple components
        INTEGER  , INTENT(IN   ) :: ILIST3( N ) !  table of third  key-tuple components
        INTEGER  , INTENT(IN   ) :: ILIST4( N ) !  table of fourth key-tuple components

        INTEGER*8, INTENT(IN   ) :: LLIST1( N ) !  table of first  key-tuple components
        INTEGER*8, INTENT(IN   ) :: LLIST2( N ) !  table of second key-tuple components
        INTEGER*8, INTENT(IN   ) :: LLIST3( N ) !  table of third  key-tuple components
        INTEGER*8, INTENT(IN   ) :: LLIST4( N ) !  table of fourth key-tuple components

        REAL     , INTENT(IN   ) :: RLIST1( N ) !  table of first  key-tuple components
        REAL     , INTENT(IN   ) :: RLIST2( N ) !  table of second key-tuple components
        REAL     , INTENT(IN   ) :: RLIST3( N ) !  table of third  key-tuple components
        REAL     , INTENT(IN   ) :: RLIST4( N ) !  table of fourth key-tuple components

C version:

    void qsortic( int        n,          /** number of elements **/
                  int        ind[],      /** index-array **/
                  const char tblc[],     /** first  key-component in tuple   **/
                  const int  k )         /** key-length as a Fortran string  **/
                  
    void qsorti1( int        n,          /** Dimension for indx, list **/
                  int        indx [],    /** subscript table **/
                  const int  list1[] );  /** key table to be sorted **/

    void qsorti2( int        n,          /** Dimension for indx, list **/
                  int        indx [],    /** subscript table **/
                  const int  list1[] ,   /** 2-key table to be sorted **/
                  const int  list2[] ) ;

    void qsorti3( int        n,          /** Dimension for indx, list **/
                  int        indx [],    /** subscript table **/
                  const int  list1[] ,   /** 3-key table to be sorted **/
                  const int  list2[] ,
                  const int  list3[] ) ;

    void qsorti4( int        n,          /** Dimension for indx, list **/
                  int        indx [],    /** subscript table **
                  const int  list1[] ,   /** 4-key table to be sorted **/
                  const int  list2[] ,
                  const int  list3[] ,
                  const int  list4[] ) ;
                  
    void qsortl1( int           n,          /** Dimension for indx, list **/
                  int           indx [],    /** subscript table **/
                  const int64_t list1[] );  /** key table to be sorted **/

    void qsortl2( int           n,          /** Dimension for indx, list **/
                  int           indx [],    /** subscript table **/
                  const int64_t list1[] ,   /** 2-key table to be sorted **/
                  const int64_t list2[] ) ;

    void qsortl3( int           n,          /** Dimension for indx, list **/
                  int           indx [],    /** subscript table **/
                  const int64_t list1[] ,   /** 3-key table to be sorted **/
                  const int64_t list2[] ,
                  const int64_t list3[] ) ;

    void qsortl4( int           n,          /** Dimension for indx, list **/
                  int           indx [],    /** subscript table **
                  const int64_t list1[] ,   /** 4-key table to be sorted **/
                  const int64_t list2[] ,
                  const int64_t list3[] ,
                  const int64_t list4[] ) ;

    void qsortr1( int         n,          /** Dimension for indx, list **/
                  int         indx [],    /** subscript table **/
                  const float list1[] );  /** key table to be sorted **/

    void qsortr2( int         n,          /** Dimension for indx, list **/
                  int         indx [],    /** subscript table **/
                  const float list1[] ,   /** 2-key table to be sorted **/
                  const float list2[] ) ;

    void qsortr3( int         n,          /** Dimension for indx, list **/
                  int         indx [],    /** subscript table **/
                  const float list1[] ,   /** 3-key table to be sorted **/
                  const float list2[] ,
                  const float list3[] ) ;

    void qsortr4( int         n,          /** Dimension for indx, list **/
                  int         indx [],    /** subscript table **
                  const float list1[] ,   /** 4-key table to be sorted **/
                  const float list2[] ,
                  const float list3[] ,
                  const float list4[] ) ;

Summary:

Sort an index-table to the indicated key-tuple table, so that the result will be in increasing order.

See also FINDC, FIND1, FIND2, FIND3, FIND4, FINDR1, FINDR2, FINDR3, FINDR4 for lookups according to sorted key-tuple tables, and LOCATC, LOCAT1, LOCAT2, LOCAT3, LOCAT4, LOCATR1, LOCATR2, LOCATR3, LOCATR4 for insertions into sorted key-tuple tables, and (post-Dec 2023) PERMUTI for in-place permutation following the use of SORTI to produce the sort-index.

For Fortran-90 generic interface SORTI(), declarations and interface checking:

    USE M3UTILIO
    

Preconditions:

Table <N, INDX, ... > to be sorted is initialized to 1, ..., N

Fortran Usage:

Use the quicksort algorithm to construct a sorted index to a set of unsorted 3-tuple tables v{LIST1,LIST2,LIST3} with an associated data arrays DATA1, DATA2, ..., and use it to construct a set of sorted 3-tuple tables {SORTED1,SORTED2,SORTED3} and their related sorted data SDATA1, SDATA2:
    ...
    USE M3UTILIO
    ...
    INTEGER       N
    PARAMETER   ( N = ...
    ...
    INTEGER       I
    INTEGER       INDX ( N )   !  index array to be sorted
    INTEGER       LIST1( N )   !  input unsorted 3-tuple table
    INTEGER       LIST2( N )   !  input unsorted 3-tuple table
    INTEGER       LIST3( N )   !  input unsorted 3-tuple table
    REAL          DATA1( N )   !  input data table with same subscripting
    REAL          DATA2( N )   !  as <LIST1,LIST2,LIST3>
    ...
    DATA          LIST1 / 1983,  1980,  1988,  1988,  1990, ...
    DATA          LIST2 /    1,     5,     4,    11,     7, ...
    DATA          LIST3 /   10,     3,    15,    19,    20, ...
    DATA          DATA1 / 1.23,  -0.7,   5.5,  11.9,  -4.3, ...
    DATA          DATA2 /1.2e5,-2.7e3, 4.8e4, 2.2e6, -7.72, ...
    INTEGER       SORTED1( N ) !  sorted 3-tuple table
    INTEGER       SORTED2( N ) !  sorted 3-tuple table
    INTEGER       SORTED3( N ) !  sorted 3-tuple table
    REAL          SDATA1( N )  !  sorted data table
    REAL          SDATA2( N )  !  sorted data table
    ...
    DO  I = 1, N	!  initialize INDX array
        INDX( I ) = I
    END DO
    CALL SORTI3( N, INDX, LIST1, LIST2, LIST3 )
    DO  I = 1, N	!  reorder according to INDX array
        SORTED1( I ) = LIST1( INDX( I ) )
        SORTED2( I ) = LIST2( INDX( I ) )
        SORTED3( I ) = LIST3( INDX( I ) )
        SDATA1( I )  = DATA1( INDX( I ) )
        SDATA2( I )  = DATA2( INDX( I ) )
        ...
    END DO
    ...

December, 2023 or later: generic routine PERMUTI can be used together with SORTI for in-place sorting, as in the following example:

    ...
    DO  I = 1, N	!  initialize INDX array
        INDX( I ) = I
    END DO
    CALL SORTI(   N, INDX, LIST1, LIST2, LIST3 )
    CALL PERMUTI( N, INDX, LIST1, LIST2, LIST3 )
    CALL PERMUTI( N, INDX, DATA1, DATA2 )
    ...

C Usage

Construct an index array ind[] to unsorted 2-key-tuple tables list1[] and list2[], call qsorti2() and use its results to generate the sorted 2-tuple tables sort1[] and sort2[]:
...
#define N ...
...
int  i, k, n ;
int  ind[ N ] ,
     list1[ N ], list2[ N ], 
     sort1[ N ], sort2[ N ] ;
...  
/*  get n and list1[i], list2[i], i=0, ..., n-1.  Then: */ 
for( i = 0; i < n ; i++ )  ind[ i ] = i ;
qsorti2( n, ind, list1, list2 ) ;
for( i = 0; i < n ; i++ )
    {
    k = ind[ i ] ;
    sort1[ i ] = list1[ k ] ;
    sort2[ i ] = list2[ k ] ;
    }
...

Previous: SMATVEC

Next: STR2S

SEE ALSO: FIND* Binary Search Routines

SEE ALSO: LOCAT* Binary Search-and-Insert Routines

SEE ALSO: SORTI* Indexed in-place permute Routines

Up: Utility Routines

To: Models-3/EDSS I/O API: The Help Pages

    $Id: SORTI.html 256 2023-12-01 15:40:40Z coats $