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 IRC_INDEX_TYPES_ALT_NAME = INT_TYPES_ALT_NAME + REAL_TYPES_ALT_NAME
17+
18+
1619
1720!! Licensing:
1821!!
@@ -520,23 +523,23 @@ module stdlib_sorting
520523!! non-decreasing sort, but if the optional argument `REVERSE` is present
521524!! with a value of `.TRUE.` the indices correspond to a non-increasing sort.
522525
523- #:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
526+ #:for ki, ti, namei in IRC_INDEX_TYPES_ALT_NAME
524527 #:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
525- module subroutine ${name1}$_sort_adj_ ${namei}$( array, index, work, iwork, &
528+ module subroutine ${name1}$_ ${namei}$_sort_adj ( array, index, work, iwork, &
526529 reverse )
527530!! Version: experimental
528531!!
529- !! `${name1}$_sort_adj_ ${namei}$( array, index[, work, iwork, reverse] )` sorts
532+ !! `${name1}$_ ${namei}$_sort_adj ( array, index[, work, iwork, reverse] )` sorts
530533!! an input `ARRAY` of type `${t1}$`
531534!! using a hybrid sort based on the `"Rust" sort` algorithm found in `slice.rs`
532535!! and returns the sorted `ARRAY` and an array `INDEX` of indices in the
533536!! order that would sort the input `ARRAY` in the desired direction.
534537 ${t1}$, intent(inout) :: array(0:)
535- ${ti}$, intent(out) :: index(0:)
538+ ${ti}$, intent(inout) :: index(0:)
536539 ${t2}$, intent(out), optional :: work(0:)
537- ${ti}$, intent(out), optional :: iwork(0:)
540+ ${ti}$, intent(out), optional :: iwork(0:)
538541 logical, intent(in), optional :: reverse
539- end subroutine ${name1}$_sort_adj_ ${namei}$
542+ end subroutine ${name1}$_ ${namei}$_sort_adj
540543
541544 #:endfor
542545#:endfor
@@ -559,7 +562,24 @@ module stdlib_sorting
559562
560563#:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
561564 #:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
562- module subroutine ${name1}$_sort_index_${namei}$( array, index, work, iwork, &
565+ !> Version: experimental
566+ !>
567+ !> `${name1}$_sort_index_${namei}$( array, index[, work, iwork, reverse] )` sorts
568+ !> an input `ARRAY` of type `${t1}$`
569+ !> using a hybrid sort based on the `"Rust" sort` algorithm found in `slice.rs`
570+ !> and returns the sorted `ARRAY` and an array `INDEX` of indices in the
571+ !> order that would sort the input `ARRAY` in the desired direction.
572+ module procedure ${name1}$_sort_index_${namei}$
573+ #:endfor
574+ #:endfor
575+
576+ end interface sort_index
577+
578+ contains
579+
580+ #:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
581+ #:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
582+ subroutine ${name1}$_sort_index_${namei}$( array, index, work, iwork, &
563583 reverse )
564584!! Version: experimental
565585!!
@@ -573,12 +593,32 @@ module stdlib_sorting
573593 ${t2}$, intent(out), optional :: work(0:)
574594 ${ti}$, intent(out), optional :: iwork(0:)
575595 logical, intent(in), optional :: reverse
596+
597+
598+ integer(int_index) :: array_size, i
599+
600+ array_size = size(array, kind=int_index)
601+
602+ if ( array_size > huge(index)) then
603+ error stop "Too many entries for the kind of index."
604+ end if
605+
606+ if ( array_size > size(index, kind=int_index) ) then
607+ error stop "Too many entries for the size of index."
608+ end if
609+
610+ do i = 0, array_size-1
611+ index(i) = int(i+1, kind=${ki}$)
612+ end do
613+
614+ call sort_adj(array, index, work, iwork, reverse)
615+
616+
617+
576618 end subroutine ${name1}$_sort_index_${namei}$
577619
578620 #:endfor
579621#:endfor
580622
581- end interface sort_index
582-
583623
584624end module stdlib_sorting
0 commit comments