Fortran/language extensions
Procedure Overloading
editLike several other languages, Fortran 90 and newer supports the ability to select the appropriate routine from a list of routines based on the arguments passed. This selection is done at compile time and is thus unencumbered by run-time performance penalties. This feature is accessed by use of modules and the interface block.
In the following example, a module is specified which contains an interface function f
which can handle arguments of various types.
module extension_m
implicit none
private
public f ! Only the interface f is accessable outside the module.
interface f ! The overloaded function is called "f".
module procedure f_i ! "f(x)" for integer argument "x" will call "f_i"
module procedure f_r ! "f(x)" for real argument "x" will call "f_r"
module procedure f_z ! ... complex .... "f_z"
end interface
contains
integer function f_i(x) result (y)
integer, intent (in) :: x
y = x**2 - 1
end function
real function f_r(x) result(y)
real, intent (in) :: x
y = x**2 - 1.0
end function
complex function f_z(x) result(y)
complex, intent (in) :: x
y = x**2 - 1.0
end function
end module
A program which uses this module now has access to a single interface function f
which accepts arguments that are of integer, real, or complex type. The return type of the function is the same as the input type. In this way the routine is much like many of the intrinsic functions defined as part of the Fortran standard. An example program is given below:
program main
use extension_m
implicit none
complex :: xz, yz
integer :: xi, yi
real :: xr, yr
xi = 2
xr = 2.0
xz = 2.0
yi = f(xi)
yr = f(xr)
yz = f(xz)
end program
Intrinsic functions
editOne can extend intrinsic functions. This is similar to overload operators.
Here we will demonstrate this by extending the sqrt
function. The intrinsic function is not implemented for arguments of integer type. This is because there is no clear idea how to define the result of non integer type (e.g. , but how to define ). We implement a method here where the result is always the nearest integer.
module sqrt_int_m
implicit none
private
public sqrt
! use intrinsic sqrt for data types which are not overloaded
intrinsic :: sqrt
! extend sqrt for integers
interface sqrt
module procedure sqrt_int
end interface
contains
pure integer function sqrt_int(i)
integer, intent (in) :: i
sqrt_int = nint(sqrt(real(i)))
end function
end module
program main
use sqrt_int_m
implicit none
integer :: i
! sqrt can be called by real and integer arguments
do i = 1, 7
print *, "i, sqrt(i), sqrt(real(i))", i, sqrt(i), sqrt(real(i))
end do
end program
Derived Data Types
editFortran 90 and newer supports the creation of new data types which are composites of existing types. In some ways this is similar to an array, but the components need not be all of the same type and they are referenced by name, not index. Such data types must be declared before variables of that type, and the declaration must be in scope to be used. An example of a simple 2d vector type is given below.
type :: vec_t
real :: x,y
end type
Variables of this type can be declared much like any other variable, including variable characteristics such are pointer or dimension.
type (vec_t) :: a,b
type (vec_t), dimension (10) :: vecs
Using derived data types, the Fortran language can be extended to represent more diverse types of data than those represented by the primitive types.
Operator Overloading
editOperators can be overloaded so that derived data types support the standard operations, opening the possibility of extending the Fortran language to have new types which behave nearly like the native types.
Assignment
editThe assignment operator = can be overloaded. We will demonstrate this by the following example. Here, we define how the assignment of a logical type on the left and an integer on the right should be performed.
module overload_assignment_m
implicit none
private
public assignment (=)
interface assignment (=)
module procedure logical_gets_integer
end interface
contains
subroutine logical_gets_integer(tf, i)
logical, intent (out) :: tf
integer, intent (in) :: i
tf = (i == 0)
end subroutine
end module
program main
use overload_assignment_m
implicit none
logical :: tf
tf = 0
print *, "tf=0:", tf ! Yields: T
tf = 1
print *, "tf=1:", tf ! Yields: F
end program
Intrinsic operators
editOne can overload intrinsic operators, such as +,-,*
.
In the following example we will overload the *
operator to work as the logical .and.
.
module overload_asterisk_m
implicit none
private
public operator (*)
interface operator (*)
module procedure logical_and
end interface
contains
pure logical function logical_and(log1, log2)
logical, intent (in) :: log1, log2
logical_and = (log1 .and. log2)
end function
end module
program main
use overload_asterisk_m
implicit none
logical, parameter :: T = .true., F = .false.
print *, "T*T:", T*T ! Yields: T
print *, "T*F:", T*F ! Yields: F
print *, "F*T:", F*T ! Yields: F
print *, "F*F:", F*F ! Yields: F
end program
New operators
editOne can create newly self-created operators.
We demonstrate this by the following example: We create an unary operator .even. <int>
which outputs a logical
if the given integer
is even as well as a binary operator <reals> .cross. <reals>
that performs the standard cross product of two real
vectors.
module new_operators_m
implicit none
private
public operator (.even.)
public operator (.cross.)
interface operator (.even.)
module procedure check_even
end interface
interface operator (.cross.)
module procedure cross_product
end interface
contains
pure logical function check_even(i)
integer, intent (in) :: i
check_even = (modulo(i, 2) == 0)
end function
function cross_product(x, y) result(z)
real, intent (in) :: x(3), y(3)
real :: z(3)
z(1) = x(2)*y(3) - x(3)*y(2)
z(2) = x(3)*y(1) - x(1)*y(3)
z(3) = x(1)*y(2) - x(2)*y(1)
end function
end module
program main
use new_operators_m
implicit none
integer :: i
real :: x(3), y(3)
do i = 1, 6
print *, "i:", i, "even?", .even. i
end do
print *
x = [ 1, 2, 3]
y = [-1, 2, -3]
print *, 'x', x
print *, 'y', y
print *, 'x cross_product y', x .cross. y
end program