Skip to content

Commit 3cf4711

Browse files
committed
addition of specs and of example
1 parent 962bcc4 commit 3cf4711

File tree

6 files changed

+195
-6
lines changed

6 files changed

+195
-6
lines changed

doc/specs/stdlib_sorting.md

Lines changed: 102 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,9 @@ data:
4646
* `ORD_SORT` is intended to sort simple arrays of intrinsic data
4747
that have significant sections that were partially ordered before
4848
the sort;
49+
* `SORT_ADJ` is based on `ORD_SORT`, but in addition to sorting the
50+
input array, it returns a related array re-ordered in the
51+
same way;
4952
* `SORT_INDEX` is based on `ORD_SORT`, but in addition to sorting the
5053
input array, it returns indices that map the original array to its
5154
sorted version. This enables related arrays to be re-ordered in the
@@ -60,10 +63,10 @@ data:
6063
The Fortran Standard Library is distributed under the MIT
6164
License. However components of the library may be based on code with
6265
additional licensing restrictions. In particular `ORD_SORT`,
63-
`SORT_INDEX`, and `SORT` are translations of codes with their
66+
`SORT_ADJ`, `SORT_INDEX`, and `SORT` are translations of codes with their
6467
own distribution restrictions.
6568

66-
The `ORD_SORT` and `SORT_INDEX` subroutines are essentially
69+
The `ORD_SORT`, `SORT_ADJ` and `SORT_INDEX` subroutines are essentially
6770
translations to Fortran 2008 of the `"Rust" sort` of the Rust Language
6871
distributed as part of
6972
[`slice.rs`](https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs).
@@ -140,6 +143,24 @@ argument or allocated internally on the stack.
140143
Arrays can be also sorted in a decreasing order by providing the argument `reverse
141144
= .true.`.
142145

146+
#### The `SORT_ADJ` subroutine
147+
148+
The `SORT` and `ORD_SORT` subroutines can sort rank 1 isolated
149+
arrays of intrinsic types, but do nothing for the coordinated sorting
150+
of related data, e.g., a related rank 1 array. Therefore the module
151+
provides a subroutine, `SORT_ADJ`, that re-order such a rank 1 array
152+
in the same way as the input array based on the `ORD_SORT` algorithm,
153+
in addition to sorting the input array.
154+
155+
The logic of `SORT_ADJ` parallels that of `ORD_SORT`, with
156+
additional housekeeping to keep the associated array consistent with
157+
the sorted positions of the input array. Because of this additional
158+
housekeeping it has slower runtime performance than `ORD_SORT`.
159+
`SORT_ADJ` requires the use of two "scratch" arrays, that may be
160+
provided as optional `work` and `iwork` arguments or allocated
161+
internally on the stack.
162+
163+
143164
#### The `SORT_INDEX` subroutine
144165

145166
The `SORT` and `ORD_SORT` subroutines can sort rank 1 isolated
@@ -198,7 +219,7 @@ factor of six. Still, even when it shows enhanced performance, its
198219
performance on partially sorted data is typically an order of
199220
magnitude slower than `ORD_SORT`. Its memory requirements are also
200221
low, being of order O(Ln(N)), while the memory requirements of
201-
`ORD_SORT` and `SORT_INDEX` are of order O(N).
222+
`ORD_SORT`, `SORT_ADJ` and `SORT_INDEX` are of order O(N).
202223

203224
#### The `RADIX_SORT` subroutine
204225

@@ -385,6 +406,84 @@ element of `array` is a `NaN`.
385406
{!example/sorting/example_radix_sort.f90!}
386407
```
387408

409+
#### `sort_adj` - sorts an associated array in the same way as the input array, while also sorting the array.
410+
411+
##### Status
412+
413+
Experimental
414+
415+
##### Description
416+
417+
Returns the input `array` sorted in the direction requested while
418+
retaining order stability, and an associated array whose elements are
419+
sorted in the same way as the input `array`.
420+
421+
##### Syntax
422+
423+
`call ` [[stdlib_sorting(module):sort_adj(interface)]] `( array, index[, work, iwork, reverse ] )`
424+
425+
##### Class
426+
427+
Generic subroutine.
428+
429+
##### Arguments
430+
431+
`array`: shall be a rank one array of any of the types:
432+
`integer(int8)`, `integer(int16)`, `integer(int32)`, `integer(int64)`,
433+
`real(sp)`, `real(dp)`, `real(qp)`, `character(*)`, `type(string_type)`,
434+
`type(bitset_64)`, or `type(bitset_large)`.
435+
It is an `intent(inout)` argument. On input it
436+
will be an array whose sorting indices are to be determined. On return
437+
it will be the sorted array.
438+
439+
`index`: shall be a rank one `integer` or `real` array of
440+
the size of `array`. It is an `intent(inout)` argument. On return it
441+
shall have values that are the indices needed to sort the original
442+
array in the desired direction.
443+
444+
`work` (optional): shall be a rank one array of any of the same type as
445+
`array`, and shall have at least `size(array)/2` elements. It is an
446+
`intent(out)` argument. It is intended to be used as "scratch"
447+
memory for internal record keeping. If associated with an array in
448+
static storage, its use can significantly reduce the stack memory
449+
requirements for the code. Its contents on return are undefined.
450+
451+
`iwork` (optional): shall be a rank one integer array of the same kind
452+
of the array `index`, and shall have at least `size(array)/2` elements. It
453+
is an `intent(out)` argument. It is intended to be used as "scratch"
454+
memory for internal record keeping. If associated with an array in
455+
static storage, its use can significantly reduce the stack memory
456+
requirements for the code. Its contents on return are undefined.
457+
458+
`reverse` (optional): shall be a scalar of type default logical. It
459+
is an `intent(in)` argument. If present with a value of `.true.` then
460+
`array` will be sorted in order of non-increasing values in stable
461+
order. Otherwise `array` will be sorted in order of non-decreasing
462+
values in stable order.
463+
464+
##### Notes
465+
466+
`SORT_ADJ` implements the hybrid sorting algorithm of `ORD_SORT`,
467+
keeping the values of `index` consistent with the elements of `array`
468+
as it is sorted. As a `merge sort` based algorithm, it is a stable
469+
sorting comparison algorithm. The optional `work` and `iwork` arrays
470+
replace "scratch" memory that would otherwise be allocated on the
471+
stack. If `array` is of any kind of `REAL` the order of the elements in
472+
`index` and `array` on return are undefined if any element of `array`
473+
is a `NaN`. Sorting of `CHARACTER(*)` and `STRING_TYPE` arrays are
474+
based on the operator `>`, and not on the function `LGT`.
475+
476+
It should be emphasized that the order of `array` will typically be
477+
different on return
478+
479+
##### Examples
480+
481+
Sorting a rank one array with `sort_adj`:
482+
483+
```Fortran
484+
{!example/sorting/example_sort_adj.f90!}
485+
```
486+
388487
#### `sort_index` - creates an array of sorting indices for an input array, while also sorting the array.
389488

390489
##### Status

example/sorting/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
ADD_EXAMPLE(ord_sort)
22
ADD_EXAMPLE(sort)
3+
ADD_EXAMPLE(sort_adj)
34
ADD_EXAMPLE(sort_index)
45
ADD_EXAMPLE(radix_sort)
56
ADD_EXAMPLE(sort_bitset)

example/sorting/example_sort_adj.f90

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
program example_sort_adj
2+
use stdlib_sorting, only: sort_adj
3+
implicit none
4+
integer, allocatable :: array(:)
5+
real, allocatable :: adj(:)
6+
7+
array = [5, 4, 3, 1, 10, 4, 9]
8+
allocate(adj, source=real(array))
9+
10+
call sort_adj(array, adj)
11+
12+
print *, array !print [1, 3, 4, 4, 5, 9, 10]
13+
print *, adj !print [1., 3., 4., 4., 5., 9., 10.]
14+
15+
end program example_sort_adj

src/stdlib_sorting.fypp

Lines changed: 70 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -295,6 +295,76 @@ module stdlib_sorting
295295
!! ! Sort the random data
296296
!! call radix_sort( array )
297297
!! ...
298+
!!```
299+
300+
public sort_adj
301+
!! Version: experimental
302+
!!
303+
!! The generic subroutine implementing the `SORT_ADJ` algorithm to
304+
!! return an index array whose elements are sorted in the same order
305+
!! as the input array in the
306+
!! desired direction. It is primarily intended to be used to sort a
307+
!! rank 1 `integer` or `real` array based on the values of a component of the array.
308+
!! Its use has the syntax:
309+
!!
310+
!! call sort_adj( array, index[, work, iwork, reverse ] )
311+
!!
312+
!! with the arguments:
313+
!!
314+
!! * array: the rank 1 array to be sorted. It is an `intent(inout)`
315+
!! argument of any of the types `integer(int8)`, `integer(int16)`,
316+
!! `integer(int32)`, `integer(int64)`, `real(real32)`, `real(real64)`,
317+
!! `real(real128)`, `character(*)`, `type(string_type)`,
318+
!! `type(bitset_64)`, `type(bitset_large)`. If both the
319+
!! type of `array` is real and at least one of the elements is a `NaN`,
320+
!! then the ordering of the `array` and `index` results is undefined.
321+
!! Otherwise it is defined to be as specified by reverse.
322+
!!
323+
!! * index: a rank 1 `integer` or `real` array. It is an `intent(inout)`
324+
!! argument of the type `integer(int_index)`. Its size shall be the
325+
!! same as `array`. On return, its elements are sorted in the same order
326+
!! as the input `array` in the direction specified by `reverse`.
327+
!!
328+
!! * work (optional): shall be a rank 1 array of the same type as
329+
!! `array`, and shall have at least `size(array)/2` elements. It is an
330+
!! `intent(out)` argument to be used as "scratch" memory
331+
!! for internal record keeping. If associated with an array in static
332+
!! storage, its use can significantly reduce the stack memory requirements
333+
!! for the code. Its value on return is undefined.
334+
!!
335+
!! * iwork (optional): shall be a rank 1 integer array of the same type as `index`,
336+
!! and shall have at least `size(array)/2` elements. It is an
337+
!! `intent(out)` argument to be used as "scratch" memory
338+
!! for internal record keeping. If associated with an array in static
339+
!! storage, its use can significantly reduce the stack memory requirements
340+
!! for the code. Its value on return is undefined.
341+
!!
342+
!! * `reverse` (optional): shall be a scalar of type default logical. It
343+
!! is an `intent(in)` argument. If present with a value of `.true.` then
344+
!! `array` will be sorted in order of non-increasing values in stable
345+
!! order. Otherwise `array` will be sorted in order of non-decreasing
346+
!! values in stable order.
347+
!!
348+
!!#### Examples
349+
!!
350+
!! Sorting a related rank one array:
351+
!!
352+
!!```Fortran
353+
!!program example_sort_adj
354+
!! use stdlib_sorting, only: sort_adj
355+
!! implicit none
356+
!! integer, allocatable :: array(:)
357+
!! real, allocatable :: adj(:)
358+
!!
359+
!! array = [5, 4, 3, 1, 10, 4, 9]
360+
!! allocate(adj, source=real(array))
361+
!!
362+
!! call sort_adj(array, adj)
363+
!!
364+
!! print *, array !print [1, 3, 4, 4, 5, 9, 10]
365+
!! print *, adj !print [1., 3., 4., 4., 5., 9., 10.]
366+
!!
367+
!!end program example_sort_adj
298368
!!```
299369

300370
public sort_index

src/stdlib_sorting_ord_sort.fypp

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -117,6 +117,8 @@ contains
117117
integer :: stat
118118

119119
array_size = size( array, kind=int_index )
120+
121+
! If necessary allocate buffers to serve as scratch memory.
120122
if ( present(work) ) then
121123
if ( size(work, kind=int_index) < array_size/2 ) then
122124
error stop "${name1}$_${sname}$_ord_sort: work array is too small."

src/stdlib_sorting_sort_adj.fypp

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@
4242
!! TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
4343
!! SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
4444
!!
45-
!! The generic subroutine, `SORT_INDEX`, is substantially a translation to
45+
!! The generic subroutine, `SORT_ADJ`, is substantially a translation to
4646
!! Fortran 2008 of the `"Rust" sort` sorting routines in
4747
!! [`slice.rs`](https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs)
4848
!! The `rust sort` implementation is distributed with the header:
@@ -95,7 +95,6 @@ contains
9595
! estimation of the optimal `run size` as suggested in Tim Peters'
9696
! original `listsort.txt`, and the optional `work` and `iwork` arrays to be
9797
! used as scratch memory.
98-
9998
${t1}$, intent(inout) :: array(0:)
10099
${ti}$, intent(inout) :: index(0:)
101100
${t3}$, intent(out), optional :: work(0:)
@@ -104,7 +103,8 @@ contains
104103

105104
${t2}$, allocatable :: buf(:)
106105
${ti}$, allocatable :: ibuf(:)
107-
integer(int_index) :: array_size, i, stat
106+
integer(int_index) :: array_size, i
107+
integer(int_index) :: stat
108108

109109
array_size = size(array, kind=int_index)
110110

@@ -136,6 +136,7 @@ contains
136136
call merge_sort( array, index, work, ibuf )
137137
end if
138138
else
139+
! Allocate a buffer to use as scratch memory.
139140
#:if t1[0:4] == "char"
140141
allocate( ${t3}$ :: buf(0:array_size/2-1), &
141142
stat=stat )
@@ -495,3 +496,4 @@ contains
495496
#:endfor
496497

497498
end submodule stdlib_sorting_sort_adj
499+

0 commit comments

Comments
 (0)