Skip to content

Commit 6bf7785

Browse files
committed
sort_index: all iterators are now set to int_index
1 parent e7cab10 commit 6bf7785

File tree

1 file changed

+31
-31
lines changed

1 file changed

+31
-31
lines changed

src/stdlib_sorting_sort_index.fypp

Lines changed: 31 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -102,17 +102,17 @@ contains
102102
${ti}$, intent(out), optional :: iwork(0:)
103103
logical, intent(in), optional :: reverse
104104

105-
${ti}$ :: array_size, i, stat
105+
integer(int_index) :: array_size, i, stat
106106
${t2}$, allocatable :: buf(:)
107107
${ti}$, allocatable :: ibuf(:)
108108

109-
if ( size(array, kind=int_index) > huge(1_${ki}$) ) then
109+
if ( size(array, kind=int_index) > huge(1_int_index) ) then
110110
error stop "Too many entries for the kind of index."
111111
end if
112112

113-
array_size = size(array, kind=${ki}$)
113+
array_size = size(array, kind=int_index)
114114

115-
if ( size(index, kind=${ki}$) < array_size ) then
115+
if ( size(index, kind=int_index) < array_size ) then
116116
error stop "index array is too small."
117117
end if
118118

@@ -126,11 +126,11 @@ contains
126126

127127
! If necessary allocate buffers to serve as scratch memory.
128128
if ( present(work) ) then
129-
if ( size(work, kind=${ki}$) < array_size/2 ) then
129+
if ( size(work, kind=int_index) < array_size/2 ) then
130130
error stop "work array is too small."
131131
end if
132132
if ( present(iwork) ) then
133-
if ( size(iwork, kind=${ki}$) < array_size/2 ) then
133+
if ( size(iwork, kind=int_index) < array_size/2 ) then
134134
error stop "iwork array is too small."
135135
endif
136136
call merge_sort( array, index, work, iwork )
@@ -148,7 +148,7 @@ contains
148148
#:endif
149149
if ( stat /= 0 ) error stop "Allocation of array buffer failed."
150150
if ( present(iwork) ) then
151-
if ( size(iwork, kind=${ki}$) < array_size/2 ) then
151+
if ( size(iwork, kind=int_index) < array_size/2 ) then
152152
error stop "iwork array is too small."
153153
endif
154154
call merge_sort( array, index, buf, iwork )
@@ -169,17 +169,17 @@ contains
169169
!! Returns the minimum length of a run from 32-63 so that N/MIN_RUN is
170170
!! less than or equal to a power of two. See
171171
!! https://svn.python.org/projects/python/trunk/Objects/listsort.txt
172-
${ti}$ :: min_run
173-
${ti}$, intent(in) :: n
172+
integer(int_index) :: min_run
173+
integer(int_index), intent(in) :: n
174174

175-
${ti}$ :: num, r
175+
integer(int_index) :: num, r
176176

177177
num = n
178-
r = 0_${ki}$
178+
r = 0_int_index
179179

180180
do while( num >= 64 )
181-
r = ior( r, iand(num, 1_${ki}$) )
182-
num = ishft(num, -1_${ki}$)
181+
r = ior( r, iand(num, 1_int_index) )
182+
num = ishft(num, -1_int_index)
183183
end do
184184
min_run = num + r
185185

@@ -192,11 +192,11 @@ contains
192192
${t1}$, intent(inout) :: array(0:)
193193
${ti}$, intent(inout) :: index(0:)
194194

195-
${ti}$ :: i, j
195+
integer(int_index) :: i, j
196196
${ti}$ :: key_index
197197
${t3}$ :: key
198198

199-
do j=1, size(array, kind=${ki}$)-1
199+
do j=1, size(array, kind=int_index)-1
200200
key = array(j)
201201
key_index = index(j)
202202
i = j - 1
@@ -220,13 +220,13 @@ contains
220220
! 1. len(-3) > len(-2) + len(-1)
221221
! 2. len(-2) > len(-1)
222222

223-
${ti}$ :: r
224-
type(run_type_${namei}$), intent(in), target :: runs(0:)
223+
integer(int_index) :: r
224+
type(run_type_default), intent(in), target :: runs(0:)
225225

226-
${ti}$ :: n
226+
integer(int_index) :: n
227227
logical :: test
228228

229-
n = size(runs, kind=${ki}$)
229+
n = size(runs, kind=int_index)
230230
test = .false.
231231
if (n >= 2) then
232232
if ( runs( n-1 ) % base == 0 .or. &
@@ -278,12 +278,12 @@ contains
278278
${ti}$, intent(inout) :: index(0:)
279279

280280
${t3}$ :: tmp
281-
${ti}$ :: i
281+
integer(int_index) :: i
282282
${ti}$ :: tmp_index
283283

284284
tmp = array(0)
285285
tmp_index = index(0)
286-
find_hole: do i=1, size(array, kind=${ki}$)-1
286+
find_hole: do i=1, size(array, kind=int_index)-1
287287
if ( array(i) >= tmp ) exit find_hole
288288
array(i-1) = array(i)
289289
index(i-1) = index(i)
@@ -320,11 +320,11 @@ contains
320320
${t3}$, intent(inout) :: buf(0:)
321321
${ti}$, intent(inout) :: ibuf(0:)
322322

323-
${ti}$ :: array_size, finish, min_run, r, r_count, &
323+
integer(int_index) :: array_size, finish, min_run, r, r_count, &
324324
start
325-
type(run_type_${namei}$) :: runs(0:max_merge_stack-1), left, right
325+
type(run_type_default) :: runs(0:max_merge_stack-1), left, right
326326

327-
array_size = size(array, kind=${ki}$)
327+
array_size = size(array, kind=int_index)
328328

329329
! Very short runs are extended using insertion sort to span at least this
330330
! many elements. Slices of up to this length are sorted using insertion sort.
@@ -372,7 +372,7 @@ contains
372372
end do Insert
373373
if ( start == 0 .and. finish == array_size - 1 ) return
374374

375-
runs(r_count) = run_type_${namei}$( base = start, &
375+
runs(r_count) = run_type_default( base = start, &
376376
len = finish - start + 1 )
377377
finish = start-1
378378
r_count = r_count + 1
@@ -390,7 +390,7 @@ contains
390390
index( left % base: &
391391
right % base + right % len - 1 ), ibuf )
392392

393-
runs(r) = run_type_${namei}$( base = left % base, &
393+
runs(r) = run_type_default( base = left % base, &
394394
len = left % len + right % len )
395395
if ( r == r_count - 3 ) runs(r+1) = runs(r+2)
396396
r_count = r_count - 1
@@ -409,14 +409,14 @@ contains
409409
! `ARRAY(0:)`. `MID` must be > 0, and < `SIZE(ARRAY)-1`. Buffer `BUF`
410410
! must be long enough to hold the shorter of the two runs.
411411
${t1}$, intent(inout) :: array(0:)
412-
${ti}$, intent(in) :: mid
412+
integer(int_index), intent(in) :: mid
413413
${t3}$, intent(inout) :: buf(0:)
414414
${ti}$, intent(inout) :: index(0:)
415415
${ti}$, intent(inout) :: ibuf(0:)
416416

417-
${ti}$ :: array_len, i, j, k
417+
integer(int_index) :: array_len, i, j, k
418418

419-
array_len = size(array, kind=${ki}$)
419+
array_len = size(array, kind=int_index)
420420

421421
! Merge first copies the shorter run into `buf`. Then, depending on which
422422
! run was shorter, it traces the copied run and the longer run forwards
@@ -477,11 +477,11 @@ contains
477477
${ti}$, intent(inout) :: index(0:)
478478

479479
${ti}$ :: itemp
480-
${ti}$ :: lo, hi
480+
integer(int_index) :: lo, hi
481481
${t3}$ :: temp
482482

483483
lo = 0
484-
hi = size( array, kind=${ki}$ ) - 1
484+
hi = size( array, kind=int_index ) - 1
485485
do while( lo < hi )
486486
temp = array(lo)
487487
array(lo) = array(hi)

0 commit comments

Comments
 (0)