Skip to content

Commit a4c8037

Browse files
committed
add test_real_radix_sorts
1 parent 80adf2b commit a4c8037

File tree

4 files changed

+189
-117
lines changed

4 files changed

+189
-117
lines changed
Lines changed: 5 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,10 @@
11
program example_radix_sort
2-
use iso_fortran_env
3-
use iso_c_binding
4-
use ieee_arithmetic
5-
use stdlib_sorting, only: radix_sort, ord_sort
2+
use iso_fortran_env, only: int8, int16, dp => real64
3+
use stdlib_sorting, only: radix_sort
64
implicit none
75
integer(int8), allocatable :: arri8(:)
86
integer(int16), allocatable :: arri16(:)
9-
real(real64), allocatable, target :: arrf64(:), x
10-
11-
real(real32), dimension(:, :), allocatable :: arr1, arr2
12-
real(real32), dimension(:), allocatable :: work
13-
integer :: i, test_size, repeat
14-
real :: start, stop
7+
real(dp), allocatable, target :: arrf64(:), x
158

169
arri8 = [-128, 127, 0, -1, 1]
1710
call radix_sort(arri8)
@@ -22,33 +15,11 @@ program example_radix_sort
2215
print *, arri16
2316

2417
allocate (arrf64(10))
25-
x = 0.0 ! divide zero will arise compile error
26-
arrf64 = [1.0/x, 0.0, 0.0/x, -1.0/x, -0.0, 1.0, -1.0, 3.45, -3.14, 3.44]
18+
x = 0.0_dp ! divide zero will arise compile error
19+
arrf64 = [1.0_dp/x, 0.0_dp, 0.0_dp/x, -1.0_dp/x, -0.0_dp, 1.0_dp, -1.0_dp, 3.45_dp, -3.14_dp, 3.44_dp]
2720
call radix_sort(arrf64)
2821
print *, arrf64
2922
! In my computer, it gives
3023
! nan, -inf, -3.14, -1.0, -0.0, 0.0, 1.0, 3.44, 3.45, inf
3124
! but the position of nan is undefined, the position of `±inf`, `±0.0` is as expected
32-
33-
test_size = 100000
34-
repeat = 100
35-
allocate (arr1(test_size, repeat))
36-
allocate (arr2(test_size, repeat))
37-
call random_number(arr1)
38-
arr1 = arr1 - 0.5
39-
arr2(:, :) = arr1(:, :)
40-
allocate (work(test_size))
41-
call cpu_time(start)
42-
do i = 1, repeat
43-
call ord_sort(arr1(:, i), work)
44-
end do
45-
call cpu_time(stop)
46-
print *, "ord_sort time = ", (stop - start)
47-
call cpu_time(start)
48-
do i = 1, repeat
49-
call radix_sort(arr2(:, i), work)
50-
end do
51-
call cpu_time(stop)
52-
print *, "radix_sort time = ", (stop - start)
53-
print *, all(arr1 == arr2)
5425
end program example_radix_sort

src/stdlib_sorting.fypp

Lines changed: 45 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -236,6 +236,51 @@ module stdlib_sorting
236236
!! ! Process the sorted data
237237
!! call array_search( array, values )
238238
!! ...
239+
!!```
240+
241+
public radix_sort
242+
!! Version: experimental
243+
!!
244+
!! The generic subroutine implementing the LSD radix sort algorithm to return
245+
!! an input array with its elements sorted in order of (non-)decreasing
246+
!! value. Its use has the syntax:
247+
!!
248+
!! call radix_sort( array[, work, reverse] )
249+
!!
250+
!! with the arguments:
251+
!!
252+
!! * array: the rank 1 array to be sorted. It is an `intent(inout)`
253+
!! argument of any of the types `integer(int8)`, `integer(int16)`,
254+
!! `integer(int32)`, `integer(int64)`, `real(real32)`, `real(real64)`.
255+
!! If both the type of `array` is real and at least one of the
256+
!! elements is a `NaN`, then the ordering of the result is undefined.
257+
!! Otherwise it is defined to be the original elements in
258+
!! non-decreasing order. Especially, -0.0 is lesser than 0.0.
259+
!!
260+
!! * work (optional): shall be a rank 1 array of the same type as
261+
!! `array`, and shall have at least `size(array)` elements. It is an
262+
!! `intent(inout)` argument to be used as buffer. Its value on return is
263+
!! undefined. If it is not present, `radix_sort` will allocate a
264+
!! buffer for use, and deallocate it before return. If you do several
265+
!! similar `radix_sort`s, reusing the `work` array is a good parctice.
266+
!! This argument is not present for `int8_radix_sort` because it use
267+
!! counting sort, so no buffer is needed.
268+
!!
269+
!! * `reverse` (optional): shall be a scalar of type default logical. It
270+
!! is an `intent(in)` argument. If present with a value of `.true.` then
271+
!! `array` will be sorted in order of non-increasing values in stable
272+
!! order. Otherwise index will sort `array` in order of non-decreasing
273+
!! values in stable order.
274+
!!
275+
!!#### Example
276+
!!
277+
!!```fortran
278+
!! ...
279+
!! ! Read random data from a file
280+
!! call read_file( 'dummy_file', array )
281+
!! ! Sort the random data
282+
!! call radix_sort( array )
283+
!! ...
239284
!!```
240285

241286
public sort_index
@@ -379,54 +424,6 @@ module stdlib_sorting
379424
#:endfor
380425

381426
end interface ord_sort
382-
383-
public radix_sort
384-
!! Version: experimental
385-
!!
386-
!! The generic subroutine implementing the LSD radix sort algorithm to return
387-
!! an input array with its elements sorted in order of (non-)decreasing
388-
!! value. Its use has the syntax:
389-
!!
390-
!! call radix_sort( array[, work, reverse] )
391-
!!
392-
!! with the arguments:
393-
!!
394-
!! * array: the rank 1 array to be sorted. It is an `intent(inout)`
395-
!! argument of any of the types `integer(int8)`, `integer(int16)`,
396-
!! `integer(int32)`, `integer(int64)`, `real(real32)`, `real(real64)`.
397-
!! If both the type of `array` is real and at least one of the
398-
!! elements is a `NaN`, then the ordering of the result is undefined.
399-
!! Otherwise it is defined to be the original elements in
400-
!! non-decreasing order. Especially, -0.0 is lesser than 0.0.
401-
!!
402-
!! * work (optional): shall be a rank 1 array of the same type as
403-
!! `array`, and shall have at least `size(array)` elements. It is an
404-
!! `intent(inout)` argument to be used as buffer. Its value on return is
405-
!! undefined. If it is not present, `radix_sort` will allocate a
406-
!! buffer for use, and deallocate it bufore return. If you do several
407-
!! similar `radix_sort`, reuse the `work` array is a good parctice.
408-
!! This argument is not present for `int8_radix_sort` because it use
409-
!! counting sort, so no buffer is needed.
410-
!!
411-
!! * `reverse` (optional): shall be a scalar of type default logical. It
412-
!! is an `intent(in)` argument. If present with a value of `.true.` then
413-
!! `array` will be sorted in order of non-increasing values in stable
414-
!! order. Otherwise index will sort `array` in order of non-decreasing
415-
!! values in stable order.
416-
!!
417-
!!#### Example
418-
!!
419-
!!```fortran
420-
!! ...
421-
!! ! Read random data from a file
422-
!! call read_file( 'dummy_file', array )
423-
!! ! Sort the random data
424-
!! call radix_sort( array )
425-
!! ! Process the sorted data
426-
!! call array_search( array, values )
427-
!! ...
428-
!!```
429-
430427
interface radix_sort
431428
!! Version: experimental
432429
!!

src/stdlib_sorting_radix_sort.f90

Lines changed: 44 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -11,12 +11,13 @@
1111
integer(kind=int64), parameter :: radix_mask_i64 = 255_int64
1212

1313
contains
14+
! For int8, radix sort becomes counting sort, so buffer is not needed
1415
pure subroutine radix_sort_u8_helper(N, arr)
15-
integer(kind=int64), intent(in) :: N
16+
integer(kind=int_size), intent(in) :: N
1617
integer(kind=int8), dimension(N), intent(inout) :: arr
17-
integer(kind=int64) :: i
18+
integer(kind=int_size) :: i
1819
integer :: bin_idx
19-
integer(kind=int64), dimension(-128:127) :: counts
20+
integer(kind=int_size), dimension(-128:127) :: counts
2021
counts(:) = 0
2122
do i = 1, N
2223
bin_idx = arr(i)
@@ -33,12 +34,12 @@ pure subroutine radix_sort_u8_helper(N, arr)
3334
end subroutine
3435

3536
pure subroutine radix_sort_u16_helper(N, arr, buf)
36-
integer(kind=int64), intent(in) :: N
37+
integer(kind=int_size), intent(in) :: N
3738
integer(kind=int16), dimension(N), intent(inout) :: arr
3839
integer(kind=int16), dimension(N), intent(inout) :: buf
39-
integer(kind=int64) :: i
40+
integer(kind=int_size) :: i
4041
integer :: b, b0, b1
41-
integer(kind=int64), dimension(0:radix_mask) :: c0, c1
42+
integer(kind=int_size), dimension(0:radix_mask) :: c0, c1
4243
c0(:) = 0
4344
c1(:) = 0
4445
do i = 1, N
@@ -64,12 +65,12 @@ pure subroutine radix_sort_u16_helper(N, arr, buf)
6465
end subroutine
6566

6667
pure subroutine radix_sort_u32_helper(N, arr, buf)
67-
integer(kind=int64), intent(in) :: N
68+
integer(kind=int_size), intent(in) :: N
6869
integer(kind=int32), dimension(N), intent(inout) :: arr
6970
integer(kind=int32), dimension(N), intent(inout) :: buf
70-
integer(kind=int64) :: i
71+
integer(kind=int_size) :: i
7172
integer :: b, b0, b1, b2, b3
72-
integer(kind=int64), dimension(0:radix_mask) :: c0, c1, c2, c3
73+
integer(kind=int_size), dimension(0:radix_mask) :: c0, c1, c2, c3
7374
c0(:) = 0
7475
c1(:) = 0
7576
c2(:) = 0
@@ -113,12 +114,12 @@ pure subroutine radix_sort_u32_helper(N, arr, buf)
113114
end subroutine radix_sort_u32_helper
114115

115116
pure subroutine radix_sort_u64_helper(N, arr, buffer)
116-
integer(kind=int64), intent(in) :: N
117+
integer(kind=int_size), intent(in) :: N
117118
integer(kind=int64), dimension(N), intent(inout) :: arr
118119
integer(kind=int64), dimension(N), intent(inout) :: buffer
119-
integer(kind=int64) :: i
120+
integer(kind=int_size) :: i
120121
integer(kind=int64) :: b, b0, b1, b2, b3, b4, b5, b6, b7
121-
integer(kind=int64), dimension(0:radix_mask) :: c0, c1, c2, c3, c4, c5, c6, c7
122+
integer(kind=int_size), dimension(0:radix_mask) :: c0, c1, c2, c3, c4, c5, c6, c7
122123
c0(:) = 0
123124
c1(:) = 0
124125
c2(:) = 0
@@ -200,15 +201,15 @@ end subroutine radix_sort_u64_helper
200201
pure module subroutine int8_radix_sort(array, reverse)
201202
integer(kind=int8), dimension(:), intent(inout) :: array
202203
logical, intent(in), optional :: reverse
203-
integer(kind=int8) :: buffer_item
204-
integer(kind=int64) :: i, N
205-
N = size(array, kind=int64)
204+
integer(kind=int8) :: item
205+
integer(kind=int_size) :: i, N
206+
N = size(array, kind=int_size)
206207
call radix_sort_u8_helper(N, array)
207208
if (optval(reverse, .false.)) then
208209
do i = 1, N/2
209-
buffer_item = array(i)
210+
item = array(i)
210211
array(i) = array(N - i + 1)
211-
array(N - i + 1) = buffer_item
212+
array(N - i + 1) = item
212213
end do
213214
end if
214215
end subroutine int8_radix_sort
@@ -217,13 +218,13 @@ pure module subroutine int16_radix_sort(array, work, reverse)
217218
integer(kind=int16), dimension(:), intent(inout) :: array
218219
integer(kind=int16), dimension(:), intent(inout), target, optional :: work
219220
logical, intent(in), optional :: reverse
220-
integer(kind=int64) :: i, N, start, middle, end
221+
integer(kind=int_size) :: i, N, start, middle, end
221222
integer(kind=int16), dimension(:), pointer :: buffer
222223
integer(kind=int16) :: item
223224
logical :: use_internal_buffer
224-
N = size(array, kind=int64)
225+
N = size(array, kind=int_size)
225226
if (present(work)) then
226-
if (size(work, kind=int64) < N) then
227+
if (size(work, kind=int_size) < N) then
227228
error stop "int16_radix_sort: work array is too small."
228229
end if
229230
use_internal_buffer = .false.
@@ -233,6 +234,9 @@ pure module subroutine int16_radix_sort(array, work, reverse)
233234
allocate (buffer(N))
234235
end if
235236
call radix_sort_u16_helper(N, array, buffer)
237+
! After calling `radix_sort_u<width>_helper. The array is sorted as unsigned integers.
238+
! In the view of signed arrsy, the negative numbers are sorted but in the tail of the array.
239+
! Use binary search to find the boundary, and move then to correct position.
236240
if (array(1) >= 0 .and. array(N) < 0) then
237241
start = 1
238242
end = N
@@ -266,13 +270,13 @@ pure module subroutine int32_radix_sort(array, work, reverse)
266270
integer(kind=int32), dimension(:), intent(inout) :: array
267271
integer(kind=int32), dimension(:), intent(inout), target, optional :: work
268272
logical, intent(in), optional :: reverse
269-
integer(kind=int64) :: i, N, start, middle, end
273+
integer(kind=int_size) :: i, N, start, middle, end
270274
integer(kind=int32), dimension(:), pointer :: buffer
271275
integer(kind=int32) :: item
272276
logical :: use_internal_buffer
273-
N = size(array, kind=int64)
277+
N = size(array, kind=int_size)
274278
if (present(work)) then
275-
if (size(work, kind=int64) < N) then
279+
if (size(work, kind=int_size) < N) then
276280
error stop "int32_radix_sort: work array is too small."
277281
end if
278282
use_internal_buffer = .false.
@@ -316,14 +320,14 @@ module subroutine sp_radix_sort(array, work, reverse)
316320
real(kind=sp), dimension(:), intent(inout), target :: array
317321
real(kind=sp), dimension(:), intent(inout), target, optional :: work
318322
logical, intent(in), optional :: reverse
319-
integer(kind=int64) :: i, N, pos, rev_pos
323+
integer(kind=int_size) :: i, N, pos, rev_pos
320324
integer(kind=int32), dimension(:), pointer :: arri32
321325
integer(kind=int32), dimension(:), pointer :: buffer
322326
real(kind=sp) :: item
323327
logical :: use_internal_buffer
324-
N = size(array, kind=int64)
328+
N = size(array, kind=int_size)
325329
if (present(work)) then
326-
if (size(work, kind=int64) < N) then
330+
if (size(work, kind=int_size) < N) then
327331
error stop "sp_radix_sort: work array is too small."
328332
end if
329333
use_internal_buffer = .false.
@@ -334,6 +338,14 @@ module subroutine sp_radix_sort(array, work, reverse)
334338
end if
335339
call c_f_pointer(c_loc(array), arri32, [N])
336340
call radix_sort_u32_helper(N, arri32, buffer)
341+
! After calling `radix_sort_u<width>_helper. The array is sorted as unsigned integers.
342+
! The positive real number is sorted, guaranteed by IEEE-754 standard.
343+
! But the negative real number is sorted in a reversed order, and also in the tail of array.
344+
! Remark that -0.0 is the minimum nagative integer, so using radix sort, -0.0 is naturally lesser than 0.0.
345+
! In IEEE-754 standard, the bit representation of `Inf` is greater than all positive real numbers,
346+
! and the `-Inf` is lesser than all negative real numbers. So the order of `Inf, -Inf` is ok.
347+
! The bit representation of `NaN` may be positive or negative integers in different machine,
348+
! thus if the array contains `NaN`, the result is undefined.
337349
if (arri32(1) >= 0 .and. arri32(N) < 0) then
338350
pos = 1
339351
rev_pos = N
@@ -361,13 +373,13 @@ pure module subroutine int64_radix_sort(array, work, reverse)
361373
integer(kind=int64), dimension(:), intent(inout) :: array
362374
integer(kind=int64), dimension(:), intent(inout), target, optional :: work
363375
logical, intent(in), optional :: reverse
364-
integer(kind=int64) :: i, N, start, middle, end
376+
integer(kind=int_size) :: i, N, start, middle, end
365377
integer(kind=int64), dimension(:), pointer :: buffer
366378
integer(kind=int64) :: item
367379
logical :: use_internal_buffer
368-
N = size(array, kind=int64)
380+
N = size(array, kind=int_size)
369381
if (present(work)) then
370-
if (size(work, kind=int64) < N) then
382+
if (size(work, kind=int_size) < N) then
371383
error stop "int64_radix_sort: work array is too small."
372384
end if
373385
use_internal_buffer = .false.
@@ -411,14 +423,14 @@ module subroutine dp_radix_sort(array, work, reverse)
411423
real(kind=dp), dimension(:), intent(inout), target :: array
412424
real(kind=dp), dimension(:), intent(inout), target, optional :: work
413425
logical, intent(in), optional :: reverse
414-
integer(kind=int64) :: i, N, pos, rev_pos
426+
integer(kind=int_size) :: i, N, pos, rev_pos
415427
integer(kind=int64), dimension(:), pointer :: arri64
416428
integer(kind=int64), dimension(:), pointer :: buffer
417429
real(kind=dp) :: item
418430
logical :: use_internal_buffer
419-
N = size(array, kind=int64)
431+
N = size(array, kind=int_size)
420432
if (present(work)) then
421-
if (size(work, kind=int64) < N) then
433+
if (size(work, kind=int_size) < N) then
422434
error stop "sp_radix_sort: work array is too small."
423435
end if
424436
use_internal_buffer = .false.

0 commit comments

Comments
 (0)