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:

  • Integer type

    The integer types can hold only whole number values.

  • Real type

    Stores floating point numbers, such as 2.0, 3.1415, -100.876, etc.

  • Complex type

    A complex number has two parts, the real part and the imaginary part. Two consecutive floating point storage units store the two parts.

  • Logical type

    There are only two logical values: .true. and .false.

  • Character type

    The character type stores strings. The length of the string can be specified by the len specifier. If no length is specified, it is 1.

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

Syntax#

    result = aimag(z)

     complex(kind=KIND),elemental :: aimag

     complex(kind=KIND),intent(in) :: z

Description#

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

Arguments#

  • z

    The type of the argument shall be complex.

Returns#

The return value is of type real with the kind type parameter of the argument.

Examples#

Sample program:

program demo_aimag
use, intrinsic :: iso_fortran_env, only : real_kinds, &
 & real32, real64, real128
implicit none
complex(kind=real32) z4
complex(kind=real64) z8
    z4 = cmplx(1.e0, 2.e0)
    z8 = cmplx(3.e0_real64, 4.e0_real64,kind=real64)
    print *, aimag(z4), aimag(z8)
    ! 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

Results:

  2.000000       4.00000000000000

 (1.000000,2.000000) (0.5000000,1.000000) (2.000000,4.000000)
 (-11.00000,-2.000000)

       2.000000       1.000000       4.000000      -2.000000

Standard#

FORTRAN 77 and later

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

cmplx#

Name#

cmplx(3) - [TYPE:NUMERIC] Complex conversion function

Syntax#

result = cmplx(x, y, kind)

   complex elemental function :: cmplx
   TYPE(kind=KIND),intent(in), x
   TYPE(kind=KIND),intent(in),optional, y
   integer,intent(in),optional :: kind

Description#

To convert numeric variables to complex, use the cmplx(3) function. Constants can be used to define a complex variable using the syntax

      z8 = (1.2345678901234567d0, 1.2345678901234567d0)

but this will not work for variables. You must use the cmplx(3) function.

cmplx(x [, y [, kind]]) returns a complex number where x is converted to the real component. If x is complex then y must not be present. If y is present it is converted to the imaginary component. If y is not present then the imaginary component is set to 0.0.

cmplx(3) and double precision#

The Fortran 90 language defines cmplx(3) as always returning a result that is type complex(kind=KIND(0.0)).

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

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

doubleprecision complex numbers require specifying a precision.

It was necessary for Fortran 90 to specify this behavior for doubleprecision arguments, since that is the behavior mandated by FORTRAN 77.

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

      integer,parameter :: dp=kind(0.0d0)
      complex(kind=dp) :: z8
      !
      ! NO: result is just the precision of default _real_ values
      !     because KIND parameter is not specified
      !
      ! 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 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)

F2018 COMPONENT SYNTAX The real and imaginary parts of a complex entity can be accessed independently with a component-like syntax in f2018:

A complex-part-designator is

``fortran designator % RE or designator % IM.


Where the designator is of complex type.

So designator%RE designates the real part of a complex value,
designator%IM designates the imaginary part of complex value. The type
of a complex-part-designator is _real_, and its kind and shape are those
of the designator.

The following are examples of complex part designators:

```fortran
       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

Arguments#

  • x The type may be integer, real, or complex.

  • y (Optional; only allowed if x is not complex.). May be integer or real.

  • kind (Optional) An integer initialization expression indicating the kind parameter of the result.

Returns#

The return value is of complex type, with a kind equal to kind if it is specified. If kind is not specified, the result is of the default complex kind, regardless of the kinds of x and y.

Examples#

Sample program:

program demo_aimag
implicit none
integer,parameter :: dp=kind(0.0d0)
complex          :: z4
complex(kind=dp) :: z8
   z4 = cmplx(1.23456789, 1.23456789)
   print *, 'Z4=',z4
   ! using kind=dp makes it keep DOUBLEPRECISION precision
   z8 = cmplx(1.2345678901234567d0, 1.2345678901234567d0,kind=dp)
   print *, 'Z8=',z8
   ! NOTE:
   ! The following is intuitive and works without calling cmplx(3)
   ! but does not work for variables just constants
   z8 = (1.2345678901234567d0 , 1.2345678901234567d0 )
   print *, 'Z8 defined with constants=',z8
end program demo_aimag

Typical Results:

    Z4= (1.23456788,1.23456788)
    Z8= (1.2345678901234567,1.2345678901234567)
    Z8 defined with constants= (1.2345678901234567,1.2345678901234567)

See Also#

Standard#

FORTRAN 77 and later

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

int#

Name#

int(3) - [TYPE:NUMERIC] Convert to integer type by truncating towards zero

Syntax#

result = int(a, kind)

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

Description#

Convert to integer type by truncating towards zero.

Arguments#

  • a

    Shall be of type integer, real, or complex or a BOZ-literal-constant.

  • kind

    An integer initialization expression indicating the kind parameter of the result.

    If not present the returned type is that of default integer type.

Returns#

returns an integer variable or array 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#

Sample program:

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

Results:

            -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#

FORTRAN 77 and later

See Also#

aint(3), anint(3), nint(3), selected_int_kind(3), ceiling(3), floor(3)

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

nint#

Name#

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

Syntax#

    elemental function nint(x [, kind=NN]) result(ANSWER)
     real(kind=??),intent(in) :: x
     integer(kind=NN) :: ANSWER

Description#

nint(x) 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 x is greater than zero, nint(x) has the value int(x+0.5).

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

Arguments#

  • x

    The type of the argument shall be real.

  • kind

    (Optional) A constant integer expression indicating the kind parameter of the result. Otherwise, the kind type parameter is that of default integer type.

Returns#

  • answer

    The result is the integer nearest x, or if there are two integers equally near x, 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#

Sample program:

program demo_nint
implicit none
integer,parameter :: dp=kind(0.0d0)
real              :: x4 = 1.234E0
real(kind=dp)     :: x8 = 4.721_dp

! basic use
   print *, nint(x4), nint(x8),nint(-x8)
   ! elemental
   print *,nint([ &
   &  -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  ])

! issues
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

Results:

     1    5   -5
    -3   -3   -2   -2   -2
    -1   -1    0    1    1
     2    2    2    3    3
    Range limits for typical KINDS:
    1 127
    2 32767
    4 2147483647
    8 9223372036854775807
    Any KIND big enough? ICHECK=          16
    These are all wrong answers for    1.2345669499901444E+019
       0
         0
              0
    -9223372036854775808

Standard#

FORTRAN 77 and later, with KIND argument - Fortran 90 and later

See Also#

aint(3), anint(3), int(3), selected_int_kind(3), ceiling(3), floor(3)

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

real#

Name#

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

Syntax#

result = real(x, kind)

Description#

real(x, kind) converts its argument x to a real type.

Arguments#

  • x

    Shall be integer, real, or complex.

  • kind

    (Optional) An integer initialization expression indicating the kind parameter of the result.

Returns#

These functions return a real variable or array under the following rules:

  1. real(x) is converted to a default real type if x is an integer or real variable.

  2. real(x) is converted to a real type with the kind type parameter of x if x is a complex variable.

  3. real(x, kind) is converted to a real type with kind type parameter kind if x is a complex, integer, or real variable.

Examples#

Sample program:

program demo_real
use,intrinsic :: iso_fortran_env, only : dp=>real64
implicit none
complex              :: zr = (1.0, 2.0)
doubleprecision      :: xd=huge(3.0d0)
complex(kind=dp) :: zd=cmplx(4.0e0_dp,5.0e0_dp,kind=dp)

   print *, real(zr), aimag(zr)
   print *, dble(zd), aimag(zd)

   write(*,*)xd,real(xd,kind=kind(0.0d0)),dble(xd)
end program demo_real

Results:

 1.00000000       2.00000000
 4.0000000000000000       5.0000000000000000
 1.7976931348623157E+308  1.7976931348623157E+308  1.7976931348623157E+308

Standard#

FORTRAN 77 and later

See Also#

dble(3), float(3)

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

dble#

Name#

dble(3) - [TYPE:NUMERIC] Double conversion function

Syntax#

result = dble(a)

    elemental function dble(a)
    type(real(kind=kind(0.0d0)))     :: dble
    type(TYPE(kind=KIND)),intent(in) :: a

where TYPE may be integer, real, or complex and KIND any kind supported by the TYPE.

Description#

dble(a) Converts a to double precision real type.

Arguments#

  • a

    The type shall be integer, real, or complex.

Returns#

The return value is of type doubleprecision. For complex input, the returned value has the magnitude and sign of the real component of the input value.

Examples#

Sample program:

program demo_dble
implicit none
real:: x = 2.18
integer :: i = 5
complex :: z = (2.3,1.14)
   print *, dble(x), dble(i), dble(z)
end program demo_dble

Results:

  2.1800000667572021  5.0000000000000000   2.2999999523162842     

Standard#

FORTRAN 77 and later

See Also#

float(3), real(3)

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

transfer#

Name#

transfer(3) - [TYPE:MOLD] Transfer bit patterns

Syntax#

result = transfer(source, mold, size)

Description#

Interprets the bitwise representation of source in memory as if it is the representation of a variable or array of the same type and type parameters as mold.

This is approximately equivalent to the C concept of *casting* one type to another.

Arguments#

  • source

    Shall be a scalar or an array of any type.

  • mold

    Shall be a scalar or an array of any type.

  • size

    (Optional) shall be a scalar of type integer.

Returns#

The result has the same type as mold, with the bit level representation of source. If size is present, the result is a one-dimensional array of length size. If size is absent but mold is an array (of any size or shape), the result is a one-dimensional array of the minimum length needed to contain the entirety of the bitwise representation of source. If size is absent and mold is a scalar, the result is a scalar.

If the bitwise representation of the result is longer than that of source, then the leading bits of the result correspond to those of source and any trailing bits are filled arbitrarily.

When the resulting bit representation does not correspond to a valid representation of a variable of the same type as mold, the results are undefined, and subsequent operations on the result cannot be guaranteed to produce sensible behavior. For example, it is possible to create logical variables for which var and .not. var both appear to be true.

Examples#

Sample program:

program demo_transfer
use,intrinsic :: iso_fortran_env, only : int32, real32
integer(kind=int32) :: i = 2143289344
real(kind=real32)   :: x
character(len=10)   :: string
character(len=1)    :: chars(10)
   x=transfer(i, 1.0)    ! prints "nan" on i686
   ! the bit patterns are the same
   write(*,'(b0,1x,g0)')x,x ! create a NaN
   write(*,'(b0,1x,g0)')i,i

   ! a string to an array of characters
   string='abcdefghij'
   chars=transfer(string,chars)
   write(*,'(*("[",a,"]":,1x))')string
   write(*,'(*("[",a,"]":,1x))')chars
end program demo_transfer

Results:

   1111111110000000000000000000000 NaN
   1111111110000000000000000000000 2143289344
   [abcdefghij]
   [a] [b] [c] [d] [e] [f] [g] [h] [i] [j]

Comments#

Joe Krahn: Fortran uses molding rather than casting.

Casting, as in C, is an in-place reinterpretation. A cast is a device that is built around an object to change its shape.

Fortran TRANSFER reinterprets data out-of-place. It can be considered molding rather than casting. A mold is a device that confers a shape onto an object placed into it.

The advantage of molding is that data is always valid in the context of the variable that holds it. For many cases, a decent compiler should optimize TRANSFER into a simple assignment.

There are disadvantages of this approach. It is problematic to define a union of data types because you must know the largest data object, which can vary by compiler or compile options. In many cases, an EQUIVALENCE would be far more effective, but Fortran Standards committees seem oblivious to the benefits of EQUIVALENCEs when used sparingly.

Standard#

Fortran 90 and later

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

logical#

Name#

logical(3) - [TYPE:LOGICAL] Converts one kind of logical variable to another

Syntax#

result = logical(l, kind)

 logical(kind=KIND) function logical(L,KIND)
  logical(kind=INK),intent(in) :: L
  integer,intent(in),optional :: KIND

Description#

Converts one kind of logical variable to another.

Arguments#

  • l

    The type shall be logical.

  • kind

    (Optional) An integer initialization expression indicating the kind parameter of the result.

Returns#

The return value is a logical value equal to l, with a kind corresponding to kind, or of the default logical kind if kind is not given.

Examples#

program demo_logical
! Access array containing the kind type parameter values supported by this
! compiler for entities of logical type
use iso_fortran_env, only : logical_kinds

   ! list kind values supported on this platform, which generally vary
   ! in storage size
   do i =1, size(logical_kinds) 
      write(*,*)logical_kinds(i)
   enddo

end program demo_logical

Results:

              1
              2
              4
              8
             16

Standard#

Fortran 95 and later, related ISO_FORTRAN_ENV module - fortran 2009

See Also#

int(3), real(3), cmplx(3)

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

kind#

Name#

kind(3) - [KIND INQUIRY] Kind of an entity

Syntax#

k = kind(x)

Description#

kind(x) returns the kind value of the entity x.

Arguments#

  • x

    Shall be of type logical, integer, real, complex or character.

Returns#

The return value is a scalar of type integer and of the default integer kind.

Examples#

Sample program:

program demo_kind
implicit none
integer,parameter :: kc = kind(' ')
integer,parameter :: kl = kind(.true.)

   print *, "The default character kind is ", kc
   print *, "The default logical kind is ", kl

end program demo_kind

Results:

    The default character kind is            1
    The default logical kind is            4

Standard#

Fortran 95 and later

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

selected_char_kind#

Name#

selected_char_kind(3) - [KIND] Choose character kind such as "Unicode"

Syntax#

result = selected_char_kind(name)

Description#

selected_char_kind(name) returns the kind value for the character set named NAME, if a character set with such a name is supported, or -1 otherwise. Currently, supported character sets include "ASCII" and "DEFAULT" (iwhich are equivalent), and "ISO_10646" (Universal Character Set, UCS-4) which is commonly known as "Unicode".

Arguments#

  • name

    Shall be a scalar and of the default character type.

Examples#

Sample program:

program demo_selected_char_kind
use iso_fortran_env
implicit none
integer, parameter :: ascii = selected_char_kind ("ascii")
integer, parameter :: ucs4  = selected_char_kind ('ISO_10646')

character(kind=ascii, len=26) :: alphabet
character(kind=ucs4,  len=30) :: hello_world

   alphabet = ascii_"abcdefghijklmnopqrstuvwxyz"
   hello_world = ucs4_'Hello World and Ni Hao -- ' &
                 // char (int (z'4F60'), ucs4)     &
                 // char (int (z'597D'), ucs4)

   write (*,*) alphabet

   open (output_unit, encoding='UTF-8')
   write (*,*) trim (hello_world)
end program demo_selected_char_kind

Results:

    abcdefghijklmnopqrstuvwxyz
    Hello World and Ni Hao -- 你好

Standard#

Fortran 2003 and later

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

selected_int_kind#

Name#

selected_int_kind(3) - [KIND] Choose integer kind

Syntax#

result = selected_int_kind(r)

Description#

selected_int_kind(r) return the kind value of the smallest integer type that can represent all values ranging from -10**r (exclusive) to 10**r (exclusive). If there is no integer kind that accommodates this range, selected_int_kind returns -1.

Arguments#

  • r

    Shall be a scalar and of type integer.

Examples#

Sample program:

program demo_selected_int_kind
implicit none
integer,parameter :: k5 = selected_int_kind(5)
integer,parameter :: k15 = selected_int_kind(15)
integer(kind=k5) :: i5
integer(kind=k15) :: i15

    print *, huge(i5), huge(i15)

    ! the following inequalities are always true
    print *, huge(i5) >= 10_k5**5-1
    print *, huge(i15) >= 10_k15**15-1
end program demo_selected_int_kind

Results:

     2147483647  9223372036854775807
    T
    T

Standard#

Fortran 95 and later

See Also#

aint(3), anint(3), int(3), nint(3), ceiling(3), floor(3)

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

selected_real_kind#

Name#

selected_real_kind(3) - [KIND] Choose real kind

Syntax#

result = selected_real_kind(p, r, radix)

Description#

selected_real_kind(p, r, radix) return the kind value of a real data type with decimal precision of at least p digits, exponent range of at least r, and with a radix of radix.

Arguments#

  • p

    (Optional) shall be a scalar and of type integer.

  • r

    (Optional) shall be a scalar and of type integer.

  • radix

    (Optional) shall be a scalar and of type integer.

Before Fortran 2008, at least one of the arguments r or p shall be present; since Fortran 2008, they are assumed to be zero if absent.

Returns#

selected_real_kind returns the value of the kind type parameter of a real data type with decimal precision of at least p digits, a decimal exponent range of at least R, and with the requested radix. If the radix parameter is absent, real kinds with any radix can be returned. If more than one real data type meet the criteria, the kind of the data type with the smallest decimal precision is returned. If no real data type matches the criteria, the result is

  • -1 if the processor does not support a real data type with a precision greater than or equal to p, but the r and radix requirements can be fulfilled

    • -2 if the processor does not support a real type with an exponent range greater than or equal to r, but p and radix are fulfillable

    • -3 if radix but not p and r requirements are fulfillable

    • -4 if radix and either p or r requirements are fulfillable

    • -5 if there is no real type with the given radix

Examples#

Sample program:

program demo_selected_real_kind
implicit none
integer,parameter :: p6 = selected_real_kind(6)
integer,parameter :: p10r100 = selected_real_kind(10,100)
integer,parameter :: r400 = selected_real_kind(r=400)
real(kind=p6) :: x
real(kind=p10r100) :: y
real(kind=r400) :: z

   print *, precision(x), range(x)
   print *, precision(y), range(y)
   print *, precision(z), range(z)
end program demo_selected_real_kind

Results:

              6          37
             15         307
             18        4931

Standard#

Fortran 95 and later; with RADIX - Fortran 2008 and later

See Also#

precision(3), range(3), radix(3)

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