select Interface

public interface select

(Specification)


Module Procedures

private subroutine select_1_iint8_int8(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int8), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int8), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int8), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int8), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int8), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint8_int16(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int8), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int16), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int8), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int16), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int16), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint8_int32(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int8), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int32), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int8), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int32), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int32), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint8_int64(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int8), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int64), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int8), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int64), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int64), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint16_int8(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int16), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int8), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int16), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int8), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int8), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint16_int16(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int16), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int16), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int16), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int16), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int16), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint16_int32(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int16), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int32), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int16), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int32), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int32), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint16_int64(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int16), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int64), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int16), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int64), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int64), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint32_int8(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int8), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int32), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int8), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int8), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint32_int16(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int16), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int32), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int16), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int16), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint32_int32(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int32), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int32), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int32), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int32), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint32_int64(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int32), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int64), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int32), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int64), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int64), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint64_int8(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int64), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int8), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int64), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int8), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int8), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint64_int16(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int64), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int16), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int64), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int16), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int16), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint64_int32(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int64), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int32), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int64), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int32), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int32), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_iint64_int64(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
integer(kind=int64), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int64), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

integer(kind=int64), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int64), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int64), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_rsp_int8(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int8), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

real(kind=sp), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int8), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int8), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_rsp_int16(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int16), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

real(kind=sp), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int16), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int16), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_rsp_int32(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int32), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

real(kind=sp), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int32), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int32), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_rsp_int64(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int64), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

real(kind=sp), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int64), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int64), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_rdp_int8(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int8), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

real(kind=dp), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int8), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int8), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_rdp_int16(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int16), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

real(kind=dp), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int16), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int16), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_rdp_int32(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int32), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

real(kind=dp), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int32), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int32), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

private subroutine select_1_rdp_int64(a, k, kth_smallest, left, right)

select - select the k-th smallest entry in a(:).

Partly derived from the "Coretran" implementation of quickSelect by Leon Foks, https://github.com/leonfoks/coretran

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(inout) :: a(:)

Array in which we seek the k-th smallest entry. On output it will be partially sorted such that all(a(1:(k-1)) <= a(k)) .and. all(a(k) <= a((k+1):size(a))) is true.

integer(kind=int64), intent(in) :: k

We want the k-th smallest entry. E.G. k=1 leads to kth_smallest=min(a), and k=size(a) leads to kth_smallest=max(a)

real(kind=dp), intent(out) :: kth_smallest

On output contains the k-th smallest value of a(:)

integer(kind=int64), intent(in), optional :: left

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).

integer(kind=int64), intent(in), optional :: right

If we know that: the k-th smallest entry of a is in a(left:right) and also that: maxval(a(1:(left-1))) <= minval(a(left:right)) and: maxval(a(left:right))) <= minval(a((right+1):size(a))) then one or both bounds can be specified to narrow the search. The constraints are available if we have previously called the subroutine with different k (because of how a(:) becomes partially sorted, see documentation for a(:)).