Skip to content

Commit 5230234

Browse files
committed
call of sort_adj in sort_index
1 parent 230a85c commit 5230234

File tree

4 files changed

+54
-124
lines changed

4 files changed

+54
-124
lines changed

src/CMakeLists.txt

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,6 @@ set(fppFiles
3939
stdlib_sorting_ord_sort.fypp
4040
stdlib_sorting_sort.fypp
4141
stdlib_sorting_sort_adj.fypp
42-
stdlib_sorting_sort_index.fypp
4342
stdlib_specialfunctions_gamma.fypp
4443
stdlib_stats.fypp
4544
stdlib_stats_corr.fypp

src/stdlib_sorting.fypp

Lines changed: 49 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,9 @@
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

584624
end module stdlib_sorting

src/stdlib_sorting_sort_adj.fypp

Lines changed: 5 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -5,13 +5,12 @@
55
#:set CHAR_TYPES_ALT_NAME = list(zip(["character(len=*)"], ["character(len=:)"], ["character(len=len(array))"], ["char"]))
66
#:set BITSET_TYPES_ALT_NAME = list(zip(BITSET_TYPES, BITSET_TYPES, BITSET_TYPES, BITSET_KINDS))
77

8-
#:set INT_INDEX_TYPES_ALT_NAME = list(zip(["int_index", "int_index_low"], ["integer(int_index)", "integer(int_index_low)"], ["default", "low"]))
9-
108
#! For better code reuse in fypp, make lists that contain the input types,
119
#! with each having output types and a separate name prefix for subroutines
1210
#! This approach allows us to have the same code for all input types.
1311
#:set IRSCB_TYPES_ALT_NAME = INT_TYPES_ALT_NAME + REAL_TYPES_ALT_NAME + STRING_TYPES_ALT_NAME + CHAR_TYPES_ALT_NAME &
1412
& + BITSET_TYPES_ALT_NAME
13+
#:set IRC_INDEX_TYPES_ALT_NAME = INT_TYPES_ALT_NAME + REAL_TYPES_ALT_NAME
1514

1615
!! Licensing:
1716
!!
@@ -68,10 +67,10 @@ submodule(stdlib_sorting) stdlib_sorting_sort_adj
6867

6968
contains
7069

71-
#:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
70+
#:for ki, ti, tii, namei in IRC_INDEX_TYPES_ALT_NAME
7271
#:for t1, t2, t3, name1 in IRSCB_TYPES_ALT_NAME
7372

74-
module subroutine ${name1}$_sort_adj_${namei}$( array, index, work, iwork, reverse )
73+
module subroutine ${name1}$_${namei}$_sort_adj( array, index, work, iwork, reverse )
7574
! A modification of `${name1}$_ord_sort` to return an array of indices that
7675
! would perform a stable sort of the `ARRAY` as input, and also sort `ARRAY`
7776
! as desired. The indices by default
@@ -98,7 +97,7 @@ contains
9897
! used as scratch memory.
9998

10099
${t1}$, intent(inout) :: array(0:)
101-
${ti}$, intent(out) :: index(0:)
100+
${ti}$, intent(inout) :: index(0:)
102101
${t3}$, intent(out), optional :: work(0:)
103102
${ti}$, intent(out), optional :: iwork(0:)
104103
logical, intent(in), optional :: reverse
@@ -117,10 +116,6 @@ contains
117116
error stop "Too many entries for the size of index."
118117
end if
119118

120-
do i = 0, array_size-1
121-
index(i) = int(i+1, kind=${ki}$)
122-
end do
123-
124119
if ( optval(reverse, .false.) ) then
125120
call reverse_segment( array, index )
126121
end if
@@ -494,7 +489,7 @@ contains
494489

495490
end subroutine reverse_segment
496491

497-
end subroutine ${name1}$_sort_adj_${namei}$
492+
end subroutine ${name1}$_${namei}$_sort_adj
498493

499494
#:endfor
500495
#:endfor

src/stdlib_sorting_sort_index.fypp

Lines changed: 0 additions & 104 deletions
This file was deleted.

0 commit comments

Comments
 (0)