Skip to content

Commit

Permalink
Merge branch 'fortran-lang:master' into sparse
Browse files Browse the repository at this point in the history
  • Loading branch information
jalvesz authored Jun 1, 2024
2 parents 8278f38 + efb53f5 commit 87bfd10
Show file tree
Hide file tree
Showing 8 changed files with 187 additions and 129 deletions.
27 changes: 17 additions & 10 deletions doc/specs/stdlib_sorting.md
Original file line number Diff line number Diff line change
Expand Up @@ -24,17 +24,18 @@ module's `string_type` type.

## Overview of the module

The module `stdlib_sorting` defines several public entities, one
default integer parameter, `int_index`, and four overloaded
The module `stdlib_sorting` defines several public entities, two
default integer parameters, `int_index` and `int_index_low`, and four overloaded
subroutines: `ORD_SORT`, `SORT`, `RADIX_SORT` and `SORT_INDEX`. The
overloaded subroutines also each have several specific names for
versions corresponding to different types of array arguments.

### The `int_index` parameter
### The parameters `int_index` and `int_index_low`

The `int_index` parameter is used to specify the kind of integer used
in indexing the various arrays. Currently the module sets `int_index`
to the value of `int64` from the `stdlib_kinds` module.
The parameters `int_index` and `int_index_low` are used to specify the kind of integer used
in indexing the various arrays. Currently the module sets `int_index` and
`int_index_low`
to the value of `int64` and `int32` from the `stdlib_kinds` module, respectively.

### The module subroutines

Expand Down Expand Up @@ -414,7 +415,7 @@ It is an `intent(inout)` argument. On input it
will be an array whose sorting indices are to be determined. On return
it will be the sorted array.

`index`: shall be a rank one integer array of kind `int_index` and of
`index`: shall be a rank one integer array of kind `int_index` or `int_index_low` and of
the size of `array`. It is an `intent(out)` argument. On return it
shall have values that are the indices needed to sort the original
array in the desired direction.
Expand All @@ -426,8 +427,8 @@ memory for internal record keeping. If associated with an array in
static storage, its use can significantly reduce the stack memory
requirements for the code. Its contents on return are undefined.

`iwork` (optional): shall be a rank one integer array of kind
`int_index`, and shall have at least `size(array)/2` elements. It
`iwork` (optional): shall be a rank one integer array of the same kind
of the array `index`, and shall have at least `size(array)/2` elements. It
is an `intent(out)` argument. It is intended to be used as "scratch"
memory for internal record keeping. If associated with an array in
static storage, its use can significantly reduce the stack memory
Expand Down Expand Up @@ -457,6 +458,12 @@ different on return

##### Examples

Sorting a rank one array with `sort_index`:

```Fortran
{!example/sorting/example_sort_index.f90!}
```

Sorting a related rank one array:

```Fortran
Expand Down Expand Up @@ -504,7 +511,7 @@ Sorting an array of a derived type based on the data in one component

```fortran
subroutine sort_a_data( a_data, a, work, index, iwork )
! Sort `a_data` in terms or its component `a`
! Sort `a_data` in terms of its component `a`
type(a_type), intent(inout) :: a_data(:)
integer(int32), intent(inout) :: a(:)
integer(int32), intent(out) :: work(:)
Expand Down
3 changes: 2 additions & 1 deletion example/sorting/CMakeLists.txt
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
ADD_EXAMPLE(ord_sort)
ADD_EXAMPLE(sort)
ADD_EXAMPLE(sort_index)
ADD_EXAMPLE(radix_sort)
ADD_EXAMPLE(sort_bitset)
ADD_EXAMPLE(sort_bitset)
15 changes: 15 additions & 0 deletions example/sorting/example_sort_index.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
program example_sort_index
use stdlib_sorting, only: sort_index
implicit none
integer, allocatable :: array(:)
integer, allocatable :: index(:)

array = [5, 4, 3, 1, 10, 4, 9]
allocate(index, mold=array)

call sort_index(array, index)

print *, array !print [1, 3, 4, 4, 5, 9, 10]
print *, index !print [4, 3, 2, 6, 1, 7, 5]

end program example_sort_index
28 changes: 18 additions & 10 deletions src/stdlib_sorting.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,8 @@
#:set CHAR_TYPES_ALT_NAME = list(zip(["character(len=*)"], ["character(len=len(array))"], ["char"]))
#:set BITSET_TYPES_ALT_NAME = list(zip(BITSET_TYPES, BITSET_TYPES, BITSET_KINDS))

#:set INT_INDEX_TYPES_ALT_NAME = list(zip(["int_index", "int_index_low"], ["integer(int_index)", "integer(int_index_low)"], ["default", "low"]))

#! For better code reuse in fypp, make lists that contain the input types,
#! with each having output types and a separate name prefix for subroutines
#! This approach allows us to have the same code for all input types.
Expand Down Expand Up @@ -138,6 +140,8 @@ module stdlib_sorting
private
integer, parameter, public :: int_index = int64 !! Integer kind for indexing
integer, parameter, public :: int_index_low = int32 !! Integer kind for indexing using less than `huge(1_int32)` values
! Constants for use by tim_sort
integer, parameter :: &
Expand All @@ -147,14 +151,16 @@ module stdlib_sorting
max_merge_stack = int( ceiling( log( 2._dp**64 ) / &
log(1.6180339887_dp) ) )
type run_type
#:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
type run_type_${namei}$
!! Version: experimental
!!
!! Used to pass state around in a stack among helper functions for the
!! `ORD_SORT` and `SORT_INDEX` algorithms
integer(int_index) :: base = 0
integer(int_index) :: len = 0
end type run_type
${ti}$ :: base = 0
${ti}$ :: len = 0
end type run_type_${namei}$
#:endfor
public ord_sort
!! Version: experimental
Expand Down Expand Up @@ -515,23 +521,25 @@ module stdlib_sorting
!! non-decreasing sort, but if the optional argument `REVERSE` is present
!! with a value of `.TRUE.` the indices correspond to a non-increasing sort.
#:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
module subroutine ${name1}$_sort_index( array, index, work, iwork, &
#:for ki, ti, namei in INT_INDEX_TYPES_ALT_NAME
#:for t1, t2, name1 in IRSCB_TYPES_ALT_NAME
module subroutine ${name1}$_sort_index_${namei}$( array, index, work, iwork, &
reverse )
!! Version: experimental
!!
!! `${name1}$_sort_index( array, index[, work, iwork, reverse] )` sorts
!! `${name1}$_sort_index_${namei}$( array, index[, work, iwork, reverse] )` sorts
!! an input `ARRAY` of type `${t1}$`
!! using a hybrid sort based on the `"Rust" sort` algorithm found in `slice.rs`
!! and returns the sorted `ARRAY` and an array `INDEX` of indices in the
!! order that would sort the input `ARRAY` in the desired direction.
${t1}$, intent(inout) :: array(0:)
integer(int_index), intent(out) :: index(0:)
${ti}$, intent(out) :: index(0:)
${t2}$, intent(out), optional :: work(0:)
integer(int_index), intent(out), optional :: iwork(0:)
${ti}$, intent(out), optional :: iwork(0:)
logical, intent(in), optional :: reverse
end subroutine ${name1}$_sort_index
end subroutine ${name1}$_sort_index_${namei}$
#:endfor
#:endfor
end interface sort_index
Expand Down
8 changes: 4 additions & 4 deletions src/stdlib_sorting_ord_sort.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -186,7 +186,7 @@ contains
! 1. len(-3) > len(-2) + len(-1)
! 2. len(-2) > len(-1)
integer(int_index) :: r
type(run_type), intent(in), target :: runs(0:)
type(run_type_default), intent(in), target :: runs(0:)
integer(int_index) :: n
logical :: test
Expand Down Expand Up @@ -277,7 +277,7 @@ contains
integer(int_index) :: array_size, finish, min_run, r, r_count, &
start
type(run_type) :: runs(0:max_merge_stack-1), left, right
type(run_type_default) :: runs(0:max_merge_stack-1), left, right
array_size = size(array, kind=int_index)
Expand Down Expand Up @@ -326,7 +326,7 @@ contains
end do Insert
if ( start == 0 .and. finish == array_size - 1 ) return

runs(r_count) = run_type( base = start, &
runs(r_count) = run_type_default( base = start, &
len = finish - start + 1 )
finish = start-1
r_count = r_count + 1
Expand All @@ -342,7 +342,7 @@ contains
right % base + right % len - 1 ), &
left % len, buf )

runs(r) = run_type( base = left % base, &
runs(r) = run_type_default( base = left % base, &
len = left % len + right % len )
if ( r == r_count - 3 ) runs(r+1) = runs(r+2)
r_count = r_count - 1
Expand Down
Loading

0 comments on commit 87bfd10

Please sign in to comment.