by a machine such as your computer.
Humans usually aren't as good writing machine code
as they are at writing Fortran (or C++, Ada, or Java),
-because is easy to make tiny mistakes writing machine code.
+because it is easy to make tiny mistakes writing machine code.
@item
Provide the user with information about the reasons why
the compiler is unable to create a binary from the source code.
Usually this will be the case if the source code is flawed.
-When writing Fortran, it is easy to make big mistakes.
-The Fortran 90 requires that the compiler can point out
+The Fortran 90 standard requires that the compiler can point out
mistakes to the user.
An incorrect usage of the language causes an @dfn{error message}.
TYPESPEC(k) x,y,z
@end smallexample
@noindent
-where @code{k} is equal to @code{size} for most types, but is equal to
-@code{size/2} for the @code{COMPLEX} type.
+where @code{k} is the kind parameter suitable for the intended precision. As
+kind parameters are implementation-dependent, use the @code{KIND},
+@code{SELECTED_INT_KIND} and @code{SELECTED_REAL_KIND} intrinsics to retrieve
+the correct value, for instance @code{REAL*8 x} can be replaced by:
+@smallexample
+INTEGER, PARAMETER :: dbl = KIND(1.0d0)
+REAL(KIND=dbl) :: x
+@end smallexample
@node Old-style variable initialization
@subsection Old-style variable initialization
The long history of the Fortran language, its wide use and broad
userbase, the large number of different compiler vendors and the lack of
some features crucial to users in the first standards have lead to the
-existence of an important number of extensions to the language. While
+existence of a number of important extensions to the language. While
some of the most useful or popular extensions are supported by the GNU
-Fortran compiler, not all existing extensions are supported. This section
+Fortran compiler, not all existing extensions are supported. This section
aims at listing these extensions and offering advice on how best make
code that uses them running with the GNU Fortran compiler.
store_catalog(7).description = "milk bottle"
store_catalog(7).price = 1.2
-! We can also manipulates the whole structure
+! We can also manipulate the whole structure
store_catalog(12) = pear
print *, store_catalog(12)
@end example
@table @asis
@item @emph{Description}:
@code{ABORT} causes immediate termination of the program. On operating
-systems that support a core dump, @code{ABORT} will produce a core dump,
-which is suitable for debugging purposes.
+systems that support a core dump, @code{ABORT} will produce a core dump even if
+the option @option{-fno-dump-core} is in effect, which is suitable for debugging
+purposes.
+@c TODO: Check if this (with -fno-dump-core) is correct.
@item @emph{Standard}:
GNU extension
@item @emph{Arguments}:
@multitable @columnfractions .15 .70
@item @var{X} @tab The type shall be @code{REAL} with a magnitude that is
-less than one.
+less than or equal to one.
@end multitable
@item @emph{Return value}:
Spaces are inserted at the end of the string as needed.
@item @emph{Standard}:
-Fortran 95 and later
+Fortran 90 and later
@item @emph{Class}:
Elemental function
program test_allocated
integer :: i = 4
real(4), allocatable :: x(:)
- if (allocated(x) .eqv. .false.) allocate(x(i))
+ if (.not. allocated(x)) allocate(x(i))
end program test_allocated
@end smallexample
@end table
@item @emph{Arguments}:
@multitable @columnfractions .15 .70
@item @var{X} @tab The type shall be @code{REAL}, and a magnitude that is
-less than one.
+less than or equal to one.
@end multitable
@item @emph{Return value}:
@table @asis
@item @emph{Description}:
@code{BIT_SIZE(I)} returns the number of bits (integer precision plus sign bit)
-represented by the type of @var{I}.
+represented by the type of @var{I}. The result of @code{BIT_SIZE(I)} is
+independent of the actual value of @var{I}.
@item @emph{Standard}:
Fortran 95 and later
@table @asis
@item @emph{Description}:
@code{BTEST(I,POS)} returns logical @code{.TRUE.} if the bit at @var{POS}
-in @var{I} is set.
+in @var{I} is set. The counting of the bits starts at 0.
@item @emph{Standard}:
Fortran 95 and later
@item @emph{Return value}:
The return value is of type @code{REAL} and it is positive
-(@math{ \cosh (x) \geq 0 }. The return value is of the same
-kind as @var{X}.
+(@math{ \cosh (x) \geq 0 }). For a @code{REAL} argument @var{X},
+@math{ \cosh (x) \geq 1 }.
+The return value is of the same kind as @var{X}.
@item @emph{Example}:
@smallexample
@code{COUNT(MASK [, DIM [, KIND]])} counts the number of @code{.TRUE.}
elements of @var{MASK} along the dimension of @var{DIM}. If @var{DIM} is
-omitted it is taken to be @code{1}. @var{DIM} is a scaler of type
+omitted it is taken to be @code{1}. @var{DIM} is a scalar of type
@code{INTEGER} in the range of @math{1 /leq DIM /leq n)} where @math{n}
is the rank of @var{MASK}.
@item @emph{Description}:
@code{CSHIFT(ARRAY, SHIFT [, DIM])} performs a circular shift on elements of
@var{ARRAY} along the dimension of @var{DIM}. If @var{DIM} is omitted it is
-taken to be @code{1}. @var{DIM} is a scaler of type @code{INTEGER} in the
+taken to be @code{1}. @var{DIM} is a scalar of type @code{INTEGER} in the
range of @math{1 /leq DIM /leq n)} where @math{n} is the rank of @var{ARRAY}.
If the rank of @var{ARRAY} is one, then all elements of @var{ARRAY} are shifted
by @var{SHIFT} places. If rank is greater than one, then all complete rank one
@node DIGITS
-@section @code{DIGITS} --- Significant digits function
+@section @code{DIGITS} --- Significant binary digits function
@fnindex DIGITS
@cindex model representation, significant digits
@table @asis
@item @emph{Description}:
-@code{DIGITS(X)} returns the number of significant digits of the internal model
-representation of @var{X}. For example, on a system using a 32-bit
+@code{DIGITS(X)} returns the number of significant binary digits of the internal
+model representation of @var{X}. For example, on a system using a 32-bit
floating point representation, a default real number would likely return 24.
@item @emph{Standard}:
@end multitable
@item @emph{Return value}:
-If the arguments are numeric, the return value is a scaler of numeric type,
+If the arguments are numeric, the return value is a scalar of numeric type,
@code{INTEGER}, @code{REAL}, or @code{COMPLEX}. If the arguments are
@code{LOGICAL}, the return value is @code{.TRUE.} or @code{.FALSE.}.
@item @emph{Description}:
@code{EOSHIFT(ARRAY, SHIFT[, BOUNDARY, DIM])} performs an end-off shift on
elements of @var{ARRAY} along the dimension of @var{DIM}. If @var{DIM} is
-omitted it is taken to be @code{1}. @var{DIM} is a scaler of type
+omitted it is taken to be @code{1}. @var{DIM} is a scalar of type
@code{INTEGER} in the range of @math{1 /leq DIM /leq n)} where @math{n} is the
rank of @var{ARRAY}. If the rank of @var{ARRAY} is one, then all elements of
@var{ARRAY} are shifted by @var{SHIFT} places. If rank is greater than one,
@item @emph{Arguments}:
@multitable @columnfractions .15 .70
-@item @var{ARRAY} @tab May be any type, not scaler.
+@item @var{ARRAY} @tab May be any type, not scalar.
@item @var{SHIFT} @tab The type shall be @code{INTEGER}.
@item @var{BOUNDARY} @tab Same type as @var{ARRAY}.
@item @var{DIM} @tab The type shall be @code{INTEGER}.
@table @asis
@item @emph{Description}:
-@code{EPSILON(X)} returns a nearly negligible number relative to @code{1}.
+@code{EPSILON(X)} returns the smallest number @var{E} of the same kind
+as @var{X} such that @math{1 + E > 1}.
@item @emph{Standard}:
Fortran 95 and later
@var{NUMBER}-th command line argument. If @var{VALUE} can not hold the argument, it is
truncated to fit the length of @var{VALUE}. If there are less than @var{NUMBER}
arguments specified at the command line, @var{VALUE} will be filled with blanks.
-If @math{@var{NUMBER} = 0}, @var{VALUE} is set to the name of the program (on systems
-that support this feature). The @var{LENGTH} argument contains the length of the
-@var{NUMBER}-th command line argument. If the argument retrival fails, @var{STATUS}
-is a positiv number; if @var{VALUE} contains a truncated command line argument,
-@var{STATUS} is -1; and otherwise the @var{STATUS} is zero.
+If @math{@var{NUMBER} = 0}, @var{VALUE} is set to the name of the program (on
+systems that support this feature). The @var{LENGTH} argument contains the
+length of the @var{NUMBER}-th command line argument. If the argument retrieval
+fails, @var{STATUS} is a positive number; if @var{VALUE} contains a truncated
+command line argument, @var{STATUS} is -1; and otherwise the @var{STATUS} is
+zero.
@item @emph{Example}:
@smallexample
@end multitable
@item @emph{Return value}:
-Does not return.
+Does not return anything.
@item @emph{Example}:
@smallexample
@end multitable
@item @emph{Return value}:
-Does not return.
+Does not return anything.
@item @emph{Example}:
@item @emph{Return value}:
The return value is of type @code{REAL} or @code{COMPLEX}.
The kind type parameter is the same as @var{X}.
+If @var{X} is @code{COMPLEX}, the imaginary part @math{\omega} is in the range
+@math{-\pi \leq \omega \leq \pi}.
@item @emph{Example}:
@smallexample
each row of the array in the @var{DIM} direction. If @var{MASK} is
present, only the elements for which @var{MASK} is @code{.TRUE.} are
considered. If the array has zero size, or all of the elements of
-@var{MASK} are @code{.FALSE.}, then the result is the most negative
-number of the type and kind of @var{ARRAY} if @var{ARRAY} is numeric, or
-a string of nulls if @var{ARRAY} is of character type.
+@var{MASK} are @code{.FALSE.}, then the result is @code{-HUGE(ARRAY)}
+if @var{ARRAY} is numeric, or a string of nulls if @var{ARRAY} is of character
+type.
@item @emph{Standard}:
Fortran 95 and later
@table @asis
@item @emph{Description}:
-@code{SELECTED_REAL_KIND(P,R)} return the kind value of a real data type
-with decimal precision greater of at least @code{P} digits and exponent
+@code{SELECTED_REAL_KIND(P,R)} returns the kind value of a real data type
+with decimal precision of at least @code{P} digits and exponent
range greater at least @code{R}.
@item @emph{Standard}:
@item @var{STATUS} @tab (Optional) @var{STATUS} shall be a scalar
integer. It has @code{INTENT(OUT)}.
@end multitable
+@c TODO: What should the interface of the handler be? Does it take arguments?
@item @emph{Return value}:
The @code{SIGNAL} function returns the value returned by @code{signal(2)}.
@end multitable
@item @emph{Return value}:
-Does not return.
+Does not return anything.
@item @emph{Example}:
See @code{RAND} and @code{IRAND} for examples.
@item @code{C_FUNLOC}
@item @code{C_LOC}
@end table
+@c TODO: Vertical spacing between C_FUNLOC and C_LOC wrong in PDF,
+@c don't really know why.
The @code{ISO_C_BINDING} module provides the following named constants of the
type integer, which can be used as KIND type parameter. Note that GNU
@item @code{CHARACTER}@tab @code{C_CHAR} @tab @code{char}
@end multitable
-Additionally, the following @code{(CHARACTER(KIND=C_CHAR)} are
+Additionally, the following @code{(CHARACTER(KIND=C_CHAR))} are
defined.
@multitable @columnfractions .20 .45 .15
@item -fall-intrinsics
@opindex @code{fall-intrinsics}
-Accept all of the intrinsic procedures provided in libgfortran
-without regard to the setting of @option{-std}. In particular,
-this option can be quite useful with @option{-std=f95}. Additionally,
-@command{gfortran} will ignore @option{-Wintrinsics-std} and will never try
-to link to an @code{EXTERNAL} version if the intrinsic is not included in the
-selected standard.
+This option causes all intrinsic procedures (including the GNU-specific
+extensions) to be accepted. This can be useful with @option{-std=f95} to
+force standard-compliance but get access to the full range of intrinsics
+available with @command{gfortran}. As a consequence, @option{-Wintrinsics-std}
+will be ignored and no user-defined procedure with the same name as any
+intrinsic will be called except when it is explicitly declared @code{EXTERNAL}.
@item -fd-lines-as-code
@item -fd-lines-as-comments
@item -fdefault-double-8
@opindex @code{fdefault-double-8}
-Set the @code{DOUBLE PRECISION} type to an 8 byte wide type.
+Set the @code{DOUBLE PRECISION} type to an 8 byte wide type. If
+@option{-fdefault-real-8} is given, @code{DOUBLE PRECISION} would
+instead be promoted to 16 bytes if possible, and @option{-fdefault-double-8}
+can be used to prevent this. The kind of real constants like @code{1.d0} will
+not be changed by @option{-fdefault-real-8} though, so also
+@option{-fdefault-double-8} does not affect it.
@item -fdefault-integer-8
@opindex @code{fdefault-integer-8}
Set the default integer and logical types to an 8 byte wide type.
-Do nothing if this is already the default.
+Do nothing if this is already the default. This option also affects
+the kind of integer constants like @code{42}.
@item -fdefault-real-8
@opindex @code{fdefault-real-8}
Set the default real type to an 8 byte wide type.
-Do nothing if this is already the default.
+Do nothing if this is already the default. This option also affects
+the kind of non-double real constants like @code{1.0}, and does promote
+the default width of @code{DOUBLE PRECISION} to 16 bytes if possible, unless
+@code{-fdefault-double-8} is given, too.
@item -fdollar-ok
@opindex @code{fdollar-ok}
(operation produced a denormal value).
Some of the routines in the Fortran runtime library, like
-@samp{CPU_TIME}, are likely to to trigger floating point exceptions when
+@samp{CPU_TIME}, are likely to trigger floating point exceptions when
@code{ffpe-trap=precision} is used. For this reason, the use of
@code{ffpe-trap=precision} is not recommended.
Enable generation of run-time checks for array subscripts
and against the declared minimum and maximum values. It also
checks array indices for assumed and deferred
-shape arrays against the actual allocated bounds.
+shape arrays against the actual allocated bounds and ensures that all string
+lengths are equal for character array constructors without an explicit
+typespec.
Some checks require that @option{-fbounds-check} is set for
the compilation of the main program.
-In the future this may also include other forms of checking, e.g., checking
-substring references.
+Note: In the future this may also include other forms of checking, e.g.,
+checking substring references.
@item fcheck-array-temporaries