Matrix multiplication, dot product, and array shifts#

cshift#

Name#

cshift(3) - [TRANSFORMATIONAL] Circular shift elements of an array

Syntax#

result = cshift(array, shift, dim)

Description#

cshift(array, shift [, dim]) 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.

Arguments#

  • array

    Shall be an array of any type.

  • shift

    The type shall be integer.

  • dim

    The type shall be integer.

Returns#

Returns an array of same type and rank as the array argument.

Examples#

Sample program:

program demo_cshift
implicit none
integer, dimension(3,3) :: a
    a = reshape( [ 1, 2, 3, 4, 5, 6, 7, 8, 9 ], [ 3, 3 ])
    print '(3i3)', a(1,:)
    print '(3i3)', a(2,:)
    print '(3i3)', a(3,:)
    a = cshift(a, SHIFT=[1, 2, -1], DIM=2)
    print *
    print '(3i3)', a(1,:)
    print '(3i3)', a(2,:)
    print '(3i3)', a(3,:)
end program demo_cshift

Results:

     1  4  7
     2  5  8
     3  6  9
    
     4  7  1
     8  2  5
     9  3  6

Standard#

Fortran 95 and later

####### fortran-lang intrinsic descriptions

dot_product#

Name#

dot_product(3) - [TRANSFORMATIONAL] Dot product function

Syntax#

result = dot_product(vector_a, vector_b)

Description#

dot_product(vector_a, vector_b) computes the dot product multiplication of two vectors vector_a and vector_b. The two vectors may be either numeric or logical and must be arrays of rank one and of equal size. 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).

Arguments#

  • vector_a

    The type shall be numeric or logical, rank 1.

  • vector_b

    The type shall be numeric if vector_a is of numeric type or logical if vector_a is of type logical. vector_b shall be a rank-one array.

Returns#

If the arguments are numeric, the return value is a scalar of numeric type, integer, real, or complex. If the arguments are logical, the return value is .true. or .false..

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 and later

####### fortran-lang intrinsic descriptions

eoshift#

Name#

eoshift(3) - [TRANSFORMATIONAL] End-off shift elements of an array

Syntax#

result = eoshift(array, shift, boundary, dim)

Description#

eoshift(array, shift[, boundary, dim]) performs an end-off 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 dropped. If boundary is present then the corresponding value of from boundary is copied back in the other end. If boundary is not present then the following are copied in depending on the type of array.

*Array Type* - *Boundary Value*

  • Numeric 0 of the type and kind of array

  • Logical .false.

  • Character(len) LEN blanks

Arguments#

  • array

    May be any type, not scalar.

  • shift

    The type shall be integer.

  • boundary

    Same type as ARRAY.

  • dim

    The type shall be integer.

Returns#

Returns an array of same type and rank as the array argument.

Examples#

Sample program:

program demo_eoshift
implicit none
    integer, dimension(3,3) :: a
    a = reshape( [ 1, 2, 3, 4, 5, 6, 7, 8, 9 ], [ 3, 3 ])
    print '(3i3)', a(1,:)
    print '(3i3)', a(2,:)
    print '(3i3)', a(3,:)
    a = eoshift(a, SHIFT=[1, 2, 1], BOUNDARY=-5, DIM=2)
    print *
    print '(3i3)', a(1,:)
    print '(3i3)', a(2,:)
    print '(3i3)', a(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 and later

####### fortran-lang intrinsic descriptions

matmul#

Name#

matmul(3) - [TRANSFORMATIONAL] matrix multiplication

Syntax#

result = matmul(matrix_a, matrix_b)

Description#

Performs a matrix multiplication on numeric or logical arguments.

Arguments#

  • matrix_a

    An array of integer, real, complex, or logical type, with a rank of one or two.

  • matrix_b

    An array of integer, real, or complex type if matrix_a is of a numeric type; otherwise, an array of logical type. The rank shall be one or two, and the first (or only) dimension of matrix_b shall be equal to the last (or only) dimension of matrix_a.

Returns#

The matrix product of matrix_a and matrix_b. The type and kind of the result follow the usual type and kind promotion rules, as for the * or .and. operators.

Standard#

Fortran 95 and later

####### fortran-lang intrinsic descriptions

parity#

Name#

parity(3) - [TRANSFORMATIONAL] Reduction with exclusive OR()

Syntax#

result = parity(mask, dim)

    function parity(mask, dim)
    type(logical(kind=LKIND))                    :: dim
    type(logical(kind=LKIND)),intent(in)         :: mask(..)
    type(integer(kind=KIND)),intent(in),optional :: dim

where KIND and LKIND are any supported kind for the type.

### __Description__

Calculates the parity (i.e. the reduction using .xor.) of __mask__ along
dimension __dim__.

### __Arguments__

  - __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__.

### __Returns__

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.

When __dim__ is specified the returned shape is similar to that of __mask__
with dimension __dim__ dropped.

### __Examples__

Sample program:

```fortran
program demo_parity
implicit none
logical :: x(2) = [ .true., .false. ]
   print *, parity(x) 
end program demo_parity

Results:

    T

Standard#

Fortran 2008 and later

####### fortran-lang intrinsic descriptions

null#

Name#

null(3) - [TRANSFORMATIONAL] Function that returns a disassociated pointer

Syntax#

ptr => null(mold)

Description#

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.

Arguments#

  • mold

    (Optional) shall be a pointer of any association status and of any type.

Returns#

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

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
!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 and later

See Also#

associated(3)

####### fortran-lang intrinsic descriptions