Swap
This subroutine can swap two integer (scalar, vector, matrix) and two real numbers (scalar, vector, matrix). It can also swap the dimension of a Fortran array.
We can use this method for swapping two variables a
and b
, where a
and b
can be scalar, vector or matrix of Fortran intrinsic types.
We can also use this method for swaping the dimension of a multi-dimension array.
For example, consider an array b(3,4)
, we can interchange the row and column dimension (i.e., transpose operation) by using swap.
Interface 1
- ܀ Interface
- ️܀ See example
- ↢
INTERFACE
MODULE PURE SUBROUTINE Swap(a, b, i1, i2)
REAL(Real32), ALLOCATABLE, INTENT(INOUT) :: a(:, :)
!! the returned array
REAL(Real32), INTENT(IN) :: b(:, :)
!! input array, it will be untouched
INTEGER(I4B), INTENT(IN) :: i1
!! index 1 is Swapped with index `i1`
!! make sure i1 is lesser than or equal to 2
INTEGER(I4B), INTENT(IN) :: i2
!! index 2 is Swapped with index `i2`
!! make sure i2 is less than or equal to 2
END SUBROUTINE Swap
END INTERFACE
Swap two scalars.
PROGRAM main
USE easifemBase
IMPLICIT NONE
REAL( DFP ), ALLOCATABLE :: a2(:,:), b2(:,:), a3(:,:,:), b3(:,:,:), &
& a4(:,:,:,:), b4(:,:,:,:)
Make a random matrix and display it.
CALL Reallocate( b2, 4, 3 )
CALL RANDOM_NUMBER(b2)
Make another matrix a
so that we can swap the indices of b
and SAVE it in a
.
In this swap we are using:
- i1=1
- i2=2
which means a=b
.
CALL SWAP(a=a2,b=b2,i1=1,i2=2)
CALL OK( ALL( a2 .approxeq. b2 ), "swap" )
Now let us use
- i1=2
- i2=1
which will produce a=transpose(b)
.
CALL SWAP(a=a2,b=b2,i1=2,i2=1)
CALL OK( ALL( a2 .approxeq. TRANSPOSE(b2) ), "swap" )
Let us see what happens when i1=1, i2=1. Actually, it will DO nothing but a=b
.
CALL SWAP(a=a2,b=b2,i1=1,i2=1)
CALL OK( ALL( a2 .approxeq. b2), "swap" )
We DO not indend to USE swap
for two-dimensional arrays, because we already have transpose
FUNCTION for doing the same. The purpose was to check that algorithm works.
END PROGRAM main
Interface 2
- ܀ Interface
- ️܀ See example
- ↢
INTERFACE
MODULE PURE SUBROUTINE Swap(a, b, i1, i2, i3)
REAL(Real32|Real64), ALLOCATABLE, INTENT(INOUT) :: a(:, :, :)
!! the returned array
REAL(Real32|Real64), INTENT(IN) :: b(:, :, :)
!! input array, it will be untouched
INTEGER(I4B), INTENT(IN) :: i1
!! index 1 is Swapped with index `i1`
!! make sure i1 is lesser than or equal to 3
INTEGER(I4B), INTENT(IN) :: i2
!! index 2 is Swapped with index `i2`
!! make sure i2 is less than or equal to 3
INTEGER(I4B), INTENT(IN) :: i3
!! index 3 is Swapped with index `i3`
!! make sure i3 is less than or equal to 3
END SUBROUTINE Swap
END INTERFACE
This example shows the usage of Swap
method.
PROGRAM main
USE easifemBase
IMPLICIT NONE
REAL( DFP ), ALLOCATABLE :: a2(:,:), b2(:,:), a3(:,:,:), b3(:,:,:), &
& a4(:,:,:,:), b4(:,:,:,:)
Now let us USE swap
for rank 3 Fortran array. But, first generate a rank 3 arrays, and display its content.
CALL Reallocate(b3, 2,3,2)
CALL Random_NUMBER(b3)
CALL Display(MdEncode(b3), "b3 = ")
b3 = ( :, :, 1 ) =
0.85128 | 7.97914E-03 | 0.12877 |
0.61923 | 2.30844E-02 | 0.67707 |
( :, :, 2 ) =
9.43064E-02 | 0.82267 | 0.40266 |
0.26413 | 0.32497 | 0.9931 |
Now swap dimension 2 with dimension 3.
CALL SWAP(a3, b3, 1,3,2)
CALL Display(MdEncode(a3), "a3=")
a3=( :, :, 1 ) =
0.85128 | 9.43064E-02 |
0.61923 | 0.26413 |
( :, :, 2 ) =
7.97914E-03 | 0.82267 |
2.30844E-02 | 0.32497 |
( :, :, 3 ) =
0.12877 | 0.40266 |
0.67707 | 0.9931 |
You can verify that the dimension 2 and dimension 3 are changed.
END PROGRAM main
Interface 3
- ܀ Interface
- ️܀ See example
- ↢
INTERFACE
MODULE PURE SUBROUTINE Swap(a, b, i1, i2, i3, i4)
REAL(Real64), ALLOCATABLE, INTENT(INOUT) :: a(:, :, :, :)
!! the returned array
REAL(Real64), INTENT(IN) :: b(:, :, :, :)
!! input array, it will be untouched
INTEGER(I4B), INTENT(IN) :: i1
!! index 1 is Swapped with index `i1`
!! make sure i1 is lesser than or equal to 4
INTEGER(I4B), INTENT(IN) :: i2
!! index 2 is Swapped with index `i2`
!! make sure i2 is less than or equal to 4
INTEGER(I4B), INTENT(IN) :: i3
!! index 3 is Swapped with index `i3`
!! make sure i3 is less than or equal to 4
INTEGER(I4B), INTENT(IN) :: i4
!! index 4 is Swapped with index `i4`
!! make sure i4 is less than or equal to 4
END SUBROUTINE Swap
END INTERFACE
This example shows the usage of Swap
method.
Swap method for rank4.
PROGRAM main
USE easifemBase
IMPLICIT NONE
REAL( DFP ), ALLOCATABLE :: a2(:,:), b2(:,:), a3(:,:,:), b3(:,:,:), &
& a4(:,:,:,:), b4(:,:,:,:)
call reallocate(a2, 2,2)
call reallocate(b2, 2,2)
a2(1,:) = [2,1]
a2(2,:) = [4,2]
b2(1,1) = 1; b2(2,2) = 2
b4 = outerprod(a2, b2)
call swap(a=a4, b=b4, i1=1, i2=2, i3=3, i4=4)
call display(MdEncode(a4), "a4")
a4(:,:,1,1) =
2 | 1 |
4 | 2 |
(:,:,2,1) =
0 | 0 |
0 | 0 |
(:,:,1,2) =
0 | 0 |
0 | 0 |
(:,:,2,2) =
4 | 2 |
8 | 4 |
call swap(a=a4, b=b4, i1=1, i2=3, i3=2, i4=4)
call display(MdEncode(a4), "a4")
a4(:,:,1,1) =
2 | 0 |
4 | 0 |
(:,:,2,1) =
1 | 0 |
2 | 0 |
(:,:,1,2) =
0 | 4 |
0 | 8 |
(:,:,2,2) =
0 | 2 |
0 | 4 |
END PROGRAM main
Interface 4
- ܀ Interface
- ️܀ See example
- ↢
INTERFACE
MODULE PURE SUBROUTINE Swap(a, b)
INTEGER(Int8| Int16 | Int32 | Int64| Real32 | Real64), INTENT(INOUT) :: a, b
END SUBROUTINE Swap
END INTERFACE
Swap two scalar numbers.
program main
use easifemBase
implicit none
real(dfp) :: a, b
a = 3; b=4
CALL Swap(a,b)
CALL OK(a.EQ.4 .AND. b.EQ.3, "test(1):")
end program main
Interface 5
- ܀ Interface
- ️܀ See example
- ↢
INTERFACE
MODULE PURE SUBROUTINE Swap(a, b)
INTEGER(Int8| Int16 | Int32 | Int64 | Real32 | Real64), INTENT(INOUT) :: a(:), b(:)
END SUBROUTINE Swap
END INTERFACE
program main
use easifemBase
implicit none
real(dfp) :: a(3), b(3)
a = 3; b=4
CALL Swap(a,b)
CALL OK(ALL(a.EQ.4) .AND. ALL(b.EQ.3), "test(1):")
end program main
Interface 6
- ܀ Interface
- ️܀ See example
- ↢
INTERFACE
MODULE PURE SUBROUTINE Swap(a, b)
INTEGER(Int8| Int16 | Int32 | Int64 | Real32 | Real64), INTENT(INOUT) :: a(:,:), b(:,:)
END SUBROUTINE Swap
END INTERFACE
program main
use easifemBase
implicit none
real(dfp) :: a(3, 2), b(3, 2)
a = 3; b=4
CALL Swap(a,b)
CALL OK(ALL(a.EQ.4) .AND. ALL(b.EQ.3), "test(1):")
end program main
Interface 7
- ܀ Interface
- ️܀ See example
- ↢
INTERFACE
MODULE PURE SUBROUTINE Swap(a, b, mask)
INTEGER(Int8| Int16 | Int32 | Int64 | Real32 | Real64), INTENT(INOUT) :: a, b
LOGICAL(LGT), INTENT(IN) :: mask
END SUBROUTINE Swap
END INTERFACE
Masked swap.
program main
use easifemBase
implicit none
real(dfp) :: a, b
a = 3; b=4
CALL Swap(a,b, a .LE.b )
CALL OK(a.EQ.4 .AND. b.EQ.3, "test(1):")
CALL Swap(a,b, a .LE.b )
CALL OK(a.EQ.4 .AND. b.EQ.3, "test(2):")
end program main
Interface 8
- ܀ Interface
- ️܀ See example
- ↢
INTERFACE
MODULE PURE SUBROUTINE Swap(a, b, mask)
INTEGER(Int8| Int16 | Int32 | Int64 | Real32 | Real64), INTENT(INOUT) :: a(:), b(:)
LOGICAL(LGT), INTENT(IN) :: mask(:)
END SUBROUTINE Swap
END INTERFACE
program main
use easifemBase
implicit none
real(dfp) :: a(2), b(2)
a = 3; b=4
CALL Swap(a,b, a .LE.b )
CALL OK(ALL(a.EQ.4 .AND. b.EQ.3), "test(1):")
CALL Swap(a,b, a .LE.b )
CALL OK(ALL(a.EQ.4 .AND. b.EQ.3), "test(2):")
end program main
Interface 9
- ܀ Interface
- ️܀ See example
- ↢
INTERFACE
MODULE PURE SUBROUTINE Swap(a, b, mask)
INTEGER(Int8| Int16 | Int32 | Int64 | Real32 | Real64), INTENT(INOUT) :: a(:, :), b(:, :)
LOGICAL(LGT), INTENT(IN) :: mask(:, :)
END SUBROUTINE Swap
END INTERFACE
program main
use easifemBase
implicit none
real(dfp) :: a(2,2), b(2,2)
a = 3; b=4
CALL Swap(a,b, a .LE.b )
CALL OK(ALL(a.EQ.4 .AND. b.EQ.3), "test(1):")
CALL Swap(a,b, a .LE.b )
CALL OK(ALL(a.EQ.4 .AND. b.EQ.3), "test(2):")
end program main