Skip to content

Commit

Permalink
Merge pull request #1 from gareth-nx/sorting_documentation_updates
Browse files Browse the repository at this point in the history
Sorting documentation fixes
  • Loading branch information
gareth-nx authored Jun 3, 2021
2 parents 4b96cdd + 4585619 commit 8b5156e
Showing 1 changed file with 17 additions and 16 deletions.
33 changes: 17 additions & 16 deletions src/stdlib_sorting.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -65,11 +65,12 @@
module stdlib_sorting
!! This module implements overloaded sorting subroutines named `ORD_SORT`,
!! `SORT_INDEX`, and `SORT`, that each can be used to sort four kinds
!! of `INTEGER` arrays and three kinds of `REAL` arrays. By default, sorting
!! is in order of increasing value, though `SORT_INDEX` has the option of
!! sorting in order of decresasing value. All the subroutines have worst
!! case run time performance of `O(N Ln(N))`, but on largely sorted data
!! `ORD_SORT` and `SORT_INDEX` can have a run time performance of `O(N)`.
!! of `INTEGER` arrays, three kinds of `REAL` arrays, character(len=*) arrays,
!! and arrays of type(string_type). By default sorting is in order of
!! increasing value, but there is an option to sort in decreasing order.
!! All the subroutines have worst case run time performance of `O(N Ln(N))`,
!! but on largely sorted data `ORD_SORT` and `SORT_INDEX` can have a run time
!! performance of `O(N)`.
!!
!! `ORD_SORT` is a translation of the `"Rust" sort` sorting algorithm in
!! `slice.rs`:
Expand Down Expand Up @@ -149,10 +150,10 @@ module stdlib_sorting
!! * array: the rank 1 array to be sorted. It is an `intent(inout)`
!! argument of any of the types `integer(int8)`, `integer(int16)`,
!! `integer(int32)`, `integer(int64)`, `real(real32)`, `real(real64)`,
!! `real(real128)`, or `character(*)`. If both the type of `array` is
!! real and at least one of the elements is a `NaN`, then the ordering
!! of the result is undefined. Otherwise it is defined to be the
!! original elements in non-decreasing order.
!! `real(real128)`, `character(*)`, `type(string_type)`. If both the
!! type of `array` is real and at least one of the elements is a
!! `NaN`, then the ordering of the result is undefined. Otherwise it
!! is defined to be the original elements in non-decreasing order.
!!
!! * work (optional): shall be a rank 1 array of the same type as
!! `array`, and shall have at least `size(array)/2` elements. It is an
Expand Down Expand Up @@ -199,9 +200,9 @@ module stdlib_sorting
!! * array: the rank 1 array to be sorted. It is an `intent(inout)`
!! argument of any of the types `integer(int8)`, `integer(int16)`,
!! `integer(int32)`, `integer(int64)`, `real(real32)`, `real(real64)`,
!! `real(real128)`, or `character(*)`. If both the type of `array` is
!! real and at least one of the elements is a `NaN`, then the ordering
!! of the result is undefined. Otherwise it is defined to be the
!! `real(real128)`, `character(*)`, `type(string_type)`. If both the type
!! of `array` is real and at least one of the elements is a `NaN`, then
!! the ordering of the result is undefined. Otherwise it is defined to be the
!! original elements in non-decreasing order.
!! * `reverse` (optional): shall be a scalar of type default logical. It
!! is an `intent(in)` argument. If present with a value of `.true.` then
Expand Down Expand Up @@ -238,10 +239,10 @@ module stdlib_sorting
!! * array: the rank 1 array to be sorted. It is an `intent(inout)`
!! argument of any of the types `integer(int8)`, `integer(int16)`,
!! `integer(int32)`, `integer(int64)`, `real(real32)`, `real(real64)`,
!! `real(real128)`, or `character(*)`. If both the type of `array` is
!! real and at least one of the elements is a `NaN`, then the ordering
!! of the `array` and `index` results is undefined. Otherwise it is
!! defined to be as specified by reverse.
!! `real(real128)`, `character(*)`, `type(string_type)`. If both the
!! type of `array` is real and at least one of the elements is a `NaN`,
!! then the ordering of the `array` and `index` results is undefined.
!! Otherwise it is defined to be as specified by reverse.
!!
!! * index: a rank 1 array of sorting indices. It is an `intent(out)`
!! argument of the type `integer(int_size)`. Its size shall be the
Expand Down

0 comments on commit 8b5156e

Please sign in to comment.