Skip to content

Commit efb53f5

Browse files
authored
Merge pull request #829 from jvdp1/sort_32
Support of `int32` `index` array in `sort_index`
2 parents dc707f8 + de505f2 commit efb53f5

8 files changed

+187
-129
lines changed

doc/specs/stdlib_sorting.md

+17-10
Original file line numberDiff line numberDiff line change
@@ -24,17 +24,18 @@ module's `string_type` type.
2424

2525
## Overview of the module
2626

27-
The module `stdlib_sorting` defines several public entities, one
28-
default integer parameter, `int_index`, and four overloaded
27+
The module `stdlib_sorting` defines several public entities, two
28+
default integer parameters, `int_index` and `int_index_low`, and four overloaded
2929
subroutines: `ORD_SORT`, `SORT`, `RADIX_SORT` and `SORT_INDEX`. The
3030
overloaded subroutines also each have several specific names for
3131
versions corresponding to different types of array arguments.
3232

33-
### The `int_index` parameter
33+
### The parameters `int_index` and `int_index_low`
3434

35-
The `int_index` parameter is used to specify the kind of integer used
36-
in indexing the various arrays. Currently the module sets `int_index`
37-
to the value of `int64` from the `stdlib_kinds` module.
35+
The parameters `int_index` and `int_index_low` are used to specify the kind of integer used
36+
in indexing the various arrays. Currently the module sets `int_index` and
37+
`int_index_low`
38+
to the value of `int64` and `int32` from the `stdlib_kinds` module, respectively.
3839

3940
### The module subroutines
4041

@@ -414,7 +415,7 @@ It is an `intent(inout)` argument. On input it
414415
will be an array whose sorting indices are to be determined. On return
415416
it will be the sorted array.
416417

417-
`index`: shall be a rank one integer array of kind `int_index` and of
418+
`index`: shall be a rank one integer array of kind `int_index` or `int_index_low` and of
418419
the size of `array`. It is an `intent(out)` argument. On return it
419420
shall have values that are the indices needed to sort the original
420421
array in the desired direction.
@@ -426,8 +427,8 @@ memory for internal record keeping. If associated with an array in
426427
static storage, its use can significantly reduce the stack memory
427428
requirements for the code. Its contents on return are undefined.
428429

429-
`iwork` (optional): shall be a rank one integer array of kind
430-
`int_index`, and shall have at least `size(array)/2` elements. It
430+
`iwork` (optional): shall be a rank one integer array of the same kind
431+
of the array `index`, and shall have at least `size(array)/2` elements. It
431432
is an `intent(out)` argument. It is intended to be used as "scratch"
432433
memory for internal record keeping. If associated with an array in
433434
static storage, its use can significantly reduce the stack memory
@@ -457,6 +458,12 @@ different on return
457458

458459
##### Examples
459460

461+
Sorting a rank one array with `sort_index`:
462+
463+
```Fortran
464+
{!example/sorting/example_sort_index.f90!}
465+
```
466+
460467
Sorting a related rank one array:
461468

462469
```Fortran
@@ -504,7 +511,7 @@ Sorting an array of a derived type based on the data in one component
504511

505512
```fortran
506513
subroutine sort_a_data( a_data, a, work, index, iwork )
507-
! Sort `a_data` in terms or its component `a`
514+
! Sort `a_data` in terms of its component `a`
508515
type(a_type), intent(inout) :: a_data(:)
509516
integer(int32), intent(inout) :: a(:)
510517
integer(int32), intent(out) :: work(:)

example/sorting/CMakeLists.txt

+2-1
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
ADD_EXAMPLE(ord_sort)
22
ADD_EXAMPLE(sort)
3+
ADD_EXAMPLE(sort_index)
34
ADD_EXAMPLE(radix_sort)
4-
ADD_EXAMPLE(sort_bitset)
5+
ADD_EXAMPLE(sort_bitset)
+15
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
program example_sort_index
2+
use stdlib_sorting, only: sort_index
3+
implicit none
4+
integer, allocatable :: array(:)
5+
integer, allocatable :: index(:)
6+
7+
array = [5, 4, 3, 1, 10, 4, 9]
8+
allocate(index, mold=array)
9+
10+
call sort_index(array, index)
11+
12+
print *, array !print [1, 3, 4, 4, 5, 9, 10]
13+
print *, index !print [4, 3, 2, 6, 1, 7, 5]
14+
15+
end program example_sort_index

src/stdlib_sorting.fypp

+18-10
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,8 @@
66
#:set CHAR_TYPES_ALT_NAME = list(zip(["character(len=*)"], ["character(len=len(array))"], ["char"]))
77
#:set BITSET_TYPES_ALT_NAME = list(zip(BITSET_TYPES, BITSET_TYPES, BITSET_KINDS))
88

9+
#:set INT_INDEX_TYPES_ALT_NAME = list(zip(["int_index", "int_index_low"], ["integer(int_index)", "integer(int_index_low)"], ["default", "low"]))
10+
911
#! For better code reuse in fypp, make lists that contain the input types,
1012
#! with each having output types and a separate name prefix for subroutines
1113
#! This approach allows us to have the same code for all input types.
@@ -138,6 +140,8 @@ module stdlib_sorting
138140
private
139141

140142
integer, parameter, public :: int_index = int64 !! Integer kind for indexing
143+
integer, parameter, public :: int_index_low = int32 !! Integer kind for indexing using less than `huge(1_int32)` values
144+
141145

142146
! Constants for use by tim_sort
143147
integer, parameter :: &
@@ -147,14 +151,16 @@ module stdlib_sorting
147151
max_merge_stack = int( ceiling( log( 2._dp**64 ) / &
148152
log(1.6180339887_dp) ) )
149153

150-
type run_type
154+
#:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
155+
type run_type_${namei}$
151156
!! Version: experimental
152157
!!
153158
!! Used to pass state around in a stack among helper functions for the
154159
!! `ORD_SORT` and `SORT_INDEX` algorithms
155-
integer(int_index) :: base = 0
156-
integer(int_index) :: len = 0
157-
end type run_type
160+
${ti}$ :: base = 0
161+
${ti}$ :: len = 0
162+
end type run_type_${namei}$
163+
#:endfor
158164

159165
public ord_sort
160166
!! Version: experimental
@@ -515,23 +521,25 @@ module stdlib_sorting
515521
!! non-decreasing sort, but if the optional argument `REVERSE` is present
516522
!! with a value of `.TRUE.` the indices correspond to a non-increasing sort.
517523

518-
#:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
519-
module subroutine ${name1}$_sort_index( array, index, work, iwork, &
524+
#:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
525+
#:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
526+
module subroutine ${name1}$_sort_index_${namei}$( array, index, work, iwork, &
520527
reverse )
521528
!! Version: experimental
522529
!!
523-
!! `${name1}$_sort_index( array, index[, work, iwork, reverse] )` sorts
530+
!! `${name1}$_sort_index_${namei}$( array, index[, work, iwork, reverse] )` sorts
524531
!! an input `ARRAY` of type `${t1}$`
525532
!! using a hybrid sort based on the `"Rust" sort` algorithm found in `slice.rs`
526533
!! and returns the sorted `ARRAY` and an array `INDEX` of indices in the
527534
!! order that would sort the input `ARRAY` in the desired direction.
528535
${t1}$, intent(inout) :: array(0:)
529-
integer(int_index), intent(out) :: index(0:)
536+
${ti}$, intent(out) :: index(0:)
530537
${t2}$, intent(out), optional :: work(0:)
531-
integer(int_index), intent(out), optional :: iwork(0:)
538+
${ti}$, intent(out), optional :: iwork(0:)
532539
logical, intent(in), optional :: reverse
533-
end subroutine ${name1}$_sort_index
540+
end subroutine ${name1}$_sort_index_${namei}$
534541

542+
#:endfor
535543
#:endfor
536544

537545
end interface sort_index

src/stdlib_sorting_ord_sort.fypp

+4-4
Original file line numberDiff line numberDiff line change
@@ -186,7 +186,7 @@ contains
186186
! 1. len(-3) > len(-2) + len(-1)
187187
! 2. len(-2) > len(-1)
188188
integer(int_index) :: r
189-
type(run_type), intent(in), target :: runs(0:)
189+
type(run_type_default), intent(in), target :: runs(0:)
190190

191191
integer(int_index) :: n
192192
logical :: test
@@ -277,7 +277,7 @@ contains
277277

278278
integer(int_index) :: array_size, finish, min_run, r, r_count, &
279279
start
280-
type(run_type) :: runs(0:max_merge_stack-1), left, right
280+
type(run_type_default) :: runs(0:max_merge_stack-1), left, right
281281

282282
array_size = size(array, kind=int_index)
283283

@@ -326,7 +326,7 @@ contains
326326
end do Insert
327327
if ( start == 0 .and. finish == array_size - 1 ) return
328328

329-
runs(r_count) = run_type( base = start, &
329+
runs(r_count) = run_type_default( base = start, &
330330
len = finish - start + 1 )
331331
finish = start-1
332332
r_count = r_count + 1
@@ -342,7 +342,7 @@ contains
342342
right % base + right % len - 1 ), &
343343
left % len, buf )
344344

345-
runs(r) = run_type( base = left % base, &
345+
runs(r) = run_type_default( base = left % base, &
346346
len = left % len + right % len )
347347
if ( r == r_count - 3 ) runs(r+1) = runs(r+2)
348348
r_count = r_count - 1

0 commit comments

Comments
 (0)