Skip to content

Navigation Menu

Sign in
Appearance settings

Search code, repositories, users, issues, pull requests...

Provide feedback

We read every piece of feedback, and take your input very seriously.

Saved searches

Use saved searches to filter your results more quickly

Sign up
Appearance settings

Commit efb26ca

Browse files
authored
Addition of sort_adj to sort an rank 1 array in the same order as an input array (#849)
2 parents a8519b6 + d65c65f commit efb26ca

File tree

8 files changed

+810
-75
lines changed

8 files changed

+810
-75
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_ADJOINT` is based on `ORD_SORT`, but in addition to sorting the
50+
input array, it re-orders a second array of the same size
51+
according to the same permutations;
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_ADJOINT`, `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_ADJOINT` 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,23 @@ 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_ADJOINT` 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_ADJOINT`, that re-order such a rank 1 array
152+
according to the same permutations as for the input array based on the `ORD_SORT` algorithm,
153+
in addition to sorting the input array.
154+
155+
The logic of `SORT_ADJOINT` 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_ADJOINT` 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+
143163
#### The `SORT_INDEX` subroutine
144164

145165
The `SORT` and `ORD_SORT` subroutines can sort rank 1 isolated
@@ -198,7 +218,7 @@ factor of six. Still, even when it shows enhanced performance, its
198218
performance on partially sorted data is typically an order of
199219
magnitude slower than `ORD_SORT`. Its memory requirements are also
200220
low, being of order O(Ln(N)), while the memory requirements of
201-
`ORD_SORT` and `SORT_INDEX` are of order O(N).
221+
`ORD_SORT`, `SORT_ADJOINT` and `SORT_INDEX` are of order O(N).
202222

203223
#### The `RADIX_SORT` subroutine
204224

@@ -385,6 +405,85 @@ element of `array` is a `NaN`.
385405
{!example/sorting/example_radix_sort.f90!}
386406
```
387407

408+
#### `sort_adjoint` - sorts an associated array
409+
according to the same permutations as for the input 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 according to the same permutations as for the input `array`.
420+
421+
##### Syntax
422+
423+
`call ` [[stdlib_sorting(module):sort_adjoint(interface)]] `( array, adjoint_array[, 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+
`adjoint_array`: 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 `adjoint_array`, 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_ADJOINT` implements the hybrid sorting algorithm of `ORD_SORT`,
467+
keeping the values of `adjoint_array` 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+
`adjoint_array` 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_adjoint`:
482+
483+
```Fortran
484+
{!example/sorting/example_sort_adjoint.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_adjoint)
34
ADD_EXAMPLE(sort_index)
45
ADD_EXAMPLE(radix_sort)
56
ADD_EXAMPLE(sort_bitset)
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
program example_sort_adjoint
2+
use stdlib_sorting, only: sort_adjoint
3+
implicit none
4+
integer, allocatable :: array(:)
5+
real, allocatable :: adjoint(:)
6+
7+
array = [5, 4, 3, 1, 10, 4, 9]
8+
allocate(adjoint, source=real(array))
9+
10+
call sort_adjoint(array, adjoint)
11+
12+
print *, array !print [1, 3, 4, 4, 5, 9, 10]
13+
print *, adjoint !print [1., 3., 4., 4., 5., 9., 10.]
14+
15+
end program example_sort_adjoint

‎src/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ set(fppFiles
4747
stdlib_sorting.fypp
4848
stdlib_sorting_ord_sort.fypp
4949
stdlib_sorting_sort.fypp
50-
stdlib_sorting_sort_index.fypp
50+
stdlib_sorting_sort_adjoint.fypp
5151
stdlib_sparse_constants.fypp
5252
stdlib_sparse_conversion.fypp
5353
stdlib_sparse_kinds.fypp

‎src/stdlib_sorting.fypp

Lines changed: 145 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@
1313
#! This approach allows us to have the same code for all input types.
1414
#:set IRSCB_TYPES_ALT_NAME = INT_TYPES_ALT_NAME + REAL_TYPES_ALT_NAME + STRING_TYPES_ALT_NAME + CHAR_TYPES_ALT_NAME &
1515
& + BITSET_TYPES_ALT_NAME
16+
#:set IR_INDEX_TYPES_ALT_NAME = INT_TYPES_ALT_NAME + REAL_TYPES_ALT_NAME
1617

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

297368
public sort_index
@@ -505,6 +576,43 @@ module stdlib_sorting
505576

506577
end interface sort
507578

579+
interface sort_adjoint
580+
!! Version: experimental
581+
!!
582+
!! The generic subroutine interface implementing the `SORT_ADJ` algorithm,
583+
!! based on the `"Rust" sort` algorithm found in `slice.rs`
584+
!! https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs#L2159
585+
!! but modified to return an array of indices that would provide a stable
586+
!! sort of the rank one `ARRAY` input.
587+
!! ([Specification](../page/specs/stdlib_sorting.html#sort_adjoint-creates-an-array-of-sorting-indices-for-an-input-array-while-also-sorting-the-array))
588+
!!
589+
!! The indices by default correspond to a
590+
!! non-decreasing sort, but if the optional argument `REVERSE` is present
591+
!! with a value of `.TRUE.` the indices correspond to a non-increasing sort.
592+
593+
#:for ti, tii, namei in IR_INDEX_TYPES_ALT_NAME
594+
#:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
595+
module subroutine ${name1}$_${namei}$_sort_adjoint( array, adjoint_array, work, iwork, &
596+
reverse )
597+
!! Version: experimental
598+
!!
599+
!! `${name1}$_${namei}$_sort_adjoint( array, adjoint_array[, work, iwork, reverse] )` sorts
600+
!! an input `ARRAY` of type `${t1}$`
601+
!! using a hybrid sort based on the `"Rust" sort` algorithm found in `slice.rs`
602+
!! and returns the sorted `ARRAY` and an array `INDEX` of indices in the
603+
!! order that would sort the input `ARRAY` in the desired direction.
604+
${t1},ドル intent(inout) :: array(0:)
605+
${ti},ドル intent(inout) :: adjoint_array(0:)
606+
${t2},ドル intent(out), optional :: work(0:)
607+
${ti},ドル intent(out), optional :: iwork(0:)
608+
logical, intent(in), optional :: reverse
609+
end subroutine ${name1}$_${namei}$_sort_adjoint
610+
611+
#:endfor
612+
#:endfor
613+
614+
end interface sort_adjoint
615+
508616
interface sort_index
509617
!! Version: experimental
510618
!!
@@ -521,7 +629,24 @@ module stdlib_sorting
521629

522630
#:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
523631
#:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
524-
module subroutine ${name1}$_sort_index_${namei}$( array, index, work, iwork, &
632+
!> Version: experimental
633+
!>
634+
!> `${name1}$_sort_index_${namei}$( array, index[, work, iwork, reverse] )` sorts
635+
!> an input `ARRAY` of type `${t1}$`
636+
!> using a hybrid sort based on the `"Rust" sort` algorithm found in `slice.rs`
637+
!> and returns the sorted `ARRAY` and an array `INDEX` of indices in the
638+
!> order that would sort the input `ARRAY` in the desired direction.
639+
module procedure ${name1}$_sort_index_${namei}$
640+
#:endfor
641+
#:endfor
642+
643+
end interface sort_index
644+
645+
contains
646+
647+
#:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
648+
#:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
649+
subroutine ${name1}$_sort_index_${namei}$( array, index, work, iwork, &
525650
reverse )
526651
!! Version: experimental
527652
!!
@@ -535,12 +660,29 @@ module stdlib_sorting
535660
${t2},ドル intent(out), optional :: work(0:)
536661
${ti},ドル intent(out), optional :: iwork(0:)
537662
logical, intent(in), optional :: reverse
663+
664+
integer(int_index) :: array_size, i
665+
666+
array_size = size(array, kind=int_index)
667+
668+
if ( array_size > huge(index)) then
669+
error stop "Too many entries for the kind of index."
670+
end if
671+
672+
if ( array_size > size(index, kind=int_index) ) then
673+
error stop "Too many entries for the size of index."
674+
end if
675+
676+
do i = 0, array_size-1
677+
index(i) = int(i+1, kind=${ki}$)
678+
end do
679+
680+
call sort_adjoint(array, index, work, iwork, reverse)
681+
538682
end subroutine ${name1}$_sort_index_${namei}$
539683

540684
#:endfor
541685
#:endfor
542686

543-
end interface sort_index
544-
545687

546688
end module stdlib_sorting

‎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."

0 commit comments

Comments
(0)

AltStyle によって変換されたページ (->オリジナル) /