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
0 commit comments