Manipulation and properties of numeric values#
abs#
Name#
abs(3) - [NUMERIC] Absolute value
Syntax#
result = abs(a)
TYPE(kind=KIND) elemental function abs(a)
TYPE(kind=KIND),intent(in) :: a
where the TYPE and KIND is determined by the type and type attributes of a, which may be any real, integer, or complex value.
If the type of a is cmplx the type returned will be real with the same kind as the real part of the input value.
Otherwise the returned type will be the same type as a.
Description#
abs(a) computes the absolute value of numeric argument a.
In mathematics, the absolute value or modulus of a real number x, denoted |x|, is the magnitude of x without regard to its sign.
The absolute value of a number may be thought of as its distance from zero, which is the definition used by abs(3) when dealing with complex values (see below).
Arguments#
- a
the type of the argument shall be an integer, real, or complex scalar or array.
Returns#
If a is of type integer or real, the value of the result is |a| and of the same type and kind as the input argument.
(Take particular note) if a is complex with value (x, y), the result is a real equal to a processor-dependent approximation to sqrt(x**2 + y**2) computed without undue overflow or underflow.
Examples#
Sample program:
program demo_abs
implicit none
integer :: i = -1
real :: x = -1.0
complex :: z = (-3.0,-4.0)
doubleprecision :: rr = -45.78d+00
character(len=*),parameter :: &
frmt = '(1x,a15,1x," In: ",g0, T51," Out: ",g0)', &
frmtc = '(1x,a15,1x," In: (",g0,",",g0,")",T51," Out: ",g0)'
integer,parameter :: dp=kind(0.0d0)
integer,parameter :: sp=kind(0.0)
write(*, frmt) 'integer ', i, abs(i)
write(*, frmt) 'real ', x, abs(x)
write(*, frmt) 'doubleprecision ', rr, abs(rr)
write(*, frmtc) 'complex ', z, abs(z)
!
!
write(*, *)
write(*, *) 'abs is elemental: ', abs([20, 0, -1, -3, 100])
write(*, *)
write(*, *) 'abs range test : ', abs(huge(0)), abs(-huge(0))
write(*, *) 'abs range test : ', abs(huge(0.0)), abs(-huge(0.0))
write(*, *) 'abs range test : ', abs(tiny(0.0)), abs(-tiny(0.0))
write(*, *) 'returned real kind:', cmplx(30.0_dp,40.0_dp,kind=dp), &
kind(cmplx(30.0_dp,40.0_dp,kind=dp))
write(*, *) 'returned real kind:', cmplx(30.0_dp,40.0_dp),&
kind(cmplx(30.0_dp,40.0_dp))
write(*, *) 'returned real kind:', cmplx(30.0_sp,40.0_sp),&
kind(cmplx(30.0_sp,40.0_sp))
write(*, *)
write(*, *) 'distance of <XX,YY> from zero is', &
& distance(30.0_dp,40.0_dp)
contains
real(kind=dp) elemental function distance(x,y)
real(kind=dp),intent(in) :: x,y
! dusty corners:
! note that KIND=DP is NOT optional
! if the desired result is KIND=dp.
! See cmplx(3).
distance=abs( cmplx(x,y,kind=dp) )
end function distance
end program demo_abs
Results:
integer In: -1 Out: 1
real In: -1.00000000 Out: 1.00000000
doubleprecision In: -45.780000000000001 Out: 45.780000000000001
complex In: (-3.00000000,-4.00000000) Out: 5.00000000
abs is elemental: 20 0 1 3 100
abs range test : 2147483647 2147483647
abs range test : 3.40282347E+38 3.40282347E+38
abs range test : 1.17549435E-38 1.17549435E-38
returned real kind: (30.000000000000000,40.000000000000000) 8
returned real kind: (30.0000000,40.0000000) 4
returned real kind: (30.0000000,40.0000000) 4
distance of <XX,YY> from zero is 50.000000000000000
Standard#
FORTRAN 77 and later
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
aint#
Name#
aint(3) - [NUMERIC] Truncate to a whole number
Syntax#
result = aint(x)
real(kind=kind(x)),elemental :: aint
real(kind=kind(x)),intent(in) :: x
or
result = aint(x, KIND)
real(kind=KIND),elemental :: aint
integer,intent(in),optional :: KIND
real(kind=kind(x)),intent(in) :: x
Description#
aint(x, kind) truncates its argument to a whole number.
Arguments#
- x
the type of the argument shall be real.
- kind
(optional) an integer initialization expression indicating the kind parameter of the result.
Returns#
The return value is of type real with the kind type parameter of the argument if the optional kind is absent; otherwise, the kind type parameter will be given by kind. If the magnitude of x is less than one, aint(x) returns zero. If the magnitude is equal to or greater than one then it returns the largest whole number that does not exceed its magnitude. The sign is the same as the sign of x.
Examples#
Sample program:
program demo_aint
use, intrinsic :: iso_fortran_env, only : real32, real64
implicit none
real(kind=real32) :: x4
real(kind=real64) :: x8
x4 = 4.3210_real32
x8 = 4.3210_real64
print *, aint(x4), aint(x8)
print *
! elemental
print *,aint([ &
& -2.7, -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, &
& 0.0, &
& +0.5, +1.0, +1.5, +2.0, +2.2, +2.5, +2.7 ])
end program demo_aint
Results:
4.00000000 4.0000000000000000
-2.00000000 -2.00000000 -2.00000000 -2.00000000
-1.00000000 -1.00000000 -0.00000000 0.00000000
0.00000000 1.00000000 1.00000000 2.00000000
2.00000000 2.00000000 2.00000000
Standard#
FORTRAN 77 and later
See Also#
anint(3), int(3), nint(3), selected_int_kind(3), ceiling(3), floor(3)
####### fortran-lang intrinsic descriptions
anint#
Name#
anint(3) - [NUMERIC] Nearest whole number
Syntax#
result = anint(a, kind)
Description#
anint(a [, kind]) rounds its argument to the nearest whole number.
Arguments#
- a
the type of the argument shall be real.
- kind
(optional) an integer initialization expression indicating the kind parameter of the result.
Returns#
The return value is of type real with the kind type parameter of the argument if the optional kind is absent; otherwise, the kind type parameter will be given by kind. If a is greater than zero, anint(a) returns aint(a + 0.5). If a is less than or equal to zero then it returns aint(a - 0.5).
Examples#
Sample program:
program demo_anint
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real32) :: x4
real(kind=real64) :: x8
x4 = 1.234E0_real32
x8 = 4.321_real64
print *, anint(x4), dnint(x8)
x8 = anint(x4,kind=real64)
print *, x8
print *
! elemental
print *,anint([ &
& -2.7, -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, &
& 0.0, &
& +0.5, +1.0, +1.5, +2.0, +2.2, +2.5, +2.7 ])
end program demo_anint
Results:
1.00000000 4.0000000000000000
1.0000000000000000
-3.00000000 -3.00000000 -2.00000000 -2.00000000
-2.00000000 -1.00000000 -1.00000000 0.00000000
1.00000000 1.00000000 2.00000000 2.00000000
2.00000000 3.00000000 3.00000000
Standard#
FORTRAN 77 and later
See Also#
aint(3), int(3), nint(3), selected_int_kind(3), ceiling(3), floor(3)
####### fortran-lang intrinsic descriptions
ceiling#
Name#
ceiling(3) - [NUMERIC] Integer ceiling function
Syntax#
result = ceiling(a, kind)
integer(kind=KIND) elemental function ceiling(a,kind)
real(kind=ANY),intent(in) :: a
integer,intent(in),optional :: kind
Description#
ceiling(a) returns the least integer greater than or equal to a.
Arguments#
- a
The type shall be real.
- kind
An integer initialization expression indicating the kind parameter of the result.
Returns#
The return value is of type integer(kind) if kind is present and a default-kind integer otherwise.
The result is undefined if it cannot be represented in the specified integer type.
Examples#
Sample program:
program demo_ceiling
implicit none
real :: x = 63.29
real :: y = -63.59
print *, ceiling(x)
print *, ceiling(y)
! elemental
print *,ceiling([ &
& -2.7, -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, &
& 0.0, &
& +0.5, +1.0, +1.5, +2.0, +2.2, +2.5, +2.7 ])
end program demo_ceiling
Results:
64
-63
-2 -2 -2 -2 -1 -1
0 0 1 1 2 2
3 3 3
Standard#
Fortran 95 and later
See Also#
aint(3), anint(3), int(3), selected_int_kind(3)
####### fortran-lang intrinsic descriptions
conjg#
Name#
conjg(3) - [NUMERIC] Complex conjugate of a complex value
Syntax#
z = conjg(z)
complex(kind=K) elemental function conjg(z)
complex(kind=K),intent(in) :: z
where K is the kind of the parameter z
Description#
conjg(z) returns the complex conjugate of the complex value z.
In mathematics, the complex conjugate of a complex_ number is the number with an equal real part and an imaginary part equal in magnitude but opposite in sign.
That is, If z is (x, y) then the result is (x, -y).
For matrices of complex numbers, conjg(array) represents the element-by-element conjugation of array; not the conjugate transpose of array .
Arguments#
- z
The type shall be complex.
Returns#
The return value is of type complex.
Examples#
Sample program:
program demo_conjg
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
complex :: z = (2.0, 3.0)
complex(kind=real64) :: dz = ( &
& 1.2345678901234567_real64, &
& -1.2345678901234567_real64)
complex :: arr(3,3)
integer :: i
print *, z
z= conjg(z)
print *, z
print *
print *, dz
dz = conjg(dz)
print *, dz
print *
! the function is elemental so it can take arrays
arr(1,:)=[(-1.0, 2.0),( 3.0, 4.0),( 5.0,-6.0)]
arr(2,:)=[( 7.0,-8.0),( 8.0, 9.0),( 9.0, 9.0)]
arr(3,:)=[( 1.0, 9.0),( 2.0, 0.0),(-3.0,-7.0)]
write(*,*)'original'
write(*,'(3("(",g8.2,",",g8.2,")",1x))')(arr(i,:),i=1,3)
arr = conjg(arr)
write(*,*)'conjugate'
write(*,'(3("(",g8.2,",",g8.2,")",1x))')(arr(i,:),i=1,3)
end program demo_conjg
Results:
(2.000000,3.000000)
(2.000000,-3.000000)
(1.23456789012346,-1.23456789012346)
(1.23456789012346,1.23456789012346)
original
(-1.0 , 2.0 ) ( 3.0 , 4.0 ) ( 5.0 ,-6.0 )
( 7.0 ,-8.0 ) ( 8.0 , 9.0 ) ( 9.0 , 9.0 )
( 1.0 , 9.0 ) ( 2.0 , 0.0 ) (-3.0 ,-7.0 )
conjugate
(-1.0 ,-2.0 ) ( 3.0 ,-4.0 ) ( 5.0 , 6.0 )
( 7.0 , 8.0 ) ( 8.0 ,-9.0 ) ( 9.0 ,-9.0 )
( 1.0 ,-9.0 ) ( 2.0 , 0.0 ) (-3.0 , 7.0 )
Standard#
FORTRAN 77 and later
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
dim#
Name#
dim(3) - [NUMERIC] Positive difference
Syntax#
result = dim(x, y)
elemental function dim(x, y)
type(TYPE(kind=KIND)) :: dim
type(TYPE(kind=KIND)),intent(in) :: x, y
where TYPE may be real or integer and KIND is any supported kind for the type.
Description#
dim(x,y) returns the difference x - y if the result is positive; otherwise it returns zero.
Arguments#
- x
The type shall be integer or real
- y
The type shall be the same type and kind as x.
Returns#
The return value is the same type and kind as the input arguments x and y.
Examples#
Sample program:
program demo_dim
use, intrinsic :: iso_fortran_env, only : real64
implicit none
integer :: i
real(kind=real64) :: x
i = dim(4, 15)
x = dim(4.321_real64, 1.111_real64)
print *, i
print *, x
! elemental
print *, dim([1,2,3],2)
print *, dim([1,2,3],[3,2,1])
print *, dim(-10,[0,-10,-20])
end program demo_dim
Results:
0
3.21000000000000
0 0 1
0 0 2
0 0 10
Standard#
FORTRAN 77 and later
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
dprod#
Name#
dprod(3) - [NUMERIC] Double product function
Syntax#
result = dprod(x, y)
Description#
dprod(x,y) produces a higher doubleprecision product of default real numbers x and y.
The result has a value equal to a processor-dependent approximation to the product of x and y. It is recommended that the processor compute the product in double precision, rather than in single precision and then converted to double precision.
- x
shall be default real.
- y
shall be default real.
The setting of compiler options specifying real size can affect this function.
Arguments#
- x
Must be of default real(kind=kind(0.0)) type
- y
Must have the same type and kind parameters as x
Returns#
The return value is of type real(kind=kind(0.0d0)).
Examples#
Sample program:
program demo_dprod
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
integer,parameter :: dp=kind(0.0d0)
real :: x = 5.2
real :: y = 2.3
real(kind=dp) :: dd
dd = dprod(x,y)
print *, dd, x*y, kind(x), kind(dd), kind(dprod(x,y))
! interesting comparisons
print *, 52*23
print *, 52*23/100.0
print *, 52*23/100.0d0
!! common extension is to take doubleprecision arguments
!! and return higher precision
bigger: block
doubleprecision :: xx = 5.2d0
doubleprecision :: yy = 2.3d0
real(kind=real128) :: ddd
!ddd = dprod(xx,yy)
!print *, ddd, xx*yy, kind(xx), kind(ddd), kind(dprod(xx,yy))
endblock bigger
end program demo_dprod
Results:
11.959999313354501 11.9599991 4 8 8
1196
11.9600000
11.960000000000001
Standard#
FORTRAN 77 and later
####### fortran-lang intrinsic descriptions
floor#
Name#
floor(3) - [NUMERIC] function to return largest integral value not greater than argument
Syntax#
result = floor(a, KIND)
elemental function floor(a,KIND)
integer(kind=KIND) :: floor
real(kind=kind(a)),intent(in) :: a
integer(kind=IKIND),intent(in),optional :: KIND
where __KIND__ is any valid value for type _integer_.
Description#
floor(a) returns the greatest integer less than or equal to a. That is, it picks the whole number at or to the left of the value on the scale -huge(int(a,kind=KIND))-1 to huge(int(a),kind=KIND).
Arguments#
- a
The type shall be real.
- kind
(Optional) A scalar integer constant initialization expression indicating the kind parameter of the result.
Returns#
The return value is of type integer(kind) if kind is present and of default-kind integer otherwise.
The result is undefined if it cannot be represented in the specified integer type.
Examples#
Sample program:
program demo_floor
implicit none
real :: x = 63.29
real :: y = -63.59
print *, x, floor(x)
print *, y, floor(y)
! elemental
print *,floor([ &
& -2.7, -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, &
& 0.0, &
& +0.5, +1.0, +1.5, +2.0, +2.2, +2.5, +2.7 ])
! note even a small deviation from the whole number changes the result
print *, [2.0,2.0-epsilon(0.0),2.0-2*epsilon(0.0)]
print *,floor([2.0,2.0-epsilon(0.0),2.0-2*epsilon(0.0)])
! A=Nan, Infinity or <huge(0_KIND)-1 < A > huge(0_KIND) is undefined
end program demo_floor
Results:
63.29000 63
-63.59000 -64
-3 -3 -3 -2 -2 -1
-1 0 0 1 1 2
2 2 2
2.000000 2.000000 2.000000
2 1 1
Standard#
Fortran 95 and later
See Also#
aint(3), anint(3), int(3), selected_int_kind(3)
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
max#
Name#
max(3) - [NUMERIC] Maximum value of an argument list
Syntax#
result = max(a1, a2, a3, ...)
Description#
Returns the argument with the largest (most positive) value.
Arguments#
- a1
The type shall be integer or real.
- a2,a3,…
An expression of the same type and kind as a1.
Returns#
The return value corresponds to the maximum value among the arguments, and has the same type and kind as the first argument.
The function is both elemental and allows for an arbitrary number of arguments. This means if some elements are scalar and some are arrays that all the arrays must be of the same size, and the returned value will be an array that is the result as if multiple calls were made with all scalar values with a single element of each array used in each call. If called with all arrays the returned array is the same as if multiple calls were made with max(arr1(1),arr2(1), …) to max(arr1(N),arr2(N)).
Examples#
Sample program
program demo_max
implicit none
real :: arr1(4)= [10.0,11.0,30.0,-100.0]
real :: arr2(5)= [20.0,21.0,32.0,-200.0,2200.0]
!! this is simple enough because it is not being called elementally
!! because all arguments are scalar
!!
write(*,*)'scalars:',max(10.0,11.0,30.0,-100.0)
!!
!! this is all max(3) could do before it became an elemental
!! function and is the most intuitive
!! except that it can take an arbitrary number of options,
!! which is not common in Fortran without
!! declaring a lot of optional parameters.
!!
!! That is it unless you want to use the elemental features of max(3)!
!! Error: Intrinsic max at (1) must have at least two arguments
!!write(*,*)max(arr1)
!! This does not work because it is like trying to return
!! [(max(arr1(i)),i=1,size(arr1))]
!! so it is trying to take the max of a single value.
!! To find the largest element of an array
!! call maxloc(3) or maxval(3).
!! Error: Different shape for arguments 'a1' and 'a2' for intrinsic
!! 'max' at (1) on dimension 1 (4 and 5)
!!write(*,*)max(arr1,arr2)
!! but this will return an array of
!! [(max(arr1(N),arr2(N),N=1,size(arr1))]
write(*,*)max(arr1,arr2(1:4))
!! so this works only if all the arrays are the same size and
!! you want an array of the largest Nth elements
!! from the input arrays.
!! maybe you wanted to do maxval([arr1,arr2]) or
!! equivalently max(maxval(arr1),maxval(arr2))
!! to find the single largest element in both arrays?
!! compares all scalars to each member of array and
!! returns array of size arr2
write(*,*)'scalars and array:',max(10.0,11.0,30.0,-100.0,arr2)
!! Error: Different shape for arguments 'a5' and 'a6'
!! for intrinsic 'max' at (1) on dimension 1 (5 and 4)
!! write(*,*)'scalars and array:',max(10.0,11.0,30.0,-100.0,arr2,arr1)
!! as the same reason above when arrays are used
!! (without scalar values) all the arrays must be the same size
write(*,*)'scalars and array:',&
& max(40.0,11.0,30.0,-100.0,arr2(:4),arr1)
end program demo_max
Results:
scalars: 30.000000
20.0000000 21.000000 32.000000 -100.00000
scalars and array: 30.000000 30.000000 32.000000 30.000000 2200.0000
scalars and array: 40.000000 40.000000 40.000000 40.000000
Standard#
FORTRAN 77 and later
See Also#
####### fortran-lang intrinsic descriptions
min#
Name#
min(3) - [NUMERIC] Minimum value of an argument list
Syntax#
result = min(a1, a2, a3, ... )
Description#
Returns the argument with the smallest (most negative) value.
Arguments#
- a1
The type shall be integer or real.
- a2, a3, ```
An expression of the same type and kind as A1.
Returns#
The return value corresponds to the minimum value among the arguments, and has the same type and kind as the first argument.
Examples#
Sample program
program demo_min
implicit none
write(*,*)min(10.0,11.0,30.0,-100.0)
end program demo_min
Results:
-100.0000000
Standard#
FORTRAN 77 and later
See Also#
####### fortran-lang intrinsic descriptions
mod#
Name#
mod(3) - [NUMERIC] Remainder function
Syntax#
result = mod(a, p)
Description#
mod(a,p) computes the remainder of the division of a by p.
Arguments#
- a
Shall be a scalar of type integer or real.
- p
Shall be a scalar of the same type and kind as a and not equal to zero.
Returns#
The return value is the result of a - (int(a/p) * p). The type and kind of the return value is the same as that of the arguments. The returned value has the same sign as a and a magnitude less than the magnitude of p.
Examples#
Sample program:
program demo_mod
implicit none
print *, mod(17,3) ! yields 2
print *, mod(17.5,5.5) ! yields 1.0
print *, mod(17.5d0,5.5d0) ! yields 1.0d0
print *, mod(17.5d0,5.5d0) ! yields 1.0d0
print *, mod(-17,3) ! yields -2
print *, mod(-17.5,5.5) ! yields -1.0
print *, mod(-17.5d0,5.5d0) ! yields -1.0d0
print *, mod(-17.5d0,5.5d0) ! yields -1.0d0
print *, mod(17,-3) ! yields 2
print *, mod(17.5,-5.5) ! yields 1.0
print *, mod(17.5d0,-5.5d0) ! yields 1.0d0
print *, mod(17.5d0,-5.5d0) ! yields 1.0d0
end program demo_mod
Results:
2
1.00000000
1.0000000000000000
1.0000000000000000
-2
-1.00000000
-1.0000000000000000
-1.0000000000000000
2
1.00000000
1.0000000000000000
1.0000000000000000
Standard#
FORTRAN 77 and later
See Also#
####### fortran-lang intrinsic descriptions
modulo#
Name#
modulo(3) - [NUMERIC] Modulo function
Syntax#
result = modulo(a, p)
Description#
modulo(a,p) computes the a modulo p.
Arguments#
- a
Shall be a scalar of type integer or real.
- p
Shall be a scalar of the same type and kind as a. It shall not be zero.
Returns#
The type and kind of the result are those of the arguments.
If a and p are of type integer: modulo(a,p) has the value of a - floor (real(a) / real(p)) * p.
If a and p are of type real: modulo(a,p) has the value of a - floor (a / p) * p.
The returned value has the same sign as p and a magnitude less than the magnitude of p.
Examples#
Sample program:
program demo_modulo
implicit none
print *, modulo(17,3) ! yields 2
print *, modulo(17.5,5.5) ! yields 1.0
print *, modulo(-17,3) ! yields 1
print *, modulo(-17.5,5.5) ! yields 4.5
print *, modulo(17,-3) ! yields -1
print *, modulo(17.5,-5.5) ! yields -4.5
end program demo_modulo
Results:
2
1.00000000
1
4.50000000
-1
-4.50000000
Standard#
Fortran 95 and later
See Also#
####### fortran-lang intrinsic descriptions
sign#
Name#
sign(3) - [NUMERIC] Sign copying function
Syntax#
result = sign(a, b)
elemental function sign(a, b)
type(TYPE(kind=KIND)) :: sign
type(TYPE(kind=KIND)),intent(in) :: a, b
where TYPE may be real or integer and KIND is any supported kind for the type.
### __Description__
__sign__(a,b) returns the value of __a__ with the sign of __b__.
For processors that distinguish between positive and negative zeros __sign()__ may be used to
distinguish between __real__ values 0.0 and −0.0. SIGN (1.0, -0.0) will
return −1.0 when a negative zero is distinguishable.
29 1 Description. Magnitude of A with the sign of B.
### __Arguments__
- __a__
: Shall be of type _integer_ or _real_
- __b__
: Shall be of the same type and kind as __a__
### __Returns__
The kind of the return value is the magnitude of __a__ with the sign of __b__. That is,
- If __b \>= 0__ then the result is __abs(a)__
- else if __b < 0__ it is -__abs(a)__.
- if __b__ is _real_ and the processor distinguishes between __-0.0__ and __0.0__ then the
result is __-abs(a)__
### __Examples__
Sample program:
```fortran
program demo_sign
implicit none
print *, sign( -12, 1 )
print *, sign( -12, 0 )
print *, sign( -12, -1 )
print *, sign( -12.0, [1.0, 0.0, -1.0] )
print *, 'can I distinguise 0 from -0? ', sign( 1.0, -0.0 ) .ne. sign( 1.0, 0.0 )
end program demo_sign
Results:
12
12
-12
12.00000 12.00000 -12.00000
can I distinguise 0 from -0? F
Standard#
FORTRAN 77 and later
####### fortran-lang intrinsic descriptions (license: MIT)
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#
####### fortran-lang intrinsic descriptions