Skip to content

Commit b1e51da

Browse files
committed
rename adj and index to adjoint
1 parent 28b6f71 commit b1e51da

File tree

6 files changed

+86
-86
lines changed

6 files changed

+86
-86
lines changed

example/sorting/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
ADD_EXAMPLE(ord_sort)
22
ADD_EXAMPLE(sort)
3-
ADD_EXAMPLE(sort_adj)
3+
ADD_EXAMPLE(sort_adjoint)
44
ADD_EXAMPLE(sort_index)
55
ADD_EXAMPLE(radix_sort)
66
ADD_EXAMPLE(sort_bitset)

example/sorting/example_sort_adj.f90

Lines changed: 0 additions & 15 deletions
This file was deleted.
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
program example_sort_adjoint
2+
use stdlib_sorting, only: sort_adjoint
3+
implicit none
4+
integer, allocatable :: array(:)
5+
real, allocatable :: adjoint(:)
6+
7+
array = [5, 4, 3, 1, 10, 4, 9]
8+
allocate(adjoint, source=real(array))
9+
10+
call sort_adjoint(array, adjoint)
11+
12+
print *, array !print [1, 3, 4, 4, 5, 9, 10]
13+
print *, adjoint !print [1., 3., 4., 4., 5., 9., 10.]
14+
15+
end program example_sort_adjoint

src/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ set(fppFiles
3838
stdlib_sorting.fypp
3939
stdlib_sorting_ord_sort.fypp
4040
stdlib_sorting_sort.fypp
41-
stdlib_sorting_sort_adj.fypp
41+
stdlib_sorting_sort_adjoint.fypp
4242
stdlib_specialfunctions_gamma.fypp
4343
stdlib_stats.fypp
4444
stdlib_stats_corr.fypp

src/stdlib_sorting.fypp

Lines changed: 19 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -295,17 +295,17 @@ module stdlib_sorting
295295
!! ...
296296
!!```
297297

298-
public sort_adj
298+
public sort_adjoint
299299
!! Version: experimental
300300
!!
301301
!! The generic subroutine implementing the `SORT_ADJ` algorithm to
302-
!! return an index array whose elements are sorted in the same order
302+
!! return an adjoint array whose elements are sorted in the same order
303303
!! as the input array in the
304304
!! desired direction. It is primarily intended to be used to sort a
305305
!! rank 1 `integer` or `real` array based on the values of a component of the array.
306306
!! Its use has the syntax:
307307
!!
308-
!! call sort_adj( array, index[, work, iwork, reverse ] )
308+
!! call sort_adjoint( array, adjoint_array[, work, iwork, reverse ] )
309309
!!
310310
!! with the arguments:
311311
!!
@@ -315,11 +315,11 @@ module stdlib_sorting
315315
!! `real(real128)`, `character(*)`, `type(string_type)`,
316316
!! `type(bitset_64)`, `type(bitset_large)`. If both the
317317
!! type of `array` is real and at least one of the elements is a `NaN`,
318-
!! then the ordering of the `array` and `index` results is undefined.
318+
!! then the ordering of the `array` and `adjoint_array` results is undefined.
319319
!! Otherwise it is defined to be as specified by reverse.
320320
!!
321-
!! * index: a rank 1 `integer` or `real` array. It is an `intent(inout)`
322-
!! argument of the type `integer(int_index)`. Its size shall be the
321+
!! * adjoint_array: a rank 1 `integer` or `real` array. It is an `intent(inout)`
322+
!! argument. Its size shall be the
323323
!! same as `array`. On return, its elements are sorted in the same order
324324
!! as the input `array` in the direction specified by `reverse`.
325325
!!
@@ -330,7 +330,7 @@ module stdlib_sorting
330330
!! storage, its use can significantly reduce the stack memory requirements
331331
!! for the code. Its value on return is undefined.
332332
!!
333-
!! * iwork (optional): shall be a rank 1 integer array of the same type as `index`,
333+
!! * iwork (optional): shall be a rank 1 integer array of the same type as `adjoint_array`,
334334
!! and shall have at least `size(array)/2` elements. It is an
335335
!! `intent(out)` argument to be used as "scratch" memory
336336
!! for internal record keeping. If associated with an array in static
@@ -348,21 +348,21 @@ module stdlib_sorting
348348
!! Sorting a related rank one array:
349349
!!
350350
!!```Fortran
351-
!!program example_sort_adj
352-
!! use stdlib_sorting, only: sort_adj
351+
!!program example_sort_adjoint
352+
!! use stdlib_sorting, only: sort_adjoint
353353
!! implicit none
354354
!! integer, allocatable :: array(:)
355355
!! real, allocatable :: adj(:)
356356
!!
357357
!! array = [5, 4, 3, 1, 10, 4, 9]
358358
!! allocate(adj, source=real(array))
359359
!!
360-
!! call sort_adj(array, adj)
360+
!! call sort_adjoint(array, adj)
361361
!!
362362
!! print *, array !print [1, 3, 4, 4, 5, 9, 10]
363363
!! print *, adj !print [1., 3., 4., 4., 5., 9., 10.]
364364
!!
365-
!!end program example_sort_adj
365+
!!end program example_sort_adjoint
366366
!!```
367367

368368
public sort_index
@@ -576,42 +576,42 @@ module stdlib_sorting
576576

577577
end interface sort
578578

579-
interface sort_adj
579+
interface sort_adjoint
580580
!! Version: experimental
581581
!!
582582
!! The generic subroutine interface implementing the `SORT_ADJ` algorithm,
583583
!! based on the `"Rust" sort` algorithm found in `slice.rs`
584584
!! https://github.com/rust-lang/rust/blob/90eb44a5897c39e3dff9c7e48e3973671dcd9496/src/liballoc/slice.rs#L2159
585585
!! but modified to return an array of indices that would provide a stable
586586
!! sort of the rank one `ARRAY` input.
587-
!! ([Specification](../page/specs/stdlib_sorting.html#sort_adj-creates-an-array-of-sorting-indices-for-an-input-array-while-also-sorting-the-array))
587+
!! ([Specification](../page/specs/stdlib_sorting.html#sort_adjoint-creates-an-array-of-sorting-indices-for-an-input-array-while-also-sorting-the-array))
588588
!!
589589
!! The indices by default correspond to a
590590
!! non-decreasing sort, but if the optional argument `REVERSE` is present
591591
!! with a value of `.TRUE.` the indices correspond to a non-increasing sort.
592592

593593
#:for ti, tii, namei in IR_INDEX_TYPES_ALT_NAME
594594
#:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
595-
module subroutine ${name1}$_${namei}$_sort_adj( array, index, work, iwork, &
595+
module subroutine ${name1}$_${namei}$_sort_adjoint( array, adjoint_array, work, iwork, &
596596
reverse )
597597
!! Version: experimental
598598
!!
599-
!! `${name1}$_${namei}$_sort_adj( array, index[, work, iwork, reverse] )` sorts
599+
!! `${name1}$_${namei}$_sort_adjoint( array, adjoint_array[, work, iwork, reverse] )` sorts
600600
!! an input `ARRAY` of type `${t1}$`
601601
!! using a hybrid sort based on the `"Rust" sort` algorithm found in `slice.rs`
602602
!! and returns the sorted `ARRAY` and an array `INDEX` of indices in the
603603
!! order that would sort the input `ARRAY` in the desired direction.
604604
${t1}$, intent(inout) :: array(0:)
605-
${ti}$, intent(inout) :: index(0:)
605+
${ti}$, intent(inout) :: adjoint_array(0:)
606606
${t2}$, intent(out), optional :: work(0:)
607607
${ti}$, intent(out), optional :: iwork(0:)
608608
logical, intent(in), optional :: reverse
609-
end subroutine ${name1}$_${namei}$_sort_adj
609+
end subroutine ${name1}$_${namei}$_sort_adjoint
610610

611611
#:endfor
612612
#:endfor
613613

614-
end interface sort_adj
614+
end interface sort_adjoint
615615

616616
interface sort_index
617617
!! Version: experimental
@@ -677,7 +677,7 @@ contains
677677
index(i) = int(i+1, kind=${ki}$)
678678
end do
679679

680-
call sort_adj(array, index, work, iwork, reverse)
680+
call sort_adjoint(array, index, work, iwork, reverse)
681681

682682
end subroutine ${name1}$_sort_index_${namei}$
683683

0 commit comments

Comments
 (0)