13
13
#! This approach allows us to have the same code for all input types.
14
14
#:set IRSCB_TYPES_ALT_NAME = INT_TYPES_ALT_NAME + REAL_TYPES_ALT_NAME + STRING_TYPES_ALT_NAME + CHAR_TYPES_ALT_NAME &
15
15
& + BITSET_TYPES_ALT_NAME
16
+ #:set IR_INDEX_TYPES_ALT_NAME = INT_TYPES_ALT_NAME + REAL_TYPES_ALT_NAME
16
17
17
18
!! Licensing:
18
19
!!
@@ -292,6 +293,76 @@ module stdlib_sorting
292
293
!! ! Sort the random data
293
294
!! call radix_sort( array )
294
295
!! ...
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
295
366
!!```
296
367
297
368
public sort_index
@@ -505,6 +576,43 @@ module stdlib_sorting
505
576
506
577
end interface sort
507
578
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
+
508
616
interface sort_index
509
617
!! Version: experimental
510
618
!!
@@ -521,7 +629,24 @@ module stdlib_sorting
521
629
522
630
#:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
523
631
#: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, &
525
650
reverse )
526
651
!! Version: experimental
527
652
!!
@@ -535,12 +660,29 @@ module stdlib_sorting
535
660
${t2},ドル intent(out), optional :: work(0:)
536
661
${ti},ドル intent(out), optional :: iwork(0:)
537
662
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
+
538
682
end subroutine ${name1}$_sort_index_${namei}$
539
683
540
684
#:endfor
541
685
#:endfor
542
686
543
- end interface sort_index
544
-
545
687
546
688
end module stdlib_sorting
0 commit comments