• Source: Fortran 95 language features
  • This is an overview of Fortran 95 language features. Included are the additional features of TR-15581:Enhanced Data Type Facilities, which have been universally implemented. Old features that have been superseded by new ones are not described – few of those historic features are used in modern programs although most have been retained in the language to maintain backward compatibility.
    The additional features of subsequent standards, up to Fortran 2023, are described in the Fortran 2023 standard document, ISO/IEC 1539-1:2023.
    Many of its new features are still being implemented in compilers.


    Language elements


    Fortran is case-insensitive. The convention of writing Fortran keywords in upper case and all other names in lower case is adopted in this article; except, by way of contrast, in the input/output descriptions (Data transfer and Operations on external files).


    = Basics

    =
    The basic component of the Fortran language is its character set. Its members are

    the letters A ... Z and a ... z (which are equivalent outside a character context)
    the numerals 0 ... 9
    the underscore _
    the special characters = : + blank - * / ( ) [ ] , . $ ' ! " % & ; < > ?
    Tokens that have a syntactic meaning to the compiler are built from those components. There are six classes of tokens:

    From the tokens, statements are built. These can be coded using the new free source form which does not require positioning in a rigid column structure:

    Note the trailing comments and the trailing continuation mark. There may be 39 continuation lines, and 132 characters per line. Blanks are significant. Where a token or character constant is split across two lines:

    a leading & on the continued line is also required.


    = Intrinsic data types

    =
    Fortran has five intrinsic data types: INTEGER, REAL, COMPLEX, LOGICAL and CHARACTER. Each of those types can be additionally characterized by a kind. Kind, basically, defines internal representation of the type: for the three numeric types, it defines the precision and range, and for the other two, the specifics of storage representation. Thus, it is an abstract concept which models the limits of data types' representation; it is expressed as a member of a set of whole numbers (e.g. it may be {1, 2, 4, 8} for integers, denoting bytes of storage), but those values are not specified by the Standard and not portable. For every type, there is a default kind, which is used if no kind is explicitly specified. For each intrinsic type, there is a corresponding form of literal constant. The numeric types INTEGER and REAL can only be signed (there is no concept of sign for type COMPLEX).


    Literal constants and kinds




    = INTEGER

    =
    Integer literal constants of the default kind take the form

    Kind can be defined as a named constant. If the desired range is ±10kind, the portable syntax for defining the appropriate kind, two_bytes is

    that allows subsequent definition of constants of the form

    Here, two_bytes is the kind type parameter; it can also be an explicit default integer literal constant, like

    but such use is non-portable.
    The KIND function supplies the value of a kind type parameter:

    and the RANGE function supplies the actual decimal range (so the user must make the actual mapping to bytes):

    Also, in DATA (initialization) statements, binary (B), octal (O) and hexadecimal (Z) constants may be used (often informally referred to as "BOZ constants"):


    = REAL

    =
    There are at least two real kinds – the default and one with greater precision (this replaces DOUBLE PRECISION). SELECTED_REAL_KIND functions returns the kind number for desired range and precision; for at least 9 decimal digits of precision and a range of 10−99 to 1099, it can be specified as:

    and literals subsequently specified as

    Also, there are the intrinsic functions

    that give in turn the kind type value, the actual precision (here at least 9), and the actual range (here at least 99).


    = COMPLEX

    =
    COMPLEX data type is built of two integer or real components:


    = LOGICAL

    =
    There are only two basic values of logical constants: .TRUE. and .FALSE.. Here, there may also be different kinds. Logicals don't have their own kind inquiry functions, but use the kinds specified for INTEGERs; default kind of LOGICAL is the same as of INTEGER.

    and the KIND function operates as expected:


    = CHARACTER

    =
    The forms of literal constants for CHARACTER data type are

    (the last being an empty string). Different kinds are allowed (for example, to distinguish ASCII and UNICODE strings), but not widely supported by compilers. Again, the kind value is given by the KIND function:


    Number model and intrinsic functions


    The numeric types are based on number models with associated inquiry functions (whose values are independent of the values of their arguments; arguments are used only to provide kind). These functions are important for portable numerical software:


    = Scalar variables

    =
    Scalar variables corresponding to the five intrinsic types are specified as follows:

    where the optional KIND parameter specifies a non-default kind, and the :: notation delimits the type and attributes from variable name(s) and their optional initial values, allowing full variable specification and initialization to be typed in one statement (in previous standards, attributes and initializers had to be declared in several statements). While it is not required in above examples (as there are no additional attributes and initialization), most Fortran-90 programmers acquire the habit to use it everywhere.
    LEN= specifier is applicable only to CHARACTERs and specifies the string length (replacing the older *len form).
    The explicit KIND= and LEN= specifiers are optional:

    works just as well.
    There are some other interesting character features. Just as a substring as in

    was previously possible, so now is the substring

    Also, zero-length strings are allowed:

    Finally, there is a set of intrinsic character functions, examples being


    = Derived data types

    =
    For derived data types, the form of the type must be defined first:

    and then, variables of that type can be defined:

    To select components of a derived type, % qualifier is used:

    Literal constants of derived types have the form TypeName(1stComponentLiteral, 2ndComponentLiteral, ...):

    which is known as a structure constructor. Definitions may refer to a previously defined type:

    and for a variable of type triangle, as in

    each component of type point is accessed as

    which, in turn, have ultimate components of type real:

    (Note that the % qualifier was chosen rather than dot (.) because of potential ambiguity with operator notation, like .OR.).


    = Implicit and explicit typing

    =
    Unless specified otherwise, all variables starting with letters I, J, K, L, M and N are default INTEGERs, and all others are default REAL; other data types must be explicitly declared. This is known as implicit typing and is a heritage of early FORTRAN days. Those defaults can be overridden by IMPLICIT TypeName (CharacterRange) statements, like:

    However, it is a good practice to explicitly type all variables, and this can be forced by inserting the statement IMPLICIT NONE
    at the beginning of each program unit.


    = Arrays

    =
    Arrays are considered to be variables in their own right. Every array is characterized by its type, rank, and shape (which defines the extents of each dimension). Bounds of each dimension are by default 1 and size, but arbitrary bounds can be explicitly specified. DIMENSION keyword is optional and considered an attribute; if omitted, the array shape must be specified after array-variable name. For example,

    declares two arrays, rank-1 and rank-2, whose elements are in column-major order. Elements are, for example,

    and are scalars. The subscripts may be any scalar integer expression.
    Sections are parts of the array variables, and are arrays themselves:

    Whole arrays and array sections are array-valued objects. Array-valued constants (constructors) are available, enclosed in (/ ... /):

    making use of an implied-DO loop notation. Fortran 2003 allows the use of brackets:
    [1, 2, 3, 4] and [([1,2,3], i=1,4)]
    instead of the first two examples above, and many compilers support this now.
    A derived data type may, of course, contain array components:

    so that

    t(2) is a scalar (a structure)
    t(2)%vertex is an array component of a scalar


    = Data initialization

    =
    Variables can be given initial values as specified in a specification statement:

    and a default initial value can be given to the component of a derived data type:

    When local variables are initialized within a procedure they implicitly acquire the SAVE attribute:

    This declaration is equivalent to

    for local variables within a subroutine or function. The SAVE attribute causes local variables to retain their value after a procedure call and then to initialize the variable to the saved value upon returning to the procedure.


    PARAMETER attribute


    A named constant can be specified directly by adding the PARAMETER attribute and the constant values to a type statement:


    DATA statement


    The DATA statement can be used for scalars and also for arrays and variables of derived type. It is also the only way to initialise just parts of such objects, as well as to initialise to binary, octal or hexadecimal values:


    Initialization expressions


    The values used in DATA and PARAMETER statements, or with these attributes, are constant expressions that may include references to: array and structure constructors, elemental intrinsic functions with integer or character arguments and results, and the six transformational functions REPEAT, SELECTED_INT_KIND, TRIM, SELECTED_REAL_KIND, RESHAPE and TRANSFER (see Intrinsic procedures):


    = Specification expressions

    =
    It is possible to specify details of variables
    using any non-constant, scalar, integer expression that may also include inquiry
    function references:


    Expressions and assignments




    = Scalar numeric

    =
    The usual arithmetic operators are available – +, -, *, /, ** (given here in increasing order of precedence).
    Parentheses are used to indicate the order of evaluation where necessary:

    The rules for scalar numeric expressions and assignments accommodate the non-default kinds. Thus, the mixed-mode numeric expression and assignment rules incorporate different kind type parameters in an expected way:

    converts integer0 to a real value of the same kind as real1; the result is of same kind, and is converted to the kind of real2 for assignment.
    These functions are available for controlled rounding of real numbers to integers:

    NINT: round to nearest integer, return integer result
    ANINT: round to nearest integer, return real result
    INT: truncate (round towards zero), return integer result
    AINT: truncate (round towards zero), return real result
    CEILING: smallest integral value not less than argument (round up) (Fortran-90)
    FLOOR: largest integral value not greater than argument (round down) (Fortran-90)


    = Scalar relational operations

    =
    For scalar relational operations of numeric types, there is a set of built-in operators:

    < <= == /= > >=
    .LT. .LE. .EQ. .NE. .GT. .GE.

    (the forms above are new to Fortran-90, and older equivalent forms are given below them). Example expressions:


    = Scalar characters

    =
    In the case of scalar characters and given CHARACTER(8) result
    it is legal to write

    Concatenation is performed by the operator '//'.


    = Derived-data types

    =
    No built-in operations (except assignment, defined on component-by component basis) exist between derived data types mutually or with intrinsic types. The meaning of existing or user-specified operators can be (re)defined though:

    we can write

    Notice the "overloaded" use of the intrinsic symbol // and the named operator, .concat. . A difference between the two cases is that, for an intrinsic operator token, the usual precedence rules apply, whereas for named operators, precedence is the highest as a unary operator or the lowest as a binary one. In

    the two expressions are equivalent only if appropriate parentheses are
    added as shown. In each case there must be defined, in a module, procedures defining the operator and assignment, and corresponding operator-procedure association, as follows:

    The string concatenation function is a more elaborated version of that shown already in Basics. Note that in order to handle the error condition that arises when the two strings together exceed the preset 80-character limit, it would be safer to use a subroutine to perform the concatenation (in this case operator-overloading would not be applicable.)

    Defined operators such as these are required for the expressions that are
    allowed also in structure constructors (see Derived-data types):


    = Arrays

    =
    In the case of arrays then, as long as they are of the same shape (conformable), operations and assignments are extended in an obvious way, on an element-by-element basis. For example, given declarations of

    it can be written:

    The order of expression evaluation is not specified in order to allow for optimization on parallel and vector machines. Of course, any operators for arrays of derived type must be defined.
    Some real intrinsic functions that are useful for numeric computations are

    These are array valued for array arguments (elemental), like all FORTRAN 77 functions (except LEN):

    Powers, logarithms, and trigonometric functions

    Complex numbers:

    The following are for characters:


    Control statements




    = Branching and conditions

    =
    The simple GO TO label exists, but is usually avoided – in most cases, a more specific branching construct will accomplish the same logic with more clarity.
    The simple conditional test is the IF statement: IF (a > b) x = y
    A full-blown IF construct is illustrated by


    = CASE construct

    =
    The CASE construct is a replacement for the computed GOTO, but is better
    structured and does not require the use of statement labels:

    Each CASE selector list may contain a list and/or range of integers,
    character or logical constants, whose values may not overlap within or between
    selectors:

    A default is available:

    There is only one evaluation, and only one match.


    = DO construct

    =
    A simplified but sufficient form of the DO construct is illustrated by

    where we note that loops may be optionally named so that any EXIT or CYCLE
    statement may specify which loop is meant.
    Many, but not all, simple loops can be replaced by array expressions and
    assignments, or by new intrinsic functions. For instance

    becomes simply tot = SUM( a(m:n) )


    Program units and procedures




    = Definitions

    =
    In order to discuss this topic we need some definitions. In logical terms, an executable program consists of one main program and zero or more subprograms (or procedures) - these do something. Subprograms are either functions or subroutines, which are either external, internal or module subroutines. (External subroutines are what we knew from FORTRAN 77.)
    From an organizational point of view, however, a complete program consists of program units. These are either main programs, external subprograms or modules and can be separately compiled.
    An example of a main (and complete) program is

    An example of a main program and an external subprogram, forming an executable program, is

    The form of a function is

    The form of reference of a function is x = name(a, b)


    = Internal procedures

    =
    An internal subprogram is one contained in another (at a maximum
    of one level of nesting) and provides a replacement for the statement function:

    We say that outer is the host of inner, and that inner obtains
    access to entities in outer by host association (e.g. to x), whereas
    y is a local variable to inner.
    The scope of a named entity is a scoping unit, here
    outer less inner, and inner.
    The names of program units and external procedures are global, and
    the names of implied-DO variables have a scope of the statement that contains
    them.


    = Modules

    =
    Modules are used to package

    global data (replaces COMMON and BLOCK DATA from Fortran 77);
    type definitions (themselves a scoping unit);
    subprograms (which among other things replaces the use of ENTRY from Fortran 77);
    interface blocks (another scoping unit, see Interface blocks);
    namelist groups (see any textbook).
    An example of a module
    containing a type definition, interface block and function subprogram is

    and the simple statement

    provides use association to all the module's entities. Module
    subprograms may, in turn, contain internal subprograms.


    = Controlling accessibility

    =
    The PUBLIC and PRIVATE attributes are used in specifications in
    modules to limit the scope of entities. The attribute form is

    and the statement form is

    The statement form has to be used to limit access to operators, and can
    also be used to change the overall default:

    For derived types there are three possibilities: the type and its
    components are all PUBLIC, the type is PUBLIC and its components PRIVATE (the
    type only is visible and one can change its details easily), or all of it is
    PRIVATE (for internal use in the module only):

    The USE statement's purpose is to gain access to entities in a module.
    It has options to resolve name clashes if an imported name is the
    same as a local one:

    or to restrict the used entities to a specified set:

    These may be combined:


    = Arguments

    =
    We may specify the intent of dummy arguments:

    Also, INOUT is possible: here the actual argument must be a variable
    (unlike the default case where it may be a constant).
    Arguments may be optional:

    allows us to call mincon by

    Arguments may be keyword rather than positional (which come first):

    Optional and keyword arguments are handled by explicit interfaces, that is
    with internal or module procedures or with interface blocks.


    = Interface blocks

    =
    Any reference to an internal or module subprogram is
    through an interface that is 'explicit' (that is, the compiler can see all the
    details). A reference to an external (or dummy) procedure is usually 'implicit'
    (the compiler assumes the details). However, we can provide an explicit
    interface in this case too. It is a copy of the header, specifications and END
    statement of the procedure concerned, either placed in a module or inserted
    directly:

    An explicit interface is obligatory for

    optional and keyword arguments;
    POINTER and TARGET arguments (see Pointers);
    POINTER function result;
    new-style array arguments and array functions (Array handling).
    It allows
    full checks at compile time between actual and dummy arguments.
    In general, the best way to ensure that a procedure interface is explicit is either to place the procedure concerned in a module or to use it as an internal procedure.


    = Overloading and generic interfaces

    =
    Interface blocks provide the
    mechanism by which we are able to define generic names for specific procedures:

    where a given set of specific names corresponding to a generic name must
    all be of functions or all of subroutines. If this interface is within a module,
    then it is simply

    We can use existing names, e.g. SIN, and the compiler sorts out the
    correct association.
    We have already seen the use of interface blocks for defined operators and
    assignment (see Modules).


    = Recursion

    =
    Indirect recursion is useful for multi-dimensional
    integration. For

    We might have

    and to integrate f(x, y) over a rectangle:

    Direct recursion is when a procedure calls itself, as in

    Here, we note the RESULT clause and termination test.


    = Pure procedures

    =
    This is a feature for parallel computing.
    In the FORALL statement and construct, any side effects in a function can impede optimization on a parallel processor – the order of execution of the assignments could affect the results. To control this situation, we add the PURE keyword to the SUBROUTINE or FUNCTION statement – an assertion that the procedure (expressed simply):

    alters no global variable,
    performs no I/O,
    has no saved variables (variables with the SAVE attribute that retains values between invocations), and
    for functions, does not alter any of its arguments.
    A compiler can check that this is the case, as in

    All the intrinsic functions are pure.


    Array handling


    Array handling is included in Fortran for two main reasons:

    the notational convenience it provides, bringing the code closer to the underlying mathematical form;
    for the additional optimization opportunities it gives compilers (although there are plenty of opportunities for degrading optimization too!).
    At the same time, major extensions of the functionality in this area have been
    added. We have already met whole arrays above #Arrays 1 and here #Arrays 2 - now
    we develop the theme.


    = Zero-sized arrays

    =
    A zero-sized array is handled by Fortran as a
    legitimate object, without special coding by the programmer. Thus, in

    no special code is required for the final iteration where i = n. We note
    that a zero-sized array is regarded as being defined; however, an array of shape
    (0,2) is not conformable with one of shape (0,3), whereas x(1:0) = 3 is a valid 'do nothing' statement.


    = Assumed-shape arrays

    =
    These are an extension and replacement for
    assumed-size arrays. Given an actual argument like:

    the corresponding dummy argument specification defines only the type and
    rank of the array, not its shape. This information has to be made available by an
    explicit interface, often using an interface block (see Interface blocks). Thus we write just

    and this is as if da were dimensioned (11,21). However, we can specify any
    lower bound and the array maps accordingly.

    The shape, not bounds, is passed, where the default lower bound is 1 and the default upper bound is the corresponding extent.


    = Automatic arrays

    =
    A partial replacement for the uses to which EQUIVALENCE
    was put is provided by this facility, useful for local, temporary arrays, as in

    The actual storage is typically maintained on a stack.


    = ALLOCATABLE and ALLOCATE

    =
    Fortran provides dynamic allocation of
    storage; it relies on a heap storage mechanism (and replaces another use of
    EQUIVALENCE). An example for establishing a work array for a whole program is

    The work array can be propagated through the whole program via a USE
    statement in each program unit. We may specify an explicit lower bound and
    allocate several entities in one statement. To free dead storage we write, for
    instance,

    Deallocation of arrays is automatic when they go out of scope.


    = Elemental operations, assignments and procedures

    =
    We have already met whole array
    assignments and operations:

    In the second assignment, an intrinsic function returns an array-valued
    result for an array-valued argument. We can write array-valued functions
    ourselves (they require an explicit interface):

    Elemental procedures are specified with scalar dummy arguments that may be called with
    array actual arguments. In the case of a function, the shape of the result is the shape of the array
    arguments.
    Most intrinsic functions are elemental and
    Fortran 95 extends this feature to non-intrinsic procedures, thus providing the effect
    of writing, in Fortran 90, 22 different versions, for ranks 0-0, 0-1, 1-0, 1-1, 0-2,
    2-0, 2-2, ... 7-7, and is further an aid to optimization on parallel processors.
    An elemental procedure must be pure.

    The dummy arguments cannot be used in specification expressions (see above) except as arguments to certain intrinsic functions (BIT_SIZE, KIND, LEN, and the numeric inquiry ones, (see below).


    = WHERE

    =
    Often, we need to mask an assignment. This we can do using the WHERE, either as a statement:

    (note: the test is element-by-element, not on whole array), or as a construct:

    or

    Further:

    it is permitted to mask not only the WHERE statement of the WHERE construct, but also any ELSEWHERE statement that it contains;
    a WHERE construct may contain any number of masked ELSEWHERE statements but at most one ELSEWHERE statement without a mask, and that must be the final one;
    WHERE constructs may be nested within one another, just FORALL constructs;
    a WHERE assignment statement is permitted to be a defined assignment, provided that it is elemental;
    a WHERE construct may be named in the same way as other constructs.


    = The FORALL statement and construct

    =
    When a DO construct is executed, each successive iteration is performed in order and one after the other – an impediment to optimization on a parallel processor.

    where the individual assignments may be carried out in any order, and even simultaneously. The FORALL may be considered to be an array assignment expressed with the help of indices.

    with masking condition.
    The FORALL construct allows several assignment statements to be executed in order.

    is equivalent to the array assignments

    The FORALL version is more readable.
    Assignment in a FORALL is like an array assignment:
    as if all the expressions were evaluated in any order, held in temporary storage, then all the assignments performed in any order. The first statement must fully complete before the second can begin.
    A FORALL may be nested, and may include a WHERE.
    Procedures referenced within a FORALL must be pure.


    = Array elements

    =
    For a simple case, given

    we can reference a single element as, for instance, a(1, 1). For a
    derived-data type like

    we can declare an array of that type:

    and a reference like tar(n, 2) is an element (a scalar!) of type fun_del, but tar(n, 2)%du is an array of type real, and tar(n, 2)%du(2) is an element of it. The basic rule to remember is that an array element
    always has a subscript or subscripts qualifying at least the last name.


    = Array subobjects (sections)

    =
    The general form of subscript for an array
    section is

    [lower] : [upper] [:stride]

    (where [ ] indicates an optional item) as in

    Note that a vector subscript with duplicate values cannot appear on the
    left-hand side of an assignment as it would be ambiguous. Thus,

    is illegal. Also, a section with a vector subscript must not be supplied
    as an actual argument to an OUT or INOUT dummy argument. Arrays of arrays are not allowed:

    We note that a given value in an array can be referenced both as an
    element and as a section:

    depending on the circumstances or requirements. By qualifying objects of
    derived type, we obtain elements or sections depending on the rule stated
    earlier:


    = Arrays intrinsic functions

    =
    Vector and matrix multiply

    Array reduction

    Array inquiry

    Array construction

    Array reshape

    Array manipulation

    Array location


    Pointers




    = Basics

    =
    Pointers are variables with the POINTER attribute; they are not a
    distinct data type (and so no 'pointer arithmetic' is possible).

    They are conceptually a descriptor listing the attributes of the objects
    (targets) that the pointer may point to, and the address, if any, of a target.
    They have no associated storage until it is allocated or otherwise associated
    (by pointer assignment, see below):

    and they are dereferenced automatically, so no special symbol required. In

    the value of the target of var is used and modified. Pointers cannot be
    transferred via I/O. The statement

    writes the value of the target of var and not the pointer descriptor
    itself.
    A pointer can point to another pointer, and hence to its target, or to a
    static object that has the TARGET attribute:

    but they are strongly typed:

    and, similarly, for arrays the ranks as well as the type must agree.
    A pointer can be a component of a derived type:

    and we can define the beginning of a linked chain of such entries:

    After suitable allocations and definitions, the first two entries could be
    addressed as

    but we would normally define additional pointers to point at, for
    instance, the first and current entries in the list.


    = Association

    =
    A pointer's association status is one of

    Some care has to be taken not to leave a pointer 'dangling' by use of DEALLOCATE on its target without nullifying any other pointer referring to it.
    The intrinsic function ASSOCIATED can test the association status of a defined pointer:

    or between a defined pointer and a defined target (which may, itself, be a pointer):

    An alternative way to initialize a pointer, also in a specification statement, is to use the NULL function:


    = Pointers in expressions and assignments

    =
    For intrinsic types we can
    'sweep' pointers over different sets of target data using the same code without
    any data movement. Given the matrix manipulation y = B C z, we can write the
    following code (although, in this case, the same result could be achieved more
    simply by other means):

    For objects of derived type we have to distinguish between pointer and
    normal assignment. In

    the assignment causes first to point at current, whereas

    causes current to overwrite first and is equivalent to


    = Pointer arguments

    =
    If an actual argument is a pointer then, if the dummy
    argument is also a pointer,

    it must have same rank,
    it receives its association status from the actual argument,
    it returns its final association status to the actual argument (note: the target may be undefined!),
    it may not have the INTENT attribute (it would be ambiguous),
    it requires an interface block.
    If the dummy argument is not a
    pointer, it becomes associated with the target of the actual argument:


    = Pointer functions

    =
    Function results may also have the POINTER attribute;
    this is useful if the result size depends on calculations performed in the
    function, as in

    where the module data_handler contains

    The result can be used in an expression (but must be associated with a
    defined target).


    = Arrays of pointers

    =
    These do not exist as such: given

    then

    would be such an object, but with an irregular storage pattern. For this
    reason they are not allowed. However, we can achieve the same effect by defining
    a derived data type with a pointer as its sole component:

    and then defining arrays of this data type

    where the storage for the rows can be allocated by, for instance,

    The array assignment s = tis then equivalent to the pointer assignments s(i)%r => t(i)%r for all components.


    = Pointers as dynamic aliases

    =
    Given an array

    that is frequently referenced with the fixed subscripts

    these references may be replaced by

    The subscripts of window are 1:n-m+1, 1:q-p+1. Similarly, for tar%u
    (as defined in already), we can use, say, taru => tar%u to point at all the u components of tar, and subscript it as taru(1, 2)
    The subscripts are as those of tar itself. (This replaces yet more of EQUIVALENCE.)
    In the pointer association

    the lower bounds for pointer are determined as if lbound was applied to array_expression. Thus, when a pointer is assigned to a whole array variable, it inherits the lower bounds of the variable, otherwise, the lower bounds default to 1.
    Fortran 2003 allows specifying arbitrary lower bounds on pointer association, like

    so that the bounds of window become r:r+n-m,s:s+q-p.
    Fortran 95 does not have this feature; however, it can be simulated using the
    following trick (based on the pointer association rules for assumed shape array dummy arguments):

    The source code of an extended example of the use of pointers to support a
    data structure is in pointer.f90.


    Intrinsic procedures


    Most of the intrinsic functions have already been mentioned. Here, we deal only with their general classification and with those that have so far been omitted. All intrinsic procedures can be used with keyword arguments:

    and many have optional arguments.
    The intrinsic procedures are grouped into four categories:

    elemental - work on scalars or arrays, e.g. ABS(a);
    inquiry - independent of value of argument (which may be undefined), e.g. PRECISION(a);
    transformational - array argument with array result of different shape, e.g. RESHAPE(a, b);
    subroutines, e.g. SYSTEM_CLOCK.
    The procedures not already introduced are
    Bit inquiry

    Bit manipulation

    Transfer function, as in

    (replaces part of EQUIVALENCE)
    Subroutines


    Data transfer




    = Formatted input/output

    =
    These examples illustrate various forms of I/O lists with some simple formats (see below):

    Variables, but not expressions, are equally valid in input statements using the READ statement:

    If an array appears as an item, it is treated as if the elements were specified in array element order.
    Any pointers in an I/O list must be associated with a target, and transfer takes place between the file and the targets.
    An item of derived type is treated as if the components were specified in the same order as in the type declaration, so

    has the same effect as the statement

    An object in an I/O list is not permitted to be of a derived type that has a pointer component at any level of component selection.
    Note that a zero-sized array may occur as an item in an I/O list. Such an item corresponds to no actual data transfer.
    The format specification may also be given in the form of a character expression:

    or as an asterisk – this is a type of I/O known as list-directed I/O (see below), in which the format is defined by the computer system:

    Input/output operations are used to transfer data between the storage of an executing program and an external medium, specified by a unit number. However, two I/O statements, PRINT and a variant of READ, do not reference any unit number: this is referred to as terminal I/O. Otherwise the form is:

    where UNIT= is optional.
    The value may be any nonnegative integer allowed by the system for this purpose (but 0, 5 and 6 often denote the error, keyboard and terminal, respectively).
    An asterisk is a variant – again from the keyboard:

    A read with a unit specifier allows exception handling:

    There a second type of formatted output statement, the WRITE statement:


    = Internal files

    =
    These allow format conversion between various representations to be carried out by the program in a storage area defined within the program itself.

    If an internal file is a scalar, it has a single record whose length is that of the scalar.
    If it is an array, its elements, in array element order, are treated as successive records of the file and each has length that of an array element.
    An example using a WRITE statement is

    that might write

    Takings for day 3 are 4329.15 dollars


    = List-directed I/O

    =
    An example of a read without a specified format for input is

    If this reads the input record

    (in which blanks are used as separators),
    then i, a, field, flag, and title will acquire the values 10, 6.4, (1.0,0.0) and (2.0,0.0), .true.
    and test respectively,
    while word remains unchanged.
    Quotation marks or apostrophes are required as delimiters for a string that
    contains a blank.


    = Non-advancing I/O

    =
    This is a form of reading and writing without always advancing the file position to ahead of the next record. Whereas an advancing I/O statement always repositions the file after the last record accessed, a non-advancing I/O statement performs no such repositioning and may therefore leave the file positioned within a record.

    A non-advancing read might read the first few characters of a record and a normal read the remainder.
    In order to write a prompt to a terminal screen and to read from the next character position on the screen without an intervening line-feed, we can write

    Non-advancing I/O is for external files, and is not available for list-directed I/O.


    = Edit descriptors

    =
    It is possible to specify that an edit descriptor be repeated a specified number of times, using a repeat count: 10f12.3
    The slash edit descriptor (see below) may have a repeat count, and a repeat count can also apply to a group of edit descriptors, enclosed in parentheses, with nesting:

    Entire format specifications can be repeated:

    writes 10 integers, each occupying 8 character positions, on each of 20 lines (repeating the format specification advances to the next line).


    Data edit descriptors




    Control edit descriptors


    Control edit descriptors setting conditions:

    Control edit descriptors for immediate processing:


    = Unformatted I/O

    =
    This type of I/O should be used only in cases where the records are generated by a program on one computer, to be read back on the same computer or another computer using the same internal number representations:


    = Direct-access files

    =
    This form of I/O is also known as random access or indexed I/O. Here, all the records have the same length, and each record is identified by an index number. It is possible to write, read, or re-write any specified record without regard to position.

    The file must be an external file and list-directed formatting and non-advancing I/O are unavailable.


    Operations on external files


    Once again, this is an overview only.


    = File positioning statements

    =


    = The OPEN statement

    =
    The statement is used to connect an external file to a unit, create a file that is preconnected, or create a file and connect it to a unit.
    The syntax is

    where olist is a list of optional specifiers. The specifiers may appear in any order.

    Other specifiers are FORM and POSITION.


    = The CLOSE statement

    =
    This is used to disconnect a file from a unit.

    as in


    = The inquire statement

    =
    At any time during the execution of a program it is possible to inquire about the status and attributes of a file using this statement.
    Using a variant of this statement, it is similarly possible to determine the status of a unit, for instance whether the unit number exists for that system.
    Another variant permits an inquiry about the length of an output list when used to write an unformatted record.
    For inquire by unit

    or for inquire by file

    or for inquire by I/O list

    As an example

    yields

    (assuming no intervening read or write operations).
    Other specifiers are IOSTAT, OPENED, NUMBER, NAMED, FORMATTED, POSITION, ACTION, READ, WRITE, READWRITE.


    References

Kata Kunci Pencarian: