@@ -380,6 +380,97 @@ module stdlib_sorting
380380
381381    end interface ord_sort
382382
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+ 
430+     interface radix_sort
431+ !! Version: experimental
432+ !!
433+ !! The generic subroutine interface implementing the LSD radix sort algorithm,
434+ !! see https://en.wikipedia.org/wiki/Radix_sort for more details.
435+ !! It is always O(N) in sorting random data, but need a O(N) buffer.
436+ !!
437+ 
438+         pure module subroutine int8_radix_sort(array, reverse)
439+             integer(kind=int8), dimension(:), intent(inout) :: array
440+             logical, intent(in), optional :: reverse
441+         end subroutine int8_radix_sort
442+ 
443+         pure module subroutine int16_radix_sort(array, work, reverse)
444+             integer(kind=int16), dimension(:), intent(inout) :: array
445+             integer(kind=int16), dimension(:), intent(inout), target, optional :: work
446+             logical, intent(in), optional :: reverse
447+         end subroutine int16_radix_sort
448+ 
449+         pure module subroutine int32_radix_sort(array, work, reverse)
450+             integer(kind=int32), dimension(:), intent(inout) :: array
451+             integer(kind=int32), dimension(:), intent(inout), target, optional :: work
452+             logical, intent(in), optional :: reverse
453+         end subroutine int32_radix_sort
454+ 
455+         pure module subroutine int64_radix_sort(array, work, reverse)
456+             integer(kind=int64), dimension(:), intent(inout) :: array
457+             integer(kind=int64), dimension(:), intent(inout), target, optional :: work
458+             logical, intent(in), optional :: reverse
459+         end subroutine int64_radix_sort
460+ 
461+         module subroutine sp_radix_sort(array, work, reverse)
462+             real(kind=sp), dimension(:), intent(inout), target :: array
463+             real(kind=sp), dimension(:), intent(inout), target, optional :: work
464+             logical, intent(in), optional :: reverse
465+         end subroutine sp_radix_sort
466+ 
467+         module subroutine dp_radix_sort(array, work, reverse)
468+             real(kind=dp), dimension(:), intent(inout), target :: array
469+             real(kind=dp), dimension(:), intent(inout), target, optional :: work
470+             logical, intent(in), optional :: reverse
471+         end subroutine dp_radix_sort
472+     end interface radix_sort
473+ 
383474    interface sort
384475!! Version: experimental
385476!!
0 commit comments