Skip to content

Commit 8b5156e

Browse files
authored
Merge pull request #1 from gareth-nx/sorting_documentation_updates
Sorting documentation fixes
2 parents 4b96cdd + 4585619 commit 8b5156e

File tree

1 file changed

+17
-16
lines changed

1 file changed

+17
-16
lines changed

src/stdlib_sorting.fypp

+17-16
Original file line numberDiff line numberDiff line change
@@ -65,11 +65,12 @@
6565
module stdlib_sorting
6666
!! This module implements overloaded sorting subroutines named `ORD_SORT`,
6767
!! `SORT_INDEX`, and `SORT`, that each can be used to sort four kinds
68-
!! of `INTEGER` arrays and three kinds of `REAL` arrays. By default, sorting
69-
!! is in order of increasing value, though `SORT_INDEX` has the option of
70-
!! sorting in order of decresasing value. All the subroutines have worst
71-
!! case run time performance of `O(N Ln(N))`, but on largely sorted data
72-
!! `ORD_SORT` and `SORT_INDEX` can have a run time performance of `O(N)`.
68+
!! of `INTEGER` arrays, three kinds of `REAL` arrays, character(len=*) arrays,
69+
!! and arrays of type(string_type). By default sorting is in order of
70+
!! increasing value, but there is an option to sort in decreasing order.
71+
!! All the subroutines have worst case run time performance of `O(N Ln(N))`,
72+
!! but on largely sorted data `ORD_SORT` and `SORT_INDEX` can have a run time
73+
!! performance of `O(N)`.
7374
!!
7475
!! `ORD_SORT` is a translation of the `"Rust" sort` sorting algorithm in
7576
!! `slice.rs`:
@@ -149,10 +150,10 @@ module stdlib_sorting
149150
!! * array: the rank 1 array to be sorted. It is an `intent(inout)`
150151
!! argument of any of the types `integer(int8)`, `integer(int16)`,
151152
!! `integer(int32)`, `integer(int64)`, `real(real32)`, `real(real64)`,
152-
!! `real(real128)`, or `character(*)`. If both the type of `array` is
153-
!! real and at least one of the elements is a `NaN`, then the ordering
154-
!! of the result is undefined. Otherwise it is defined to be the
155-
!! original elements in non-decreasing order.
153+
!! `real(real128)`, `character(*)`, `type(string_type)`. If both the
154+
!! type of `array` is real and at least one of the elements is a
155+
!! `NaN`, then the ordering of the result is undefined. Otherwise it
156+
!! is defined to be the original elements in non-decreasing order.
156157
!!
157158
!! * work (optional): shall be a rank 1 array of the same type as
158159
!! `array`, and shall have at least `size(array)/2` elements. It is an
@@ -199,9 +200,9 @@ module stdlib_sorting
199200
!! * array: the rank 1 array to be sorted. It is an `intent(inout)`
200201
!! argument of any of the types `integer(int8)`, `integer(int16)`,
201202
!! `integer(int32)`, `integer(int64)`, `real(real32)`, `real(real64)`,
202-
!! `real(real128)`, or `character(*)`. If both the type of `array` is
203-
!! real and at least one of the elements is a `NaN`, then the ordering
204-
!! of the result is undefined. Otherwise it is defined to be the
203+
!! `real(real128)`, `character(*)`, `type(string_type)`. If both the type
204+
!! of `array` is real and at least one of the elements is a `NaN`, then
205+
!! the ordering of the result is undefined. Otherwise it is defined to be the
205206
!! original elements in non-decreasing order.
206207
!! * `reverse` (optional): shall be a scalar of type default logical. It
207208
!! is an `intent(in)` argument. If present with a value of `.true.` then
@@ -238,10 +239,10 @@ module stdlib_sorting
238239
!! * array: the rank 1 array to be sorted. It is an `intent(inout)`
239240
!! argument of any of the types `integer(int8)`, `integer(int16)`,
240241
!! `integer(int32)`, `integer(int64)`, `real(real32)`, `real(real64)`,
241-
!! `real(real128)`, or `character(*)`. If both the type of `array` is
242-
!! real and at least one of the elements is a `NaN`, then the ordering
243-
!! of the `array` and `index` results is undefined. Otherwise it is
244-
!! defined to be as specified by reverse.
242+
!! `real(real128)`, `character(*)`, `type(string_type)`. If both the
243+
!! type of `array` is real and at least one of the elements is a `NaN`,
244+
!! then the ordering of the `array` and `index` results is undefined.
245+
!! Otherwise it is defined to be as specified by reverse.
245246
!!
246247
!! * index: a rank 1 array of sorting indices. It is an `intent(out)`
247248
!! argument of the type `integer(int_size)`. Its size shall be the

0 commit comments

Comments
 (0)