@@ -41,6 +41,7 @@ to the value of `int64` from the `stdlib_kinds` module.
41
41
The ` stdlib_sorting ` module provides three different overloaded
42
42
subroutines intended to sort three different kinds of arrays of
43
43
data:
44
+
44
45
* ` ORD_SORT ` is intended to sort simple arrays of intrinsic data
45
46
that have significant sections that were partially ordered before
46
47
the sort;
@@ -235,8 +236,9 @@ Generic subroutine.
235
236
236
237
` array ` : shall be a rank one array of any of the types:
237
238
` integer(int8) ` , ` integer(int16) ` , ` integer(int32) ` , ` integer(int64) ` ,
238
- ` real(sp) ` , ` real(dp) ` , ` real(qp) ` , ` character(*) ` , or
239
- ` type(string_type) ` . It is an ` intent(inout) ` argument. On input it is
239
+ ` real(sp) ` , ` real(dp) ` , ` real(qp) ` , ` character(*) ` , ` type(string_type) ` ,
240
+ ` type(bitset_64) ` , or ` type(bitset_large) ` .
241
+ It is an ` intent(inout) ` argument. On input it is
240
242
the array to be sorted. If both the type of ` array ` is real and at
241
243
least one of the elements is a ` NaN ` , then the ordering of the result
242
244
is undefined. Otherwise on return its elements will be sorted in order
@@ -301,8 +303,9 @@ Pure generic subroutine.
301
303
302
304
` array ` : shall be a rank one array of any of the types:
303
305
` integer(int8) ` , ` integer(int16) ` , ` integer(int32) ` , ` integer(int64) ` ,
304
- ` real(sp) ` , ` real(dp) ` , ` real(qp) ` . ` character(*) ` , or
305
- ` type(string_type) ` . It is an ` intent(inout) ` argument. On return its
306
+ ` real(sp) ` , ` real(dp) ` , ` real(qp) ` . ` character(*) ` , ` type(string_type) ` ,
307
+ ` type(bitset_64) ` , or ` type(bitset_large) ` .
308
+ It is an ` intent(inout) ` argument. On return its
306
309
input elements will be sorted in order of non-decreasing value.
307
310
308
311
@@ -405,8 +408,9 @@ Generic subroutine.
405
408
406
409
` array ` : shall be a rank one array of any of the types:
407
410
` integer(int8) ` , ` integer(int16) ` , ` integer(int32) ` , ` integer(int64) ` ,
408
- ` real(sp) ` , ` real(dp) ` , ` real(qp) ` , ` character(*) ` , or
409
- ` type(string_type) ` . It is an ` intent(inout) ` argument. On input it
411
+ ` real(sp) ` , ` real(dp) ` , ` real(qp) ` , ` character(*) ` , ` type(string_type) ` ,
412
+ ` type(bitset_64) ` , or ` type(bitset_large) ` .
413
+ It is an ` intent(inout) ` argument. On input it
410
414
will be an array whose sorting indices are to be determined. On return
411
415
it will be the sorted array.
412
416
@@ -460,60 +464,60 @@ Sorting a related rank one array:
460
464
! Sort `a`, and also sort `b` to be reorderd the same way as `a`
461
465
integer, intent(inout) :: a(:)
462
466
integer(int32), intent(inout) :: b(:) ! The same size as a
463
- integer(int32), intent(out) :: work(:)
464
- integer(int_size), intent(out) :: index(:)
465
- integer(int_size), intent(out) :: iwork(:)
466
- ! Find the indices to sort a
467
+ integer(int32), intent(out) :: work(:)
468
+ integer(int_size), intent(out) :: index(:)
469
+ integer(int_size), intent(out) :: iwork(:)
470
+ ! Find the indices to sort a
467
471
call sort_index(a, index(1:size(a)),&
468
472
work(1:size(a)/2), iwork(1:size(a)/2))
469
- ! Sort b based on the sorting of a
470
- b(:) = b( index(1:size(a)) )
471
- end subroutine sort_related_data
473
+ ! Sort b based on the sorting of a
474
+ b(:) = b( index(1:size(a)) )
475
+ end subroutine sort_related_data
472
476
```
473
477
474
478
Sorting a rank 2 array based on the data in a column
475
479
476
480
``` Fortran
477
- subroutine sort_related_data( array, column, work, index, iwork )
478
- ! Reorder rows of `array` such that `array(:, column)` is sorted
479
- integer, intent(inout) :: array(:,:)
480
- integer(int32), intent(in) :: column
481
- integer(int32), intent(out) :: work(:)
482
- integer(int_size), intent(out) :: index(:)
483
- integer(int_size), intent(out) :: iwork(:)
484
- integer, allocatable :: dummy(:)
485
- integer :: i
486
- allocate(dummy(size(array, dim=1)))
487
- ! Extract a column of `array`
488
- dummy(:) = array(:, column)
489
- ! Find the indices to sort the column
490
- call sort_index(dummy, index(1:size(dummy)),&
491
- work(1:size(dummy)/2), iwork(1:size(dummy)/2))
492
- ! Sort a based on the sorting of its column
493
- do i=1, size(array, dim=2)
494
- array(:, i) = array(index(1:size(array, dim=1)), i)
495
- end do
496
- end subroutine sort_related_data
481
+ subroutine sort_related_data( array, column, work, index, iwork )
482
+ ! Reorder rows of `array` such that `array(:, column)` is sorted
483
+ integer, intent(inout) :: array(:,:)
484
+ integer(int32), intent(in) :: column
485
+ integer(int32), intent(out) :: work(:)
486
+ integer(int_size), intent(out) :: index(:)
487
+ integer(int_size), intent(out) :: iwork(:)
488
+ integer, allocatable :: dummy(:)
489
+ integer :: i
490
+ allocate(dummy(size(array, dim=1)))
491
+ ! Extract a column of `array`
492
+ dummy(:) = array(:, column)
493
+ ! Find the indices to sort the column
494
+ call sort_index(dummy, index(1:size(dummy)),&
495
+ work(1:size(dummy)/2), iwork(1:size(dummy)/2))
496
+ ! Sort a based on the sorting of its column
497
+ do i=1, size(array, dim=2)
498
+ array(:, i) = array(index(1:size(array, dim=1)), i)
499
+ end do
500
+ end subroutine sort_related_data
497
501
```
498
502
499
503
Sorting an array of a derived type based on the data in one component
500
504
501
505
``` fortran
502
- subroutine sort_a_data( a_data, a, work, index, iwork )
503
- ! Sort `a_data` in terms or its component `a`
504
- type(a_type), intent(inout) :: a_data(:)
505
- integer(int32), intent(inout) :: a(:)
506
- integer(int32), intent(out) :: work(:)
507
- integer(int_size), intent(out) :: index(:)
508
- integer(int_size), intent(out) :: iwork(:)
509
- ! Extract a component of `a_data`
510
- a(1:size(a_data)) = a_data(:) % a
511
- ! Find the indices to sort the component
512
- call sort_index(a(1:size(a_data)), index(1:size(a_data)),&
513
- work(1:size(a_data)/2), iwork(1:size(a_data)/2))
514
- ! Sort a_data based on the sorting of that component
515
- a_data(:) = a_data( index(1:size(a_data)) )
516
- end subroutine sort_a_data
506
+ subroutine sort_a_data( a_data, a, work, index, iwork )
507
+ ! Sort `a_data` in terms or its component `a`
508
+ type(a_type), intent(inout) :: a_data(:)
509
+ integer(int32), intent(inout) :: a(:)
510
+ integer(int32), intent(out) :: work(:)
511
+ integer(int_size), intent(out) :: index(:)
512
+ integer(int_size), intent(out) :: iwork(:)
513
+ ! Extract a component of `a_data`
514
+ a(1:size(a_data)) = a_data(:) % a
515
+ ! Find the indices to sort the component
516
+ call sort_index(a(1:size(a_data)), index(1:size(a_data)),&
517
+ work(1:size(a_data)/2), iwork(1:size(a_data)/2))
518
+ ! Sort a_data based on the sorting of that component
519
+ a_data(:) = a_data( index(1:size(a_data)) )
520
+ end subroutine sort_a_data
517
521
```
518
522
519
523
0 commit comments