Skip to content

Commit 3d283a7

Browse files
authored
Merge pull request #824 from jvdp1/rename_int_size
Rename `int size` to `int_index`
2 parents 32018f2 + ec38362 commit 3d283a7

7 files changed

+146
-146
lines changed

doc/specs/stdlib_sorting.md

+12-12
Original file line numberDiff line numberDiff line change
@@ -25,15 +25,15 @@ module's `string_type` type.
2525
## Overview of the module
2626

2727
The module `stdlib_sorting` defines several public entities, one
28-
default integer parameter, `int_size`, and four overloaded
28+
default integer parameter, `int_index`, and four overloaded
2929
subroutines: `ORD_SORT`, `SORT`, `RADIX_SORT` and `SORT_INDEX`. The
3030
overloaded subroutines also each have several specific names for
3131
versions corresponding to different types of array arguments.
3232

33-
### The `int_size` parameter
33+
### The `int_index` parameter
3434

35-
The `int_size` parameter is used to specify the kind of integer used
36-
in indexing the various arrays. Currently the module sets `int_size`
35+
The `int_index` parameter is used to specify the kind of integer used
36+
in indexing the various arrays. Currently the module sets `int_index`
3737
to the value of `int64` from the `stdlib_kinds` module.
3838

3939
### The module subroutines
@@ -414,7 +414,7 @@ It is an `intent(inout)` argument. On input it
414414
will be an array whose sorting indices are to be determined. On return
415415
it will be the sorted array.
416416

417-
`index`: shall be a rank one integer array of kind `int_size` and of
417+
`index`: shall be a rank one integer array of kind `int_index` and of
418418
the size of `array`. It is an `intent(out)` argument. On return it
419419
shall have values that are the indices needed to sort the original
420420
array in the desired direction.
@@ -427,7 +427,7 @@ static storage, its use can significantly reduce the stack memory
427427
requirements for the code. Its contents on return are undefined.
428428

429429
`iwork` (optional): shall be a rank one integer array of kind
430-
`int_size`, and shall have at least `size(array)/2` elements. It
430+
`int_index`, and shall have at least `size(array)/2` elements. It
431431
is an `intent(out)` argument. It is intended to be used as "scratch"
432432
memory for internal record keeping. If associated with an array in
433433
static storage, its use can significantly reduce the stack memory
@@ -465,8 +465,8 @@ Sorting a related rank one array:
465465
integer, intent(inout) :: a(:)
466466
integer(int32), intent(inout) :: b(:) ! The same size as a
467467
integer(int32), intent(out) :: work(:)
468-
integer(int_size), intent(out) :: index(:)
469-
integer(int_size), intent(out) :: iwork(:)
468+
integer(int_index), intent(out) :: index(:)
469+
integer(int_index), intent(out) :: iwork(:)
470470
! Find the indices to sort a
471471
call sort_index(a, index(1:size(a)),&
472472
work(1:size(a)/2), iwork(1:size(a)/2))
@@ -483,8 +483,8 @@ Sorting a rank 2 array based on the data in a column
483483
integer, intent(inout) :: array(:,:)
484484
integer(int32), intent(in) :: column
485485
integer(int32), intent(out) :: work(:)
486-
integer(int_size), intent(out) :: index(:)
487-
integer(int_size), intent(out) :: iwork(:)
486+
integer(int_index), intent(out) :: index(:)
487+
integer(int_index), intent(out) :: iwork(:)
488488
integer, allocatable :: dummy(:)
489489
integer :: i
490490
allocate(dummy(size(array, dim=1)))
@@ -508,8 +508,8 @@ Sorting an array of a derived type based on the data in one component
508508
type(a_type), intent(inout) :: a_data(:)
509509
integer(int32), intent(inout) :: a(:)
510510
integer(int32), intent(out) :: work(:)
511-
integer(int_size), intent(out) :: index(:)
512-
integer(int_size), intent(out) :: iwork(:)
511+
integer(int_index), intent(out) :: index(:)
512+
integer(int_index), intent(out) :: iwork(:)
513513
! Extract a component of `a_data`
514514
a(1:size(a_data)) = a_data(:) % a
515515
! Find the indices to sort the component

src/stdlib_sorting.fypp

+16-16
Original file line numberDiff line numberDiff line change
@@ -137,7 +137,7 @@ module stdlib_sorting
137137
implicit none
138138
private
139139

140-
integer, parameter, public :: int_size = int64 !! Integer kind for indexing
140+
integer, parameter, public :: int_index = int64 !! Integer kind for indexing
141141

142142
! Constants for use by tim_sort
143143
integer, parameter :: &
@@ -152,8 +152,8 @@ module stdlib_sorting
152152
!!
153153
!! Used to pass state around in a stack among helper functions for the
154154
!! `ORD_SORT` and `SORT_INDEX` algorithms
155-
integer(int_size) :: base = 0
156-
integer(int_size) :: len = 0
155+
integer(int_index) :: base = 0
156+
integer(int_index) :: len = 0
157157
end type run_type
158158

159159
public ord_sort
@@ -313,7 +313,7 @@ module stdlib_sorting
313313
!! Otherwise it is defined to be as specified by reverse.
314314
!!
315315
!! * index: a rank 1 array of sorting indices. It is an `intent(out)`
316-
!! argument of the type `integer(int_size)`. Its size shall be the
316+
!! argument of the type `integer(int_index)`. Its size shall be the
317317
!! same as `array`. On return, if defined, its elements would
318318
!! sort the input `array` in the direction specified by `reverse`.
319319
!!
@@ -324,7 +324,7 @@ module stdlib_sorting
324324
!! storage, its use can significantly reduce the stack memory requirements
325325
!! for the code. Its value on return is undefined.
326326
!!
327-
!! * iwork (optional): shall be a rank 1 integer array of kind `int_size`,
327+
!! * iwork (optional): shall be a rank 1 integer array of kind `int_index`,
328328
!! and shall have at least `size(array)/2` elements. It is an
329329
!! `intent(out)` argument to be used as "scratch" memory
330330
!! for internal record keeping. If associated with an array in static
@@ -347,8 +347,8 @@ module stdlib_sorting
347347
!! integer, intent(inout) :: a(:)
348348
!! integer(int32), intent(inout) :: b(:) ! The same size as a
349349
!! integer(int32), intent(out) :: work(:)
350-
!! integer(int_size), intent(out) :: index(:)
351-
!! integer(int_size), intent(out) :: iwork(:)
350+
!! integer(int_index), intent(out) :: index(:)
351+
!! integer(int_index), intent(out) :: iwork(:)
352352
!! ! Find the indices to sort a
353353
!! call sort_index(a, index(1:size(a)),&
354354
!! work(1:size(a)/2), iwork(1:size(a)/2))
@@ -365,8 +365,8 @@ module stdlib_sorting
365365
!! integer, intent(inout) :: a(:,:)
366366
!! integer(int32), intent(in) :: column
367367
!! integer(int32), intent(out) :: work(:)
368-
!! integer(int_size), intent(out) :: index(:)
369-
!! integer(int_size), intent(out) :: iwork(:)
368+
!! integer(int_index), intent(out) :: index(:)
369+
!! integer(int_index), intent(out) :: iwork(:)
370370
!! integer, allocatable :: dummy(:)
371371
!! integer :: i
372372
!! allocate(dummy(size(a, dim=1)))
@@ -389,8 +389,8 @@ module stdlib_sorting
389389
!! type(a_type), intent(inout) :: a_data(:)
390390
!! integer(int32), intent(inout) :: a(:)
391391
!! integer(int32), intent(out) :: work(:)
392-
!! integer(int_size), intent(out) :: index(:)
393-
!! integer(int_size), intent(out) :: iwork(:)
392+
!! integer(int_index), intent(out) :: index(:)
393+
!! integer(int_index), intent(out) :: iwork(:)
394394
!! ! Extract a component of `a_data`
395395
!! a(1:size(a_data)) = a_data(:) % a
396396
!! ! Find the indices to sort the component
@@ -525,11 +525,11 @@ module stdlib_sorting
525525
!! using a hybrid sort based on the `"Rust" sort` algorithm found in `slice.rs`
526526
!! and returns the sorted `ARRAY` and an array `INDEX` of indices in the
527527
!! order that would sort the input `ARRAY` in the desired direction.
528-
${t1}$, intent(inout) :: array(0:)
529-
integer(int_size), intent(out) :: index(0:)
530-
${t2}$, intent(out), optional :: work(0:)
531-
integer(int_size), intent(out), optional :: iwork(0:)
532-
logical, intent(in), optional :: reverse
528+
${t1}$, intent(inout) :: array(0:)
529+
integer(int_index), intent(out) :: index(0:)
530+
${t2}$, intent(out), optional :: work(0:)
531+
integer(int_index), intent(out), optional :: iwork(0:)
532+
logical, intent(in), optional :: reverse
533533
end subroutine ${name1}$_sort_index
534534

535535
#:endfor

src/stdlib_sorting_ord_sort.fypp

+23-23
Original file line numberDiff line numberDiff line change
@@ -113,12 +113,12 @@ contains
113113
${t3}$, intent(out), optional :: work(0:)
114114

115115
${t2}$, allocatable :: buf(:)
116-
integer(int_size) :: array_size
116+
integer(int_index) :: array_size
117117
integer :: stat
118118

119-
array_size = size( array, kind=int_size )
119+
array_size = size( array, kind=int_index )
120120
if ( present(work) ) then
121-
if ( size( work, kind=int_size) < array_size/2 ) then
121+
if ( size( work, kind=int_index) < array_size/2 ) then
122122
error stop "${name1}$_${sname}$_ord_sort: work array is too small."
123123
endif
124124
! Use the work array as scratch memory
@@ -141,17 +141,17 @@ contains
141141
!! Returns the minimum length of a run from 32-63 so that N/MIN_RUN is
142142
!! less than or equal to a power of two. See
143143
!! https://svn.python.org/projects/python/trunk/Objects/listsort.txt
144-
integer(int_size) :: min_run
145-
integer(int_size), intent(in) :: n
144+
integer(int_index) :: min_run
145+
integer(int_index), intent(in) :: n
146146

147-
integer(int_size) :: num, r
147+
integer(int_index) :: num, r
148148

149149
num = n
150-
r = 0_int_size
150+
r = 0_int_index
151151

152152
do while( num >= 64 )
153-
r = ior( r, iand(num, 1_int_size) )
154-
num = ishft(num, -1_int_size)
153+
r = ior( r, iand(num, 1_int_index) )
154+
num = ishft(num, -1_int_index)
155155
end do
156156
min_run = num + r
157157

@@ -162,10 +162,10 @@ contains
162162
! Sorts `ARRAY` using an insertion sort.
163163
${t1}$, intent(inout) :: array(0:)
164164

165-
integer(int_size) :: i, j
165+
integer(int_index) :: i, j
166166
${t3}$ :: key
167167

168-
do j=1, size(array, kind=int_size)-1
168+
do j=1, size(array, kind=int_index)-1
169169
key = array(j)
170170
i = j - 1
171171
do while( i >= 0 )
@@ -185,13 +185,13 @@ contains
185185
!
186186
! 1. len(-3) > len(-2) + len(-1)
187187
! 2. len(-2) > len(-1)
188-
integer(int_size) :: r
188+
integer(int_index) :: r
189189
type(run_type), intent(in), target :: runs(0:)
190190

191-
integer(int_size) :: n
191+
integer(int_index) :: n
192192
logical :: test
193193

194-
n = size(runs, kind=int_size)
194+
n = size(runs, kind=int_index)
195195
test = .false.
196196
if (n >= 2) then
197197
if ( runs( n-1 ) % base == 0 .or. &
@@ -240,10 +240,10 @@ contains
240240
${t1}$, intent(inout) :: array(0:)
241241

242242
${t3}$ :: tmp
243-
integer(int_size) :: i
243+
integer(int_index) :: i
244244

245245
tmp = array(0)
246-
find_hole: do i=1, size(array, kind=int_size)-1
246+
find_hole: do i=1, size(array, kind=int_index)-1
247247
if ( array(i) ${signt}$= tmp ) exit find_hole
248248
array(i-1) = array(i)
249249
end do find_hole
@@ -275,11 +275,11 @@ contains
275275
${t1}$, intent(inout) :: array(0:)
276276
${t3}$, intent(inout) :: buf(0:)
277277

278-
integer(int_size) :: array_size, finish, min_run, r, r_count, &
278+
integer(int_index) :: array_size, finish, min_run, r, r_count, &
279279
start
280280
type(run_type) :: runs(0:max_merge_stack-1), left, right
281281

282-
array_size = size(array, kind=int_size)
282+
array_size = size(array, kind=int_index)
283283

284284
! Very short runs are extended using insertion sort to span at least
285285
! min_run elements. Slices of up to this length are sorted using insertion
@@ -361,12 +361,12 @@ contains
361361
! `ARRAY(0:)`. `MID` must be > 0, and < `SIZE(ARRAY)-1`. Buffer `BUF`
362362
! must be long enough to hold the shorter of the two runs.
363363
${t1}$, intent(inout) :: array(0:)
364-
integer(int_size), intent(in) :: mid
364+
integer(int_index), intent(in) :: mid
365365
${t3}$, intent(inout) :: buf(0:)
366366

367-
integer(int_size) :: array_len, i, j, k
367+
integer(int_index) :: array_len, i, j, k
368368

369-
array_len = size(array, kind=int_size)
369+
array_len = size(array, kind=int_index)
370370

371371
! Merge first copies the shorter run into `buf`. Then, depending on which
372372
! run was shorter, it traces the copied run and the longer run forwards
@@ -417,11 +417,11 @@ contains
417417
! Reverse a segment of an array in place
418418
${t1}$, intent(inout) :: array(0:)
419419

420-
integer(int_size) :: lo, hi
420+
integer(int_index) :: lo, hi
421421
${t3}$ :: temp
422422

423423
lo = 0
424-
hi = size( array, kind=int_size ) - 1
424+
hi = size( array, kind=int_index ) - 1
425425
do while( lo < hi )
426426
temp = array(lo)
427427
array(lo) = array(hi)

0 commit comments

Comments
 (0)