General mathematical functions#
acos#
Name#
acos(3) - [MATHEMATICS:TRIGONOMETRIC] arccosine (inverse cosine) function
Syntax#
result = acos(x)
TYPE(kind=KIND),elemental :: acos
TYPE(kind=KIND,intent(in) :: x
where TYPE may be real or complex and KIND may be any KIND supported by the associated type.
Description#
acos(x) computes the arccosine of x (inverse of cos(x)).
Arguments#
- x
Must be type real or complex. If the type is real, the value must satisfy |x| <= 1.
Returns#
The return value is of the same type and kind as x. The real part of the result is in radians and lies in the range 0 <= acos(x%re) <= PI .
Examples#
Sample program:
program demo_acos
use, intrinsic :: iso_fortran_env, only : real_kinds,real32,real64,real128
implicit none
character(len=*),parameter :: all='(*(g0,1x))'
real(kind=real64) :: x = 0.866_real64
real(kind=real64),parameter :: d2r=acos(-1.0_real64)/180.0_real64
print all,'acos(',x,') is ', acos(x)
print all,'90 degrees is ', d2r*90.0_real64, ' radians'
print all,'180 degrees is ', d2r*180.0_real64, ' radians'
print all,'for reference &
&PI ~ 3.14159265358979323846264338327950288419716939937510'
print all,'elemental',acos([-1.0,-0.5,0.0,0.50,1.0])
end program demo_acos
Results:
acos( .8660000000000000 ) is .5236495809318289
90 degrees is 1.570796326794897 radians
180 degrees is 3.141592653589793 radians
for reference PI ~ 3.14159265358979323846264338327950288419716939937510
elemental 3.141593 2.094395 1.570796 1.047198 .000000
Standard#
FORTRAN 77 and later; for a complex argument - Fortran 2008 and later
See Also#
Inverse function: cos(3)
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
acosh#
Name#
acosh(3) - [MATHEMATICS:TRIGONOMETRIC] Inverse hyperbolic cosine function
Syntax#
result = acosh(x)
TYPE(kind=KIND),elemental :: acosh
TYPE(kind=KIND,intent(in) :: x
where TYPE may be real or complex and KIND may be any KIND supported by the associated type.
Description#
acosh(x) computes the inverse hyperbolic cosine of x in radians.
Arguments#
- x
the type shall be real or complex.
Returns#
The return value has the same type and kind as x.
If x is complex, the imaginary part of the result is in radians and lies between
0 <= aimag(acosh(x)) <= PI
Examples#
Sample program:
program demo_acosh
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=dp), dimension(3) :: x = [ 1.0d0, 2.0d0, 3.0d0 ]
write (*,*) acosh(x)
end program demo_acosh
Results:
0.000000000000000E+000 1.31695789692482 1.76274717403909
Standard#
Fortran 2008 and later
See Also#
Inverse function: cosh(3)
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
asin#
Name#
asin(3) - [MATHEMATICS:TRIGONOMETRIC] Arcsine function
Syntax#
result = asin(x)
elemental TYPE(kind=KIND) function asin(x)
TYPE(kind=KIND) :: x
where the returned value has the kind of the input value and TYPE may be real or complex
Description#
asin(x) computes the arcsine of its argument x.
The arcsine is the inverse function of the sine function. It is commonly used in trigonometry when trying to find the angle when the lengths of the hypotenuse and the opposite side of a right triangle are known.
Arguments#
- x
The type shall be either real and a magnitude that is less than or equal to one; or be complex.
Returns#
- result
The return value is of the same type and kind as x. The real part of the result is in radians and lies in the range -PI/2 <= asin(x) <= PI/2.
Examples#
The arcsine will allow you to find the measure of a right angle when you know the ratio of the side opposite the angle to the hypotenuse.
So if you knew that a train track rose 1.25 vertical miles on a track that was 50 miles long, you could determine the average angle of incline of the track using the arcsine. Given
sin(theta) = 1.25 miles/50 miles (opposite/hypotenuse)
program demo_asin
use, intrinsic :: iso_fortran_env, only : dp=>real64
implicit none
! value to convert degrees to radians
real(kind=dp),parameter :: D2R=acos(-1.0_dp)/180.0_dp
real(kind=dp) :: angle, rise, run
character(len=*),parameter :: all='(*(g0,1x))'
! given sine(theta) = 1.25 miles/50 miles (opposite/hypotenuse)
! then taking the arcsine of both sides of the equality yields
! theta = arcsine(1.25 miles/50 miles) ie. arcsine(opposite/hypotenuse)
rise=1.250_dp
run=50.00_dp
angle = asin(rise/run)
print all, 'angle of incline(radians) = ', angle
angle = angle/D2R
print all, 'angle of incline(degrees) = ', angle
print all, 'percent grade=',rise/run*100.0_dp
end program demo_asin
Results:
angle of incline(radians) = 2.5002604899361139E-002
angle of incline(degrees) = 1.4325437375665075
percent grade= 2.5000000000000000
The percentage grade is the slope, written as a percent. To calculate the slope you divide the rise by the run. In the example the rise is 1.25 mile over a run of 50 miles so the slope is 1.25/50 = 0.025. Written as a percent this is 2.5 %.
For the US, two and 1/2 percent is generally thought of as the upper limit. This means a rise of 2.5 feet when going 100 feet forward. In the US this was the maximum grade on the first major US railroad, the Baltimore and Ohio. Note curves increase the frictional drag on a train reducing the allowable grade.
Standard#
FORTRAN 77 and later, for a complex argument Fortran 2008 or later
See Also#
Inverse function: sin(3)
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
asinh#
Name#
asinh(3) - [MATHEMATICS:TRIGONOMETRIC] Inverse hyperbolic sine function
Syntax#
result = asinh(x)
elemental TYPE(kind=KIND) function asinh(x)
TYPE(kind=KIND) :: x
Where the returned value has the kind of the input value and TYPE may be real or complex
Description#
asinh(x) computes the inverse hyperbolic sine of x.
Arguments#
- x
The type shall be real or complex.
Returns#
The return value is of the same type and kind as x. If x is complex, the imaginary part of the result is in radians and lies between -PI/2 <= aimag(asinh(x)) <= PI/2.
Examples#
Sample program:
program demo_asinh
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=dp), dimension(3) :: x = [ -1.0d0, 0.0d0, 1.0d0 ]
write (*,*) asinh(x)
end program demo_asinh
Results:
-0.88137358701954305 0.0000000000000000 0.88137358701954305
Standard#
Fortran 2008 and later
See Also#
Inverse function: sinh(3)
####### fortran-lang intrinsic descriptions
atan#
Name#
atan(3) - [MATHEMATICS:TRIGONOMETRIC] Arctangent function
Syntax#
- result = __atan(y, x)__
TYPE(kind=KIND):: atan
TYPE(kind=KIND,intent(in) :: x
TYPE(kind=KIND,intent(in),optional :: y
where TYPE may be real or complex and KIND may be any KIND supported by the associated type. If y is present x is _real`.
Description#
atan(x) computes the arctangent of x.
Arguments#
- x
The type shall be real or complex; if y is present, x shall be real.
- y
Shall be of the same type and kind as x. If x is zero, y must not be zero.
Returns#
The returned value is of the same type and kind as x. If y is present, the result is identical to atan2(y,x). Otherwise, it is the arc tangent of x, where the real part of the result is in radians and lies in the range -PI/2 <= atan(x) <= PI/2
Examples#
Sample program:
program demo_atan
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
character(len=*),parameter :: all='(*(g0,1x))'
real(kind=real64),parameter :: &
Deg_Per_Rad = 57.2957795130823208767981548_real64
real(kind=real64) :: x
x=2.866_real64
print all, atan(x)
print all, atan( 2.0d0, 2.0d0),atan( 2.0d0, 2.0d0)*Deg_Per_Rad
print all, atan( 2.0d0,-2.0d0),atan( 2.0d0,-2.0d0)*Deg_Per_Rad
print all, atan(-2.0d0, 2.0d0),atan(-2.0d0, 2.0d0)*Deg_Per_Rad
print all, atan(-2.0d0,-2.0d0),atan(-2.0d0,-2.0d0)*Deg_Per_Rad
end program demo_atan
Results:
1.235085437457879
.7853981633974483 45.00000000000000
2.356194490192345 135.0000000000000
-.7853981633974483 -45.00000000000000
-2.356194490192345 -135.0000000000000
Standard#
FORTRAN 77 and later for a complex argument; and for two arguments Fortran 2008 or later
See Also#
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
atan2#
Name#
atan2(3) - [MATHEMATICS:TRIGONOMETRIC] Arctangent function
Syntax#
result = atan2(y, x)
Description#
atan2(y, x) computes the arctangent of the complex number ( x + i y ) .
This function can be used to transform from Cartesian into polar coordinates and allows to determine the angle in the correct quadrant. To convert from Cartesian Coordinates (x,y) to polar coordinates
(r,theta): $$ \begin{aligned} r &= \sqrt{x2 + y2} \ \theta &= \tan**{-1}(y / x) \end{aligned} $$
Arguments#
- y
The type shall be real.
- x
The type and kind type parameter shall be the same as y. If y is zero, then x must be nonzero.
Returns#
The return value has the same type and kind type parameter as y. It is the principal value of the complex number (x + i, y). If x is nonzero, then it lies in the range -PI <= atan(x) <= PI. The sign is positive if y is positive. If y is zero, then the return value is zero if x is strictly positive, PI if x is negative and y is positive zero (or the processor does not handle signed zeros), and -PI if x is negative and Y is negative zero. Finally, if x is zero, then the magnitude of the result is PI/2.
Examples#
Sample program:
program demo_atan2
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
implicit none
real(kind=sp) :: x = 1.e0_sp, y = 0.5e0_sp, z
z = atan2(y,x)
write(*,*)x,y,z
end program demo_atan2
Results:
1.00000000 0.500000000 0.463647604
Standard#
FORTRAN 77 and later
####### fortran-lang intrinsic descriptions
atanh#
Name#
atanh(3) - [MATHEMATICS:TRIGONOMETRIC] Inverse hyperbolic tangent function
Syntax#
result = atanh(x)
Description#
atanh(x) computes the inverse hyperbolic tangent of x.
Arguments#
- x
The type shall be real or complex.
Returns#
The return value has same type and kind as x. If x is complex, the imaginary part of the result is in radians and lies between
-PI/2 <= aimag(atanh(x)) <= PI/2
Examples#
Sample program:
program demo_atanh
implicit none
real, dimension(3) :: x = [ -1.0, 0.0, 1.0 ]
write (*,*) atanh(x)
end program demo_atanh
Results:
-Infinity 0.00000000 Infinity
Standard#
Fortran 2008 and later
See Also#
Inverse function: tanh(3)
####### fortran-lang intrinsic descriptions
cos#
Name#
cos(3) - [MATHEMATICS:TRIGONOMETRIC] Cosine function
Syntax#
result = cos(x)
TYPE(kind=KIND),elemental :: cos
TYPE(kind=KIND,intent(in) :: x
where TYPE may be real or complex and KIND may be any KIND supported by the associated type.
Description#
cos(x) computes the cosine of an angle x given the size of the angle in radians.
The cosine of a real value is the ratio of the adjacent side to the hypotenuse of a right-angled triangle.
Arguments#
- x
The type shall be real or complex. x is assumed to be in radians.
Returns#
The return value is of the same type and kind as x.
If x is of the type real, the return value lies in the range -1 <= cos(x) <= 1 .
Examples#
Sample program:
program demo_cos
implicit none
doubleprecision,parameter :: PI=atan(1.0d0)*4.0d0
write(*,*)'COS(0.0)=',cos(0.0)
write(*,*)'COS(PI)=',cos(PI)
write(*,*)'COS(PI/2.0d0)=',cos(PI/2.0d0),' EPSILON=',epsilon(PI)
write(*,*)'COS(2*PI)=',cos(2*PI)
write(*,*)'COS(-2*PI)=',cos(-2*PI)
write(*,*)'COS(-2000*PI)=',cos(-2000*PI)
write(*,*)'COS(3000*PI)=',cos(3000*PI)
end program demo_cos
Results:
COS(0.0)= 1.00000000
COS(PI)= -1.0000000000000000
COS(PI/2.0d0)= 6.1232339957367660E-017
EPSILON= 2.2204460492503131E-016
COS(2*PI)= 1.0000000000000000
COS(-2*PI)= 1.0000000000000000
COS(-2000*PI)= 1.0000000000000000
Standard#
FORTRAN 77 and later
See Also#
####### fortran-lang intrinsic descriptions
cosh#
Name#
cosh(3) - [MATHEMATICS:TRIGONOMETRIC] Hyperbolic cosine function
Syntax#
result = cosh(x)
TYPE(kind=KIND) elemental function cosh(x)
TYPE(kind=KIND),intent(in) :: x
where TYPE may be real or complex and KIND may be any supported kind for the associated type. The returned value will be the same type and kind as the input value x.
Description#
cosh(x) computes the hyperbolic cosine of x.
Arguments#
- x
The type shall be real or complex.
Returns#
The return value has same type and kind as x. If x is complex, the imaginary part of the result is in radians.
If x is real, the return value has a lower bound of one, cosh(x) >= 1.
Examples#
Sample program:
program demo_cosh
use, intrinsic :: iso_fortran_env, only : &
& real_kinds, real32, real64, real128
implicit none
real(kind=real64) :: x = 1.0_real64
x = cosh(x)
end program demo_cosh
Standard#
FORTRAN 77 and later, for a complex argument - Fortran 2008 or later
See Also#
Inverse function: acosh(3)
####### fortran-lang intrinsic descriptions
sin#
Name#
sin(3) - [MATHEMATICS:TRIGONOMETRIC] Sine function
Syntax#
result = sin(x)
elemental TYPE(kind=KIND) function sin(x)
TYPE(kind=KIND) :: x
Where the returned value has the kind of the input value and TYPE may be real or complex
Description#
sin(x) computes the sine of an angle given the size of the angle in radians.
The sine of an angle in a right-angled triangle is the ratio of the length of the side opposite the given angle divided by the length of the hypotenuse.
Arguments#
- x
The type shall be real or complex in radians.
Returns#
- result
The return value has the same type and kind as x.
Examples#
Sample program:
program sample_sin
implicit none
real :: x = 0.0
x = sin(x)
end program sample_sin
Haversine Formula#
From the article on «Haversine formula» in Wikipedia:
The haversine formula is an equation important in navigation,
giving great-circle distances between two points on a sphere from
their longitudes and latitudes.
So to show the great-circle distance between the Nashville International Airport (BNA) in TN, USA, and the Los Angeles International Airport (LAX) in CA, USA you would start with their latitude and longitude, commonly given as
BNA: N 36 degrees 7.2', W 86 degrees 40.2'
LAX: N 33 degrees 56.4', W 118 degrees 24.0'
which converted to floating-point values in degrees is:
Latitude Longitude
- BNA
36.12, -86.67
- LAX
33.94, -118.40
And then use the haversine formula to roughly calculate the distance along the surface of the Earth between the locations:
Sample program:
program demo_sin
implicit none
real :: d
d = haversine(36.12,-86.67, 33.94,-118.40) ! BNA to LAX
print '(A,F9.4,A)', 'distance: ',d,' km'
contains
function haversine(latA,lonA,latB,lonB) result (dist)
!
! calculate great circle distance in kilometers
! given latitude and longitude in degrees
!
real,intent(in) :: latA,lonA,latB,lonB
real :: a,c,dist,delta_lat,delta_lon,lat1,lat2
real,parameter :: radius = 6371 ! mean earth radius in kilometers,
! recommended by the International Union of Geodesy and Geophysics
! generate constant pi/180
real, parameter :: deg_to_rad = atan(1.0)/45.0
delta_lat = deg_to_rad*(latB-latA)
delta_lon = deg_to_rad*(lonB-lonA)
lat1 = deg_to_rad*(latA)
lat2 = deg_to_rad*(latB)
a = (sin(delta_lat/2))**2 + &
& cos(lat1)*cos(lat2)*(sin(delta_lon/2))**2
c = 2*asin(sqrt(a))
dist = radius*c
end function haversine
end program demo_sin
Results:
distance: 2886.4446 km
Standard#
FORTRAN 77 and later
See Also#
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
sinh#
Name#
sinh(3) - [MATHEMATICS:TRIGONOMETRIC] Hyperbolic sine function
Syntax#
result = sinh(x)
elemental TYPE(kind=KIND) function sinh(x)
TYPE(kind=KIND) :: x
Where the returned value has the kind of the input value and TYPE may be real or complex
Description#
sinh(x) computes the hyperbolic sine of x.
The hyperbolic sine of x is defined mathematically as:
sinh(x) = (exp(x) - exp(-x)) / 2.0
If x is of type complex its imaginary part is regarded as a value in radians.
Arguments#
- x
The type shall be real or complex.
Returns#
The return value has same type and kind as x.
Examples#
Sample program:
program demo_sinh
use, intrinsic :: iso_fortran_env, only : &
& real_kinds, real32, real64, real128
implicit none
real(kind=real64) :: x = - 1.0_real64
real(kind=real64) :: nan, inf
character(len=20) :: line
print *, sinh(x)
print *, (exp(x)-exp(-x))/2.0
! sinh(3) is elemental and can handle an array
print *, sinh([x,2.0*x,x/3.0])
! a NaN input returns NaN
line='NAN'
read(line,*) nan
print *, sinh(nan)
! a Inf input returns Inf
line='Infinity'
read(line,*) inf
print *, sinh(inf)
! an overflow returns Inf
x=huge(0.0d0)
print *, sinh(x)
end program demo_sinh
Results:
-1.1752011936438014
-1.1752011936438014
-1.1752011936438014 -3.6268604078470190 -0.33954055725615012
NaN
Infinity
Infinity
Standard#
Fortran 95 and later, for a complex argument Fortran 2008 or later
See Also#
####### fortran-lang intrinsic descriptions
tan#
Name#
tan(3) - [MATHEMATICS:TRIGONOMETRIC] Tangent function
Syntax#
result = tan(x)
Description#
tan(x) computes the tangent of x.
Arguments#
- x
The type shall be real or complex.
Returns#
The return value has the same type and kind as x.
Examples#
Sample program:
program demo_tan
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 0.165_real64
write(*,*)x, tan(x)
end program demo_tan
Results:
0.16500000000000001 0.16651386310913616
Standard#
FORTRAN 77 and later. For a complex argument, Fortran 2008 or later.
See Also#
####### fortran-lang intrinsic descriptions
tanh#
Name#
tanh(3) - [MATHEMATICS:TRIGONOMETRIC] Hyperbolic tangent function
Syntax#
x = tanh(x)
Description#
tanh(x) computes the hyperbolic tangent of x.
Arguments#
- x
The type shall be real or complex.
Returns#
The return value has same type and kind as x. If x is complex, the imaginary part of the result is in radians. If x is real, the return value lies in the range
-1 <= tanh(x) <= 1.
Examples#
Sample program:
program demo_tanh
use, intrinsic :: iso_fortran_env, only : &
& real_kinds, real32, real64, real128
implicit none
real(kind=real64) :: x = 2.1_real64
write(*,*)x, tanh(x)
end program demo_tanh
Results:
2.1000000000000001 0.97045193661345386
Standard#
FORTRAN 77 and later, for a complex argument Fortran 2008 or later
See Also#
####### fortran-lang intrinsic descriptions
random_number#
Name#
random_number(3) - [MATHEMATICS:RANDOM] Pseudo-random number
Syntax#
random_number(harvest)
Description#
Returns a single pseudorandom number or an array of pseudorandom numbers from the uniform distribution over the range 0 <= x < 1.
Arguments#
- harvest
Shall be a scalar or an array of type real.
Examples#
Sample program:
program demo_random_number
use, intrinsic :: iso_fortran_env, only : dp=>real64
implicit none
integer, allocatable :: seed(:)
integer :: n
integer :: first,last
integer :: i
integer :: rand_int
integer,allocatable :: count(:)
real(kind=dp) :: rand_val
call random_seed(size = n)
allocate(seed(n))
call random_seed(get=seed)
first=1
last=10
allocate(count(last-first+1))
! To have a discrete uniform distribution on the integers
! [first, first+1, ..., last-1, last] carve the continuous
! distribution up into last+1-first equal sized chunks,
! mapping each chunk to an integer.
!
! One way is:
! call random_number(rand_val)
! choose one from last-first+1 integers
! rand_int = first + FLOOR((last+1-first)*rand_val)
count=0
! generate a lot of random integers from 1 to 10 and count them.
! with a large number of values you should get about the same
! number of each value
do i=1,100000000
call random_number(rand_val)
rand_int=first+floor((last+1-first)*rand_val)
if(rand_int.ge.first.and.rand_int.le.last)then
count(rand_int)=count(rand_int)+1
else
write(*,*)rand_int,' is out of range'
endif
enddo
write(*,'(i0,1x,i0)')(i,count(i),i=1,size(count))
end program demo_random_number
Results:
1 10003588
2 10000104
3 10000169
4 9997996
5 9995349
6 10001304
7 10001909
8 9999133
9 10000252
10 10000196
Standard#
Fortran 95 and later
See Also#
####### fortran-lang intrinsic descriptions
random_seed#
Name#
random_seed(3) - [MATHEMATICS:RANDOM] Initialize a pseudo-random number sequence
Syntax#
call random_seed(size, put, get)
Description#
Restarts or queries the state of the pseudorandom number generator used by random_number.
If random_seed is called without arguments, it is seeded with random data retrieved from the operating system.
Arguments#
- size
(Optional) Shall be a scalar and of type default integer, with intent(out). It specifies the minimum size of the arrays used with the put and get arguments.
- put
(Optional) Shall be an array of type default integer and rank one. It is intent(in) and the size of the array must be larger than or equal to the number returned by the size argument.
- get
(Optional) Shall be an array of type default integer and rank one. It is intent(out) and the size of the array must be larger than or equal to the number returned by the size argument.
Examples#
Sample program:
program demo_random_seed
implicit none
integer, allocatable :: seed(:)
integer :: n
call random_seed(size = n)
allocate(seed(n))
call random_seed(get=seed)
write (*, *) seed
end program demo_random_seed
Results:
-674862499 -1750483360 -183136071 -317862567 682500039
349459 344020729 -1725483289
Standard#
Fortran 95 and later
See Also#
####### fortran-lang intrinsic descriptions
exp#
Name#
exp(3) - [MATHEMATICS] Exponential function
Syntax#
result = exp(x)
Description#
exp(x) computes the base «e» exponential of x where «e» is Euler’s constant.
If x is of type complex, its imaginary part is regarded as a value in radians such that (see Euler’s formula):
if cx=(re,im) then exp(cx)=exp(re)*cmplx(cos(im),sin(im),kind=kind(cx))
Since exp(3) is the inverse function of log(3) the maximum valid magnitude of the real component of x is log(huge(x)).
Arguments#
- x
The type shall be real or complex.
Returns#
The value of the result is e**x where e is Euler’s constant.
The return value has the same type and kind as x.
Examples#
Sample program:
program demo_exp
implicit none
real :: x , re, im
complex :: cx
x = 1.0
write(*,*)"Euler's constant is approximately",exp(x)
!! complex values
! given
re=3.0
im=4.0
cx=cmplx(re,im)
! complex results from complex arguments are Related to Euler's formula
write(*,*)'given the complex value ',cx
write(*,*)'exp(x) is',exp(cx)
write(*,*)'is the same as',exp(re)*cmplx(cos(im),sin(im),kind=kind(cx))
! exp(3) is the inverse function of log(3) so
! the real component of the input must be less than or equal to
write(*,*)'maximum real component',log(huge(0.0))
! or for double precision
write(*,*)'maximum doubleprecision component',log(huge(0.0d0))
! but since the imaginary component is passed to the cos(3) and sin(3)
! functions the imaginary component can be any real value
end program demo_exp
Results:
Euler's constant is approximately 2.718282
given the complex value (3.000000,4.000000)
exp(x) is (-13.12878,-15.20078)
is the same as (-13.12878,-15.20078)
maximum real component 88.72284
maximum doubleprecision component 709.782712893384
Standard#
FORTRAN 77 and later
See Also#
Wikipedia:Exponential function
Wikipedia:Euler’s formula
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
log#
Name#
log(3) - [MATHEMATICS] Logarithm function
Syntax#
result = log(x)
Description#
log(x) computes the natural logarithm of x, i.e. the logarithm to the base «e».
Arguments#
- x
The type shall be real or complex.
Returns#
The return value is of type real or complex. The kind type parameter is the same as x. If x is complex, the imaginary part OMEGA is in the range
-PI < OMEGA <= PI.
Examples#
Sample program:
program demo_log
implicit none
real(kind(0.0d0)) :: x = 2.71828182845904518d0
complex :: z = (1.0, 2.0)
write(*,*)x, log(x) ! will yield (approximately) 1
write(*,*)z, log(z)
end program demo_log
Results:
2.7182818284590451 1.0000000000000000
(1.00000000,2.00000000) (0.804718971,1.10714877)
Standard#
FORTRAN 77 and later
####### fortran-lang intrinsic descriptions
log10#
Name#
log10(3) - [MATHEMATICS] Base 10 logarithm function
Syntax#
result = log10(x)
real(kind=KIND) elemental function log10(x)
real(kind=KIND),intent(in) :: x
Description#
log10(x) computes the base 10 logarithm of x. This is generally called the «common logarithm».
Arguments#
- x
A real value > 0 to take the log of.
Returns#
The return value is of type real . The kind type parameter is the same as x.
Examples#
Sample program:
program demo_log10
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 10.0_real64
x = log10(x)
write(*,'(*(g0))')'log10(',x,') is ',log10(x)
! elemental
write(*, *)log10([1.0, 10.0, 100.0, 1000.0, 10000.0, &
& 100000.0, 1000000.0, 10000000.0])
end program demo_log10
Results:
log10(1.0000000000000000) is 0.0000000000000000
0.00000000 1.00000000 2.00000000 3.00000000
4.00000000 5.00000000 6.00000000 7.00000000
Standard#
FORTRAN 77 and later
####### fortran-lang intrinsic descriptions
sqrt#
Name#
sqrt(3) - [MATHEMATICS] Square-root function
Syntax#
result = sqrt(x)
TYPE(kind=KIND) elemental function sqrt(x) result(value)
TYPE(kind=KIND),intent(in) :: x
TYPE(kind=KIND) :: value
Where TYPE may be real or complex and KIND may be any kind valid for the declared type.
Description#
sqrt(x) computes the principal square root of x.
In mathematics, a square root of a number x is a number y such that y*y = x.
The number whose square root is being considered is known as the radicand.
Every nonnegative number x has two square roots of the same unique magnitude, one positive and one negative. The nonnegative square root is called the principal square root.
The principal square root of 9 is 3, for example, even though (-3)*(-3) is also 9.
A real, radicand must be positive.
Square roots of negative numbers are a special case of complex numbers, where the components of the radicand need not be positive in order to have a valid square root.
Arguments#
- x
If x is real its value must be greater than or equal to zero. The type shall be real or complex.
Returns#
The return value is of type real or complex. The kind type parameter is the same as x.
Examples#
Sample program:
program demo_sqrt
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x, x2
complex :: z, z2
x = 2.0_real64
z = (1.0, 2.0)
write(*,*)x,z
x2 = sqrt(x)
z2 = sqrt(z)
write(*,*)x2,z2
x2 = x**0.5
z2 = z**0.5
write(*,*)x2,z2
end program demo_sqrt
Results:
2.0000000000000000 (1.00000000,2.00000000)
1.4142135623730951 (1.27201962,0.786151350)
1.4142135623730951 (1.27201962,0.786151350)
Standard#
FORTRAN 77 and later
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
hypot#
Name#
hypot(3) - [MATHEMATICS] returns the distance between the point and the origin.
Syntax#
result = hypot(x, y)
real(kind=KIND) elemental function hypot(x,y) result(value)
real(kind=KIND),intent(in) :: x, y
where x,y,value shall all be of the same kind.
Description#
hypot(x,y) is referred to as the Euclidean distance function. It is equal to sqrt(x2 + y2), without undue underflow or overflow.
In mathematics, the Euclidean distance between two points in Euclidean space is the length of a line segment between two points.
hypot(x,y) returns the distance between the point <x,y> and the origin.
Arguments#
- x
The type shall be real.
- y
The type and kind type parameter shall be the same as x.
Returns#
The return value has the same type and kind type parameter as x.
The result is the positive magnitude of the distance of the point <x,y> from the origin <0.0,0.0> .
Examples#
Sample program:
program demo_hypot
use, intrinsic :: iso_fortran_env, only : &
& real_kinds, real32, real64, real128
implicit none
real(kind=real32) :: x, y
real(kind=real32),allocatable :: xs(:), ys(:)
integer :: i
character(len=*),parameter :: f='(a,/,SP,*(3x,g0,1x,g0:,/))'
x = 1.e0_real32
y = 0.5e0_real32
write(*,*)
write(*,'(*(g0))')'point <',x,',',y,'> is ',hypot(x,y)
write(*,'(*(g0))')'units away from the origin'
write(*,*)
! elemental
xs=[ x, x**2, x*10.0, x*15.0, -x**2 ]
ys=[ y, y**2, -y*20.0, y**2, -y**2 ]
write(*,f)"the points",(xs(i),ys(i),i=1,size(xs))
write(*,f)"have distances from the origin of ",hypot(xs,ys)
write(*,f)"the closest is",minval(hypot(xs,ys))
end program demo_hypot
Results:
point <1.00000000,0.500000000> is 1.11803401
units away from the origin
the points
+1.00000000 +0.500000000
+1.00000000 +0.250000000
+10.0000000 -10.0000000
+15.0000000 +0.250000000
-1.00000000 -0.250000000
have distances from the origin of
+1.11803401 +1.03077638
+14.1421356 +15.0020828
+1.03077638
the closest is
+1.03077638
Standard#
Fortran 2008 and later
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
bessel_j0#
Name#
bessel_j0(3) - [MATHEMATICS] Bessel function of the first kind of order 0
Syntax#
result = bessel_j0(x)
Description#
bessel_j0(x) computes the Bessel function of the first kind of order 0 of x.
Arguments#
- x
The type shall be real.
Returns#
The return value is of type real and lies in the range -0.4027 <= bessel(0,x) <= 1. It has the same kind as x.
Examples#
Sample program:
program demo_besj0
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 0.0_real64
x = bessel_j0(x)
write(*,*)x
end program demo_besj0
Results:
1.0000000000000000
Standard#
Fortran 2008 and later
See Also#
bessel_j1(3), bessel_jn(3), bessel_y0(3), bessel_y1(3), bessel_yn(3)
####### fortran-lang intrinsic descriptions
bessel_j1#
Name#
bessel_j1(3) - [MATHEMATICS] Bessel function of the first kind of order 1
Syntax#
result = bessel_j1(x)
Description#
bessel_j1(x) computes the Bessel function of the first kind of order 1 of x.
Arguments#
- x
The type shall be real.
Returns#
The return value is of type real and lies in the range -0.5818 <= bessel(0,x) <= 0.5818 . It has the same kind as x.
Examples#
Sample program:
program demo_besj1
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 1.0_real64
x = bessel_j1(x)
write(*,*)x
end program demo_besj1
Results:
0.44005058574493350
Standard#
Fortran 2008 and later
See Also#
bessel_j0(3), bessel_jn(3), bessel_y0(3), bessel_y1(3), bessel_yn(3)
####### fortran-lang intrinsic descriptions
bessel_jn#
Name#
bessel_jn(3) - [MATHEMATICS] Bessel function of the first kind
Syntax#
result = bessel_jn(n, x)
result = bessel_jn(n1, n2, x)
Description#
bessel_jn(n, x) computes the Bessel function of the first kind of order n of x. If n and x are arrays, their ranks and shapes shall conform.
bessel_jn(n1, n2, x) returns an array with the Bessel function|Bessel functions of the first kind of the orders n1 to n2.
Arguments#
- n
Shall be a scalar or an array of type integer.
- n1
Shall be a non-negative scalar of type integer.
- n2
Shall be a non-negative scalar of type integer.
- x
Shall be a scalar or an array of type real. For bessel_jn(n1, n2, x) it shall be scalar.
Returns#
The return value is a scalar of type real. It has the same kind as x.
Examples#
Sample program:
program demo_besjn
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 1.0_real64
x = bessel_jn(5,x)
write(*,*)x
end program demo_besjn
Results:
2.4975773021123450E-004
Standard#
Fortran 2008 and later
See Also#
bessel_j0(3), bessel_j1(3), bessel_y0(3), bessel_y1(3), bessel_yn(3)
####### fortran-lang intrinsic descriptions
bessel_y0#
Name#
bessel_y0(3) - [MATHEMATICS] Bessel function of the second kind of order 0
Syntax#
result = bessel_y0(x)
Description#
bessel_y0(x) computes the Bessel function of the second kind of order 0 of x.
Arguments#
- x
The type shall be real.
Returns#
The return value is of type real. It has the same kind as x.
Examples#
Sample program:
program demo_besy0
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 0.0_real64
x = bessel_y0(x)
write(*,*)x
end program demo_besy0
Results:
-Infinity
Standard#
Fortran 2008 and later
See Also#
bessel_j0(3), bessel_j1(3), bessel_jn(3), bessel_y1(3), bessel_yn(3)
####### fortran-lang intrinsic descriptions
bessel_y1#
Name#
bessel_y1(3) - [MATHEMATICS] Bessel function of the second kind of order 1
Syntax#
result = bessel_y1(x)
Description#
bessel_y1(x) computes the Bessel function of the second kind of order 1 of x.
Arguments#
- x
The type shall be real.
Returns#
The return value is real. It has the same kind as x.
Examples#
Sample program:
program demo_besy1
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 1.0_real64
write(*,*)x, bessel_y1(x)
end program demo_besy1
Standard#
Fortran 2008 and later
See Also#
bessel_j0(3), bessel_j1(3), bessel_jn(3), bessel_y0(3), bessel_yn(3)
####### fortran-lang intrinsic descriptions
bessel_yn#
Name#
bessel_yn(3) - [MATHEMATICS] Bessel function of the second kind
Syntax#
result = bessel_yn(n, x)
result = bessel_yn(n1, n2, x)
Description#
bessel_yn(n, x) computes the Bessel function of the second kind of order n of x. If n and x are arrays, their ranks and shapes shall conform.
bessel_yn(n1, n2, x) returns an array with the Bessel function|Bessel functions of the first kind of the orders n1 to n2.
Arguments#
- n
Shall be a scalar or an array of type integer.
- n1
Shall be a non-negative scalar of type integer.
- n2
Shall be a non-negative scalar of type integer.
- x
Shall be a scalar or an array of type real; for bessel_yn(n1, n2, x) it shall be scalar.
Returns#
The return value is real. It has the same kind as x.
Examples#
Sample program:
program demo_besyn
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 1.0_real64
write(*,*) x,bessel_yn(5,x)
end program demo_besyn
Results:
1.0000000000000000 -260.40586662581222
Standard#
Fortran 2008 and later
See Also#
bessel_j0(3), bessel_j1(3), bessel_jn(3), bessel_y0(3), bessel_y1(3)
####### fortran-lang intrinsic descriptions
erf#
Name#
erf(3) - [MATHEMATICS] Error function
Syntax#
result = erf(x)
Description#
erf(x) computes the error function of x, defined as $$ \text{erf}(x) = \frac{2}{\sqrt{\pi}} \int_0^x e^{-t^2} dt. $$
Arguments#
- x
The type shall be real.
Returns#
The return value is of type real, of the same kind as x and lies in the range -1 <= erf(x) <= 1 .
Examples#
Sample program:
program demo_erf
use, intrinsic :: iso_fortran_env, only : real_kinds, &
& real32, real64, real128
implicit none
real(kind=real64) :: x = 0.17_real64
write(*,*)x, erf(x)
end program demo_erf
Results:
0.17000000000000001 0.18999246120180879
Standard#
Fortran 2008 and later
See also#
####### fortran-lang intrinsic descriptions
erfc#
Name#
erfc(3) - [MATHEMATICS] Complementary error function
Syntax#
result = erfc(x)
elemental function erfc(x)
real(kind=KIND) :: erfc
real(kind=KIND),intent(in) :: x
Description#
erfc(x) computes the complementary error function of x. Simpy put this is equivalent to 1 - erf(x), but erfc is provided because of the extreme loss of relative accuracy if erf(x) is called for large x and the result is subtracted from 1.
erfc(x) is defined as
$$ \text{erfc}(x) = 1 - \text{erf}(x) = 1 - \frac{2}{\sqrt{\pi}} \int_x^{\infty} e^{-t^2} dt. $$
Arguments#
- x
The type shall be real.
Returns#
The return value is of type real and of the same kind as x. It lies in the range
0 <= erfc(x) <= 2.
Examples#
Sample program:
program demo_erfc
use, intrinsic :: iso_fortran_env, only : &
& real_kinds, real32, real64, real128
implicit none
real(kind=real64) :: x = 0.17_real64
write(*,*)x, erfc(x)
end program demo_erfc
Results:
0.17000000000000001 0.81000753879819121
Standard#
Fortran 2008 and later
See also#
####### fortran-lang intrinsic descriptions license: MIT) @urbanjost
erfc_scaled#
Name#
erfc_scaled(3) - [MATHEMATICS] Error function
Syntax#
result = erfc_scaled(x)
Description#
erfc_scaled(x) computes the exponentially-scaled complementary error function of x:
$$ e^{x^2} \frac{2}{\sqrt{\pi}} \int_{x}^{\infty} e^{-t^2} dt. $$
Arguments#
- x
The type shall be real.
Returns#
The return value is of type real and of the same kind as x.
Examples#
Sample program:
program demo_erfc_scaled
implicit none
real(kind(0.0d0)) :: x = 0.17d0
x = erfc_scaled(x)
print *, x
end program demo_erfc_scaled
Results:
0.83375830214998126
Standard#
Fortran 2008 and later
####### fortran-lang intrinsic descriptions
gamma#
Name#
gamma(3) - [MATHEMATICS] Gamma function, which yields factorials for positive whole numbers
Syntax#
x = gamma(x)
Description#
gamma(x) computes Gamma of x. For positive whole number values of n the Gamma function can be used to calculate factorials, as (n-1)! == gamma(real(n)). That is
n! == gamma(real(n+1))
$$ \Gamma(x) = \int_0**\infty t**{x-1}{\mathrm{e}}**{-t}\,{\mathrm{d}}t $$
Arguments#
- x
Shall be of type real and neither zero nor a negative integer.
Returns#
The return value is of type real of the same kind as x.
Examples#
Sample program:
program demo_gamma
use, intrinsic :: iso_fortran_env, only : wp=>real64
implicit none
real :: x, xa(4)
integer :: i
x = gamma(1.0)
write(*,*)'gamma(1.0)=',x
! elemental
xa=gamma([1.0,2.0,3.0,4.0])
write(*,*)xa
write(*,*)
! gamma(3) is related to the factorial function
do i=1,20
! check value is not too big for default integer type
if(factorial(i).gt.huge(0))then
write(*,*)i,factorial(i)
else
write(*,*)i,factorial(i),int(factorial(i))
endif
enddo
! more factorials
FAC: block
integer,parameter :: n(*)=[0,1,5,11,170]
integer :: j
do j=1,size(n)
write(*,'(*(g0,1x))')'factorial of', n(j),' is ', &
& product([(real(i,kind=wp),i=1,n(j))]), &
& gamma(real(n(j)+1,kind=wp))
enddo
endblock FAC
contains
function factorial(i) result(f)
integer,parameter :: dp=kind(0d0)
integer,intent(in) :: i
real :: f
if(i.le.0)then
write(*,'(*(g0))')'<ERROR> gamma(3) function value ',i,' <= 0'
stop '<STOP> bad value in gamma function'
endif
f=gamma(real(i+1))
end function factorial
end program demo_gamma
Results:
gamma(1.0)= 1.000000
1.000000 1.000000 2.000000 6.000000
1 1.000000 1
2 2.000000 2
3 6.000000 6
4 24.00000 24
5 120.0000 120
6 720.0000 720
7 5040.000 5040
8 40320.00 40320
9 362880.0 362880
10 3628800. 3628800
11 3.9916800E+07 39916800
12 4.7900160E+08 479001600
13 6.2270208E+09
14 8.7178289E+10
15 1.3076744E+12
16 2.0922791E+13
17 3.5568741E+14
18 6.4023735E+15
19 1.2164510E+17
20 2.4329020E+18
factorial of 0 is 1.000000000000000 1.000000000000000
factorial of 1 is 1.000000000000000 1.000000000000000
factorial of 5 is 120.0000000000000 120.0000000000000
factorial of 11 is 39916800.00000000 39916800.00000000
factorial of 170 is .7257415615307994E+307 .7257415615307999E+307
Standard#
Fortran 2008 and later
See Also#
Logarithm of the Gamma function: log_gamma(3)
####### fortran-lang intrinsic descriptions
log_gamma#
Name#
log_gamma(3) - [MATHEMATICS] Logarithm of the Gamma function
Syntax#
x = log_gamma(x)
Description#
log_gamma(x) computes the natural logarithm of the absolute value of the Gamma function.
Arguments#
- x
Shall be of type real and neither zero nor a negative integer.
Returns#
The return value is of type real of the same kind as x.
Examples#
Sample program:
program demo_log_gamma
implicit none
real :: x = 1.0
write(*,*)x,log_gamma(x) ! returns 0.0
end program demo_log_gamma
Results:
1.00000000 0.00000000
Standard#
Fortran 2008 and later
See Also#
Gamma function: gamma(3)
####### fortran-lang intrinsic descriptions
log_gamma#
Name#
log_gamma(3) - [MATHEMATICS] Logarithm of the Gamma function
Syntax#
x = log_gamma(x)
Description#
log_gamma(x) computes the natural logarithm of the absolute value of the Gamma function.
Arguments#
- x
Shall be of type real and neither zero nor a negative integer.
Returns#
The return value is of type real of the same kind as x.
Examples#
Sample program:
program demo_log_gamma
implicit none
real :: x = 1.0
write(*,*)x,log_gamma(x) ! returns 0.0
end program demo_log_gamma
Results:
1.00000000 0.00000000
Standard#
Fortran 2008 and later
See Also#
Gamma function: gamma(3)
####### fortran-lang intrinsic descriptions
norm2#
Name#
norm2(3) - [MATHEMATICS] Euclidean vector norm
Syntax#
result = norm2(array, dim)
real function result norm2(array, dim)
real,intent(in) :: array(..)
integer,intent(in),optional :: dim
Description#
Calculates the Euclidean vector norm (L_2 norm) of array along dimension dim.
Arguments#
- array
Shall be an array of type real.
- dim
shall be a scalar of type integer with a value in the range from 1 to rank(array).
Returns#
The result is of the same type as array.
If dim is absent, a scalar with the square root of the sum of squares of the elements of array is returned.
Otherwise, an array of rank n-1, where n equals the rank of array, and a shape similar to that of array with dimension DIM dropped is returned.
Examples#
Sample program:
program demo_norm2
implicit none
integer :: i
real :: x(3,3) = reshape([ &
1, 2, 3, &
4, 5 ,6, &
7, 8, 9 &
],shape(x),order=[2,1])
write(*,*) 'x='
write(*,'(4x,3f4.0)')transpose(x)
write(*,*) 'norm2(x)=',norm2(x)
write(*,*) 'x**2='
write(*,'(4x,3f4.0)')transpose(x**2)
write(*,*)'sqrt(sum(x**2))=',sqrt(sum(x**2))
end program demo_norm2
Results:
x=
1. 2. 3.
4. 5. 6.
7. 8. 9.
norm2(x)= 16.88194
x**2=
1. 4. 9.
16. 25. 36.
49. 64. 81.
sqrt(sum(x**2))= 16.88194
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions