Skip to content

Commit 71280a4

Browse files
committed
Rename int_size to int_index in source code
1 parent 5fd9924 commit 71280a4

File tree

6 files changed

+134
-134
lines changed

6 files changed

+134
-134
lines changed

src/stdlib_sorting.fypp

Lines changed: 16 additions & 16 deletions
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

Lines changed: 23 additions & 23 deletions
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)

src/stdlib_sorting_radix_sort.f90

Lines changed: 29 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,11 @@
1313
contains
1414
! For int8, radix sort becomes counting sort, so buffer is not needed
1515
pure subroutine radix_sort_u8_helper(N, arr)
16-
integer(kind=int_size), intent(in) :: N
16+
integer(kind=int_index), intent(in) :: N
1717
integer(kind=int8), dimension(N), intent(inout) :: arr
18-
integer(kind=int_size) :: i
18+
integer(kind=int_index) :: i
1919
integer :: bin_idx
20-
integer(kind=int_size), dimension(-128:127) :: counts
20+
integer(kind=int_index), dimension(-128:127) :: counts
2121
counts(:) = 0
2222
do i = 1, N
2323
bin_idx = arr(i)
@@ -34,12 +34,12 @@ pure subroutine radix_sort_u8_helper(N, arr)
3434
end subroutine
3535

3636
pure subroutine radix_sort_u16_helper(N, arr, buf)
37-
integer(kind=int_size), intent(in) :: N
37+
integer(kind=int_index), intent(in) :: N
3838
integer(kind=int16), dimension(N), intent(inout) :: arr
3939
integer(kind=int16), dimension(N), intent(inout) :: buf
40-
integer(kind=int_size) :: i
40+
integer(kind=int_index) :: i
4141
integer :: b, b0, b1
42-
integer(kind=int_size), dimension(0:radix_mask) :: c0, c1
42+
integer(kind=int_index), dimension(0:radix_mask) :: c0, c1
4343
c0(:) = 0
4444
c1(:) = 0
4545
do i = 1, N
@@ -65,12 +65,12 @@ pure subroutine radix_sort_u16_helper(N, arr, buf)
6565
end subroutine
6666

6767
pure subroutine radix_sort_u32_helper(N, arr, buf)
68-
integer(kind=int_size), intent(in) :: N
68+
integer(kind=int_index), intent(in) :: N
6969
integer(kind=int32), dimension(N), intent(inout) :: arr
7070
integer(kind=int32), dimension(N), intent(inout) :: buf
71-
integer(kind=int_size) :: i
71+
integer(kind=int_index) :: i
7272
integer :: b, b0, b1, b2, b3
73-
integer(kind=int_size), dimension(0:radix_mask) :: c0, c1, c2, c3
73+
integer(kind=int_index), dimension(0:radix_mask) :: c0, c1, c2, c3
7474
c0(:) = 0
7575
c1(:) = 0
7676
c2(:) = 0
@@ -114,12 +114,12 @@ pure subroutine radix_sort_u32_helper(N, arr, buf)
114114
end subroutine radix_sort_u32_helper
115115

116116
pure subroutine radix_sort_u64_helper(N, arr, buffer)
117-
integer(kind=int_size), intent(in) :: N
117+
integer(kind=int_index), intent(in) :: N
118118
integer(kind=int64), dimension(N), intent(inout) :: arr
119119
integer(kind=int64), dimension(N), intent(inout) :: buffer
120-
integer(kind=int_size) :: i
120+
integer(kind=int_index) :: i
121121
integer(kind=int64) :: b, b0, b1, b2, b3, b4, b5, b6, b7
122-
integer(kind=int_size), dimension(0:radix_mask) :: c0, c1, c2, c3, c4, c5, c6, c7
122+
integer(kind=int_index), dimension(0:radix_mask) :: c0, c1, c2, c3, c4, c5, c6, c7
123123
c0(:) = 0
124124
c1(:) = 0
125125
c2(:) = 0
@@ -202,8 +202,8 @@ pure module subroutine int8_radix_sort(array, reverse)
202202
integer(kind=int8), dimension(:), intent(inout) :: array
203203
logical, intent(in), optional :: reverse
204204
integer(kind=int8) :: item
205-
integer(kind=int_size) :: i, N
206-
N = size(array, kind=int_size)
205+
integer(kind=int_index) :: i, N
206+
N = size(array, kind=int_index)
207207
call radix_sort_u8_helper(N, array)
208208
if (optval(reverse, .false.)) then
209209
do i = 1, N/2
@@ -218,13 +218,13 @@ pure module subroutine int16_radix_sort(array, work, reverse)
218218
integer(kind=int16), dimension(:), intent(inout) :: array
219219
integer(kind=int16), dimension(:), intent(inout), target, optional :: work
220220
logical, intent(in), optional :: reverse
221-
integer(kind=int_size) :: i, N, start, middle, end
221+
integer(kind=int_index) :: i, N, start, middle, end
222222
integer(kind=int16), dimension(:), pointer :: buffer
223223
integer(kind=int16) :: item
224224
logical :: use_internal_buffer
225-
N = size(array, kind=int_size)
225+
N = size(array, kind=int_index)
226226
if (present(work)) then
227-
if (size(work, kind=int_size) < N) then
227+
if (size(work, kind=int_index) < N) then
228228
error stop "int16_radix_sort: work array is too small."
229229
end if
230230
use_internal_buffer = .false.
@@ -270,13 +270,13 @@ pure module subroutine int32_radix_sort(array, work, reverse)
270270
integer(kind=int32), dimension(:), intent(inout) :: array
271271
integer(kind=int32), dimension(:), intent(inout), target, optional :: work
272272
logical, intent(in), optional :: reverse
273-
integer(kind=int_size) :: i, N, start, middle, end
273+
integer(kind=int_index) :: i, N, start, middle, end
274274
integer(kind=int32), dimension(:), pointer :: buffer
275275
integer(kind=int32) :: item
276276
logical :: use_internal_buffer
277-
N = size(array, kind=int_size)
277+
N = size(array, kind=int_index)
278278
if (present(work)) then
279-
if (size(work, kind=int_size) < N) then
279+
if (size(work, kind=int_index) < N) then
280280
error stop "int32_radix_sort: work array is too small."
281281
end if
282282
use_internal_buffer = .false.
@@ -320,14 +320,14 @@ module subroutine sp_radix_sort(array, work, reverse)
320320
real(kind=sp), dimension(:), intent(inout), target :: array
321321
real(kind=sp), dimension(:), intent(inout), target, optional :: work
322322
logical, intent(in), optional :: reverse
323-
integer(kind=int_size) :: i, N, pos, rev_pos
323+
integer(kind=int_index) :: i, N, pos, rev_pos
324324
integer(kind=int32), dimension(:), pointer :: arri32
325325
integer(kind=int32), dimension(:), pointer :: buffer
326326
real(kind=sp) :: item
327327
logical :: use_internal_buffer
328-
N = size(array, kind=int_size)
328+
N = size(array, kind=int_index)
329329
if (present(work)) then
330-
if (size(work, kind=int_size) < N) then
330+
if (size(work, kind=int_index) < N) then
331331
error stop "sp_radix_sort: work array is too small."
332332
end if
333333
use_internal_buffer = .false.
@@ -373,13 +373,13 @@ pure module subroutine int64_radix_sort(array, work, reverse)
373373
integer(kind=int64), dimension(:), intent(inout) :: array
374374
integer(kind=int64), dimension(:), intent(inout), target, optional :: work
375375
logical, intent(in), optional :: reverse
376-
integer(kind=int_size) :: i, N, start, middle, end
376+
integer(kind=int_index) :: i, N, start, middle, end
377377
integer(kind=int64), dimension(:), pointer :: buffer
378378
integer(kind=int64) :: item
379379
logical :: use_internal_buffer
380-
N = size(array, kind=int_size)
380+
N = size(array, kind=int_index)
381381
if (present(work)) then
382-
if (size(work, kind=int_size) < N) then
382+
if (size(work, kind=int_index) < N) then
383383
error stop "int64_radix_sort: work array is too small."
384384
end if
385385
use_internal_buffer = .false.
@@ -423,14 +423,14 @@ module subroutine dp_radix_sort(array, work, reverse)
423423
real(kind=dp), dimension(:), intent(inout), target :: array
424424
real(kind=dp), dimension(:), intent(inout), target, optional :: work
425425
logical, intent(in), optional :: reverse
426-
integer(kind=int_size) :: i, N, pos, rev_pos
426+
integer(kind=int_index) :: i, N, pos, rev_pos
427427
integer(kind=int64), dimension(:), pointer :: arri64
428428
integer(kind=int64), dimension(:), pointer :: buffer
429429
real(kind=dp) :: item
430430
logical :: use_internal_buffer
431-
N = size(array, kind=int_size)
431+
N = size(array, kind=int_index)
432432
if (present(work)) then
433-
if (size(work, kind=int_size) < N) then
433+
if (size(work, kind=int_index) < N) then
434434
error stop "sp_radix_sort: work array is too small."
435435
end if
436436
use_internal_buffer = .false.

0 commit comments

Comments
 (0)