stdlib_sorting 模块

此模块实现了名为 ORD_SORTSORT_INDEXSORT 的重载排序子程序,每个子程序都可用于对四种类型的 INTEGER 数组、三种类型的 REAL 数组、character(len=*) 数组以及 type(string_type) 数组进行排序。(规范

默认情况下,排序按值递增顺序进行,但可以选择按递减顺序排序。所有子程序的最坏情况运行时性能均为 O(N Ln(N)),但在大部分已排序的数据上,ORD_SORTSORT_INDEX 运行时性能可以达到 O(N)

ORD_SORTslice.rs"Rust" sort 排序算法的翻译:https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs,该算法又受到 Tim Peters 的 timsort 算法的启发,http://svn.python.org/projects/python/trunk/Objects/listsort.txt。ORD_SORT 是一种混合稳定的比较算法,结合了 merge sortinsertion sort。它在对随机数据进行排序时始终最坏情况下为 O(N Ln(N)),在处理此类数据的性能比 SORT 慢约 25%,但在部分排序的数据上具有比 SORT 更好的性能,在均匀非递增或非递减数据上具有 O(N) 性能。

SORT_INDEXORD_SORT 的修改版本,因此除了对输入数组进行排序外,它还返回映射到原始数组稳定排序的索引。这些索引旨在用于对与输入数组相关联的数据进行排序,例如,数据库中的不同数组、秩 2 数组的不同列、派生类型的不同元素。它在对简单数组进行排序时的效率低于 ORD_SORT

SORT 使用 David Musser 的 INTROSORT 排序算法,http://www.cs.rpi.edu/~musser/gp/introsort.ps。introsort 是一种混合不稳定的比较算法,结合了 quicksortinsertion sortheap sort。虽然此算法始终为 O(N Ln(N)),但在随机排序的数据上相对较快,但在部分排序的数据上性能不一致,有时具有 merge sort 性能,有时具有比 quicksort 更好的性能。UNORD_SOORT 在对纯随机数据进行排序时的效率比 ORD_SORT 高约 25%,但在对部分排序的数据进行排序时的效率降低了 Ln(N) 数量级。

版本:实验性

实现 ORD_SORT 算法的通用子程序,以返回其元素按(非)递减顺序排序的输入数组。其用法语法如下:

 call ord_sort( array[, work, reverse] )

参数为

  • array:要排序的秩 1 数组。它是 intent(inout) 参数,其类型可以是 integer(int8)integer(int16)integer(int32)integer(int64)real(real32)real(real64)real(real128)character(*)type(string_type)type(bitset_64)type(bitset_large) 中的任何一种。如果 array 的类型为 real,并且至少有一个元素为 NaN,则结果的排序顺序未定义。否则,定义为按非递减顺序排列的原始元素。

  • work(可选):应为与 array 类型相同的秩 1 数组,并且应至少具有 size(array)/2 个元素。它是 intent(out) 参数,用于作为内部记录保存的“暂存”内存。如果与静态存储中的数组相关联,则使用它可以显著减少代码的堆栈内存需求。其返回值未定义。

  • reverse(可选):应为默认逻辑类型的标量。它是 intent(in) 参数。如果存在且值为 .true.,则 array 将按稳定顺序以非递减值的顺序排序。否则,index 将按稳定顺序以非递减值的顺序排序 array

示例

    ...
    ! 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 )
    ...

版本:实验性

实现 SORT 算法的通用子程序,以返回其元素按(非)递减顺序排序的输入数组。其用法语法如下:

 call sort( array[, reverse] )

参数为

  • array:要排序的秩 1 数组。它是 intent(inout) 参数,其类型可以是 integer(int8)integer(int16)integer(int32)integer(int64)real(real32)real(real64)real(real128)character(*)type(string_type)type(bitset_64)type(bitset_large) 中的任何一种。如果 array 的类型为 real,并且至少有一个元素为 NaN,则结果的排序顺序未定义。否则,定义为按非递减顺序排列的原始元素。
  • reverse(可选):应为默认逻辑类型的标量。它是 intent(in) 参数。如果存在且值为 .true.,则 array 将按不稳定顺序以非递减值的顺序排序。否则,index 将按不稳定顺序以非递减值的顺序排序 array

示例

    ...
    ! 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 )
    ...

版本:实验性

实现 LSD 基数排序算法的通用子程序,以返回其元素按(非)递减顺序排序的输入数组。其用法语法如下:

 call radix_sort( array[, work, reverse] )

参数为

  • array:要排序的秩 1 数组。它是 intent(inout) 参数,其类型可以是 integer(int8)integer(int16)integer(int32)integer(int64)real(real32)real(real64) 中的任何一种。如果 array 的类型为 real,并且至少有一个元素为 NaN,则结果的排序顺序未定义。否则,定义为按非递减顺序排列的原始元素。特别是,-0.0 小于 0.0。

  • work(可选):应为与 array 类型相同的秩 1 数组,并且应至少具有 size(array) 个元素。它是 intent(inout) 参数,用作缓冲区。其返回值未定义。如果它不存在,radix_sort 将分配一个缓冲区以供使用,并在返回之前释放它。如果您执行了几个类似的 radix_sort,则重用 work 数组是一个好习惯。此参数在 int8_radix_sort 中不存在,因为它使用计数排序,因此不需要缓冲区。

  • reverse(可选):应为默认逻辑类型的标量。它是 intent(in) 参数。如果存在且值为 .true.,则 array 将按稳定顺序以非递减值的顺序排序。否则,index 将按稳定顺序以非递减值的顺序排序 array

示例

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

版本:实验性

实现 SORT_INDEX 算法的通用子程序,以返回一个索引数组,其元素将按所需方向对输入数组进行排序。它主要用于基于数组组件的值对派生类型数组进行排序。其用法语法如下:

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

参数为

  • array:要排序的秩 1 数组。它是 intent(inout) 参数,其类型可以是 integer(int8)integer(int16)integer(int32)integer(int64)real(real32)real(real64)real(real128)character(*)type(string_type)type(bitset_64)type(bitset_large) 中的任何一种。如果 array 的类型为 real,并且至少有一个元素为 NaN,则 arrayindex 结果的排序顺序未定义。否则,定义为由 reverse 指定。

  • index:排序索引的秩 1 数组。它是类型 integer(int_index)intent(out) 参数。其大小应与 array 相同。在返回时,如果已定义,其元素将按 reverse 指定的方向对输入 array 进行排序。

  • work(可选):应为与 array 类型相同的秩 1 数组,并且应至少具有 size(array)/2 个元素。它是 intent(out) 参数,用于作为内部记录保存的“暂存”内存。如果与静态存储中的数组相关联,则使用它可以显著减少代码的堆栈内存需求。其返回值未定义。

  • iwork(可选):应为 kind 为 int_index 的秩 1 整数数组,并且应至少具有 size(array)/2 个元素。它是 intent(out) 参数,用于作为内部记录保存的“暂存”内存。如果与静态存储中的数组相关联,则使用它可以显著减少代码的堆栈内存需求。其返回值未定义。

  • reverse(可选):应为默认逻辑类型的标量。它是 intent(in) 参数。如果存在且值为 .true.,则 index 将按稳定顺序以非递减值的顺序排序 array。否则,index 将按稳定顺序以非递减值的顺序排序 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_index), intent(out) :: index(:)
        integer(int_index), 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

基于列中的数据对秩二数组进行排序

    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_index), intent(out) :: index(:)
        integer(int_index), 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

基于一个组件中的数据对派生类型数组进行排序

    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_index), intent(out) :: index(:)
        integer(int_index), 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


变量

类型 可见性 属性 名称 初始
integer, public, parameter :: int_index = int64

用于索引的整数种类

integer, public, parameter :: int_index_low = int32

使用小于 huge(1_int32) 值的索引的整数种类


接口

public interface ord_sort

实现 ORD_SORT 算法的通用子程序接口,它是对在 slice.rs 中找到的 "Rust" sort 算法(https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs#L2159)的 Fortran 2008 翻译。ORD_SORT 是一种混合稳定的比较算法,结合了 merge sortinsertion sort。(规范

它在对随机数据进行排序时始终最坏情况下为 O(N Ln(N)),在处理此类数据的性能比 SORT 慢约 25%,但在部分排序的数据上具有比 SORT 更好的性能,在均匀非递增或非递减数据上具有 O(N) 性能。

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

    bitset_64_ord_sort( array ) 使用基于在 slice.rs 中找到的 "Rust" sort 算法的混合排序对类型为 type(bitset_64) 的输入 ARRAY 进行排序

    参数

    类型 意图可选 属性 名称
    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 ) 使用基于在 slice.rs 中找到的 "Rust" sort 算法的混合排序对类型为 type(bitset_large) 的输入 ARRAY 进行排序

    参数

    类型 意图可选 属性 名称
    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 ) 使用基于在 slice.rs 中找到的 "Rust" sort 算法的混合排序对类型为 character(len=*) 的输入 ARRAY 进行排序

    参数

    类型 意图可选 属性 名称
    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 ) 使用基于在 slice.rs 中找到的 "Rust" sort 算法的混合排序对类型为 real(dp) 的输入 ARRAY 进行排序

    参数

    类型 意图可选 属性 名称
    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 ) 对输入数组 ARRAY(类型为 integer(int16))进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序算法。

    参数

    类型 意图可选 属性 名称
    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 ) 对输入数组 ARRAY(类型为 integer(int32))进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序算法。

    参数

    类型 意图可选 属性 名称
    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 ) 对输入数组 ARRAY(类型为 integer(int64))进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序算法。

    参数

    类型 意图可选 属性 名称
    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 ) 对输入数组 ARRAY(类型为 integer(int8))进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序算法。

    参数

    类型 意图可选 属性 名称
    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 ) 对输入数组 ARRAY(类型为 real(sp))进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序算法。

    参数

    类型 意图可选 属性 名称
    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 ) 对输入数组 ARRAY(类型为 type(string_type))进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序算法。

    参数

    类型 意图可选 属性 名称
    type(string_type), intent(inout) :: array(0:)
    type(string_type), intent(out), optional :: work(0:)
    logical, intent(in), optional :: reverse

public interface radix_sort

实现 LSD 基数排序算法的通用子程序接口,更多详情请参考 https://en.wikipedia.org/wiki/Radix_sort。对于随机数据,它始终是 O(N) 的排序,但需要 O(N) 的缓冲区。(规范

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

    参数

    类型 意图可选 属性 名称
    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)

    参数

    类型 意图可选 属性 名称
    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)

    参数

    类型 意图可选 属性 名称
    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)

    参数

    类型 意图可选 属性 名称
    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)

    参数

    类型 意图可选 属性 名称
    integer(kind=int8), intent(inout), dimension(:) :: array
    logical, intent(in), optional :: reverse
  • private module subroutine sp_radix_sort(array, work, reverse)

    参数

    类型 意图可选 属性 名称
    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

实现 SORT 算法的通用子程序接口,该算法基于 David Musser 的 introsort。(规范

  • private pure module subroutine bitset_64_sort(array, reverse)

    bitset_64_sort( array[, reverse] ) 使用基于 David Musser 的 introsort 的混合排序算法对输入数组 ARRAY(类型为 type(bitset_64))进行排序。该算法对于所有输入都是 O(N Ln(N)) 级的。因为它依赖于 quicksort,所以与其他排序算法相比,对于随机数据,O(N Ln(N)) 行为的系数较小。

    参数

    类型 意图可选 属性 名称
    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] ) 使用基于 David Musser 的 introsort 的混合排序算法对输入数组 ARRAY(类型为 type(bitset_large))进行排序。该算法对于所有输入都是 O(N Ln(N)) 级的。因为它依赖于 quicksort,所以与其他排序算法相比,对于随机数据,O(N Ln(N)) 行为的系数较小。

    参数

    类型 意图可选 属性 名称
    type(bitset_large), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine char_sort(array, reverse)

    char_sort( array[, reverse] ) 使用基于 David Musser 的 introsort 的混合排序算法对输入数组 ARRAY(类型为 character(len=*))进行排序。该算法对于所有输入都是 O(N Ln(N)) 级的。因为它依赖于 quicksort,所以与其他排序算法相比,对于随机数据,O(N Ln(N)) 行为的系数较小。

    参数

    类型 意图可选 属性 名称
    character(len=*), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine dp_sort(array, reverse)

    dp_sort( array[, reverse] ) 使用基于 David Musser 的 introsort 的混合排序算法对输入数组 ARRAY(类型为 real(dp))进行排序。该算法对于所有输入都是 O(N Ln(N)) 级的。因为它依赖于 quicksort,所以与其他排序算法相比,对于随机数据,O(N Ln(N)) 行为的系数较小。

    参数

    类型 意图可选 属性 名称
    real(kind=dp), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine int16_sort(array, reverse)

    int16_sort( array[, reverse] ) 使用基于 David Musser 的 introsort 的混合排序算法对输入数组 ARRAY(类型为 integer(int16))进行排序。该算法对于所有输入都是 O(N Ln(N)) 级的。因为它依赖于 quicksort,所以与其他排序算法相比,对于随机数据,O(N Ln(N)) 行为的系数较小。

    参数

    类型 意图可选 属性 名称
    integer(kind=int16), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine int32_sort(array, reverse)

    int32_sort( array[, reverse] ) 使用基于 David Musser 的 introsort 的混合排序算法对输入数组 ARRAY(类型为 integer(int32))进行排序。该算法对于所有输入都是 O(N Ln(N)) 级的。因为它依赖于 quicksort,所以与其他排序算法相比,对于随机数据,O(N Ln(N)) 行为的系数较小。

    参数

    类型 意图可选 属性 名称
    integer(kind=int32), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine int64_sort(array, reverse)

    int64_sort( array[, reverse] ) 使用基于 David Musser 的 introsort 的混合排序算法对输入数组 ARRAY(类型为 integer(int64))进行排序。该算法对于所有输入都是 O(N Ln(N)) 级的。因为它依赖于 quicksort,所以与其他排序算法相比,对于随机数据,O(N Ln(N)) 行为的系数较小。

    参数

    类型 意图可选 属性 名称
    integer(kind=int64), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine int8_sort(array, reverse)

    int8_sort( array[, reverse] ) 使用基于 David Musser 的 introsort 的混合排序算法对输入数组 ARRAY(类型为 integer(int8))进行排序。该算法对于所有输入都是 O(N Ln(N)) 级的。因为它依赖于 quicksort,所以与其他排序算法相比,对于随机数据,O(N Ln(N)) 行为的系数较小。

    参数

    类型 意图可选 属性 名称
    integer(kind=int8), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse
  • private pure module subroutine sp_sort(array, reverse)

    sp_sort( array[, reverse] ) 使用基于 David Musser 的 introsort 的混合排序算法对输入数组 ARRAY(类型为 real(sp))进行排序。该算法对于所有输入都是 O(N Ln(N)) 级的。因为它依赖于 quicksort,所以与其他排序算法相比,对于随机数据,O(N Ln(N)) 行为的系数较小。

    参数

    类型 意图可选 属性 名称
    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] ) 使用基于 David Musser 的 introsort 的混合排序算法对输入数组 ARRAY(类型为 type(string_type))进行排序。该算法对于所有输入都是 O(N Ln(N)) 级的。因为它依赖于 quicksort,所以与其他排序算法相比,对于随机数据,O(N Ln(N)) 行为的系数较小。

    参数

    类型 意图可选 属性 名称
    type(string_type), intent(inout) :: array(0:)
    logical, intent(in), optional :: reverse

public interface sort_index

实现 SORT_INDEX 算法的通用子程序接口,该算法基于 slice.rs 中的 "Rust" sort 算法 https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs#L2159,但进行了修改以返回一个索引数组,该数组将提供一维输入数组 ARRAY 的稳定排序。(规范

默认情况下,索引对应于非递减排序,但如果存在可选参数 REVERSE 且其值为 .TRUE.,则索引对应于非递增排序。

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

    bitset_64_sort_index_default( array, index[, work, iwork, reverse] ) 使用基于 slice.rs"Rust" sort 算法的混合排序算法对类型为 type(bitset_64) 的输入 ARRAY 进行排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该数组按所需方向对输入 ARRAY 进行排序。

    参数

    类型 意图可选 属性 名称
    type(bitset_64), intent(inout) :: array(0:)
    integer(kind=int_index), intent(out) :: index(0:)
    type(bitset_64), intent(out), optional :: work(0:)
    integer(kind=int_index), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine bitset_64_sort_index_low(array, index, work, iwork, reverse)

    bitset_64_sort_index_low( array, index[, work, iwork, reverse] ) 对类型为 type(bitset_64) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    type(bitset_64), intent(inout) :: array(0:)
    integer(kind=int_index_low), intent(out) :: index(0:)
    type(bitset_64), intent(out), optional :: work(0:)
    integer(kind=int_index_low), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine bitset_large_sort_index_default(array, index, work, iwork, reverse)

    bitset_large_sort_index_default( array, index[, work, iwork, reverse] ) 对类型为 type(bitset_large) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    type(bitset_large), intent(inout) :: array(0:)
    integer(kind=int_index), intent(out) :: index(0:)
    type(bitset_large), intent(out), optional :: work(0:)
    integer(kind=int_index), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine bitset_large_sort_index_low(array, index, work, iwork, reverse)

    bitset_large_sort_index_low( array, index[, work, iwork, reverse] ) 对类型为 type(bitset_large) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    type(bitset_large), intent(inout) :: array(0:)
    integer(kind=int_index_low), intent(out) :: index(0:)
    type(bitset_large), intent(out), optional :: work(0:)
    integer(kind=int_index_low), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine char_sort_index_default(array, index, work, iwork, reverse)

    char_sort_index_default( array, index[, work, iwork, reverse] ) 对类型为 character(len=*) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    character(len=*), intent(inout) :: array(0:)
    integer(kind=int_index), intent(out) :: index(0:)
    character(len=len), intent(out), optional :: work(0:)
    integer(kind=int_index), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine char_sort_index_low(array, index, work, iwork, reverse)

    char_sort_index_low( array, index[, work, iwork, reverse] ) 对类型为 character(len=*) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    character(len=*), intent(inout) :: array(0:)
    integer(kind=int_index_low), intent(out) :: index(0:)
    character(len=len), intent(out), optional :: work(0:)
    integer(kind=int_index_low), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine dp_sort_index_default(array, index, work, iwork, reverse)

    dp_sort_index_default( array, index[, work, iwork, reverse] ) 对类型为 real(dp) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    real(kind=dp), intent(inout) :: array(0:)
    integer(kind=int_index), intent(out) :: index(0:)
    real(kind=dp), intent(out), optional :: work(0:)
    integer(kind=int_index), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine dp_sort_index_low(array, index, work, iwork, reverse)

    dp_sort_index_low( array, index[, work, iwork, reverse] ) 对类型为 real(dp) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    real(kind=dp), intent(inout) :: array(0:)
    integer(kind=int_index_low), intent(out) :: index(0:)
    real(kind=dp), intent(out), optional :: work(0:)
    integer(kind=int_index_low), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int16_sort_index_default(array, index, work, iwork, reverse)

    int16_sort_index_default( array, index[, work, iwork, reverse] ) 对类型为 integer(int16) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    integer(kind=int16), intent(inout) :: array(0:)
    integer(kind=int_index), intent(out) :: index(0:)
    integer(kind=int16), intent(out), optional :: work(0:)
    integer(kind=int_index), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int16_sort_index_low(array, index, work, iwork, reverse)

    int16_sort_index_low( array, index[, work, iwork, reverse] ) 对类型为 integer(int16) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    integer(kind=int16), intent(inout) :: array(0:)
    integer(kind=int_index_low), intent(out) :: index(0:)
    integer(kind=int16), intent(out), optional :: work(0:)
    integer(kind=int_index_low), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int32_sort_index_default(array, index, work, iwork, reverse)

    int32_sort_index_default( array, index[, work, iwork, reverse] ) 对类型为 integer(int32) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    integer(kind=int32), intent(inout) :: array(0:)
    integer(kind=int_index), intent(out) :: index(0:)
    integer(kind=int32), intent(out), optional :: work(0:)
    integer(kind=int_index), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int32_sort_index_low(array, index, work, iwork, reverse)

    int32_sort_index_low( array, index[, work, iwork, reverse] ) 对类型为 integer(int32) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    integer(kind=int32), intent(inout) :: array(0:)
    integer(kind=int_index_low), intent(out) :: index(0:)
    integer(kind=int32), intent(out), optional :: work(0:)
    integer(kind=int_index_low), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int64_sort_index_default(array, index, work, iwork, reverse)

    int64_sort_index_default( array, index[, work, iwork, reverse] ) 对类型为 integer(int64) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    integer(kind=int64), intent(inout) :: array(0:)
    integer(kind=int_index), intent(out) :: index(0:)
    integer(kind=int64), intent(out), optional :: work(0:)
    integer(kind=int_index), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int64_sort_index_low(array, index, work, iwork, reverse)

    int64_sort_index_low( array, index[, work, iwork, reverse] ) 对类型为 integer(int64) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    integer(kind=int64), intent(inout) :: array(0:)
    integer(kind=int_index_low), intent(out) :: index(0:)
    integer(kind=int64), intent(out), optional :: work(0:)
    integer(kind=int_index_low), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int8_sort_index_default(array, index, work, iwork, reverse)

    int8_sort_index_default( array, index[, work, iwork, reverse] ) 对类型为 integer(int8) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    integer(kind=int8), intent(inout) :: array(0:)
    integer(kind=int_index), intent(out) :: index(0:)
    integer(kind=int8), intent(out), optional :: work(0:)
    integer(kind=int_index), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine int8_sort_index_low(array, index, work, iwork, reverse)

    int8_sort_index_low( array, index[, work, iwork, reverse] ) 对类型为 integer(int8) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    integer(kind=int8), intent(inout) :: array(0:)
    integer(kind=int_index_low), intent(out) :: index(0:)
    integer(kind=int8), intent(out), optional :: work(0:)
    integer(kind=int_index_low), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine sp_sort_index_default(array, index, work, iwork, reverse)

    sp_sort_index_default( array, index[, work, iwork, reverse] ) 对类型为 real(sp) 的输入 ARRAY 进行排序,使用基于 slice.rs"Rust" sort 算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该索引数组指示按所需方向对输入 ARRAY 进行排序的顺序。

    参数

    类型 意图可选 属性 名称
    real(kind=sp), intent(inout) :: array(0:)
    integer(kind=int_index), intent(out) :: index(0:)
    real(kind=sp), intent(out), optional :: work(0:)
    integer(kind=int_index), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine sp_sort_index_low(array, index, work, iwork, reverse)

    sp_sort_index_low( array, index[, work, iwork, reverse] ) 对类型为 real(sp) 的输入 ARRAY 使用基于 slice.rs"Rust" 排序算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该数组中的索引顺序可以按照所需方向对输入 ARRAY 进行排序。

    参数

    类型 意图可选 属性 名称
    real(kind=sp), intent(inout) :: array(0:)
    integer(kind=int_index_low), intent(out) :: index(0:)
    real(kind=sp), intent(out), optional :: work(0:)
    integer(kind=int_index_low), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine string_type_sort_index_default(array, index, work, iwork, reverse)

    string_type_sort_index_default( array, index[, work, iwork, reverse] ) 对类型为 type(string_type) 的输入 ARRAY 使用基于 slice.rs"Rust" 排序算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该数组中的索引顺序可以按照所需方向对输入 ARRAY 进行排序。

    参数

    类型 意图可选 属性 名称
    type(string_type), intent(inout) :: array(0:)
    integer(kind=int_index), intent(out) :: index(0:)
    type(string_type), intent(out), optional :: work(0:)
    integer(kind=int_index), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse
  • private module subroutine string_type_sort_index_low(array, index, work, iwork, reverse)

    string_type_sort_index_low( array, index[, work, iwork, reverse] ) 对类型为 type(string_type) 的输入 ARRAY 使用基于 slice.rs"Rust" 排序算法的混合排序,并返回已排序的 ARRAY 和一个索引数组 INDEX,该数组中的索引顺序可以按照所需方向对输入 ARRAY 进行排序。

    参数

    类型 意图可选 属性 名称
    type(string_type), intent(inout) :: array(0:)
    integer(kind=int_index_low), intent(out) :: index(0:)
    type(string_type), intent(out), optional :: work(0:)
    integer(kind=int_index_low), intent(out), optional :: iwork(0:)
    logical, intent(in), optional :: reverse