11#:include "common.fypp"
2- #:set IRS_KINDS_TYPES = INT_KINDS_TYPES + REAL_KINDS_TYPES + STRING_KINDS_TYPES
2+
3+ #:set INT_TYPES_ALT_NAME = list(zip(INT_TYPES, INT_TYPES, INT_KINDS))
4+ #:set REAL_TYPES_ALT_NAME = list(zip(REAL_TYPES, REAL_TYPES, REAL_KINDS))
5+ #:set STRING_TYPES_ALT_NAME = list(zip(STRING_TYPES, STRING_TYPES, STRING_KINDS))
6+ #:set CHAR_TYPES_ALT_NAME = list(zip(["character(len=*)"], ["character(len=len(array))"], ["char"]))
7+
8+ #! For better code reuse in fypp, make lists that contain the input types,
9+ #! with each having output types and a separate name prefix for subroutines
10+ #! This approach allows us to have the same code for all input types.
11+ #:set IRSC_TYPES_ALT_NAME = INT_TYPES_ALT_NAME + REAL_TYPES_ALT_NAME + STRING_TYPES_ALT_NAME + CHAR_TYPES_ALT_NAME
312
413!! Licensing:
514!!
@@ -353,30 +362,19 @@ module stdlib_sorting
353362!! sorted data, having O(N) performance on uniformly non-increasing or
354363!! non-decreasing data.
355364
356- #:for k1, t1 in IRS_KINDS_TYPES
357- module subroutine ${k1 }$_ord_sort( array, work, reverse )
365+ #:for t1, t2, name1 in IRSC_TYPES_ALT_NAME
366+ module subroutine ${name1 }$_ord_sort( array, work, reverse )
358367!! Version: experimental
359368!!
360- !! `${k1 }$_ord_sort( array )` sorts the input `ARRAY` of type `${t1}$`
369+ !! `${name1 }$_ord_sort( array )` sorts the input `ARRAY` of type `${t1}$`
361370!! using a hybrid sort based on the `'Rust" sort` algorithm found in `slice.rs`
362371 ${t1}$, intent(inout) :: array(0:)
363- ${t1 }$, intent(out), optional :: work(0:)
372+ ${t2 }$, intent(out), optional :: work(0:)
364373 logical, intent(in), optional :: reverse
365- end subroutine ${k1 }$_ord_sort
374+ end subroutine ${name1 }$_ord_sort
366375
367376#:endfor
368377
369- module subroutine char_ord_sort( array, work, reverse )
370- !! Version: experimental
371- !!
372- !! `char_ord_sort( array[, work, reverse] )` sorts the input `ARRAY` of type
373- !! `CHARACTER(*)` using a hybrid sort based on the `'Rust" sort` algorithm
374- !! found in `slice.rs`
375- character(len=*), intent(inout) :: array(0:)
376- character(len=len(array)), intent(out), optional :: work(0:)
377- logical, intent(in), optional :: reverse
378- end subroutine char_ord_sort
379-
380378 end interface ord_sort
381379
382380 interface sort
@@ -386,33 +384,21 @@ module stdlib_sorting
386384!! on the `introsort` of David Musser.
387385!! ([Specification](../page/specs/stdlib_sorting.html#sort-sorts-an-input-array))
388386
389- #:for k1, t1 in IRS_KINDS_TYPES
390- pure module subroutine ${k1 }$_sort( array, reverse )
387+ #:for t1, t2, name1 in IRSC_TYPES_ALT_NAME
388+ pure module subroutine ${name1 }$_sort( array, reverse )
391389!! Version: experimental
392390!!
393- !! `${k1 }$_sort( array[, reverse] )` sorts the input `ARRAY` of type `${t1}$`
391+ !! `${name1 }$_sort( array[, reverse] )` sorts the input `ARRAY` of type `${t1}$`
394392!! using a hybrid sort based on the `introsort` of David Musser.
395393!! The algorithm is of order O(N Ln(N)) for all inputs.
396394!! Because it relies on `quicksort`, the coefficient of the O(N Ln(N))
397395!! behavior is small for random data compared to other sorting algorithms.
398396 ${t1}$, intent(inout) :: array(0:)
399397 logical, intent(in), optional :: reverse
400- end subroutine ${k1 }$_sort
398+ end subroutine ${name1 }$_sort
401399
402400#:endfor
403401
404- pure module subroutine char_sort( array, reverse )
405- !! Version: experimental
406- !!
407- !! `char_sort( array[, reverse] )` sorts the input `ARRAY` of type
408- !! `CHARACTER(*)` using a hybrid sort based on the `introsort` of David Musser.
409- !! The algorithm is of order O(N Ln(N)) for all inputs.
410- !! Because it relies on `quicksort`, the coefficient of the O(N Ln(N))
411- !! behavior is small for random data compared to other sorting algorithms.
412- character(len=*), intent(inout) :: array(0:)
413- logical, intent(in), optional :: reverse
414- end subroutine char_sort
415-
416402 end interface sort
417403
418404 interface sort_index
@@ -429,41 +415,25 @@ module stdlib_sorting
429415!! non-decreasing sort, but if the optional argument `REVERSE` is present
430416!! with a value of `.TRUE.` the indices correspond to a non-increasing sort.
431417
432- #:for k1, t1 in IRS_KINDS_TYPES
433- module subroutine ${k1 }$_sort_index( array, index, work, iwork, &
418+ #:for t1, t2, name1 in IRSC_TYPES_ALT_NAME
419+ module subroutine ${name1 }$_sort_index( array, index, work, iwork, &
434420 reverse )
435421!! Version: experimental
436422!!
437- !! `${k1 }$_sort_index( array, index[, work, iwork, reverse] )` sorts
423+ !! `${name1 }$_sort_index( array, index[, work, iwork, reverse] )` sorts
438424!! an input `ARRAY` of type `${t1}$`
439425!! using a hybrid sort based on the `'Rust" sort` algorithm found in `slice.rs`
440426!! and returns the sorted `ARRAY` and an array `INDEX of indices in the
441427!! order that would sort the input `ARRAY` in the desired direction.
442428 ${t1}$, intent(inout) :: array(0:)
443429 integer(int_size), intent(out) :: index(0:)
444- ${t1 }$, intent(out), optional :: work(0:)
430+ ${t2 }$, intent(out), optional :: work(0:)
445431 integer(int_size), intent(out), optional :: iwork(0:)
446432 logical, intent(in), optional :: reverse
447- end subroutine ${k1 }$_sort_index
433+ end subroutine ${name1 }$_sort_index
448434
449435#:endfor
450436
451- module subroutine char_sort_index( array, index, work, iwork, &
452- reverse )
453- !! Version: experimental
454- !!
455- !! `char_sort_index( array, index[, work, iwork, reverse] )` sorts
456- !! an input `ARRAY` of type `CHARACTER(*)`
457- !! using a hybrid sort based on the `'Rust" sort` algorithm found in `slice.rs`
458- !! and returns the sorted `ARRAY` and an array `INDEX of indices in the
459- !! order that would sort the input `ARRAY` in the desired direction.
460- character(len=*), intent(inout) :: array(0:)
461- integer(int_size), intent(out) :: index(0:)
462- character(len=len(array)), intent(out), optional :: work(0:)
463- integer(int_size), intent(out), optional :: iwork(0:)
464- logical, intent(in), optional :: reverse
465- end subroutine char_sort_index
466-
467437 end interface sort_index
468438
469439
0 commit comments