swap Interface

public interface swap

Swap the values of the lhs and rhs arguments (Specification)

Version: experimental


Module Procedures

private elemental subroutine swap_int8(lhs, rhs)

Arguments

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

private elemental subroutine swap_int16(lhs, rhs)

Arguments

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

private elemental subroutine swap_int32(lhs, rhs)

Arguments

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

private elemental subroutine swap_int64(lhs, rhs)

Arguments

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

private elemental subroutine swap_sp(lhs, rhs)

Arguments

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

private elemental subroutine swap_dp(lhs, rhs)

Arguments

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

private elemental subroutine swap_bitset_64(lhs, rhs)

Arguments

Type IntentOptional Attributes Name
type(bitset_64), intent(inout) :: lhs
type(bitset_64), intent(inout) :: rhs

private elemental subroutine swap_bitset_large(lhs, rhs)

Arguments

Type IntentOptional Attributes Name
type(bitset_large), intent(inout) :: lhs
type(bitset_large), intent(inout) :: rhs

private elemental subroutine swap_csp(lhs, rhs)

Arguments

Type IntentOptional Attributes Name
complex(kind=sp), intent(inout) :: lhs
complex(kind=sp), intent(inout) :: rhs

private elemental subroutine swap_cdp(lhs, rhs)

Arguments

Type IntentOptional Attributes Name
complex(kind=dp), intent(inout) :: lhs
complex(kind=dp), intent(inout) :: rhs

private elemental subroutine swap_bool(lhs, rhs)

Arguments

Type IntentOptional Attributes Name
logical, intent(inout) :: lhs
logical, intent(inout) :: rhs

private elemental subroutine swap_str(lhs, rhs)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(inout) :: lhs
character(len=*), intent(inout) :: rhs

private elemental subroutine swap_stt(lhs, rhs)

Arguments

Type IntentOptional Attributes Name
type(string_type), intent(inout) :: lhs
type(string_type), intent(inout) :: rhs