Manipulation and properties of numeric values#
abs#
Name#
abs(3) - [NUMERIC] Absolute value
Synopsis#
result = abs(a)
elemental TYPE(kind=KIND) function abs(a)
TYPE(kind=KIND),intent(in) :: a
Characteristics#
a may be any real, integer, or complex value.
If a is complex the returned value will be a real with the same kind as a.
Otherwise the returned type and kind is the same as for a.
Description#
abs(3) 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. So for a complex value the absolute value is a real number with magnitude sqrt(x%re**2,x%im**2), as if the real component is the x value and the imaginary value is the y value for the point <x,y>.
Options#
- a
The value to compute the absolute value of.
Result#
If a is of type integer or real, the value of the result is the absolute value |a| and of the same type and kind as the input argument.
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 (that means the computation of the result can overflow the allowed magnitude of the real value returned, and that very small values can produce underflows if they are squared while calculating the returned value, for example).
That is, if you think of non-complex values as being complex values on the x-axis and complex values as being x-y points <x%re,x%im> the result of abs(3) is the (positive) magnitude of the distance of the value from the origin.
Examples#
Sample program:
program demo_abs
implicit none
integer,parameter :: dp=kind(0.0d0)
integer :: i = -1
real :: x = -1.0
complex :: z = (-3.0,-4.0)
doubleprecision :: rr = -45.78_dp
character(len=*),parameter :: &
! some formats
frmt = '(1x,a15,1x," In: ",g0, T51," Out: ",g0)', &
frmtc = '(1x,a15,1x," In: (",g0,",",g0,")",T51," Out: ",g0)', &
g = '(*(g0,1x))'
! basic usage
! any integer, real, or complex type
write(*, frmt) 'integer ', i, abs(i)
write(*, frmt) 'real ', x, abs(x)
write(*, frmt) 'doubleprecision ', rr, abs(rr)
write(*, frmtc) 'complex ', z, abs(z)
! You can take the absolute value of any value whose positive value
! is representable with the same type and kind.
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))
! A dusty corner is that abs(-huge(0)-1) of an integer would be
! a representable negative value on most machines but result in a
! positive value out of range.
! elemental
write(*, g) ' abs is elemental:', abs([20, 0, -1, -3, 100])
! COMPLEX input produces REAL output
write(*, g)' complex input produces real output', &
& abs(cmplx(30.0_dp,40.0_dp,kind=dp))
! dusty corner: "kind=dp" is required or the value returned by
! CMPLX() is a default real instead of double precision
! the returned value for complex input can be thought of as the
! distance from the origin <0,0>
write(*, g) ' distance of (', z, ') from zero is', abs( z )
write(*, g) ' so beware of overflow with complex values'
!write(*, g) abs(cmplx( huge(0.0), huge(0.0) ))
write(*, g) ' because the biggest default real is',huge(0.0)
end program demo_abs
Results:
integer In: -1 Out: 1
real In: -1.000000 Out: 1.000000
doubleprecision In: -45.78000000000000 Out: 45.78000000000000
complex In: (-3.000000,-4.000000) Out: 5.000000
abs range test : 2147483647 2147483647
abs range test : 3.4028235E+38 3.4028235E+38
abs range test : 1.1754944E-38 1.1754944E-38
abs is elemental: 20 0 1 3 100
complex input produces real output 50.00000000000000
distance of ( -3.000000 -4.000000 ) from zero is 5.000000
so beware of overflow with complex values
Inf
because the biggest default real is .3402823E+39
Standard#
FORTRAN 77
See Also#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
aint#
Name#
aint(3) - [NUMERIC] Truncate toward zero to a whole number
Synopsis#
result = aint(x [,kind])
elemental real(kind=KIND) function iaint(x,KIND)
real(kind=**),intent(in) :: x
integer(kind=**),intent(in),optional :: KIND
Characteristics#
a kind designated as ** may be any supported kind for the type
the result is a real of the default kind unless kind is specified.
kind is an integer initialization expression indicating the kind parameter of the result.
Description#
aint(3) truncates its argument toward zero to a whole number.
Options#
- x
the real value to truncate.
- kind
indicates the kind parameter of the result.
Result#
The sign is the same as the sign of x unless the magnitude of x is less than one, in which case zero is returned.
Otherwise aint(3) returns the largest whole number that does not exceed the magnitude of x with the same sign as the input.
That is, it truncates the value towards zero.
Examples#
Sample program:
program demo_aint
use, intrinsic :: iso_fortran_env, only : sp=>real32, dp=>real64
implicit none
real(kind=dp) :: x8
print *,'basics:'
print *,' just chops off the fractional part'
print *, aint(-2.999), aint(-2.1111)
print *,' if |x| < 1 a positive zero is returned'
print *, aint(-0.999), aint( 0.9999)
print *,' input may be of any real kind'
x8 = 4.3210_dp
print *, aint(-x8), 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:
basics:
just chops off the fractional part
-2.000000 -2.000000
if |x| < 1 a positive zero is returned
0.0000000E+00 0.0000000E+00
input may be of any real kind
-4.00000000000000 4.00000000000000
elemental:
-2.000000 -2.000000 -2.000000 -2.000000 -1.000000
-1.000000 0.0000000E+00 0.0000000E+00 0.0000000E+00 1.000000
1.000000 2.000000 2.000000 2.000000 2.000000
Standard#
FORTRAN 77
See Also#
anint(3), int(3), nint(3), selected_int_kind(3), ceiling(3), floor(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
anint#
Name#
anint(3) - [NUMERIC] Real nearest whole number
Synopsis#
result = anint(a [,kind])
elemental real(kind=KIND) function anint(x,KIND)
real(kind=**),intent(in) :: x
integer,intent(in),optional :: KIND
Characteristics#
a is type real of any kind
KIND is a scalar integer constant expression.
the result is type real. The kind of the result is the same as x unless specified by kind.
Description#
anint(3) rounds its argument to the nearest whole number.
Unlike nint(3) which returns an integer the full range or real values can be returned (integer types typically have a smaller range of values than real types).
Options#
- a
the value to round
- kind
specifies the kind of the result. The default is the kind of a.
Result#
The return value is the real whole number nearest a.
If a is greater than zero, anint(a)(3) returns aint(a + 0.5).
If a is less than or equal to zero then it returns aint(a - 0.5), except aint specifies that for |a| < 1 the result is zero (0).
It is processor-dependent whether anint(a) returns negative zero when -0.5 < a <= -0.0. Compiler switches are often available which enable or disable support of negative zero.
Examples#
Sample program:
program demo_anint
use, intrinsic :: iso_fortran_env, only : real32, real64, real128
implicit none
real,allocatable :: arr(:)
! basics
print *, 'ANINT (2.783) has the value 3.0 =>', anint(2.783)
print *, 'ANINT (-2.783) has the value -3.0 =>', anint(-2.783)
print *, 'by default the kind of the output is the kind of the input'
print *, anint(1234567890.1234567890e0)
print *, anint(1234567890.1234567890d0)
print *, 'sometimes specifying the result kind is useful when passing'
print *, 'results as an argument, for example.'
print *, 'do you know why the results are different?'
print *, anint(1234567890.1234567890,kind=real64)
print *, anint(1234567890.1234567890d0,kind=real64)
! elemental
print *, 'numbers on a cusp are always the most troublesome'
print *, anint([ -2.7, -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, 0.0 ])
print *, 'negative zero is processor dependent'
arr=[ 0.0, 0.1, 0.5, 1.0, 1.5, 2.0, 2.2, 2.5, 2.7 ]
print *, anint(arr)
arr=[ -0.0, -0.1, -0.5, -1.0, -1.5, -2.0, -2.2, -2.5, -2.7 ]
print *, anint(arr)
end program demo_anint
Results:
> ANINT (2.783) has the value 3.0 => 3.000000
> ANINT (-2.783) has the value -3.0 => -3.000000
> by default the kind of the output is the kind of the input
> 1.2345679E+09
> 1234567890.00000
> sometimes specifying the result kind is useful when passing
> results as an argument, for example.
> do you know why the results are different?
> 1234567936.00000
> 1234567890.00000
> numbers on a cusp are always the most troublesome
> -3.000000 -3.000000 -2.000000 -2.000000 -2.000000
> -1.000000 -1.000000 0.0000000E+00
> negative zero is processor dependent
> 0.0000000E+00 0.0000000E+00 1.000000 1.000000 2.000000
> 2.000000 2.000000 3.000000 3.000000
> 0.0000000E+00 0.0000000E+00 -1.000000 -1.000000 -2.000000
> -2.000000 -2.000000 -3.000000 -3.000000
Standard#
FORTRAN 77
See Also#
aint(3), int(3), nint(3), selected_int_kind(3), ceiling(3), floor(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
ceiling#
Name#
ceiling(3) - [NUMERIC] Integer ceiling function
Synopsis#
result = ceiling(a [,kind])
elemental integer(KIND) function ceiling(a,KIND)
real(kind=**),intent(in) :: a
integer,intent(in),optional :: KIND
Characteristics#
** a is of type real
KIND shall be a scalar integer constant expression. It specifies the kind of the result if present.
the result is integer. It is default kind if KIND is not specified
Description#
ceiling(3) returns the least integer greater than or equal to a.
On the number line -n <-- 0 -> +n the value returned is always at or to the right of the input value.
Options#
- a
A real value to produce a ceiling for.
- kind
indicates the kind parameter of the result.
Result#
The result will be the integer value equal to a or the least integer greater than a if the input value is not equal to a whole number.
If a is equal to a whole number, the returned value is int(a).
The result is undefined if it cannot be represented in the specified integer type.
Examples#
Sample program:
program demo_ceiling
implicit none
! just a convenient format for a list of integers
character(len=*),parameter :: ints='(*(" > ",5(i0:,",",1x),/))'
real :: x
real :: y
! basic usage
x = 63.29
y = -63.59
print ints, ceiling(x)
print ints, ceiling(y)
! note the result was the next integer larger to the right
! real values equal to whole numbers
x = 63.0
y = -63.0
print ints, ceiling(x)
print ints, ceiling(y)
! elemental (so an array argument is allowed)
print ints , &
& 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
> 63
> -63
> -2, -2, -2, -2, -1,
> -1, 0, 0, 1, 1,
> 2, 2, 3, 3, 3
Standard#
Fortran 95
See Also#
aint(3), anint(3), int(3), selected_int_kind(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
conjg#
Name#
conjg(3) - [NUMERIC] Complex conjugate of a complex value
Synopsis#
result = conjg(z)
elemental complex(kind=KIND) function conjg(z)
complex(kind=**),intent(in) :: z
Characteristics#
z is a complex value of any valid kind.
The returned value has the same complex type as the input.
Description#
conjg(3) returns the complex conjugate of the complex value z.
That is, If z is the complex value (x, y) then the result is (x, -y).
In mathematics, the complex conjugate of a complex number is a value whose real and imaginary part are equal parts are equal in magnitude to each other but the y value has opposite sign.
For matrices of complex numbers, conjg(array) represents the element-by-element conjugation of array; not the conjugate transpose of the array .
Options#
- z
The value to create the conjugate of.
Result#
Returns a value equal to the input value except the sign of the imaginary component is the opposite of the input value.
That is, if z has the value (x,y), the result has the value (x, -y).
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
! basics
! notice the sine of the imaginary component changes
print *, z, conjg(z)
! any complex kind is supported. z is of default kind but
! dz is kind=real64.
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
See Also#
aimag(3) - Imaginary part of complex number
cmplx(3) - Complex conversion function
real(3) - Convert to real type
Fortran has strong support for complex values, including many intrinsics that take or produce complex values in addition to algebraic and logical expressions:
abs(3), acosh(3), acos(3), asinh(3), asin(3), atan2(3), atanh(3), atan(3), cosh(3), cos(3), co_sum(3), dble(3), dot_product(3), exp(3), int(3), is_contiguous(3), kind(3), log(3), matmul(3), precision(3), product(3), range(3), rank(3), sinh(3), sin(3), sqrt(3), storage_size(3), sum(3), tanh(3), tan(3), unpack(3),
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
dim#
Name#
dim(3) - [NUMERIC] Positive difference of X - Y
Synopsis#
result = dim(x, y)
elemental TYPE(kind=KIND) function dim(x, y )
TYPE(kind=KIND),intent(in) :: x, y
Characteristics#
x and y may be any real or integer but of the same type and kind
the result is of the same type and kind as the arguments
Description#
dim(3) returns the maximum of x - y and zero. That is, it returns the difference x - y if the result is positive; otherwise it returns zero. It is equivalent to
max(0,x-y)
Options#
- x
the subtrahend, ie. the number being subtracted from.
- y
the minuend; ie. the number being subtracted
Result#
Returns the difference x - y or zero, whichever is larger.
Examples#
Sample program:
program demo_dim
use, intrinsic :: iso_fortran_env, only : real64
implicit none
integer :: i
real(kind=real64) :: x
! basic usage
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
See Also#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
dprod#
Name#
dprod(3) - [NUMERIC] Double precision real product
Synopsis#
result = dprod(x,y)
elemental function dprod(x,y)
real,intent(in) :: x
real,intent(in) :: y
doubleprecision :: dprod
Characteristics#
x is a default real.
y is a default real.
the result is a doubleprecision real.
The setting of compiler options specifying the size of a default real can affect this function.
Description#
dprod(3) produces a doubleprecision product of default real values x and y.
That is, it is expected to convert the arguments to double precision before multiplying, which a simple expression x*y would not be required to do. This can be significant in specialized computations requiring high precision.
The result has a value equal to a processor-dependent approximation to the product of x and y. Note it is recommended in the standard that the processor compute the product in double precision, rather than in single precision then converted to double precision; but is only a recommendation.
Options#
- x
the multiplier
- y
the multiplicand
Result#
The returned value of the product should have the same value as dble(x)*dble(y).
Examples#
Sample program:
program demo_dprod
implicit none
integer,parameter :: dp=kind(0.0d0)
real :: x = 5.2
real :: y = 2.3
doubleprecision :: xx
real(kind=dp) :: dd
print *,'algebraically 5.2 x 2.3 is exactly 11.96'
print *,'as floating point values results may differ slightly:'
! basic usage
dd = dprod(x,y)
print *, 'compare dprod(xy)=',dd, &
& 'to x*y=',x*y, &
& 'to dble(x)*dble(y)=',dble(x)*dble(y)
print *,'test if an expected result is produced'
xx=-6.0d0
write(*,*)DPROD(-3.0, 2.0),xx
write(*,*)merge('PASSED','FAILED',DPROD(-3.0, 2.0) == xx)
print *,'elemental'
print *, dprod( [2.3,3.4,4.5], 10.0 )
print *, dprod( [2.3,3.4,4.5], [9.8,7.6,5.4] )
end program demo_dprod
Results: (this can vary between programming environments):
> algebraically 5.2 x 2.3 is exactly 11.96
> as floating point values results may differ slightly:
> compare dprod(xy)= 11.9599993133545 to x*y= 11.96000
> to dble(x)*dble(y)= 11.9599993133545
> test if an expected result is produced
> -6.00000000000000 -6.00000000000000
> PASSED
> elemental
> 22.9999995231628 34.0000009536743 45.0000000000000
> 22.5399999713898 25.8400004005432 24.3000004291534
Standard#
FORTRAN 77
See Also#
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
floor#
Name#
floor(3) - [NUMERIC] Function to return largest integral value not greater than argument
Synopsis#
result = floor(a [,kind])
elemental integer(kind=KIND) function floor( a ,kind )
real(kind=**),intent(in) :: a
integer(kind=**),intent(in),optional :: KIND
Characteristics#
a kind designated as ** may be any supported kind for the type
a is a real of any kind
KIND is any valid value for type integer.
the result is an integer of the specified or default kind
Description#
floor(3) returns the greatest integer less than or equal to a.
In other words, it picks the whole number at or to the left of the value on the number line.
This means care has to be taken that the magnitude of the real value a does not exceed the range of the output value, as the range of values supported by real values is typically larger than the range for integers.
Options#
- a
The value to operate on. Valid values are restricted by the size of the returned integer kind to the range -huge(int(a,kind=KIND))-1 to huge(int(a),kind=KIND).
- kind
A scalar integer constant initialization expression indicating the kind parameter of the result.
Result#
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.
If in range for the kind of the result the result is the whole number at or to the left of the input value on the number line.
If a is positive the result is the value with the fractional part removed.
If a is negative, it is the whole number at or to the left of the input value.
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
See Also#
ceiling(3), nint(3), 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
Synopsis#
result = max(a1, a2, a3, ...)
elemental TYPE(kind=KIND) function max(a1, a2, a3, ... )
TYPE(kind=KIND,intent(in),optional :: a1
TYPE(kind=KIND,intent(in),optional :: a2
TYPE(kind=KIND,intent(in),optional :: a3
:
:
:
Characteristics#
a3, a3, a4, ... must be of the same type and kind as a1
the arguments may (all) be integer, real or character
there must be at least two arguments
the length of a character result is the length of the longest argument
the type and kind of the result is the same as those of the arguments
Description#
max(3) returns the argument with the largest (most positive) value.
For arguments of character type, the result is as if the arguments had been successively compared with the intrinsic operational operators, taking into account the collating sequence of the character kind.
If the selected character argument is shorter than the longest argument, the result is as all values were extended with blanks on the right to the length of the longest argument.
It is unusual for a Fortran intrinsic to take an arbitrary number of options, and in addition max(3) is elemental, meaning any number of arguments may be arrays as long as they are of the same shape. The examples have an extended description clarifying the resulting behavior for those not familiar with calling a "scalar" function elementally with arrays.
See maxval(3) for simply getting the max value of an array.
Options#
- a1
The first argument determines the type and kind of the returned value, and of any remaining arguments as well as being a member of the set of values to find the maximum (most positive) value of.
- a2,a3,...
the remaining arguments of which to find the maximum value(s) of.
There must be at least two arguments to max(3).
Result#
The return value corresponds to an array of the same shape of any array argument, or a scalar if all arguments are scalar.
The returned value when any argument is an array will be an array of the same shape where each element is the maximum value occurring at that location, treating all the scalar values as arrays of that same shape with all elements set to the scalar value.
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]
integer :: box(3,4)= reshape([-6,-5,-4,-3,-2,-1,1,2,3,4,5,6],shape(box))
! basic usage
! this is simple enough when all arguments are scalar
! the most positive value is returned, not the one with the
! largest magnitude
write(*,*)'scalars:',max(10.0,11.0,30.0,-100.0)
write(*,*)'scalars:',max(-22222.0,-0.0001)
! strings do not need to be of the same length
write(*,*)'characters:',max('the','words','order')
! leading spaces are significant; everyone is padded on the right
! to the length of the longest argument
write(*,*)'characters:',max('c','bb','a')
write(*,*)'characters:',max(' c','b','a')
! elemental
! there must be at least two arguments, so even if A1 is an array
! max(A1) is not valid. See MAXVAL(3) and/or MAXLOC(3) instead.
! strings in a single array do need to be of the same length
! but the different objects can still be of different lengths.
write(*,"(*('""',a,'""':,1x))")MAX(['A','Z'],['BB','Y '])
! note the result is now an array with the max of every element
! position, as can be illustrated numerically as well:
write(*,'(a,*(i3,1x))')'box= ',box
write(*,'(a,*(i3,1x))')'box**2=',sign(1,box)*box**2
write(*,'(a,*(i3,1x))')'max ',max(box,sign(1,box)*box**2)
! Remember if any argument is an array by the definition of an
! elemental function all the array arguments must be the same shape.
! to find the single largest value of arrays you could use something
! like MAXVAL([arr1, arr2]) or probably better (no large temp array),
! max(maxval(arr1),maxval(arr2)) instead
! so this returns an array of the same shape as any input array
! where each result is the maximum that occurs at that position.
write(*,*)max(arr1,arr2(1:4))
! this returns an array just like arr1 except all values less than
! zero are set to zero:
write(*,*)max(box,0)
! When mixing arrays and scalars you can think of the scalars
! as being a copy of one of the arrays with all values set to
! the scalar value.
end program demo_max
Results:
scalars: 30.00000
scalars: -9.9999997E-05
characters:words
characters:c
characters:b
"BB" "Z "
box= -6 -5 -4 -3 -2 -1 1 2 3 4 5 6
box**2=-36 -25 -16 -9 -4 -1 1 4 9 16 25 36
max -6 -5 -4 -3 -2 -1 1 4 9 16 25 36
20.00000 21.00000 32.00000 -100.0000
0 0 0 0 0 0
1 2 3 4 5 6
Standard#
FORTRAN 77
See Also#
maxloc(3), minloc(3), maxval(3), minval(3), min(3)
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
min#
Name#
min(3) - [NUMERIC] Minimum value of an argument list
Synopsis#
result = min(a1, a2, a3, ... )
elemental TYPE(kind=KIND) function min(a1, a2, a3, ... )
TYPE(kind=KIND,intent(in) :: a1
TYPE(kind=KIND,intent(in) :: a2
TYPE(kind=KIND,intent(in) :: a3
:
:
:
Characteristics#
TYPE may be integer, real or character.
Description#
min(3) returns the argument with the smallest (most negative) value.
See max(3) for an extended example of the behavior of min(3) as and max(3).
Options#
- a1
the first element of the set of values to determine the minimum of.
- a2, a3, ...
An expression of the same type and kind as a1 completing the set of values to find the minimum of.
Result#
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
See Also#
maxloc(3), minloc(3), minval(3), max(3),
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
mod#
Name#
mod(3) - [NUMERIC] Remainder function
Synopsis#
result = mod(a, p)
elemental type(TYPE(kind=KIND)) function mod(a,p)
type(TYPE(kind=KIND),intent(in) :: a
type(TYPE(kind=KIND),intent(in) :: p
Characteristics#
The result and arguments are all of the same type and kind.
The type may be any kind of real or integer.
Description#
mod(3) computes the remainder of the division of a by p.
In mathematics, the remainder is the amount "left over" after performing some computation. In arithmetic, the remainder is the integer "left over" after dividing one integer by another to produce an integer quotient (integer division). In algebra of polynomials, the remainder is the polynomial "left over" after dividing one polynomial by another. The modulo operation is the operation that produces such a remainder when given a dividend and divisor.
(remainder). (2022, October 10). In Wikipedia. https://en.wikipedia.org/wiki/Remainder
Options#
- a
The dividend
- p
the divisor (not equal to zero).
Result#
The return value is the result of a - (int(a/p) * p).
As can be seen by the formula the sign of p is canceled out. Therefore the returned value always has the sign of a.
Of course, the magnitude of the result will be less than the magnitude of p, as the result has been reduced by all multiples of p.
Examples#
Sample program:
program demo_mod
implicit none
! basics
print *, mod( -17, 3 ), modulo( -17, 3 )
print *, mod( 17, -3 ), modulo( 17, -3 )
print *, mod( 17, 3 ), modulo( 17, 3 )
print *, mod( -17, -3 ), modulo( -17, -3 )
print *, mod(-17.5, 5.2), modulo(-17.5, 5.2)
print *, mod( 17.5,-5.2), modulo( 17.5,-5.2)
print *, mod( 17.5, 5.2), modulo( 17.5, 5.2)
print *, mod(-17.5,-5.2), modulo(-17.5,-5.2)
! with a divisor of 1 the fractional part is returned
print *, mod(-17.5, 1.0), modulo(-17.5, 1.0)
print *, mod( 17.5,-1.0), modulo( 17.5,-1.0)
print *, mod( 17.5, 1.0), modulo( 17.5, 1.0)
print *, mod(-17.5,-1.0), modulo(-17.5,-1.0)
end program demo_mod
Results:
-2 1
2 -1
2 2
-2 -2
-1.900001 3.299999
1.900001 -3.299999
1.900001 1.900001
-1.900001 -1.900001
-0.5000000 0.5000000
0.5000000 -0.5000000
0.5000000 0.5000000
-0.5000000 -0.5000000
Standard#
FORTRAN 77
See Also#
modulo(3) - Modulo function
aint(3) - truncate toward zero to a whole real number
int(3) - truncate toward zero to a whole integer number
anint(3) - real nearest whole number
nint(3) - integer nearest whole number
fortran-lang intrinsic descriptions (license: MIT) @urbanjost
modulo#
Name#
modulo(3) - [NUMERIC] Modulo function
Synopsis#
result = modulo(a, p)
elemental TYPE(kind=KIND) function modulo(a,p)
TYPE(kind=KIND),intent(in) :: a
TYPE(kind=KIND),intent(in) :: p
Characteristics#
a may be any kind of real or integer.
p is the same type and kind as a
The result and arguments are all of the same type and kind.
Description#
modulo(3) computes the a modulo p.
Options#
- a
the value to take the modulo of
- p
The value to reduce a by till the remainder is <= p. It shall not be zero.
Result#
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.000000
> 1
> 4.500000
> -1
> -4.500000
Standard#
Fortran 95
See Also#
fortran-lang intrinsic descriptions
sign#
Name#
sign(3) - [NUMERIC] Sign copying function
Synopsis#
result = sign(a, b)
elemental type(TYPE(kind=KIND))function sign(a, b)
type(TYPE(kind=KIND)),intent(in) :: a, b
Characteristics#
a shall be of type integer or real.
b shall be of the same type as a.
the characteristics of the result are the same as a.
Description#
sign(3) returns a value with the magnitude of a but 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.
Options#
- a
The value whose magnitude will be returned.
- b
The value whose sign will be returned.
Result#
a value with 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:
program demo_sign
implicit none
! basics
print *, sign( -12, 1 )
print *, sign( -12, 0 )
print *, sign( -12, -1 )
print *, sign( 12, 1 )
print *, sign( 12, 0 )
print *, sign( 12, -1 )
if(sign(1.0,-0.0)== -1.0)then
print *, 'this processor distinguishes +0 from -0'
else
print *, 'this processor does not distinguish +0 from -0'
endif
print *, 'elemental', sign( -12.0, [1.0, 0.0, -1.0] )
end program demo_sign
Results:
12
12
-12
12
12
-12
this processor does not distinguish +0 from -0
elemental 12.00000 12.00000 -12.00000
Standard#
FORTRAN 77
See also#
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