Intrinsic Procedures
Description of all intrinsic procedures, from FORTRAN 77 to Fortran 2023:
- Logical Functions
- Mathematical Functions
- Arithmetic Functions
- Bit Procedures
- Array Procedures
- Vector & Matrix Functions
- Character Functions
- Type & Kind Functions
- Type Conversion Functions
- Random Number Procedures
- System Procedures
- ISO_C_BINDING Procedures
- Coarray Procedures
The procedure tables have the following form:
Syntax | ||
---|---|---|
Description | Procedure Class | Language Standard |
Logical Functions
result = iand(i, j) |
||
---|---|---|
Returns the bitwise logical AND of |
elemental function | Fortran 90, Fortran 2008 |
result = ior(i, j) |
||
Returns the bitwise logical inclusive-OR of |
elemental function | Fortran 90, Fortran 2008 |
result = ieor(i, j) |
||
Returns the bitwise logical exclusive-OR of |
elemental function | Fortran 90, Fortran 2008 |
result = not(i) |
||
Returns the bitwise logical inverse of |
elemental function | Fortran 90 |
Mathematical Functions
Power & Logarithmic Functions
result = exp(x) |
||
---|---|---|
Returns the base e exponential of |
elemental function | FORTRAN 77 |
result = gamma(x) |
||
Returns gamma of |
elemental function | Fortran 2008 |
result = log(x) |
||
The natural logarithm of |
elemental function | FORTRAN 77 |
result = log10(x) |
||
The logarithm of |
elemental function | FORTRAN 77 |
result = log_gamma(x) |
||
Returns the natural logarithm of the absolute value of the gamma
function [real], with |
elemental function | Fortran 2008 |
result = sqrt(x) |
||
Returns the square root of |
elemental function | FORTRAN 77 |
Trigonometric Functions
result = acos(x) |
||
---|---|---|
The arc cosine of |
elemental function | FORTRAN 77, Fortran 2008 |
result = asin(x) |
||
The arc sin of |
elemental function | FORTRAN 77, Fortran 2008 |
result = atan(x) result = atan(x, y) |
||
The arc tangent of |
elemental function | FORTRAN 77, Fortran 2008 |
result = atan2(y, x) |
||
The arc tangent of |
elemental function | FORTRAN 77 |
result = cos(x) |
||
The cosine of |
elemental function | FORTRAN 77 |
result = hypot(x, y) |
||
Returns the Euclidean distance between |
elemental function | Fortran 2008 |
result = norm2(array[, dim]) |
||
Returns the Euclidean vector norm (L2 norm) of
|
transformational function | Fortran 2008 |
result = sin(x) |
||
The sine of |
elemental function | FORTRAN 77 |
result = tan(x) |
||
The tangent of |
elemental function | FORTRAN 77, Fortran 2008 |
Trigonometric Functions (Degrees)
result = acosd(x) |
||
---|---|---|
The arc cosine of |
elemental function | Fortran 2023 |
result = asind(x) |
||
The arc sine of |
elemental function | Fortran 2023 |
result = atand(x) result = atand(y, x)
|
||
The arc tangent of |
elemental function | Fortran 2023 |
result = atan2d(y, x) |
||
The arc tangent of |
elemental function | Fortran 2023 |
result = cosd(x) |
||
The cosine of |
elemental function | Fortran 2023 |
result = sind(x) |
||
The sine of |
elemental function | Fortran 2023 |
result = tand(x) |
||
The tangent of |
elemental function | Fortran 2023 |
Trigonometric Functions (Half-Revolutions)
result = acospi(x) |
||
---|---|---|
The arc cosine of |
elemental function | Fortran 2023 |
result = asinpi(x) |
||
The arc sine of |
elemental function | Fortran 2023 |
result = atanpi(x) |
||
The arc tangent of |
elemental function | Fortran 2023 |
result = atanpi(y, x) result = atan2pi(y, x)
|
||
The arc tangent of |
elemental function | Fortran 2023 |
result = cospi(x) |
||
The cosine of |
elemental function | Fortran 2023 |
result = sinpi(x) |
||
The sine of |
elemental function | Fortran 2023 |
result = tanpi(x) |
||
The tangent of |
elemental function | Fortran 2023 |
Hyperbolic Functions
result = acosh(x) |
||
---|---|---|
The inverse hyperbolic cosine of |
elemental function | Fortran 2008 |
result = asinh(x) |
||
The inverse hyperbolic sine of |
elemental function | Fortran 2008 |
result = atanh(x) |
||
The inverse hyperbolic tangent of |
elemental function | Fortran 2008 |
result = cosh(x) |
||
The hyperbolic cosine of |
elemental function | FORTRAN 77, Fortran 2008 |
result = sinh(x) |
||
The hyperbolic sine of |
elemental function | Fortran 90, Fortran 2008 |
result = tanh(x) |
||
The hyperbolic tangent of |
elemental function | FORTRAN 77, Fortran 2008 |
Error Functions
result = erf(x) |
||
---|---|---|
Computes the error function of |
elemental function | Fortran 2008 |
result = erfc(x) |
||
Computes the complementary error function of |
elemental function | Fortran 2008 |
result = erfc_scaled(x) |
||
Computes the exponentially-scaled complementary error function of
|
elemental function | Fortran 2008 |
Bessel Functions
result = bessel_j0(x) |
||
---|---|---|
Computes the Bessel function of the first kind of order 0 of
|
elemental function | Fortran 2008 |
result = bessel_j1(x) |
||
Computes the Bessel function of the first kind of order 1 of
|
elemental function | Fortran 2008 |
result = bessel_jn(n, x) result = bessel_jn(n1, n2, x) |
||
The elemental function The transformational function |
elemental function, transformational function | Fortran 2008 |
result = bessel_y0(x) |
||
Computes the Bessel function of the second kind of order 0 of
|
elemental function | Fortran 2008 |
result = bessel_y1(x) |
||
Computes the Bessel function of the second kind of order 1 of
|
elemental function | Fortran 2008 |
result = bessel_yn(n, x) result = bessel_yn(n1, n2, x) |
||
The elemental function The transformational function |
elemental function, transformational function | Fortran 2008 |
Arithmetic Functions
result = abs(a) |
||
---|---|---|
Returns the absolute value of |
elemental function | FORTRAN 77 |
result = aimag(z) |
||
Yields the imaginary part [real] of the argument z [complex]. The result has the kind parameter of the argument. |
elemental function | FORTRAN 77 |
result = aint(a[, kind]) |
||
Truncates the argument |
elemental function | FORTRAN 77 |
result = anint(a[, kind]) |
||
Rounds the argument |
elemental function | FORTRAN 77 |
result = ceiling(a[, kind]) |
||
Returns the least integer greater than or equal to |
elemental function | Fortran 95 |
result = conjg(z) |
||
Returns the conjugate of |
elemental function | FORTRAN 77 |
result = digits(x) |
||
Returns the number of significant binary digits of the internal model
representation of |
inquiry function | Fortran 90 |
result = dim(x, y) |
||
Returns the difference |
elemental function | FORTRAN 77 |
result = dprod(x, y) |
||
Returns the double product of |
elemental function | FORTRAN 77 |
result = epsilon(x) |
||
Returns the smallest number e of the same kind as |
inquiry function | Fortran 90 |
result = exponent(x) |
||
Returns the value of the exponent part of |
elemental function | Fortran 90 |
result = floor(a[, kind]) |
||
Returns the greatest integer less than or equal to |
elemental function | Fortran 95 |
result = fraction(x) |
||
Returns the fractional part of the model representation of |
elemental function | Fortran 90 |
result = huge(x) |
||
Returns the largest number that is not an infinity in the model of
the type of |
inquiry function | Fortran 90 |
result = maxexponent(x) |
||
Returns the maximum exponent [integer] in the model of
the type of |
inquiry function | Fortran 90 |
result = minexponent(x) |
||
Returns the minimum exponent [integer] in the model of
the type of |
elemental function | Fortran 90 |
result = nearest(x, s) |
||
Returns the processor-representable number nearest to |
elemental function | Fortran 90 |
result = modulo(a, p) |
||
Computes |
elemental function | Fortran 95 |
result = nint(a, kind) |
||
Returns argument |
elemental function | FORTRAN 77, Fortran 90 |
result = precision(x) |
||
Returns the decimal precision in the model of the type of
|
inquiry function | Fortran 90 |
result = radix(x) |
||
Returns the base of the model representing the entity
|
inquiry function | Fortran 90 |
result = range(x) |
||
Returns the decimal exponent range in the model of the type of
|
inquiry function | Fortran 90 |
result = rrspacing(x) |
||
Returns the reciprocal of the relative spacing of model numbers near
|
elemental function | Fortran 90 |
result = scale(x, i) |
||
Returns |
elemental function | Fortran 90 |
result = set_exponent(x, i) |
||
Returns the real number whose fractional part is that of
|
elemental function | Fortran 90 |
result = sign(a, b) |
||
Returns the value of |
elemental function | FORTRAN 77, Fortran 2018 |
result = spacing(x) |
||
Returns the distance between |
elemental function | Fortran 90 |
result = tiny(x) |
||
Returns the smallest number that is not 0 in the model of
the type of |
inquiry function | Fortran 90 |
Bit Procedures
result = bge(i, j) |
||
---|---|---|
Returns |
elemental function | Fortran 2008 |
result = bgt(i, j) |
||
Returns |
elemental function | Fortran 2008 |
result = ble(i, j) |
||
Returns |
elemental function | Fortran 2008 |
result = blt(i, j) |
||
Returns |
elemental function | Fortran 2008 |
result = btest(i, pos) |
||
Returns |
elemental function | Fortran 90 |
result = bit_size(i) |
||
Returns the number of bits (integer precision plus sign bit)
represented by the type of |
inquiry function | Fortran 90 |
result = dshiftl(i, j, shift) |
||
Combines bits of |
elemental function | Fortran 2008 |
result = dshiftr(i, j, shift) |
||
Combines bits of |
elemental function | Fortran 2008 |
result = ibclr(i, pos) |
||
Returns the value of |
elemental function | Fortran 90 |
result = ibits(i, pos, len) |
||
Extracts a field of length |
elemental function | Fortran 90 |
result = ibset(i, pos) |
||
Returns the value of |
elemental function | Fortran 90 |
result = ishft(i, shift) |
||
Returns |
elemental function | Fortran 90 |
result = ishftc(i, shift[, size]) |
||
Returns a value corresponding to A value of The absolute value of |
elemental function | Fortran 90 |
result = leadz(i) |
||
Returns the number of leading zero bits of |
elemental function | Fortran 2008 |
result = maskl(i[, kind]) |
||
Returns an integer that has its leftmost |
elemental function | Fortran 2008 |
result = maskr(i[, kind]) |
||
Returns an integer that has its rightmost |
elemental function | Fortran 2008 |
result = merge_bits(i, j, mask) |
||
Merges the bit of |
elemental function | Fortran 2008 |
call mvbits(from, frompos, len, to, topos) |
||
Moves The values of |
elemental subroutine | Fortran 90 |
result = popcnt(i) |
||
Returns the number of bits set (i. e., |
elemental function | Fortran 2008 |
result = poppar(i) |
||
Returns the parity of the number of bits set in |
elemental function | Fortran 2008 |
result = shifta(i, shift) |
||
Returns |
elemental function | Fortran 2008 |
result = shiftl(i, shift) |
||
Returns |
elemental function | Fortran 2008 |
result = shiftr(i, shift) |
||
Returns |
elemental function | Fortran 2008 |
result = trailz(i) |
||
Returns the number of trailing zero bits of |
elemental function | Fortran 2008 |
Array Procedures
result = all(mask[, dim]) |
||
---|---|---|
Determines if all the values in array |
transformational function | Fortran 90 |
result = any(mask[, dim]) |
||
Determines if any of the values in array |
transformational function | Fortran 90 |
result = count(mask[, dim, kind]) |
||
Counts the number of |
transformational function | Fortran 90, Fortran 2003 |
result = cshift(array, shift[, dim]) |
||
Performs a circular shift on elements of If the rank of Elements shifted out one end of each rank one section are shifted back in the other end. |
transformational function | Fortran 90 |
result = eoshift(array, shift[, boundary, dim]) |
||
Performs an end-off shift on elements of If the rank of Elements shifted out one end of each rank one section are
dropped. If |
transformational function | Fortran 90 |
result = findloc(array, value, dim[, mask][, kind][, back]) result = findloc(array, value[, mask][, kind][, back]) |
||
Determines the location [integer] of the element in
If If If the array has zero size, or all of the elements of
|
transformational function | Fortran 2008 |
result = iall(array[, mask]) result = iall(array, dim[, mask]) |
||
Bitwise AND of array elements [integer]. Reduces
with bitwise AND the elements of |
transformational function | Fortran 2008 |
result = iany(array[, mask]) result = iany(array, dim[, mask]) |
||
Bitwise inclusive-OR of array elements [integer].
Reduces with bitwise OR the elements of |
transformational function | Fortran 2008 |
result = is_contiguous(array) |
||
Returns |
inquiry function | Fortran 2008 |
result = lbound(array[, dim[, kind]]) |
||
Returns the lower bounds of |
inquiry function | Fortran 90, Fortran 2003 |
result = max(a1, a2 [, a3 [, …]]) |
||
Returns the argument [integer, real] with the largest value. The return value has the same type and kind as the first argument. |
elemental function | FORTRAN 77 |
result = maxloc(array, dim[, mask[, kind[, back]]]) result = maxloc(array[, mask][, kind][, back]) |
||
Determines the location of the element [integer] in
If If the array has zero size, or all of the elements of
|
transformational function | Fortran 95, Fortran 2003, Fortran 2008 |
result = maxval(array, dim[, mask]) result = maxval(array[, mask]) |
||
Returns the maximum value of the elements in If If |
transformational function | Fortran 90 |
result = merge(tsource, fsource[, mask]) |
||
Select values from two arrays according to a logical mask. The
result is equal to |
elemental function | Fortran 95 |
result = min(a1, a2 [, a3 [, …]]) |
||
Returns the argument [integer, real] with the smallest value. The return value has the same type and kind as the first argument. |
elemental function | FORTRAN 77 |
result = minloc(array, dim[, mask][, kind][, back]) result = minloc(array[, mask][, kind][, back]) |
||
Determines the location of the element [integer] in
If If the array has zero size, or all of the elements of
|
transformational function | Fortran 90, Fortran 2003, Fortran 2008 |
result = minval(array, dim[, mask]) result = minval(array[, mask]) |
||
Returns the minimum value of the elements in If If |
transformational function | Fortran 90 |
call move_alloc(from, to[, stat][, errmsg]) |
||
Moves the allocation from array |
pure subroutine | Fortran 2003, Fortran 2018 |
result = pack(array, mask[, vector]) |
||
Stores the elements of The beginning of the resulting array is made up of elements
whose |
transformational function | Fortran 90 |
result = product(array[, mask]) result = product(array, dim[, mask]) |
||
Multiplies the elements of |
transformational function | Fortran 90 |
result = rank(a) |
||
Returns the rank of a scalar or array data object |
inquiry function | Fortran 2008 |
result = reduce(array, operation[, mask][, identity][, ordered]) result = reduce(array, operation, dim[, mask][, identity][, ordered]) |
||
Performs a general array reduction of The initial order of the sequence is array element order. While
there is more than one element in the sequence, each iteration
calculates If
|
transformational function | Fortran 2018 |
result = reshape(source, shape[, pad, order]) |
||
Reshapes array |
transformational function | Fortran 90 |
result = shape(source[, kind]) |
||
Determines the shape of array |
inquiry function | Fortran 90, Fortran 2003 |
result = size(array[, dim[, kind]]) |
||
Determine the extent of |
inquiry function | Fortran 90, Fortran 2003 |
result = spread(source, dim, ncopies) |
||
Replicates a |
transformational function | Fortran 90 |
result = sum(array[, mask]) result = sum(array, dim[, mask]) |
||
Adds the elements of |
transformational function | Fortran 90 |
result = ubound(array[, dim[, kind]]) |
||
Returns the upper bounds of |
inquiry function | Fortran 90, Fortran 2003 |
result = unpack(vector, mask, field) |
||
Stores the elements of |
transformational function | Fortran 90 |
Vector & Matrix Functions
result = dot_product(vector_a, vector_b) |
||
---|---|---|
Computes the dot product multiplication of two vectors
|
transformational function | Fortran 90 |
result = matmul(matrix_a, matrix_b) |
||
Performs a matrix multiplication on numeric or logical arguments, with rank one or two. |
transformational function | Fortran 90 |
result = transpose(matrix) |
||
Transposes array |
transformational function | Fortran 90 |
Character Functions
result = achar(i[, kind]) |
||
---|---|---|
Returns the character located at position |
elemental function | FORTRAN 77, Fortran 2003 |
result = adjustl(string) |
||
Left-adjust |
elemental function | Fortran 90 |
result = adjustr(string) |
||
Right-adjust |
elemental function | Fortran 90 |
result = iachar(c[, kind]) |
||
Returns the code for the ASCII character in the first character
position of |
elemental function | Fortran 95, Fortran 2003 |
result = index(string, substring[, back[, kind]]) |
||
Returns the position of the start of the first occurrence of
If |
elemental function | FORTRAN 77, Fortran 2003 |
result = len(string[, kind]) |
||
Returns the length of |
inquiry function | FORTRAN 77, Fortran 2003 |
result = len_trim(string[, kind]) |
||
Returns the length of |
elemental function | Fortran 90, Fortran 2003 |
result = lge(string_a, string_b) |
||
Returns If |
elemental function | FORTRAN 77 |
result = lgt(string_a, string_b) |
||
Returns If |
elemental function | FORTRAN 77 |
result = lle(string_a, string_b) |
||
Returns If |
elemental function | FORTRAN 77 |
result = llt(string_a, string_b) |
||
Returns If |
elemental function | FORTRAN 77 |
result = new_line(c) |
||
Returns the new-line character [character(len=1)] of the
same kind as argument |
inquiry function | Fortran 2003 |
result = repeat(string, ncopies) |
||
Concatenates |
transformational function | Fortran 90 |
result = scan(string, set[, back[, kind]]) |
||
Scans a If no character of |
elemental function | Fortran 90, Fortran 2003 |
call split(string, set, pos[, back]) |
||
Parses Argument If |
subroutine | Fortran 2023 |
call tokenize(string, set, tokens[, separator]) call tokenize(string, set, first, last)
|
||
Parses Optional argument Each element in array Each element in array |
subroutine | Fortran 2023 |
result = trim(string) |
||
Removes trailing blank character of |
transformational function | Fortran 90 |
result = verify(string, set[, back[, kind]]) |
||
Verifies that all the characters in If |
elemental function | Fortran 90, Fortran 2003 |
Type & Kind Functions
result = allocated(array) result = allocated(scalar) |
||
---|---|---|
Returns |
inquiry function | Fortran 90, Fortran 2003 |
result = associated(pointer[, target]) |
||
Returns |
inquiry function | Fortran 90 |
result = extends_type_of(a, mold) |
||
Queries dynamic type for extension. Returns |
inquiry function | Fortran 2003 |
result = is_iostat_end(i) |
||
Returns |
elemental function | Fortran 2003 |
result = is_iostat_eor(i) |
||
Returns |
elemental function | Fortran 2003 |
result = kind(x) |
||
Returns the kind value of the entity |
transformational function | Fortran 95 |
result = next(a[, stat]) |
||
Returns the next enumeration value of |
inquiry function | Fortran 2023 |
result = null([mold]) |
||
Returns a disassociated pointer. If |
transformational function | Fortran 95, Fortran 2003 |
result = out_of_range(x, mold[, round]) |
||
Returns |
elemental function | Fortran 2018 |
result = present(a) |
||
Returns |
inquiry function | Fortran 90 |
result = previous(a[, stat]) |
||
Returns the previous enumeration value of |
inquiry function | Fortran 2023 |
result = same_type_as(a, b) |
||
Queries dynamic types for equality. Returns |
inquiry function | Fortran 2003 |
result = selected_char_kind(name) |
||
Returns the kind value [integer] for the character set
named The character sets are compiler-depended, and may include
|
transformational function | Fortran 2003 |
result = selected_int_kind(r) |
||
Return the kind value [integer] of the smallest integer type that can represent all values ranging from −10r (exclusive) to 10r (exclusive) [integer]. If there is no integer kind that accommodates this range, the function returns −1. |
transformational function | Fortran 90 |
result = selected_logical_kind(bits) |
||
Return the kind value [integer] of a logical type whose
storage size in bits is at least |
transformational function | Fortran 2023 |
result = selected_real_kind([p, r, radix]) |
||
Returns the kind value [integer] of a real data type with
decimal precision of at least If the |
transformational function | Fortran 90, Fortran 2008 |
result = storage_size(x[, kind]) |
||
Returns the storage size of argument |
elemental function | Fortran 2008 |
result = transfer(source, mold[, size]) |
||
Interprets the bitwise representation of This is approximately equivalent to the C concept of casting one
type to another. The result has the same type as |
transformational function | Fortran 90 |
Type Conversion Functions
result = char(c[, kind]) |
||
---|---|---|
Returns the character represented by |
elemental function | FORTRAN 77 |
result = cmplx(x[, y[, kind]]) |
||
Returns a complex number where |
elemental function | FORTRAN 77 |
result = dble(a) |
||
Converts |
elemental function | FORTRAN 77 |
result = ichar(c[, kind]) |
||
Returns the code for the character in the first character position
of |
elemental function | FORTRAN 77, Fortran 2003 |
result = int(a[, kind]) |
||
Converts |
elemental function | FORTRAN 77, Fortran 2008 |
result = logical(l[, kind]) |
||
Converts |
elemental function | Fortran 90 |
result = real(a[, kind]) |
||
Converts |
elemental function | FORTRAN 77, Fortran 90 |
Random Number Procedures
call random_init(repeatable, image_distinct) |
||
---|---|---|
Initialises a pseudo-random number generator. If
|
subroutine | Fortran 2018 |
call random_number(harvest) |
||
Returns a single pseudorandom number or an array of pseudorandom
numbers from the uniform distribution over the range
0 ≤ x < 1 in scalar or array
|
subroutine | Fortran 90 |
call random_seed([size, put, get]) |
||
Restarts or queries the state of the pseudo-random number
generator used by The optional argument |
subroutine | Fortran 90 |
System Procedures
result = compiler_options() |
||
---|---|---|
Returns a string with the options used for compiling. The function
has to be imported from module |
inquiry function | Fortran 2008 |
result = compiler_version() |
||
Returns a string with the name and the version of the compiler. The
function has to be imported from module
|
inquiry function | Fortran 2008 |
result = command_argument_count() |
||
Returns the number of arguments passed on the command-line as integer. |
inquiry function | Fortran 2003 |
call cpu_time(time) |
||
Returns the elapsed CPU time in seconds in |
subroutine | Fortran 95 |
call date_and_time(date, time, zone, values) |
||
Returns the corresponding date and time information from the real-time system clock. The argument The argument
|
subroutine | Fortran 90 |
call execute_command_line(command[, wait, exitstat, cmdstat, cmdmsg]) |
||
Runs a shell command Argument |
subroutine | Fortran 2008 |
call get_command([command, length, status, errmsg]) |
||
Retrieves the entire command-line that was used to invoke the
program. If If |
subroutine | Fortran 2003, Fortran 2018 |
call get_command_argument(number[, value, length, status, errmsg]) |
||
Retrieves the If If the argument retrieval fails, |
subroutine | Fortran 2003, Fortran 2018 |
call get_environment_variable(name[, value, length, status, trim_name, errmsg]) |
||
Retrieves the The subroutine need not be thread-safe. It is the responsibility of the user to ensure that the environment is not being updated concurrently with a call to the subroutine. |
subroutine | Fortran 2003, Fortran 2018 |
call system_clock([count, count_rate, count_max]) |
||
Determines the count [integer] of a processor
clock since an unspecified time in the past modulo
count_max [integer]. Argument
count_rate [integer] determines the number of
clock ticks per second. If the platform supports a monotonic
clock, that clock is used and can, depending on the platform clock
implementation, provide up to nanosecond resolution. If a monotonic
clock is not available, the implementation falls back to a
real-time clock.
Argument If there is no clock, or querying the clock fails,
It is recommended that all references to
|
subroutine | Fortran 90 |
ISO_C_BINDING Procedures
The intrinsic Fortran module iso_c_binding
has to imported
with use, intrinsic :: iso_c_binding
first to access any of the
following procedures.
result = c_associated(cptr1[, cptr2]) |
||
---|---|---|
Returns |
transformational function | Fortran 2003 |
call c_f_pointer(cptr, fptr[, shape][, lower]) |
||
Assigns the target of the C pointer The optional argument |
subroutine | Fortran 2003, Fortran 2023 |
call c_f_procpointer(cptr, fptr) |
||
Assigns the target of the C function pointer |
subroutine | Fortran 2003 |
call c_f_strpointer(cstrarray, fstrptr[, nchars]) call c_f_strpointer(cstrptr, fstrptr[, nchars])
|
||
Converts the rank one character array The length type parameter of |
subroutine | Fortran 2023 |
result = c_funloc(x) |
||
Determines the C address [type(c_funptr)] of procedure
|
transformational function | Fortran 2003 |
result = c_loc(x) |
||
Determines the C address [type(c_ptr)] of variable
|
transformational function | Fortran 2003 |
result = c_sizeof(x) |
||
Calculates the number of bytes of storage
[integer(kind=c_size_t)] the expression If |
inquiry function | Fortran 2008 |
result = f_c_string(string[, asis]) |
||
Returns a character scalar of the same type and kind as
|
transformational function | Fortran 2023 |
Coarray Procedures
call atomic_add(atom, value[, stat]) |
||
---|---|---|
Atomically adds When In particular, for a coindexed |
atomic subroutine | Fortran 2018 |
call atomic_and(atom, value[, stat]) |
||
Atomically defines When In particular, for a coindexed |
atomic subroutine | Fortran 2018 |
call atomic_cas(atom, old, compare, new[, stat]) |
||
Compares the variable
When |
atomic subroutine | Fortran 2018 |
call atomic_define(atom, value[, stat]) |
||
Defines the variable When |
atomic subroutine | Fortran 2008, Fortran 2018 |
call atomic_fetch_add(atom, value, old[, stat]) |
||
Atomically stores the value of When |
atomic subroutine | Fortran 2018 |
call atomic_fetch_and(atom, value, old[, stat]) |
||
Atomically stores the value of When |
atomic subroutine | Fortran 2018 |
call atomic_fetch_or(atom, value, old[, stat]) |
||
Atomically stores the value of When |
atomic subroutine | Fortran 2018 |
call atomic_fetch_xor(atom, value, old[, stat]) |
||
Atomically stores the value of When |
atomic subroutine | Fortran 2018 |
call atomic_or(atom, value[, stat]) |
||
Atomically defines When |
atomic subroutine | Fortran 2018 |
call atomic_ref(value, atom[, stat]) |
||
Atomically assigns the value of the variable When |
atomic subroutine | Fortran 2008, Fortran 2018 |
call atomic_xor(atom, value[, stat]) |
||
Atomically defines When |
atomic subroutine | Fortran 2018 |
call co_broadcast(a, source_image[, stat, errmsg]) |
||
Copies the value of argument If the execution was successful and |
collective subroutine | Fortran 2018 |
call co_max(a[, result_image, stat, errmsg]) |
||
Determines element-wise the maximal value of If the execution was successful and |
collective subroutine | Fortran 2018 |
call co_min(a[, result_image, stat, errmsg]) |
||
Determines element-wise the minimum value of If the execution was successful and |
collective subroutine | Fortran 2018 |
call co_reduce(a, operator[, result_image, stat, errmsg]) |
||
Determines element-wise the reduction of the value of
If If the execution was successful and |
collective subroutine | Fortran 2018 |
call co_sum(a[, result_image, stat, errmsg]) |
||
Sums up the values of each element of If the execution was successful and |
collective subroutine | Fortran 2018 |
result = coshape(coarray[, kind]) |
||
Returns a rank-one integer array whose size is the corank of
|
function | Fortran 2018 |
call event_query(event, count[, stat]) |
||
Assigns the number of events to When |
subroutine | Fortran 2018 |
result = image_index(coarray, sub) |
||
Returns the image index belonging to a cosubscript. For invalid cosubscripts the result is zero. |
inquiry function | Fortran 2008 |
result = lcobound(coarray[, dim[, kind]]) |
||
Returns the lower bounds of |
inquiry function | Fortran 2008 |
result = num_images(distance, failed) |
||
Returns the number of images, with optional
If If |
transformational function | Fortran 2008, Fortran 2018 |
result = this_image() result = this_image(distance) result = this_image(coarray[, dim]) |
||
Returns the cosubscript for this image, with optional
If If If |
transformational function | Fortran 2008, Fortran 2018 |
result = ucobound(coarray[, dim[, kind]]) |
||
Returns the upper bounds of |
inquiry function | Fortran 2008 |
References
- Fortran-Lang.org: Intrinsic Procedures
- The GNU Fortran Compiler: Intrinsic Procedures
< Control Structures | [Index] | Fortran Standard Library > |