@@ -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,6 +424,50 @@ module stdlib_sorting
379424#:endfor
380425
381426 end interface ord_sort
427+ interface radix_sort
428+ !! Version: experimental
429+ !!
430+ !! The generic subroutine interface implementing the LSD radix sort algorithm,
431+ !! see https://en.wikipedia.org/wiki/Radix_sort for more details.
432+ !! It is always O(N) in sorting random data, but need a O(N) buffer.
433+ !! ([Specification](../page/specs/stdlib_sorting.html#radix_sort-sorts-an-input-array))
434+ !!
435+
436+ pure module subroutine int8_radix_sort(array, reverse)
437+ integer(kind=int8), dimension(:), intent(inout) :: array
438+ logical, intent(in), optional :: reverse
439+ end subroutine int8_radix_sort
440+
441+ pure module subroutine int16_radix_sort(array, work, reverse)
442+ integer(kind=int16), dimension(:), intent(inout) :: array
443+ integer(kind=int16), dimension(:), intent(inout), target, optional :: work
444+ logical, intent(in), optional :: reverse
445+ end subroutine int16_radix_sort
446+
447+ pure module subroutine int32_radix_sort(array, work, reverse)
448+ integer(kind=int32), dimension(:), intent(inout) :: array
449+ integer(kind=int32), dimension(:), intent(inout), target, optional :: work
450+ logical, intent(in), optional :: reverse
451+ end subroutine int32_radix_sort
452+
453+ pure module subroutine int64_radix_sort(array, work, reverse)
454+ integer(kind=int64), dimension(:), intent(inout) :: array
455+ integer(kind=int64), dimension(:), intent(inout), target, optional :: work
456+ logical, intent(in), optional :: reverse
457+ end subroutine int64_radix_sort
458+
459+ module subroutine sp_radix_sort(array, work, reverse)
460+ real(kind=sp), dimension(:), intent(inout), target :: array
461+ real(kind=sp), dimension(:), intent(inout), target, optional :: work
462+ logical, intent(in), optional :: reverse
463+ end subroutine sp_radix_sort
464+
465+ module subroutine dp_radix_sort(array, work, reverse)
466+ real(kind=dp), dimension(:), intent(inout), target :: array
467+ real(kind=dp), dimension(:), intent(inout), target, optional :: work
468+ logical, intent(in), optional :: reverse
469+ end subroutine dp_radix_sort
470+ end interface radix_sort
382471
383472 interface sort
384473!! Version: experimental
0 commit comments