stdlib_sorting Module

This module implements overloaded sorting subroutines named ORD_SORT, SORT_INDEX, and SORT, that each can be used to sort four kinds of INTEGER arrays, three kinds of REAL arrays, character(len=*) arrays, and arrays of type(string_type). (Specification)

By default sorting is in order of increasing value, but there is an option to sort in decreasing order. All the subroutines have worst case run time performance of O(N Ln(N)), but on largely sorted data ORD_SORT and SORT_INDEX can have a run time performance of O(N).

ORD_SORT is a translation of the "Rust" sort sorting algorithm in slice.rs: https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs which in turn is inspired by the timsort algorithm of Tim Peters, http://svn.python.org/projects/python/trunk/Objects/listsort.txt. ORD_SORT is a hybrid stable comparison algorithm combining merge sort, and insertion sort. It is always at worst O(N Ln(N)) in sorting random data, having a performance about 25% slower than SORT on such data, but has much better performance than SORT on partially sorted data, having O(N) performance on uniformly non-increasing or non-decreasing data.

SORT_INDEX is a modification of ORD_SORT so that in addition to sorting the input array, it returns the indices that map to a stable sort of the original array. These indices are intended to be used to sort data that is correlated with the input array, e.g., different arrays in a database, different columns of a rank 2 array, different elements of a derived type. It is less efficient than ORD_SORT at sorting a simple array.

SORT uses the INTROSORT sorting algorithm of David Musser, http://www.cs.rpi.edu/~musser/gp/introsort.ps. introsort is a hybrid unstable comparison algorithm combining quicksort, insertion sort, and heap sort. While this algorithm is always O(N Ln(N)) it is relatively fast on randomly ordered data, but inconsistent in performance on partly sorted data, sometimes having merge sort performance, sometimes having better than quicksort performance. UNORD_SOORT is about 25% more efficient than ORD_SORT at sorting purely random data, but af an order of Ln(N) less efficient at sorting partially sorted data.

Version: experimental

The generic subroutine implementing the ORD_SORT algorithm to return an input array with its elements sorted in order of (non-)decreasing value. Its use has the syntax:

 call ord_sort( array[, work, reverse] )

with the arguments:

  • array: the rank 1 array to be sorted. It is an intent(inout) argument of any of the types integer(int8), integer(int16), integer(int32), integer(int64), real(real32), real(real64), real(real128), character(*), type(string_type), type(bitset_64), type(bitset_large). If both the type of array is real and at least one of the elements is a NaN, then the ordering of the result is undefined. Otherwise it is defined to be the original elements in non-decreasing order.

  • work (optional): shall be a rank 1 array of the same type as array, and shall have at least size(array)/2 elements. It is an intent(out) argument to be used as "scratch" memory for internal record keeping. If associated with an array in static storage, its use can significantly reduce the stack memory requirements for the code. Its value on return is undefined.

  • reverse (optional): shall be a scalar of type default logical. It is an intent(in) argument. If present with a value of .true. then array will be sorted in order of non-increasing values in stable order. Otherwise index will sort array in order of non-decreasing values in stable order.

Example

    ...
    ! Read arrays from sorted files
    call read_sorted_file( 'dummy_file1', array1 )
    call read_sorted_file( 'dummy_file2', array2 )
    ! Concatenate the arrays
    allocate( array( size(array1) + size(array2) ) )
    array( 1:size(array1) ) = array1(:)
    array( size(array1)+1:size(array1)+size(array2) ) = array2(:)
    ! Sort the resulting array
    call ord_sort( array, work )
    ! Process the sorted array
    call array_search( array, values )
    ...

Version: experimental

The generic subroutine implementing the SORT algorithm to return an input array with its elements sorted in order of (non-)decreasing value. Its use has the syntax:

 call sort( array[, reverse] )

with the arguments:

  • array: the rank 1 array to be sorted. It is an intent(inout) argument of any of the types integer(int8), integer(int16), integer(int32), integer(int64), real(real32), real(real64), real(real128), character(*), type(string_type), type(bitset_64), type(bitset_large). If both the type of array is real and at least one of the elements is a NaN, then the ordering of the result is undefined. Otherwise it is defined to be the original elements in non-decreasing order.
  • reverse (optional): shall be a scalar of type default logical. It is an intent(in) argument. If present with a value of .true. then array will be sorted in order of non-increasing values in unstable order. Otherwise index will sort array in order of non-decreasing values in unstable order.

Example

    ...
    ! Read random data from a file
    call read_file( 'dummy_file', array )
    ! Sort the random data
    call sort( array )
    ! Process the sorted data
    call array_search( array, values )
    ...

Version: experimental

The generic subroutine implementing the LSD radix sort algorithm to return an input array with its elements sorted in order of (non-)decreasing value. Its use has the syntax:

 call radix_sort( array[, work, reverse] )

with the arguments:

  • array: the rank 1 array to be sorted. It is an intent(inout) argument of any of the types integer(int8), integer(int16), integer(int32), integer(int64), real(real32), real(real64). If both the type of array is real and at least one of the elements is a NaN, then the ordering of the result is undefined. Otherwise it is defined to be the original elements in non-decreasing order. Especially, -0.0 is lesser than 0.0.

  • work (optional): shall be a rank 1 array of the same type as array, and shall have at least size(array) elements. It is an intent(inout) argument to be used as buffer. Its value on return is undefined. If it is not present, radix_sort will allocate a buffer for use, and deallocate it before return. If you do several similar radix_sorts, reusing the work array is a good parctice. This argument is not present for int8_radix_sort because it use counting sort, so no buffer is needed.

  • reverse (optional): shall be a scalar of type default logical. It is an intent(in) argument. If present with a value of .true. then array will be sorted in order of non-increasing values in stable order. Otherwise index will sort array in order of non-decreasing values in stable order.

Example

    ...
    ! Read random data from a file
    call read_file( 'dummy_file', array )
    ! Sort the random data
    call radix_sort( array )
    ...

Version: experimental

The generic subroutine implementing the SORT_INDEX algorithm to return an index array whose elements would sort the input array in the desired direction. It is primarily intended to be used to sort a derived type array based on the values of a component of the array. Its use has the syntax:

 call sort_index( array, index[, work, iwork, reverse ] )

with the arguments:

  • array: the rank 1 array to be sorted. It is an intent(inout) argument of any of the types integer(int8), integer(int16), integer(int32), integer(int64), real(real32), real(real64), real(real128), character(*), type(string_type), type(bitset_64), type(bitset_large). If both the type of array is real and at least one of the elements is a NaN, then the ordering of the array and index results is undefined. Otherwise it is defined to be as specified by reverse.

  • index: a rank 1 array of sorting indices. It is an intent(out) argument of the type integer(int_size). Its size shall be the same as array. On return, if defined, its elements would sort the input array in the direction specified by reverse.

  • work (optional): shall be a rank 1 array of the same type as array, and shall have at least size(array)/2 elements. It is an intent(out) argument to be used as "scratch" memory for internal record keeping. If associated with an array in static storage, its use can significantly reduce the stack memory requirements for the code. Its value on return is undefined.

  • iwork (optional): shall be a rank 1 integer array of kind int_size, and shall have at least size(array)/2 elements. It is an intent(out) argument to be used as "scratch" memory for internal record keeping. If associated with an array in static storage, its use can significantly reduce the stack memory requirements for the code. Its value on return is undefined.

  • reverse (optional): shall be a scalar of type default logical. It is an intent(in) argument. If present with a value of .true. then index will sort array in order of non-increasing values in stable order. Otherwise index will sort array in order of non-decreasing values in stable order.

Examples

Sorting a related rank one array:

    subroutine sort_related_data( a, b, work, index, iwork )
        ! Sort `b` in terms or its related array `a`
        integer, intent(inout)         :: a(:)
        integer(int32), intent(inout)  :: b(:) ! The same size as a
        integer(int32), intent(out)    :: work(:)
        integer(int_size), intent(out) :: index(:)
        integer(int_size), intent(out) :: iwork(:)
    ! Find the indices to sort a
        call sort_index(a, index(1:size(a)),&
            work(1:size(a)/2), iwork(1:size(a)/2))
    ! Sort b based on the sorting of a
        b(:) = b( index(1:size(a)) )
    end subroutine sort_related_data

Sorting a rank 2 array based on the data in a column

    subroutine sort_related_data( array, column, work, index, iwork )
    ! Sort `a_data` in terms or its component `a`
        integer, intent(inout)         :: a(:,:)
        integer(int32), intent(in)     :: column
        integer(int32), intent(out)    :: work(:)
        integer(int_size), intent(out) :: index(:)
        integer(int_size), intent(out) :: iwork(:)
        integer, allocatable           :: dummy(:)
        integer :: i
        allocate(dummy(size(a, dim=1)))
    ! Extract a component of `a_data`
        dummy(:) = a(:, column)
    ! Find the indices to sort the column
        call sort_index(dummy, index(1:size(dummy)),&
                        work(1:size(dummy)/2), iwork(1:size(dummy)/2))
    ! Sort a based on the sorting of its column
        do i=1, size(a, dim=2)
            a(:, i) = a(index(1:size(a, dim=1)), i)
        end do
    end subroutine sort_related_data

Sorting an array of a derived type based on the dsta in one component

    subroutine sort_a_data( a_data, a, work, index, iwork )
    ! Sort `a_data` in terms or its component `a`
        type(a_type), intent(inout)    :: a_data(:)
        integer(int32), intent(inout)  :: a(:)
        integer(int32), intent(out)    :: work(:)
        integer(int_size), intent(out) :: index(:)
        integer(int_size), intent(out) :: iwork(:)
    ! Extract a component of `a_data`
        a(1:size(a_data)) = a_data(:) % a
    ! Find the indices to sort the component
        call sort_index(a(1:size(a_data)), index(1:size(a_data)),&
                        work(1:size(a_data)/2), iwork(1:size(a_data)/2))
    ! Sort a_data based on the sorting of that component
        a_data(:) = a_data( index(1:size(a_data)) )
    end subroutine sort_a_data


Variables

Type Visibility Attributes Name Initial
integer, public, parameter :: int_size = int64

Integer kind for indexing


Interfaces

public interface ord_sort

The generic subroutine interface implementing the ORD_SORT algorithm, a translation to Fortran 2008, of the "Rust" sort algorithm found in slice.rs https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs#L2159 ORD_SORT is a hybrid stable comparison algorithm combining merge sort, and insertion sort. (Specification)

It is always at worst O(N Ln(N)) in sorting random data, having a performance about 25% slower than SORT on such data, but has much better performance than SORT on partially sorted data, having O(N) performance on uniformly non-increasing or non-decreasing data.

  • private module subroutine bitset_64_ord_sort(array, work, reverse)

    bitset_64_ord_sort( array ) sorts the input ARRAY of type type(bitset_64) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs

    Arguments

    Type IntentOptional Attributes Name
    type(bitset_64), intent(inout) :: array(0:)
    type(bitset_64), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine bitset_large_ord_sort(array, work, reverse)

    bitset_large_ord_sort( array ) sorts the input ARRAY of type type(bitset_large) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs

    Arguments

    Type IntentOptional Attributes Name
    type(bitset_large), intent(inout) :: array(0:)
    type(bitset_large), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine char_ord_sort(array, work, reverse)

    char_ord_sort( array ) sorts the input ARRAY of type character(len=*) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(inout) :: array(0:)
    character(len=len), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine dp_ord_sort(array, work, reverse)

    dp_ord_sort( array ) sorts the input ARRAY of type real(dp) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: array(0:)
    real(kind=dp), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int16_ord_sort(array, work, reverse)

    int16_ord_sort( array ) sorts the input ARRAY of type integer(int16) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(inout) :: array(0:)
    integer(kind=int16), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int32_ord_sort(array, work, reverse)

    int32_ord_sort( array ) sorts the input ARRAY of type integer(int32) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(inout) :: array(0:)
    integer(kind=int32), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int64_ord_sort(array, work, reverse)

    int64_ord_sort( array ) sorts the input ARRAY of type integer(int64) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(inout) :: array(0:)
    integer(kind=int64), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int8_ord_sort(array, work, reverse)

    int8_ord_sort( array ) sorts the input ARRAY of type integer(int8) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(inout) :: array(0:)
    integer(kind=int8), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine sp_ord_sort(array, work, reverse)

    sp_ord_sort( array ) sorts the input ARRAY of type real(sp) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: array(0:)
    real(kind=sp), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine string_type_ord_sort(array, work, reverse)

    string_type_ord_sort( array ) sorts the input ARRAY of type type(string_type) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(inout) :: array(0:)
    type(string_type), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse

public interface radix_sort

The generic subroutine interface implementing the LSD radix sort algorithm, see https://en.wikipedia.org/wiki/Radix_sort for more details. It is always O(N) in sorting random data, but need a O(N) buffer. (Specification)

  • private module subroutine dp_radix_sort(array, work, reverse)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), dimension(:), target :: array
    real(kind=dp), intent(inout), optional, dimension(:), target :: work
    logical, intent(in), optional :: reverse
  • private pure module subroutine int16_radix_sort(array, work, reverse)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(inout), dimension(:) :: array
    integer(kind=int16), intent(inout), optional, dimension(:), target :: work
    logical, intent(in), optional :: reverse
  • private pure module subroutine int32_radix_sort(array, work, reverse)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(inout), dimension(:) :: array
    integer(kind=int32), intent(inout), optional, dimension(:), target :: work
    logical, intent(in), optional :: reverse
  • private pure module subroutine int64_radix_sort(array, work, reverse)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(inout), dimension(:) :: array
    integer(kind=int64), intent(inout), optional, dimension(:), target :: work
    logical, intent(in), optional :: reverse
  • private pure module subroutine int8_radix_sort(array, reverse)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(inout), dimension(:) :: array
    logical, intent(in), optional :: reverse
  • private module subroutine sp_radix_sort(array, work, reverse)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), dimension(:), target :: array
    real(kind=sp), intent(inout), optional, dimension(:), target :: work
    logical, intent(in), optional :: reverse

public interface sort

The generic subroutine interface implementing the SORT algorithm, based on the introsort of David Musser. (Specification)

  • private pure module subroutine bitset_64_sort(array, reverse)

    bitset_64_sort( array[, reverse] ) sorts the input ARRAY of type type(bitset_64) using a hybrid sort based on the introsort of David Musser. The algorithm is of order O(N Ln(N)) for all inputs. Because it relies on quicksort, the coefficient of the O(N Ln(N)) behavior is small for random data compared to other sorting algorithms.

    Arguments

    Type IntentOptional Attributes Name
    type(bitset_64), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine bitset_large_sort(array, reverse)

    bitset_large_sort( array[, reverse] ) sorts the input ARRAY of type type(bitset_large) using a hybrid sort based on the introsort of David Musser. The algorithm is of order O(N Ln(N)) for all inputs. Because it relies on quicksort, the coefficient of the O(N Ln(N)) behavior is small for random data compared to other sorting algorithms.

    Arguments

    Type IntentOptional Attributes Name
    type(bitset_large), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine char_sort(array, reverse)

    char_sort( array[, reverse] ) sorts the input ARRAY of type character(len=*) using a hybrid sort based on the introsort of David Musser. The algorithm is of order O(N Ln(N)) for all inputs. Because it relies on quicksort, the coefficient of the O(N Ln(N)) behavior is small for random data compared to other sorting algorithms.

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine dp_sort(array, reverse)

    dp_sort( array[, reverse] ) sorts the input ARRAY of type real(dp) using a hybrid sort based on the introsort of David Musser. The algorithm is of order O(N Ln(N)) for all inputs. Because it relies on quicksort, the coefficient of the O(N Ln(N)) behavior is small for random data compared to other sorting algorithms.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine int16_sort(array, reverse)

    int16_sort( array[, reverse] ) sorts the input ARRAY of type integer(int16) using a hybrid sort based on the introsort of David Musser. The algorithm is of order O(N Ln(N)) for all inputs. Because it relies on quicksort, the coefficient of the O(N Ln(N)) behavior is small for random data compared to other sorting algorithms.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine int32_sort(array, reverse)

    int32_sort( array[, reverse] ) sorts the input ARRAY of type integer(int32) using a hybrid sort based on the introsort of David Musser. The algorithm is of order O(N Ln(N)) for all inputs. Because it relies on quicksort, the coefficient of the O(N Ln(N)) behavior is small for random data compared to other sorting algorithms.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine int64_sort(array, reverse)

    int64_sort( array[, reverse] ) sorts the input ARRAY of type integer(int64) using a hybrid sort based on the introsort of David Musser. The algorithm is of order O(N Ln(N)) for all inputs. Because it relies on quicksort, the coefficient of the O(N Ln(N)) behavior is small for random data compared to other sorting algorithms.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine int8_sort(array, reverse)

    int8_sort( array[, reverse] ) sorts the input ARRAY of type integer(int8) using a hybrid sort based on the introsort of David Musser. The algorithm is of order O(N Ln(N)) for all inputs. Because it relies on quicksort, the coefficient of the O(N Ln(N)) behavior is small for random data compared to other sorting algorithms.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine sp_sort(array, reverse)

    sp_sort( array[, reverse] ) sorts the input ARRAY of type real(sp) using a hybrid sort based on the introsort of David Musser. The algorithm is of order O(N Ln(N)) for all inputs. Because it relies on quicksort, the coefficient of the O(N Ln(N)) behavior is small for random data compared to other sorting algorithms.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine string_type_sort(array, reverse)

    string_type_sort( array[, reverse] ) sorts the input ARRAY of type type(string_type) using a hybrid sort based on the introsort of David Musser. The algorithm is of order O(N Ln(N)) for all inputs. Because it relies on quicksort, the coefficient of the O(N Ln(N)) behavior is small for random data compared to other sorting algorithms.

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse

public interface sort_index

The generic subroutine interface implementing the SORT_INDEX algorithm, based on the "Rust" sort algorithm found in slice.rs https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs#L2159 but modified to return an array of indices that would provide a stable sort of the rank one ARRAY input. (Specification)

The indices by default correspond to a non-decreasing sort, but if the optional argument REVERSE is present with a value of .TRUE. the indices correspond to a non-increasing sort.

  • private module subroutine bitset_64_sort_index(array, index, work, iwork, reverse)

    bitset_64_sort_index( array, index[, work, iwork, reverse] ) sorts an input ARRAY of type type(bitset_64) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs and returns the sorted ARRAY and an array INDEX of indices in the order that would sort the input ARRAY in the desired direction.

    Arguments

    Type IntentOptional Attributes Name
    type(bitset_64), intent(inout) :: array(0:)
    integer(kind=int_size), intent(out) :: index(0:)
    type(bitset_64), intent(out), optional :: work(0:)
    integer(kind=int_size), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine bitset_large_sort_index(array, index, work, iwork, reverse)

    bitset_large_sort_index( array, index[, work, iwork, reverse] ) sorts an input ARRAY of type type(bitset_large) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs and returns the sorted ARRAY and an array INDEX of indices in the order that would sort the input ARRAY in the desired direction.

    Arguments

    Type IntentOptional Attributes Name
    type(bitset_large), intent(inout) :: array(0:)
    integer(kind=int_size), intent(out) :: index(0:)
    type(bitset_large), intent(out), optional :: work(0:)
    integer(kind=int_size), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine char_sort_index(array, index, work, iwork, reverse)

    char_sort_index( array, index[, work, iwork, reverse] ) sorts an input ARRAY of type character(len=*) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs and returns the sorted ARRAY and an array INDEX of indices in the order that would sort the input ARRAY in the desired direction.

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(inout) :: array(0:)
    integer(kind=int_size), intent(out) :: index(0:)
    character(len=len), intent(out), optional :: work(0:)
    integer(kind=int_size), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine dp_sort_index(array, index, work, iwork, reverse)

    dp_sort_index( array, index[, work, iwork, reverse] ) sorts an input ARRAY of type real(dp) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs and returns the sorted ARRAY and an array INDEX of indices in the order that would sort the input ARRAY in the desired direction.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: array(0:)
    integer(kind=int_size), intent(out) :: index(0:)
    real(kind=dp), intent(out), optional :: work(0:)
    integer(kind=int_size), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int16_sort_index(array, index, work, iwork, reverse)

    int16_sort_index( array, index[, work, iwork, reverse] ) sorts an input ARRAY of type integer(int16) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs and returns the sorted ARRAY and an array INDEX of indices in the order that would sort the input ARRAY in the desired direction.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(inout) :: array(0:)
    integer(kind=int_size), intent(out) :: index(0:)
    integer(kind=int16), intent(out), optional :: work(0:)
    integer(kind=int_size), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int32_sort_index(array, index, work, iwork, reverse)

    int32_sort_index( array, index[, work, iwork, reverse] ) sorts an input ARRAY of type integer(int32) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs and returns the sorted ARRAY and an array INDEX of indices in the order that would sort the input ARRAY in the desired direction.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(inout) :: array(0:)
    integer(kind=int_size), intent(out) :: index(0:)
    integer(kind=int32), intent(out), optional :: work(0:)
    integer(kind=int_size), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int64_sort_index(array, index, work, iwork, reverse)

    int64_sort_index( array, index[, work, iwork, reverse] ) sorts an input ARRAY of type integer(int64) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs and returns the sorted ARRAY and an array INDEX of indices in the order that would sort the input ARRAY in the desired direction.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(inout) :: array(0:)
    integer(kind=int_size), intent(out) :: index(0:)
    integer(kind=int64), intent(out), optional :: work(0:)
    integer(kind=int_size), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int8_sort_index(array, index, work, iwork, reverse)

    int8_sort_index( array, index[, work, iwork, reverse] ) sorts an input ARRAY of type integer(int8) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs and returns the sorted ARRAY and an array INDEX of indices in the order that would sort the input ARRAY in the desired direction.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(inout) :: array(0:)
    integer(kind=int_size), intent(out) :: index(0:)
    integer(kind=int8), intent(out), optional :: work(0:)
    integer(kind=int_size), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine sp_sort_index(array, index, work, iwork, reverse)

    sp_sort_index( array, index[, work, iwork, reverse] ) sorts an input ARRAY of type real(sp) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs and returns the sorted ARRAY and an array INDEX of indices in the order that would sort the input ARRAY in the desired direction.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: array(0:)
    integer(kind=int_size), intent(out) :: index(0:)
    real(kind=sp), intent(out), optional :: work(0:)
    integer(kind=int_size), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine string_type_sort_index(array, index, work, iwork, reverse)

    string_type_sort_index( array, index[, work, iwork, reverse] ) sorts an input ARRAY of type type(string_type) using a hybrid sort based on the "Rust" sort algorithm found in slice.rs and returns the sorted ARRAY and an array INDEX of indices in the order that would sort the input ARRAY in the desired direction.

    Arguments

    Type IntentOptional Attributes Name
    type(string_type), intent(inout) :: array(0:)
    integer(kind=int_size), intent(out) :: index(0:)
    type(string_type), intent(out), optional :: work(0:)
    integer(kind=int_size), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse