@@ -156,7 +156,7 @@ module stdlib_sorting
156156!!
157157!! * work (optional): shall be a rank 1 array of the same type as
158158!! `array`, and shall have at least `size(array)/2` elements. It is an
159- !! `intent(inout )` argument to be used as "scratch" memory
159+ !! `intent(out )` argument to be used as "scratch" memory
160160!! for internal record keeping. If associated with an array in static
161161!! storage, its use can significantly reduce the stack memory requirements
162162!! for the code. Its value on return is undefined.
@@ -232,21 +232,21 @@ module stdlib_sorting
232232!! of the `array` and `index` results is undefined. Otherwise it is
233233!! defined to be as specified by reverse.
234234!!
235- !! * index: a rank 1 array of sorting indices. It is an `intent(inout )`
235+ !! * index: a rank 1 array of sorting indices. It is an `intent(out )`
236236!! argument of the type `integer(int_size)`. Its size shall be the
237237!! same as `array`. On return, if defined, its elements would
238238!! sort the input `array` in the direction specified by `reverse`.
239239!!
240240!! * work (optional): shall be a rank 1 array of the same type as
241241!! `array`, and shall have at least `size(array)/2` elements. It is an
242- !! `intent(inout )` argument to be used as "scratch" memory
242+ !! `intent(out )` argument to be used as "scratch" memory
243243!! for internal record keeping. If associated with an array in static
244244!! storage, its use can significantly reduce the stack memory requirements
245245!! for the code. Its value on return is undefined.
246246!!
247247!! * iwork (optional): shall be a rank 1 integer array of kind `int_size`,
248248!! and shall have at least `size(array)/2` elements. It is an
249- !! `intent(inout )` argument to be used as "scratch" memory
249+ !! `intent(out )` argument to be used as "scratch" memory
250250!! for internal record keeping. If associated with an array in static
251251!! storage, its use can significantly reduce the stack memory requirements
252252!! for the code. Its value on return is undefined.
@@ -264,11 +264,11 @@ module stdlib_sorting
264264!!```Fortran
265265!! subroutine sort_related_data( a, b, work, index, iwork )
266266!! ! Sort `b` in terms or its related array `a`
267- !! integer, intent(inout) :: a(:)
268- !! integer(int32), intent(inout) :: b(:) ! The same size as a
269- !! integer(int32), intent(inout ) :: work(:)
270- !! integer(int_size), intent(inout ) :: index(:)
271- !! integer(int_size), intent(inout ) :: iwork(:)
267+ !! integer, intent(inout) :: a(:)
268+ !! integer(int32), intent(inout) :: b(:) ! The same size as a
269+ !! integer(int32), intent(out ) :: work(:)
270+ !! integer(int_size), intent(out ) :: index(:)
271+ !! integer(int_size), intent(out ) :: iwork(:)
272272!! ! Find the indices to sort a
273273!! call sort_index(a, index(1:size(a)),&
274274!! work(1:size(a)/2), iwork(1:size(a)/2))
@@ -282,12 +282,12 @@ module stdlib_sorting
282282!!```Fortran
283283!! subroutine sort_related_data( array, column, work, index, iwork )
284284!! ! Sort `a_data` in terms or its component `a`
285- !! integer, intent(inout) :: a(:,:)
286- !! integer(int32), intent(in) :: column
287- !! integer(int32), intent(inout ) :: work(:)
288- !! integer(int_size), intent(inout ) :: index(:)
289- !! integer(int_size), intent(inout ) :: iwork(:)
290- !! integer, allocatable :: dummy(:)
285+ !! integer, intent(inout) :: a(:,:)
286+ !! integer(int32), intent(in) :: column
287+ !! integer(int32), intent(out ) :: work(:)
288+ !! integer(int_size), intent(out ) :: index(:)
289+ !! integer(int_size), intent(out ) :: iwork(:)
290+ !! integer, allocatable :: dummy(:)
291291!! integer :: i
292292!! allocate(dummy(size(a, dim=1)))
293293!! ! Extract a component of `a_data`
@@ -306,11 +306,11 @@ module stdlib_sorting
306306!!```fortran
307307!! subroutine sort_a_data( a_data, a, work, index, iwork )
308308!! ! Sort `a_data` in terms or its component `a`
309- !! type(a_type), intent(inout) :: a_data(:)
310- !! integer(int32), intent(inout) :: a(:)
311- !! integer(int32), intent(inout ) :: work(:)
312- !! integer(int_size), intent(inout ) :: index(:)
313- !! integer(int_size), intent(inout ) :: iwork(:)
309+ !! type(a_type), intent(inout) :: a_data(:)
310+ !! integer(int32), intent(inout) :: a(:)
311+ !! integer(int32), intent(out ) :: work(:)
312+ !! integer(int_size), intent(out ) :: index(:)
313+ !! integer(int_size), intent(out ) :: iwork(:)
314314!! ! Extract a component of `a_data`
315315!! a(1:size(a_data)) = a_data(:) % a
316316!! ! Find the indices to sort the component
@@ -341,8 +341,8 @@ module stdlib_sorting
341341!!
342342!! `${k1}$_ord_sort( array )` sorts the input `ARRAY` of type `${t1}$`
343343!! using a hybrid sort based on the `'Rust" sort` algorithm found in `slice.rs`
344- ${t1}$, intent(inout) :: array(0:)
345- ${t1}$, intent(inout ), optional :: work(0:)
344+ ${t1}$, intent(inout) :: array(0:)
345+ ${t1}$, intent(out ), optional :: work(0:)
346346 end subroutine ${k1}$_ord_sort
347347
348348#:endfor
@@ -352,8 +352,8 @@ module stdlib_sorting
352352!!
353353!! `char_ord_sort( array )` sorts the input `ARRAY` of type `CHARACTER(*)`
354354!! using a hybrid sort based on the `'Rust" sort` algorithm found in `slice.rs`
355- character(len=*), intent(inout) :: array(0:)
356- character(len=len(array)), intent(inout ), optional :: work(0:)
355+ character(len=*), intent(inout) :: array(0:)
356+ character(len=len(array)), intent(out ), optional :: work(0:)
357357 end subroutine char_ord_sort
358358
359359 end interface ord_sort
@@ -411,11 +411,11 @@ module stdlib_sorting
411411!! using a hybrid sort based on the `'Rust" sort` algorithm found in `slice.rs`
412412!! and returns the sorted `ARRAY` and an array `INDEX of indices in the
413413!! order that would sort the input `ARRAY` in the desired direction.
414- ${t1}$, intent(inout) :: array(0:)
415- integer(int_size), intent(inout ) :: index(0:)
416- ${t1}$, intent(inout ), optional :: work(0:)
417- integer(int_size), intent(inout ), optional :: iwork(0:)
418- logical, intent(in), optional :: reverse
414+ ${t1}$, intent(inout) :: array(0:)
415+ integer(int_size), intent(out ) :: index(0:)
416+ ${t1}$, intent(out ), optional :: work(0:)
417+ integer(int_size), intent(out ), optional :: iwork(0:)
418+ logical, intent(in), optional :: reverse
419419 end subroutine ${k1}$_sort_index
420420
421421#:endfor
@@ -428,11 +428,11 @@ module stdlib_sorting
428428!! using a hybrid sort based on the `'Rust" sort` algorithm found in `slice.rs`
429429!! and returns the sorted `ARRAY` and an array `INDEX of indices in the
430430!! order that would sort the input `ARRAY` in the desired direction.
431- character(len=*), intent(inout) :: array(0:)
432- integer(int_size), intent(inout ) :: index(0:)
433- character(len=len(array)), intent(inout ), optional :: work(0:)
434- integer(int_size), intent(inout ), optional :: iwork(0:)
435- logical, intent(in), optional :: reverse
431+ character(len=*), intent(inout) :: array(0:)
432+ integer(int_size), intent(out ) :: index(0:)
433+ character(len=len(array)), intent(out ), optional :: work(0:)
434+ integer(int_size), intent(out ), optional :: iwork(0:)
435+ logical, intent(in), optional :: reverse
436436 end subroutine char_sort_index
437437
438438 end interface sort_index
0 commit comments