Matrix multiplication, dot product, and array shifts#
cshift#
Name#
cshift(3) - [TRANSFORMATIONAL] Circular shift elements of an array
Synopsis#
result = cshift(array, shift [,dim])
type(TYPE, kind=KIND) function cshift(array, shift, dim )
type(TYPE,kind=KIND),intent(in) :: array(..)
integer(kind=**),intent(in) :: shift
integer(kind=**),intent(in) :: dim
Characteristics#
array may be any type and rank
shift an integer scalar if array has rank one. Otherwise, it shall be scalar or of rank n-1 and of shape [d1, d2, …, dDIM-1, dDIM+1, …, dn] where [d1, d2, …, dn] is the shape of array.
dim is an integer scalar with a value in the range 1 <= dim <= n, where n is the rank of array. If dim is absent, it is as if it were present with the value 1.
the result will automatically be of the same type, kind and shape as array.
NOTE: :a kind designated as ** may be any supported kind for the type
Description#
cshift(3) performs a circular shift on elements of array along the dimension of dim. If dim is omitted it is taken to be 1. dim is a scalar of type integer in the range of 1 <= dim <= n, where «n» is the rank of array.
If the rank of array is one, then all elements of array are shifted by shift places. If rank is greater than one, then all complete rank one sections of array along the given dimension are shifted. Elements shifted out one end of each rank one section are shifted back in the other end.
Options#
- array
An array of any type which is to be shifted
- shift
the number of positions to circularly shift. A negative value produces a right shift, a positive value produces a left shift.
- dim
the dimension along which to shift a multi-rank array. Defaults to 1.
Result#
Returns an array of same type and rank as the array argument.
The rows of an array of rank two may all be shifted by the same amount or by different amounts.
cshift#
Examples#
Sample program:
program demo_cshift
implicit none
integer, dimension(5) :: i1,i2,i3
integer, dimension(3,4) :: a, b
!basics
i1=[10,20,30,40,50]
print *,'start with:'
print '(1x,5i3)', i1
print *,'shift -2'
print '(1x,5i3)', cshift(i1,-2)
print *,'shift +2'
print '(1x,5i3)', cshift(i1,+2)
print *,'start with a matrix'
a = reshape( [ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12 ], [ 3, 4 ])
print '(4i3)', a(1,:)
print '(4i3)', a(2,:)
print '(4i3)', a(3,:)
print *,'matrix shifted along rows, each by its own amount [-1,0,1]'
b = cshift(a, SHIFT=[1, 0, -1], DIM=2)
print *
print '(4i3)', b(1,:)
print '(4i3)', b(2,:)
print '(4i3)', b(3,:)
end program demo_cshift
Results:
> start with:
> 10 20 30 40 50
> shift -2
> 40 50 10 20 30
> shift +2
> 30 40 50 10 20
> start with a matrix
> 1 4 7 10
> 2 5 8 11
> 3 6 9 12
> matrix shifted along rows, each by its own amount
>
> 4 7 10 1
> 2 5 8 11
> 12 3 6 9
Standard#
Fortran 95
See Also#
eoshift(3) - End-off shift elements of an array
sum(3) - sum the elements of an array
product(3) - Product of array elements
findloc(3) - Location of first element of ARRAY identified by MASK along dimension DIM having a value
maxloc(3) - Location of the maximum value within an array
fortran-lang intrinsic descriptions
dot_product#
Name#
dot_product(3) - [TRANSFORMATIONAL] Dot product of two vectors
Synopsis#
result = dot_product(vector_a, vector_b)
TYPE(kind=KIND) function dot_product(vector_a, vector_b)
TYPE(kind=KIND),intent(in) :: vector_a(:)
TYPE(kind=KIND),intent(in) :: vector_b(:)
Characteristics#
vector_a, vector_b may be any numeric or logical type array of rank one of the same size
the two vectors need not be of the same kind, but both must be logical or numeric for any given call.
the result is the same type and kind of the vector that is the higher type that the other vector is optionally promoted to if they differ.
The two vectors may be either numeric or logical and must be arrays of rank one and of equal size.
Description#
dot_product(3) computes the dot product multiplication of two vectors vector_a and vector_b.
Options#
- vector_a
A rank 1 vector of values
- vector_b
The type shall be numeric if vector_a is of numeric type or logical if vectora is of type _logical. vector_b shall be a rank-one array of the same size as vector_a.
Result#
If the arguments are numeric, the return value is a scalar of numeric type. If the arguments are logical, the return value is .true. or .false..
If the vectors are integer or real, the result is
sum(vector_a*vector_b)
If the vectors are complex, the result is
sum(conjg(vector_a)*vector_b)**
If the vectors are logical, the result is
any(vector_a .and. vector_b)
Examples#
Sample program:
program demo_dot_prod
implicit none
integer, dimension(3) :: a, b
a = [ 1, 2, 3 ]
b = [ 4, 5, 6 ]
print '(3i3)', a
print *
print '(3i3)', b
print *
print *, dot_product(a,b)
end program demo_dot_prod
Results:
> 1 2 3
>
> 4 5 6
>
> 32
Standard#
Fortran 95
See Also#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
eoshift#
Name#
eoshift(3) - [TRANSFORMATIONAL] End-off shift of elements of an array
Synopsis#
result = eoshift( array, shift [,boundary] [,dim] )
type(TYPE(kind=KIND)) function eoshift(array,shift,boundary,dim)
type(TYPE(kind=KIND)),intent(in) :: array(..)
integer(kind=**),intent(in) :: shift(..)
type(TYPE(kind=KIND)),intent(in) :: boundary(..)
integer(kind=**),intent(in) :: dim
Characteristics#
array an array of any type
shift is an integer of any kind. It may be a scalar. If the rank of array is greater than one, and dim is specified it is the same shape as array reduced by removing dimension dim.
boundary May be a scalar of the same type and kind as array. It must be a scalar when array has a rank of one. Otherwise, it may be an array of the same shape as array reduced by dimension dim. It may only be absent for certain types, as described below.
dim is an integer of any kind. It defaults to one.
the result has the same type, type parameters, and shape as array.
a kind designated as ** may be any supported kind for the type
The result is an array of same type, kind and rank as the array argument.
Description#
eoshift(3) performs an end-off shift on elements of array along the dimension of dim.
Elements shifted out one end of each rank one section are dropped.
If boundary is present then the corresponding value from boundary is copied back in the other end, else default values are used.
Options#
- array
array of any type whose elements are to be shifted. If the rank of array is one, then all elements of array are shifted by shift places. If rank is greater than one, then all complete rank one sections of array along the given dimension are shifted.
- shift
the number of elements to shift. A negative value shifts to the right, a positive value to the left of the vector(s) being shifted.
- boundary
the value to use to fill in the elements vacated by the shift. If boundary is not present then the following are copied in depending on the type of array.
Array Type | Boundary Value
-----------------------------------------------------
Numeric | 0, 0.0, or (0.0, 0.0) of the type and kind of "array"
Logical | .false.
Character(len)| LEN blanks
These are the only types for which boundary may not be present. For these types the kind is converted as neccessary to the kind of array.
- dim
dim is in the range of
1 <= DIM <= n
where «n» is the rank of array. If dim is omitted it is taken to be 1.
Result#
Returns an array of the same characteristics as the input with the specified number of elements dropped off along the specified direction indicated, backfilling the vacated elements with a value indicated by the boundary value.
Examples#
Sample program:
program demo_eoshift
implicit none
integer, dimension(3,3) :: a
integer :: i
a = reshape( [ 1, 2, 3, 4, 5, 6, 7, 8, 9 ], [ 3, 3 ])
print '(3i3)', (a(i,:),i=1,3)
print *
! shift it
a = eoshift(a, SHIFT=[1, 2, 1], BOUNDARY=-5, DIM=2)
print '(3i3)', (a(i,:),i=1,3)
end program demo_eoshift
Results:
> 1 4 7
> 2 5 8
> 3 6 9
>
> 4 7 -5
> 8 -5 -5
> 6 9 -5
Standard#
Fortran 95
See Also#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
matmul#
Name#
matmul(3) - [TRANSFORMATIONAL] Numeric or logical matrix multiplication
Synopsis#
result = matmul(matrix_a,matrix_b)
function matmul(matrix_a, matrix_b)
type(TYPE1(kind=**) :: matrix_a(..)
type(TYPE2(kind=**) :: matrix_b(..)
type(TYPE(kind=PROMOTED)) :: matmul(..)
Characteristics#
matrix_a is a numeric (integer, real, or complex ) or logical array of rank one two.
matrix_b is a numeric (integer, real, or complex ) or logical array of rank one two.
At least one argument must be rank two.
the size of the first dimension of matrix_b must equal the size of the last dimension of matrix_a.
the type of the result is the same as if an element of each argument had been multiplied as a RHS expression (that is, if the arguments are not of the same type the result follows the same rules of promotion as a simple scalar multiplication of the two types would produce)
If one argument is logical, both must be logical. For logicals the resulting type is as if the .and. operator has been used on elements from the arrays.
The shape of the result depends on the shapes of the arguments as described below.
Description#
matmul(3) performs a matrix multiplication on numeric or logical arguments.
Options#
- matrix_a
A numeric or logical array with a rank of one or two.
- matrix_b
A numeric or logical array with a rank of one or two. The last dimension of matrix_a and the first dimension of matrix_b must be equal.
Note that matrix_a and matrix_b may be different numeric types.
Result#
Numeric Arguments#
If matrix_a and matrix_b are numeric the result is an array containing the conventional matrix product of matrix_a and matrix_b.
First, for the numeric expression C=matmul(A,B)
Any vector A(n) is treated as a row vector A(1,n).
Any vector B(n) is treated as a column vector B(n,1).
Shape and Rank#
The shape of the result can then be determined as the number of rows of the first matrix and the number of columns of the second; but if any argument is of rank one (a vector) the result is also rank one. Conversely when both arguments are of rank two, the result has a rank of two. That is …
If matrix_a has shape [n,m] and matrix_b has shape [m,k], the result has shape [n,k].
If matrix_a has shape [m] and matrix_b has shape [m,k], the result has shape [k].
If matrix_a has shape [n,m] and matrix_b has shape [m], the result has shape [n].
Values#
Then element C(i,j) of the product is obtained by multiplying term-by-term the entries of the ith row of A and the jth column of B, and summing these products. In other words, C(i,j) is the dot product of the ith row of A and the jth column of B.
Logical Arguments#
Values#
If matrix_a and matrix_b are of type logical, the array elements of the result are instead:
Value_of_Element (i,j) = &
ANY( (row_i_of_MATRIX_A) .AND. (column_j_of_MATRIX_B) )
Examples#
Sample program:
program demo_matmul
implicit none
integer :: a(2,3), b(3,2), c(2), d(3), e(2,2), f(3), g(2), v1(4),v2(4)
a = reshape([1, 2, 3, 4, 5, 6], [2, 3])
b = reshape([10, 20, 30, 40, 50, 60], [3, 2])
c = [1, 2]
d = [1, 2, 3]
e = matmul(a, b)
f = matmul(c,a)
g = matmul(a,d)
call print_matrix_int('A is ',a)
call print_matrix_int('B is ',b)
call print_vector_int('C is ',c)
call print_vector_int('D is ',d)
call print_matrix_int('E is matmul(A,B)',e)
call print_vector_int('F is matmul(C,A)',f)
call print_vector_int('G is matmul(A,D)',g)
! look at argument shapes when one is a vector
write(*,'(" > shape")')
! at least one argument must be of rank two
! so for two vectors at least one must be reshaped
v1=[11,22,33,44]
v2=[10,20,30,40]
! these return a vector C(1:1)
! treat A(1:n) as A(1:1,1:n)
call print_vector_int('Cd is a vector (not a scalar)',&
& matmul(reshape(v1,[1,size(v1)]),v2))
! or treat B(1:m) as B(1:m,1:1)
call print_vector_int('cD is a vector too',&
& matmul(v1,reshape(v2,[size(v2),1])))
! or treat A(1:n) as A(1:1,1:n) and B(1:m) as B(1:m,1:1)
! but note this returns a matrix C(1:1,1:1) not a vector!
call print_matrix_int('CD is a matrix',matmul(&
& reshape(v1,[1,size(v1)]), &
& reshape(v2,[size(v2),1])))
contains
! CONVENIENCE ROUTINES TO PRINT IN ROW-COLUMN ORDER
subroutine print_vector_int(title,arr)
character(len=*),intent(in) :: title
integer,intent(in) :: arr(:)
call print_matrix_int(title,reshape(arr,[1,shape(arr)]))
end subroutine print_vector_int
subroutine print_matrix_int(title,arr)
!@(#) print small 2d integer arrays in row-column format
character(len=*),parameter :: all='(" > ",*(g0,1x))' ! a handy format
character(len=*),intent(in) :: title
integer,intent(in) :: arr(:,:)
integer :: i
character(len=:),allocatable :: biggest
print all
print all, trim(title)
biggest=' ' ! make buffer to write integer into
! find how many characters to use for integers
write(biggest,'(i0)')ceiling(log10(real(maxval(abs(arr)))))+2
! use this format to write a row
biggest='(" > [",*(i'//trim(biggest)//':,","))'
! print one row of array at a time
do i=1,size(arr,dim=1)
write(*,fmt=biggest,advance='no')arr(i,:)
write(*,'(" ]")')
enddo
end subroutine print_matrix_int
end program demo_matmul
Results:
>
> A is
> [ 1, 3, 5 ]
> [ 2, 4, 6 ]
>
> B is
> [ 10, 40 ]
> [ 20, 50 ]
> [ 30, 60 ]
>
> C is
> [ 1, 2 ]
>
> D is
> [ 1, 2, 3 ]
>
> E is matmul(A,B)
> [ 220, 490 ]
> [ 280, 640 ]
>
> F is matmul(C,A)
> [ 5, 11, 17 ]
>
> G is matmul(A,D)
> [ 22, 28 ]
> shape
>
> Cd is a vector (not a scalar)
> [ 3300 ]
>
> cD is a vector too
> [ 3300 ]
>
> CD is a matrix
> [ 3300 ]
Standard#
Fortran 95
See Also#
Resources#
The Winograd variant of Strassen’s matrix-matrix multiply algorithm may be of interest for optimizing multiplication of very large matrices. See
"GEMMW: A portable level 3 BLAS Winograd variant of Strassen's
matrix-matrix multiply algorithm",
Douglas, C. C., Heroux, M., Slishman, G., and Smith, R. M.,
Journal of Computational Physics,
Vol. 110, No. 1, January 1994, pages 1-10.
The numerical instabilities of Strassen's method for matrix
multiplication requires special processing.
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
parity#
Name#
parity(3) - [ARRAY:REDUCTION] Array reduction by .NEQV. operation
Synopsis#
result = parity( mask [,dim] )
logical(kind=KIND) function parity(mask, dim)
type(logical(kind=KIND)),intent(in) :: mask(..)
type(integer(kind=**)),intent(in),optional :: dim
Characteristics#
mask is a logical array
dim is an integer scalar
the result is of type logical with the same kind type parameter as mask. It is a scalar if dim does not appear; otherwise it is the rank and shape of mask with the dimension specified by dim removed.
a kind designated as ** may be any supported kind for the type
Description#
parity(3) calculates the parity array (i.e. the reduction using .neqv.) of mask along dimension dim if dim is present and not 1. Otherwise, it returns the parity of the entire mask array as a scalar.
Options#
- mask
Shall be an array of type logical.
- dim
(Optional) shall be a scalar of type integer with a value in the range from 1 to n, where n equals the rank of mask.
Result#
The result is of the same type as mask.
If dim is absent, a scalar with the parity of all elements in mask is returned: .true. if an odd number of elements are .true. and .false. otherwise.
If MASK has rank one, PARITY (MASK, DIM) is equal to PARITY (MASK). Otherwise, the result is an array of parity values with dimension dim dropped.
Examples#
Sample program:
program demo_parity
implicit none
logical, parameter :: T=.true., F=.false.
logical :: x(3,4)
! basics
print *, parity([T,F])
print *, parity([T,F,F])
print *, parity([T,F,F,T])
print *, parity([T,F,F,T,T])
x(1,:)=[T,T,T,T]
x(2,:)=[T,T,T,T]
x(3,:)=[T,T,T,T]
print *, parity(x)
print *, parity(x,dim=1)
print *, parity(x,dim=2)
end program demo_parity
Results:
> T
> T
> F
> T
> F
> T T T T
> F F F
Standard#
Fortran 2008
See also#
all(3) - Determines if all the values are true
any(3) - Determines if any of the values in the logical array are .true.
count(3) - Count true values in an array
sum(3) - Sum the elements of an array
maxval(3) - Determines the maximum value in an array or row
minval(3) - Minimum value of an array
product(3) - Product of array elements
reduce(3) - General array reduction
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
null#
Name#
null(3) - [TRANSFORMATIONAL] Function that returns a disassociated pointer
Synopsis#
ptr => null( [mold] )
function null(mold)
type(TYPE(kind=**)),pointer,optional :: mold
Characteristics#
mold is a pointer of any association status and of any type.
The result is a disassociated pointer or an unallocated allocatable entity.
Description#
null(3) returns a disassociated pointer.
If mold is present, a disassociated pointer of the same type is returned, otherwise the type is determined by context.
In Fortran 95, mold is optional. Please note that Fortran 2003 includes cases where it is required.
Options#
- mold
a pointer of any association status and of any type.
Result#
A disassociated pointer or an unallocated allocatable entity.
Examples#
Sample program:
!program demo_null
module showit
implicit none
private
character(len=*),parameter :: g='(*(g0,1x))'
public gen
! a generic interface that only differs in the
! type of the pointer the second argument is
interface gen
module procedure s1
module procedure s2
end interface
contains
subroutine s1 (j, pi)
integer j
integer, pointer :: pi
if(associated(pi))then
write(*,g)'Two integers in S1:,',j,'and',pi
else
write(*,g)'One integer in S1:,',j
endif
end subroutine s1
subroutine s2 (k, pr)
integer k
real, pointer :: pr
if(associated(pr))then
write(*,g)'integer and real in S2:,',k,'and',pr
else
write(*,g)'One integer in S2:,',k
endif
end subroutine s2
end module showit
program demo_null
use showit, only : gen
real,target :: x = 200.0
integer,target :: i = 100
real, pointer :: real_ptr
integer, pointer :: integer_ptr
! so how do we call S1() or S2() with a disassociated pointer?
! the answer is the null() function with a mold value
! since s1() and s2() both have a first integer
! argument the NULL() pointer must be associated
! to a real or integer type via the mold option
! so the following can distinguish whether s1(1)
! or s2() is called, even though the pointers are
! not associated or defined
call gen (1, null (real_ptr) ) ! invokes s2
call gen (2, null (integer_ptr) ) ! invokes s1
real_ptr => x
integer_ptr => i
call gen (3, real_ptr ) ! invokes s2
call gen (4, integer_ptr ) ! invokes s1
end program demo_null
Results:
One integer in S2:, 1
One integer in S1:, 2
integer and real in S2:, 3 and 200.000000
Two integers in S1:, 4 and 100
Standard#
Fortran 95
See Also#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
reduce#
Name#
reduce(3) - [TRANSFORMATIONAL] General reduction of an array
Synopsis#
There are two forms to this function:
result = reduce(array, operation [,mask] [,identity] [,ordered] )
or
result = reduce (array, operation, dim &
& [,mask] [,identity] [,ordered] )
type(TYPE(kind=KIND)) function reduce &
& (array, operation, dim, mask, identity, ordered )
type(TYPE(kind=KIND)),intent(in) :: array
pure function :: operation
integer,intent(in),optional :: dim
logical,optional :: mask
type(TYPE),intent(in),optional :: identity
logical,intent(in),optional :: ordered
Characteristics#
array is an array of any type
operation is a pure function with exactly two arguments
each argument is scalar, non-allocatable, a nonpointer, nonpolymorphic and nonoptional with the same type and kind as array.
if one argument has the asynchronous, target, or value attribute so shall the other.
dim is an integer scalar
mask is a logical conformable with array
identity is a scalar with the same type and type parameters as array
ordered is a logical scalar
the result is of the same type and type parameters as array.
Description#
reduce(3) reduces a list of conditionally selected values from an array to a single value by iteratively applying a binary function.
Common in functional programming, a reduce function applies a binary operator (a pure function with two arguments) to all elements cumulatively.
reduce is a «higher-order» function; ie. it is a function that receives other functions as arguments.
The reduce function receives a binary operator (a function with two arguments, just like the basic arithmetic operators). It is first applied to two unused values in the list to generate an accumulator value which is subsequently used as the first argument to the function as the function is recursively applied to all the remaining selected values in the input array.
Options#
- array
An array of any type and allowed rank to select values from.
- operation
shall be a pure function with exactly two arguments; each argument shall be a scalar, nonallocatable, nonpointer, nonpolymorphic, nonoptional dummy data object with the same type and type parameters as array. If one argument has the ASYNCHRONOUS, TARGET, or VALUE attribute, the other shall have that attribute. Its result shall be a nonpolymorphic scalar and have the same type and type parameters as array. operation should implement a mathematically associative operation. It need not be commutative.
NOTE
If operation is not computationally associative, REDUCE without ORDERED=.TRUE. with the same argument values might not always produce the same result, as the processor can apply the associative law to the evaluation.
Many operations that mathematically are associative are not when applied to floating-point numbers. The order you sum values in may affect the result, for example.
- dim
An integer scalar with a value in the range 1<= dim <= n, where n is the rank of array.
- mask
(optional) shall be of type logical and shall be conformable with array.
When present only those elements of array are passed to operation for which the corresponding elements of mask are true, as if **array* was filtered with **pack(3)**.
- identity
shall be scalar with the same type and type parameters as array. If the initial sequence is empty, the result has the value identify if identify is present, and otherwise, error termination is initiated.
- ordered
shall be a logical scalar. If ordered is present with the value .true., the calls to the operator function begins with the first two elements of array and the process continues in row-column order until the sequence has only one element which is the value of the reduction. Otherwise, the compiler is free to assume that the operation is commutative and may evaluate the reduction in the most optimal way.
Result#
The result is of the same type and type parameters as array. It is scalar if dim does not appear.
If dim is present, it indicates the one dimension along which to perform the reduction, and the resultant array has a rank reduced by one relative to the input array.
Examples#
The following examples all use the function MY_MULT, which returns the product of its two real arguments.
program demo_reduce
implicit none
character(len=*),parameter :: f='("[",*(g0,",",1x),"]")'
integer,allocatable :: arr(:), b(:,:)
! Basic usage:
! the product of the elements of an array
arr=[1, 2, 3, 4 ]
write(*,*) arr
write(*,*) 'product=', reduce(arr, my_mult)
write(*,*) 'sum=', reduce(arr, my_sum)
! Examples of masking:
! the product of only the positive elements of an array
arr=[1, -1, 2, -2, 3, -3 ]
write(*,*)'positive value product=',reduce(arr, my_mult, mask=arr>0)
! sum values ignoring negative values
write(*,*)'sum positive values=',reduce(arr, my_sum, mask=arr>0)
! a single-valued array returns the single value as the
! calls to the operator stop when only one element remains
arr=[ 1234 ]
write(*,*)'single value sum',reduce(arr, my_sum )
write(*,*)'single value product',reduce(arr, my_mult )
! Example of operations along a dimension:
! If B is the array 1 3 5
! 2 4 6
b=reshape([1,2,3,4,5,6],[2,3])
write(*,f) REDUCE(B, MY_MULT),'should be [720]'
write(*,f) REDUCE(B, MY_MULT, DIM=1),'should be [2,12,30]'
write(*,f) REDUCE(B, MY_MULT, DIM=2),'should be [15, 48]'
contains
pure function my_mult(a,b) result(c)
integer,intent(in) :: a, b
integer :: c
c=a*b
end function my_mult
pure function my_sum(a,b) result(c)
integer,intent(in) :: a, b
integer :: c
c=a+b
end function my_sum
end program demo_reduce
Results:
> 1 2 3 4
> product= 24
> sum= 10
> positive value sum= 6
> sum positive values= 6
> single value sum 1234
> single value product 1234
> [720, should be [720],
> [2, 12, 30, should be [2,12,30],
> [15, 48, should be [15, 48],
Standard#
Fortran 2018
See Also#
Resources#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost