value OPERATOR value (binary operator) OPERATOR value (uniary operator) |
|
(This requirement is not enforced in C++)
The special keyword interface is used to defined an operator function:
interface operator (OP_SYMBOL)
one or more function declarations...
end interface
|
Example:
interface operator (*)
one or more function declarations...
end interface
|
The * is now mapped to (one or more) ordinary F90 function(s)
|
INTERFACE operator (*)
FUNCTION f1(x, y)
integer, INTENT(IN) :: x
real, INTENT(IN) :: y
real :: f1
END FUNCTION
FUNCTION f2(y, x)
integer, INTENT(IN) :: x
real, INTENT(IN) :: y
real :: f2
END FUNCTION
END INTERFACE
INTEGER i
REAL r
REAL x
x = i * r ! F90 will invoke f1
x = r * i ! F90 will invoke f2
|
Do the following:
|
(1) The interface definition:
interface operator (*)
function MatVecMult(A,v) result (w)
real, dimension(:,:), INTENT(IN) :: A
real, dimension(:), INTENT(IN) :: v
real, dimension(SIZE(A,1)) :: w
end interface
|
function MatVecMult(A, v) result (w)
implicit none
real, dimension(:,:), INTENT(IN) :: A
real, dimension(:), INTENT(IN) :: v
real, dimension( SIZE(A,1) ) :: w
integer :: i, j
integer :: N
N = size(v)
w = 0.0 !! clear whole vector
DO i = 1, N
w = w + v(i) * A( :, i )
END DO
end function
|
program myProg
interface operator (*)
function MatVecMult(A,v) result (w)
real, dimension(:,:), INTENT(IN) :: A
real, dimension(:), INTENT(IN) :: v
real, dimension(SIZE(A,1)) :: w
end interface
real, dimension( 3, 3 ) :: A
real, dimension( 3 ) :: v1, v2
v2 = A * v1
end program
|
(1) The interface block:
interface operator (*)
function MatVecMult(A,v) result (w)
real, dimension(:,:), INTENT(IN) :: A
real, dimension(:), INTENT(IN) :: v
real, dimension(SIZE(A,1)) :: w
function VecMatMult(v, A) result (w)
real, dimension(:), INTENT(IN) :: v
real, dimension(:,:), INTENT(IN) :: A
real, dimension( SIZE(A,2) ) :: w
end function
end interface
|
(2) The implementation of the functions:
(1a) This function process the Matrix * Vector multiply function:
function MatVecMult(A, v) result (w)
implicit none
real, dimension(:,:), INTENT(IN) :: A
real, dimension(:) ::, INTENT(IN) v
real, dimension( SIZE(A,1) ) :: w
integer :: i, j
integer :: N
N = size(v)
w = 0.0 !! clear whole vector
DO i = 1, N
w = w + v(i) * A( :, i )
END DO
end function
|
(1b) This is a Vector * Matrix multiply function:
function VecMatMult(v, A) result (w)
implicit none
real, dimension(:), INTENT(IN) :: v
real, dimension(:,:), INTENT(IN) :: A
real, dimension( SIZE(A,2) ) :: w
integer :: i, N
N = size(v)
w = 0.0 !! clear whole vector
DO i = 1, N
w = w + v(i) * A( i , : )
END DO
end function
|
program myProg
interface operator (*)
function MatVecMult(A,v) result (w) !! Function 1
real, dimension(:,:), INTENT(IN) :: A
real, dimension(:), INTENT(IN) :: v
real, dimension(SIZE(A,1)) :: w
function VecMatMult(v, A) result (w) !! Function 2
real, dimension(:), INTENT(IN) :: v
real, dimension(:,:), INTENT(IN) :: A
real, dimension( SIZE(A,2) ) :: w
end function
end interface
real, dimension( 3, 3 ) :: A
real, dimension( 3 ) :: v1, v2
v2 = A * v1 !! Matrix * Vector
v2 = v1 * A !! Vector * Matrix
|
function Add(A, B) result (C)
implicit none
real, INTENT(IN) :: A
real, INTENT(IN) :: B
real :: C
C = A - B
end function
|
|
Experiment:
|
F90 already has an Matrix * Matrix operator:
real, dimension(3,3) :: A, B, C
C = A * B "Array multiplication"
Is equivalent to:
DO i = 1, 3
DO j = 1, 3
C(i,j) = A(i,j) * B(i,j)
END DO
END DO
|
You can inadvertantly define the same operator with dire consequences ...
Example:
function MatMatMult(A, B) result (C)
implicit none
real, dimension(:,:), INTENT(IN) :: A
real, dimension(:,:), INTENT(IN) :: B
real, dimension( size(A,1), size(B, 2) ) :: C
M = size(A,1)
N = size(B,2)
X = size(A,2) ! Which is also size(B(:,1))
C = 0.0 !! clear whole matrix
DO i = 1, M
DO j = 1, N
DO k = 1, X
C(i,j) = C(i,j) + A(i,k) * B(k,j)
END DO
END DO
END DO
end function
|
Experiment:
|
|
|
interface operator (*)
function MatMatMult(A,B) result (C)
TYPE(MyReal), dimension(:,:), INTENT(IN) :: A
TYPE(MyReal), dimension(:,:), INTENT(IN) :: B
TYPE(MyReal), dimension( size(A,1), size(B, 2) ) :: C
end function
end interface
|
.OperatorName. |
interface operator ( .OperatorName. )
....
end interface
|
Interface used to define the .AVG. operator:
interface operator (.avg.)
function ComputeAvg(x, y)
real, INTENT(IN) :: x
real, INTENT(IN) :: y
real :: ComputeAvg
end function
end interface
|
Function that implements the .AVG. operator:
|
PROGRAM Main
implicit none
interface operator (.avg.)
function ComputeAvg(x, y)
real, INTENT(IN) :: x
real, INTENT(IN) :: y
real :: ComputeAvg
end function
end interface
REAL a, b, c
a = 4; b = 8
c = a .avg. b
END PROGRAM
|
B = A <=> "CALL operator(=) (B, A)"
|
Example:
TYPE(MyType) :: x, y y = x !! Copies each field from x to y |
And as in C++, this default assignment operator copies memory space verbatim from LHS (left hand side) to RHS (righthand side)
|
We want to define this operation:
REAL, DIMENSION(3,3) :: A TYPE(MyReal), DIMENSION(3,3) :: B B = A ! Illegal |
Compile the program and you will see the error message:
ERROR: Assignment of a REAL expression to a type(MYREAL) variable
is not allowed.
|
interface assignment(=)
SUBROUTINE MyAssign(Y, X)
use MyRealModule
REAL, DIMENSION(3,3), INTENT(IN) :: X
TYPE(MyReal), DIMENSION(3,3), INTENT(OUT) :: Y
END SUBROUTINE
end interface
|
Implement the MyAssign(Y, X) subroutine:
SUBROUTINE MyAssign(Y, X) use MyRealModule implicit none REAL, DIMENSION(3,3), INTENT(IN) :: X TYPE(MyReal), DIMENSION(3,3), INTENT(INOUT) :: Y Y(:,:).x = X(:,:) RETURN END SUBROUTINE |
MODULE MyRealModule
TYPE MyReal
REAL x ! <---- Our own REAL type
END TYPE MyReal
END MODULE MyRealModule
|
|