Types and kinds#

These intrinsics allow for explicitly casting one type of variable to another or can be used to conditionally execute code blocks based on variable types when working with polymorphic variables.

Fortran Data Types#

Fortran provides five basic intrinsic data types:

These “types” can be of many “kinds”. Often different numeric kinds take up different storage sizes and therefore can represent different ranges; but a different kind can have other meanings. A character variable might represent ASCII characters or UTF-8 or Unicode characters, for example.

You can derive your own data types from these fundamental types as well.

Implicit Typing#

Fortran allows a feature called implicit typing, i.e., you do not have to declare some variables before use. By default if a variable is not declared, then the first letter of its name will determine its type:

  1. Variable names starting with i-n (the first two letters of “integer”) specify integer variables.
  2. All other variable names default to real.

However, in most circles it is considered good programming practice to declare all the variables. For that to be enforced, you start your variable declaration section with a statement that turns off implicit typing: the statement

implicit none 

For more information refer to the implicit statement.

aimag#

Name#

aimag(3) - [TYPE:NUMERIC] Imaginary part of complex number

Synopsis#

result = aimag(z) 
elemental complex(kind=KIND) function aimag(z) complex(kind=KIND),intent(in) :: z 

Characteristics#

Description#

aimag(3) yields the imaginary part of the complex argument z.

This is similar to the modern complex-part-designator %IM which also designates the imaginary part of a value, accept a designator can appear on the left-hand side of an assignment as well, as in val%im=10.0.

Options#

Result#

The return value is a real value with the magnitude and sign of the imaginary component of the argument z.

That is, If z has the value (x,y), the result has the value y.

Examples#

program demo_aimag use, intrinsic :: iso_fortran_env, only : real_kinds, & & real32, real64, real128 implicit none character(len=*),parameter :: g='(*(1x,g0))' complex :: z4 complex(kind=real64) :: z8 ! basics z4 = cmplx(1.e0, 2.e0) print *, 'value=',z4 print g, 'imaginary part=',aimag(z4),'or', z4%im ! other kinds other than the default may be supported z8 = cmplx(3.e0_real64, 4.e0_real64,kind=real64) print *, 'value=',z8 print g, 'imaginary part=',aimag(z8),'or', z8%im ! an elemental function can be passed an array print * print *, [z4,z4/2.0,z4+z4,z4**3] print * print *, aimag([z4,z4/2.0,z4+z4,z4**3]) end program demo_aimag 
value= (1.00000000,2.00000000) imaginary part= 2.00000000 or 2.00000000 value= (3.0000000000000000,4.0000000000000000) imaginary part= 4.0000000000000000 or 4.0000000000000000 (1.00000000,2.00000000) (0.500000000,1.00000000) (2.00000000,4.00000000) (-11.0000000,-2.00000000) 2.00000000 1.00000000 4.00000000 -2.00000000

Standard#

See Also#

Fortran has strong support for complex values, including many intrinsics that take or produce complex values in addition to algebraic and logical expressions:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

cmplx#

Name#

cmplx(3) - [TYPE:NUMERIC] Conversion to a complex type

Synopsis#

result = cmplx(x [,kind]) | cmplx(x [,y] [,kind])
elemental complex(kind=KIND) function cmplx( x, y, kind ) type(TYPE(kind=**)),intent(in) :: x type(TYPE(kind=**)),intent(in),optional :: y integer(kind=**),intent(in),optional :: KIND 

Characteristics#

The type of the arguments does not affect the kind of the result except for a complex x value.

NOTE: a kind designated as ** may be any supported kind for the type

Description#

The cmplx(3) function converts numeric values to a complex value.

Even though constants can be used to define a complex variable using syntax like

z = (1.23456789, 9.87654321) 

this will not work for variables. So you cannot enter

z = (a, b) ! NO ! (unless a and b are constants, not variables) 

so to construct a complex value using non-complex values you must use the cmplx(3) function:

z = cmplx(a, b) 

or assign values separately to the imaginary and real components using the %IM and %RE designators:

z%re = a z%im = b 

If x is complex y is not allowed and cmplx essentially returns the input value except for an optional change of kind, which can be useful when passing a value to a procedure that requires the arguments to have a different kind (and does not return an altered value):

call something(cmplx(z,kind=real64)) 

would pass a copy of a value with kind=real64 even if z had a different kind

but otherwise is equivalent to a simple assign. So if z1 and z2 were complex:

z2 = z1 ! equivalent statements z2 = cmplx(z1) 

If x is not complex x is only used to define the real component of the result but y is still optional – the imaginary part of the result will just be assigned a value of zero.

If y is present it is converted to the imaginary component.

cmplx(3) and double precision#

Primarily in order to maintain upward compatibility you need to be careful when working with complex values of higher precision that the default.

It was necessary for Fortran to continue to specify that cmplx(3) always return a result of the default kind if the kind option is absent, since that is the behavior mandated by FORTRAN 77.

It might have been preferable to use the highest precision of the arguments for determining the return kind, but that is not the case. So with arguments with greater precision than default values you are required to use the kind argument or the greater precision values will be reduced to default precision.

This means cmplx(d1,d2), where d1 and d2 are doubleprecision, is treated as:

cmplx(sngl(d1), sngl(d2)) 

which looses precision.

So Fortran 90 extends the cmplx(3) intrinsic by adding an extra argument used to specify the desired kind of the complex result.

integer,parameter :: dp=kind(0.0d0) complex(kind=dp) :: z8 ! wrong ways to specify constant values ! note this was stored with default real precision ! z8 = cmplx(1.2345678901234567d0, 1.2345678901234567d0) print *, 'NO, Z8=',z8,real(z8),aimag(z8) z8 = cmplx(1.2345678901234567e0_dp, 1.2345678901234567e0_dp) ! again, note output components are just real print *, 'NO, Z8=',z8,real(z8),aimag(z8) ! ! YES ! ! kind= makes it work z8 = cmplx(1.2345678901234567d0, 1.2345678901234567d0,kind=dp) print *, 'YES, Z8=',z8,real(z8),aimag(z8) 

A more recent alternative to using cmplx(3) is “F2018 component syntax” where real and imaginary parts of a complex entity can be accessed independently:

value%RE ! %RE specifies the real part or value%IM ! %IM specifies the imaginary part 

Where the designator value is of course of complex type.

The type of a complex-part-designator is real, and its kind and shape are those of the designator. That is, you retain the precision of the complex value by default, unlike with cmplx.

The following are examples of complex part designators:

impedance%re !-- Same value as real(impedance) fft%im !-- Same value as AIMAG(fft) x%im = 0.0 !-- Sets the imaginary part of x to zero x(1:2)%re=[10,20] !-- even if x is an array 

NOTE for I/O#

Note that if format statements are specified a complex value is treated as two real values.

For list-directed I/O (ie. using an asterisk for a format) and NAMELIST output the values are expected to be delimited by “(” and “)” and of the form “(realpart,imaginary_part)”. For NAMELIST input parenthesized values or lists of multiple _real values are acceptable.

Options#

result = CMPLX (REAL (X), AIMAG (X), KIND). 

That is, a complex x value is copied to the result value with a possible change of kind.

Result#

The return value is of complex type, with magnitudes determined by the values x and y.

The common case when x is not complex is that the real component of the result is assigned the value of x and the imaginary part is zero or the value of y if y is present.

When x is complex y is not allowed and the result is the same value as x with a possible change of kind. That is, the real part is real(x, kind) and the imaginary part is real(y, kind).

Examples#

program demo_aimag implicit none integer,parameter :: dp=kind(0.0d0) real(kind=dp) :: precise complex(kind=dp) :: z8 complex :: z4, zthree(3) precise=1.2345678901234567d0 ! basic z4 = cmplx(-3) print *, 'Z4=',z4 z4 = cmplx(1.23456789, 1.23456789) print *, 'Z4=',z4 ! with a format treat a complex as two real values print '(1x,g0,1x,g0,1x,g0)','Z4=',z4 ! working with higher precision values ! using kind=dp makes it keep DOUBLEPRECISION precision ! otherwise the result would be of default kind z8 = cmplx(precise, -precise ) print *, 'lost precision Z8=',z8 z8 = cmplx(precise, -precise ,kind=dp) print *, 'kept precision Z8=',z8 ! assignment of constant values does not require cmplx(3)00 ! The following is intuitive and works without calling cmplx(3) ! but does not work for variables just constants z8 = (1.1111111111111111d0, 2.2222222222222222d0 ) print *, 'Z8 defined with constants=',z8 ! what happens when you assign a complex to a real? precise=z8 print *, 'LHS=',precise,'RHS=',z8 ! elemental zthree=cmplx([10,20,30],-1) print *, 'zthree=',zthree ! descriptors are an alternative zthree(1:2)%re=[100,200] print *, 'zthree=',zthree end program demo_aimag 
Z4= (-3.000000,0.0000000E+00) Z4= (1.234568,1.234568) Z4= 1.234568 1.234568 lost precision Z8= (1.23456788063049,-1.23456788063049) kept precision Z8= (1.23456789012346,-1.23456789012346) Z8 defined with constants= (1.11111111111111,2.22222222222222) LHS= 1.11111111111111 RHS= (1.11111111111111,2.22222222222222) zthree= (10.00000,-1.000000) (20.00000,-1.000000) (30.00000,-1.000000) zthree= (100.0000,-1.000000) (200.0000,-1.000000) (30.00000,-1.000000)

Standard#

FORTRAN 77, KIND added in Fortran 90.

See Also#

Fortran has strong support for complex values, including many intrinsics that take or produce complex values in addition to algebraic and logical expressions:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

int#

Name#

int(3) - [TYPE:NUMERIC] Truncate towards zero and convert to integer

Synopsis#

result = int(a [,kind]) 
elemental integer(kind=KIND) function int(a, KIND ) TYPE(kind=**),intent(in) :: a integer,optional :: KIND 

Characteristics#

Description#

int(3) truncates towards zero and return an integer.

Options#

Result#

returns an integer variable applying the following rules:

Case:

  1. If a is of type integer, int(a) = a
  2. If a is of type real and |a| < 1, int(a)equals 0. If |a| >= 1, then int(a) equals the integer whose magnitude does not exceed a and whose sign is the same as the sign of a.
  3. If a is of type complex, rule 2 is applied to the real part of a.
  4. If a is a boz-literal constant, it is treated as an integer with the kind specified. The interpretation of a bit sequence whose most significant bit is 1 is processor dependent.

The result is undefined if it cannot be represented in the specified integer type.

Examples#

program demo_int use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64 implicit none integer :: i = 42 complex :: z = (-3.7, 1.0) real :: x=-10.5, y=10.5 print *, int(x), int(y) print *, int(i) print *, int(z), int(z,8) ! elemental print *, int([-10.9,-10.5,-10.3,10.3,10.5,10.9]) ! note int(3) truncates towards zero ! CAUTION: ! a number bigger than a default integer can represent ! produces an incorrect result and is not required to ! be detected by the program. x=real(huge(0))+1000.0 print *, int(x),x ! using a larger kind print *, int(x,kind=int64),x print *, int(& & B"111111111111111111111111111111111111111111111111111111111111111",& & kind=int64) print *, int(O"777777777777777777777",kind=int64) print *, int(Z"7FFFFFFFFFFFFFFF",kind=int64) ! elemental print * print *,int([ & & -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_int 
> -10 10 > 42 > -3 -3 > -10 -10 -10 10 10 10 > -2147483648 2.14748467E+09 > 2147484672 2.14748467E+09 > 9223372036854775807 > 9223372036854775807 > 9223372036854775807 > > -2 -2 -2 -2 -1 > -1 0 0 0 1 > 1 2 2 2 2

Standard#

See Also#

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

nint#

Name#

nint(3) - [TYPE:NUMERIC] Nearest whole number

Synopsis#

result = nint( a [,kind] ) 
elemental integer(kind=KIND) function nint(a, kind ) real(kind=**),intent(in) :: a integer(kind=**),intent(in),optional :: KIND 

Characteristics#

Description#

nint(3) rounds its argument to the nearest whole number with its sign preserved.

The user must ensure the value is a valid value for the range of the kind returned. If the processor cannot represent the result in the kind specified, the result is undefined.

If a is greater than zero, nint(a) has the value int(a+0.5).

If a is less than or equal to zero, nint(a) has the value int(a-0.5).

Options#

Result#

The result is the integer nearest a, or if there are two integers equally near a, the result is whichever such integer has the greater magnitude.

The result is undefined if it cannot be represented in the specified integer type.

Examples#

program demo_nint implicit none integer,parameter :: dp=kind(0.0d0) real,allocatable :: in(:) integer,allocatable :: out(:) integer :: i real :: x4 real(kind=dp) :: x8 ! basic use x4 = 1.234E0 x8 = 4.721_dp print *, nint(x4), nint(-x4) print *, nint(x8), nint(-x8) ! elemental in = [ -2.7, -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, -0.4, & & 0.0, & & +0.04, +0.5, +1.0, +1.5, +2.0, +2.2, +2.5, +2.7 ] out = nint(in) do i=1,size(in) write(*,*)in(i),out(i) enddo ! dusty corners ISSUES: block use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64 integer :: icheck ! make sure input is in range for the type returned write(*,*)'Range limits for typical KINDS:' write(*,'(1x,g0,1x,g0)') & & int8,huge(0_int8), & & int16,huge(0_int16), & & int32,huge(0_int32), & & int64,huge(0_int64) ! the standard does not require this to be an error . x8=12345.67e15 ! too big of a number icheck=selected_int_kind(ceiling(log10(x8))) write(*,*)'Any KIND big enough? ICHECK=',icheck print *, 'These are all wrong answers for ',x8 print *, nint(x8,kind=int8) print *, nint(x8,kind=int16) print *, nint(x8,kind=int32) print *, nint(x8,kind=int64) endblock ISSUES end program demo_nint 
> 1 -1 > 5 -5 > -2.700000 -3 > -2.500000 -3 > -2.200000 -2 > -2.000000 -2 > -1.500000 -2 > -1.000000 -1 > -0.5000000 -1 > -0.4000000 0 > 0.0000000E+00 0 > 3.9999999E-02 0 > 0.5000000 1 > 1.000000 1 > 1.500000 2 > 2.000000 2 > 2.200000 2 > 2.500000 3 > 2.700000 3 > Range limits for typical KINDS: > 1 127 > 2 32767 > 4 2147483647 > 8 9223372036854775807 > Any KIND big enough? ICHECK= -1 > These are all wrong answers for 1.234566949990144E+019 > 0 > 0 > -2147483648 > -9223372036854775808

Standard#

FORTRAN 77 , with KIND argument - Fortran 90

See Also#

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

real#

Name#

real(3) - [TYPE:NUMERIC] Convert to real type

Synopsis#

result = real(x [,kind]) 
elemental real(kind=KIND) function real(x,KIND) TYPE(kind=**),intent(in) :: x integer(kind=**),intent(in),optional :: KIND 

Characteristics#