1@c Copyright (C) 2004-2015 Free Software Foundation, Inc.
2@c This is part of the GNU Fortran manual.   
3@c For copying conditions, see the file gfortran.texi.
4
5@ignore
6@c man begin COPYRIGHT
7Copyright @copyright{} 2004-2015 Free Software Foundation, Inc.
8
9Permission is granted to copy, distribute and/or modify this document
10under the terms of the GNU Free Documentation License, Version 1.3 or
11any later version published by the Free Software Foundation; with the
12Invariant Sections being ``Funding Free Software'', the Front-Cover
13Texts being (a) (see below), and with the Back-Cover Texts being (b)
14(see below).  A copy of the license is included in the gfdl(7) man page.
15
16(a) The FSF's Front-Cover Text is:
17
18     A GNU Manual
19
20(b) The FSF's Back-Cover Text is:
21
22     You have freedom to copy and modify this GNU Manual, like GNU
23     software.  Copies published by the Free Software Foundation raise
24     funds for GNU development.
25@c man end
26@c Set file name and title for the man page.
27@setfilename gfortran
28@settitle GNU Fortran compiler.
29@c man begin SYNOPSIS
30gfortran [@option{-c}|@option{-S}|@option{-E}]
31         [@option{-g}] [@option{-pg}] [@option{-O}@var{level}]
32         [@option{-W}@var{warn}@dots{}] [@option{-pedantic}]
33         [@option{-I}@var{dir}@dots{}] [@option{-L}@var{dir}@dots{}]
34         [@option{-D}@var{macro}[=@var{defn}]@dots{}] [@option{-U}@var{macro}]
35         [@option{-f}@var{option}@dots{}]
36         [@option{-m}@var{machine-option}@dots{}]
37         [@option{-o} @var{outfile}] @var{infile}@dots{}
38
39Only the most useful options are listed here; see below for the
40remainder.
41@c man end
42@c man begin SEEALSO
43gpl(7), gfdl(7), fsf-funding(7),
44cpp(1), gcov(1), gcc(1), as(1), ld(1), gdb(1), adb(1), dbx(1), sdb(1)
45and the Info entries for @file{gcc}, @file{cpp}, @file{gfortran}, @file{as},
46@file{ld}, @file{binutils} and @file{gdb}.
47@c man end
48@c man begin BUGS
49For instructions on reporting bugs, see
50@w{@value{BUGURL}}.
51@c man end
52@c man begin AUTHOR
53See the Info entry for @command{gfortran} for contributors to GCC and
54GNU Fortran.
55@c man end
56@end ignore
57
58@node Invoking GNU Fortran
59@chapter GNU Fortran Command Options
60@cindex GNU Fortran command options
61@cindex command options
62@cindex options, @command{gfortran} command
63
64@c man begin DESCRIPTION
65
66The @command{gfortran} command supports all the options supported by the
67@command{gcc} command.  Only options specific to GNU Fortran are documented
68here.
69
70@xref{Invoking GCC,,GCC Command Options,gcc,Using the GNU Compiler
71Collection (GCC)}, for information
72on the non-Fortran-specific aspects of the @command{gcc} command (and,
73therefore, the @command{gfortran} command).
74
75@cindex options, negative forms
76All GCC and GNU Fortran options
77are accepted both by @command{gfortran} and by @command{gcc}
78(as well as any other drivers built at the same time,
79such as @command{g++}),
80since adding GNU Fortran to the GCC distribution
81enables acceptance of GNU Fortran options
82by all of the relevant drivers.
83
84In some cases, options have positive and negative forms;
85the negative form of @option{-ffoo} would be @option{-fno-foo}.
86This manual documents only one of these two forms, whichever
87one is not the default.
88@c man end
89
90@menu
91* Option Summary::      Brief list of all @command{gfortran} options,
92                        without explanations.
93* Fortran Dialect Options::  Controlling the variant of Fortran language
94                             compiled.
95* Preprocessing Options::  Enable and customize preprocessing.
96* Error and Warning Options::     How picky should the compiler be?
97* Debugging Options::   Symbol tables, measurements, and debugging dumps.
98* Directory Options::   Where to find module files
99* Link Options ::       Influencing the linking step
100* Runtime Options::     Influencing runtime behavior
101* Code Gen Options::    Specifying conventions for function calls, data layout
102                        and register usage.
103* Environment Variables:: Environment variables that affect @command{gfortran}.
104@end menu
105
106@node Option Summary
107@section Option summary
108
109@c man begin OPTIONS
110
111Here is a summary of all the options specific to GNU Fortran, grouped
112by type.  Explanations are in the following sections.
113
114@table @emph
115@item Fortran Language Options
116@xref{Fortran Dialect Options,,Options controlling Fortran dialect}.
117@gccoptlist{-fall-intrinsics -fbackslash -fcray-pointer -fd-lines-as-code @gol
118-fd-lines-as-comments -fdefault-double-8 -fdefault-integer-8 @gol
119-fdefault-real-8 -fdollar-ok -ffixed-line-length-@var{n} @gol
120-ffixed-line-length-none -ffree-form -ffree-line-length-@var{n} @gol
121-ffree-line-length-none -fimplicit-none -finteger-4-integer-8 @gol
122-fmax-identifier-length -fmodule-private -ffixed-form -fno-range-check @gol
123-fopenacc -fopenmp -freal-4-real-10 -freal-4-real-16 -freal-4-real-8 @gol
124-freal-8-real-10 -freal-8-real-16 -freal-8-real-4 -std=@var{std}
125}
126
127@item Preprocessing Options
128@xref{Preprocessing Options,,Enable and customize preprocessing}.
129@gccoptlist{-A-@var{question}@r{[}=@var{answer}@r{]}
130-A@var{question}=@var{answer} -C -CC -D@var{macro}@r{[}=@var{defn}@r{]}
131-H -P @gol
132-U@var{macro} -cpp -dD -dI -dM -dN -dU -fworking-directory
133-imultilib @var{dir} @gol
134-iprefix @var{file} -iquote -isysroot @var{dir} -isystem @var{dir} -nocpp 
135-nostdinc @gol
136-undef
137}
138
139@item Error and Warning Options
140@xref{Error and Warning Options,,Options to request or suppress errors
141and warnings}.
142@gccoptlist{-Waliasing -Wall -Wampersand -Warray-bounds
143-Wc-binding-type -Wcharacter-truncation @gol
144-Wconversion -Wfunction-elimination -Wimplicit-interface @gol
145-Wimplicit-procedure -Wintrinsic-shadow -Wuse-without-only -Wintrinsics-std @gol
146-Wline-truncation -Wno-align-commons -Wno-tabs -Wreal-q-constant @gol
147-Wsurprising -Wunderflow -Wunused-parameter -Wrealloc-lhs -Wrealloc-lhs-all @gol
148-Wtarget-lifetime -fmax-errors=@var{n} -fsyntax-only -pedantic -pedantic-errors
149}
150
151@item Debugging Options
152@xref{Debugging Options,,Options for debugging your program or GNU Fortran}.
153@gccoptlist{-fbacktrace -fdump-fortran-optimized -fdump-fortran-original @gol
154-fdump-parse-tree -ffpe-trap=@var{list} -ffpe-summary=@var{list}
155}
156
157@item Directory Options
158@xref{Directory Options,,Options for directory search}.
159@gccoptlist{-I@var{dir}  -J@var{dir} -fintrinsic-modules-path @var{dir}}
160
161@item Link Options
162@xref{Link Options,,Options for influencing the linking step}.
163@gccoptlist{-static-libgfortran}
164
165@item Runtime Options
166@xref{Runtime Options,,Options for influencing runtime behavior}.
167@gccoptlist{-fconvert=@var{conversion} -fmax-subrecord-length=@var{length} @gol
168-frecord-marker=@var{length} -fsign-zero
169}
170
171@item Code Generation Options
172@xref{Code Gen Options,,Options for code generation conventions}.
173@gccoptlist{-faggressive-function-elimination -fblas-matmul-limit=@var{n} @gol
174-fbounds-check -fcheck-array-temporaries @gol
175-fcheck=@var{<all|array-temps|bounds|do|mem|pointer|recursion>} @gol
176-fcoarray=@var{<none|single|lib>} -fexternal-blas -ff2c
177-ffrontend-optimize @gol
178-finit-character=@var{n} -finit-integer=@var{n} -finit-local-zero @gol
179-finit-logical=@var{<true|false>}
180-finit-real=@var{<zero|inf|-inf|nan|snan>} @gol
181-fmax-array-constructor=@var{n} -fmax-stack-var-size=@var{n}
182-fno-align-commons @gol
183-fno-automatic -fno-protect-parens -fno-underscoring @gol
184-fsecond-underscore -fpack-derived -frealloc-lhs -frecursive @gol
185-frepack-arrays -fshort-enums -fstack-arrays
186}
187@end table
188
189@node Fortran Dialect Options
190@section Options controlling Fortran dialect
191@cindex dialect options
192@cindex language, dialect options
193@cindex options, dialect
194
195The following options control the details of the Fortran dialect
196accepted by the compiler:
197
198@table @gcctabopt
199@item -ffree-form
200@itemx -ffixed-form
201@opindex @code{ffree-form}
202@opindex @code{ffixed-form}
203@cindex options, Fortran dialect
204@cindex file format, free
205@cindex file format, fixed
206Specify the layout used by the source file.  The free form layout
207was introduced in Fortran 90.  Fixed form was traditionally used in
208older Fortran programs.  When neither option is specified, the source
209form is determined by the file extension.
210
211@item -fall-intrinsics
212@opindex @code{fall-intrinsics}
213This option causes all intrinsic procedures (including the GNU-specific
214extensions) to be accepted.  This can be useful with @option{-std=f95} to
215force standard-compliance but get access to the full range of intrinsics
216available with @command{gfortran}.  As a consequence, @option{-Wintrinsics-std}
217will be ignored and no user-defined procedure with the same name as any
218intrinsic will be called except when it is explicitly declared @code{EXTERNAL}.
219
220@item -fd-lines-as-code
221@itemx -fd-lines-as-comments
222@opindex @code{fd-lines-as-code}
223@opindex @code{fd-lines-as-comments}
224Enable special treatment for lines beginning with @code{d} or @code{D}
225in fixed form sources.  If the @option{-fd-lines-as-code} option is
226given they are treated as if the first column contained a blank.  If the
227@option{-fd-lines-as-comments} option is given, they are treated as
228comment lines.
229
230@item -fdollar-ok
231@opindex @code{fdollar-ok}
232@cindex @code{$}
233@cindex symbol names
234@cindex character set
235Allow @samp{$} as a valid non-first character in a symbol name. Symbols 
236that start with @samp{$} are rejected since it is unclear which rules to
237apply to implicit typing as different vendors implement different rules.
238Using @samp{$} in @code{IMPLICIT} statements is also rejected.
239
240@item -fbackslash
241@opindex @code{backslash}
242@cindex backslash
243@cindex escape characters
244Change the interpretation of backslashes in string literals from a single
245backslash character to ``C-style'' escape characters. The following
246combinations are expanded @code{\a}, @code{\b}, @code{\f}, @code{\n},
247@code{\r}, @code{\t}, @code{\v}, @code{\\}, and @code{\0} to the ASCII
248characters alert, backspace, form feed, newline, carriage return,
249horizontal tab, vertical tab, backslash, and NUL, respectively.
250Additionally, @code{\x}@var{nn}, @code{\u}@var{nnnn} and
251@code{\U}@var{nnnnnnnn} (where each @var{n} is a hexadecimal digit) are
252translated into the Unicode characters corresponding to the specified code
253points. All other combinations of a character preceded by \ are
254unexpanded.
255
256@item -fmodule-private
257@opindex @code{fmodule-private}
258@cindex module entities
259@cindex private
260Set the default accessibility of module entities to @code{PRIVATE}.
261Use-associated entities will not be accessible unless they are explicitly
262declared as @code{PUBLIC}.
263
264@item -ffixed-line-length-@var{n}
265@opindex @code{ffixed-line-length-}@var{n}
266@cindex file format, fixed
267Set column after which characters are ignored in typical fixed-form
268lines in the source file, and through which spaces are assumed (as
269if padded to that length) after the ends of short fixed-form lines.
270
271Popular values for @var{n} include 72 (the
272standard and the default), 80 (card image), and 132 (corresponding
273to ``extended-source'' options in some popular compilers).
274@var{n} may also be @samp{none}, meaning that the entire line is meaningful
275and that continued character constants never have implicit spaces appended
276to them to fill out the line.
277@option{-ffixed-line-length-0} means the same thing as
278@option{-ffixed-line-length-none}.
279
280@item -ffree-line-length-@var{n}
281@opindex @code{ffree-line-length-}@var{n}
282@cindex file format, free
283Set column after which characters are ignored in typical free-form
284lines in the source file. The default value is 132.
285@var{n} may be @samp{none}, meaning that the entire line is meaningful.
286@option{-ffree-line-length-0} means the same thing as
287@option{-ffree-line-length-none}.
288
289@item -fmax-identifier-length=@var{n}
290@opindex @code{fmax-identifier-length=}@var{n}
291Specify the maximum allowed identifier length. Typical values are
29231 (Fortran 95) and 63 (Fortran 2003 and Fortran 2008).
293
294@item -fimplicit-none
295@opindex @code{fimplicit-none}
296Specify that no implicit typing is allowed, unless overridden by explicit
297@code{IMPLICIT} statements.  This is the equivalent of adding
298@code{implicit none} to the start of every procedure.
299
300@item -fcray-pointer
301@opindex @code{fcray-pointer}
302Enable the Cray pointer extension, which provides C-like pointer
303functionality.
304
305@item -fopenacc
306@opindex @code{fopenacc}
307@cindex OpenACC
308Enable the OpenACC extensions.  This includes OpenACC @code{!$acc}
309directives in free form and @code{c$acc}, @code{*$acc} and
310@code{!$acc} directives in fixed form, @code{!$} conditional
311compilation sentinels in free form and @code{c$}, @code{*$} and
312@code{!$} sentinels in fixed form, and when linking arranges for the
313OpenACC runtime library to be linked in.
314
315Note that this is an experimental feature, incomplete, and subject to
316change in future versions of GCC.  See
317@w{@uref{https://gcc.gnu.org/wiki/OpenACC}} for more information.
318
319@item -fopenmp
320@opindex @code{fopenmp}
321@cindex OpenMP
322Enable the OpenMP extensions.  This includes OpenMP @code{!$omp} directives
323in free form
324and @code{c$omp}, @code{*$omp} and @code{!$omp} directives in fixed form,
325@code{!$} conditional compilation sentinels in free form
326and @code{c$}, @code{*$} and @code{!$} sentinels in fixed form, 
327and when linking arranges for the OpenMP runtime library to be linked
328in.  The option @option{-fopenmp} implies @option{-frecursive}.
329
330@item -fno-range-check
331@opindex @code{frange-check}
332Disable range checking on results of simplification of constant
333expressions during compilation.  For example, GNU Fortran will give
334an error at compile time when simplifying @code{a = 1. / 0}.
335With this option, no error will be given and @code{a} will be assigned
336the value @code{+Infinity}.  If an expression evaluates to a value
337outside of the relevant range of [@code{-HUGE()}:@code{HUGE()}],
338then the expression will be replaced by @code{-Inf} or @code{+Inf}
339as appropriate.
340Similarly, @code{DATA i/Z'FFFFFFFF'/} will result in an integer overflow
341on most systems, but with @option{-fno-range-check} the value will
342``wrap around'' and @code{i} will be initialized to @math{-1} instead.
343
344@item -fdefault-integer-8
345@opindex @code{fdefault-integer-8}
346Set the default integer and logical types to an 8 byte wide type.  This option
347also affects the kind of integer constants like @code{42}. Unlike
348@option{-finteger-4-integer-8}, it does not promote variables with explicit
349kind declaration.
350
351@item -fdefault-real-8
352@opindex @code{fdefault-real-8}
353Set the default real type to an 8 byte wide type. This option also affects
354the kind of non-double real constants like @code{1.0}, and does promote
355the default width of @code{DOUBLE PRECISION} to 16 bytes if possible, unless
356@code{-fdefault-double-8} is given, too. Unlike @option{-freal-4-real-8},
357it does not promote variables with explicit kind declaration.
358
359@item -fdefault-double-8
360@opindex @code{fdefault-double-8}
361Set the @code{DOUBLE PRECISION} type to an 8 byte wide type.  Do nothing if this
362is already the default.  If @option{-fdefault-real-8} is given,
363@code{DOUBLE PRECISION} would instead be promoted to 16 bytes if possible, and
364@option{-fdefault-double-8} can be used to prevent this.  The kind of real
365constants like @code{1.d0} will not be changed by @option{-fdefault-real-8}
366though, so also @option{-fdefault-double-8} does not affect it.
367
368@item -finteger-4-integer-8
369@opindex @code{finteger-4-integer-8}
370Promote all @code{INTEGER(KIND=4)} entities to an @code{INTEGER(KIND=8)}
371entities.  If @code{KIND=8} is unavailable, then an error will be issued.
372This option should be used with care and may not be suitable for your codes.
373Areas of possible concern include calls to external procedures,
374alignment in @code{EQUIVALENCE} and/or @code{COMMON}, generic interfaces,
375BOZ literal constant conversion, and I/O.  Inspection of the intermediate
376representation of the translated Fortran code, produced by
377@option{-fdump-tree-original}, is suggested.
378
379@item  -freal-4-real-8
380@itemx -freal-4-real-10
381@itemx -freal-4-real-16
382@itemx -freal-8-real-4
383@itemx -freal-8-real-10
384@itemx -freal-8-real-16
385@opindex @code{freal-4-real-8}
386@opindex @code{freal-4-real-10}
387@opindex @code{freal-4-real-16}
388@opindex @code{freal-8-real-4}
389@opindex @code{freal-8-real-10}
390@opindex @code{freal-8-real-16}
391@cindex options, real kind type promotion
392Promote all @code{REAL(KIND=M)} entities to @code{REAL(KIND=N)} entities.
393If @code{REAL(KIND=N)} is unavailable, then an error will be issued.
394All other real kind types are unaffected by this option.
395These options should be used with care and may not be suitable for your
396codes.  Areas of possible concern include calls to external procedures,
397alignment in @code{EQUIVALENCE} and/or @code{COMMON}, generic interfaces,
398BOZ literal constant conversion, and I/O.  Inspection of the intermediate
399representation of the translated Fortran code, produced by
400@option{-fdump-tree-original}, is suggested.
401
402@item -std=@var{std}
403@opindex @code{std=}@var{std} option
404Specify the standard to which the program is expected to conform, which
405may be one of @samp{f95}, @samp{f2003}, @samp{f2008}, @samp{gnu}, or
406@samp{legacy}.  The default value for @var{std} is @samp{gnu}, which
407specifies a superset of the Fortran 95 standard that includes all of the
408extensions supported by GNU Fortran, although warnings will be given for
409obsolete extensions not recommended for use in new code.  The
410@samp{legacy} value is equivalent but without the warnings for obsolete
411extensions, and may be useful for old non-standard programs.  The
412@samp{f95}, @samp{f2003} and @samp{f2008} values specify strict
413conformance to the Fortran 95, Fortran 2003 and Fortran 2008 standards,
414respectively; errors are given for all extensions beyond the relevant
415language standard, and warnings are given for the Fortran 77 features
416that are permitted but obsolescent in later standards. @samp{-std=f2008ts}
417allows the Fortran 2008 standard including the additions of the 
418Technical Specification (TS) 29113 on Further Interoperability of Fortran
419with C and TS 18508 on Additional Parallel Features in Fortran.
420
421@end table
422
423@node Preprocessing Options
424@section Enable and customize preprocessing
425@cindex preprocessor
426@cindex options, preprocessor
427@cindex CPP
428
429Preprocessor related options. See section 
430@ref{Preprocessing and conditional compilation} for more detailed
431information on preprocessing in @command{gfortran}.
432
433@table @gcctabopt
434@item -cpp
435@itemx -nocpp
436@opindex @code{cpp}
437@opindex @code{fpp}
438@cindex preprocessor, enable
439@cindex preprocessor, disable
440Enable preprocessing. The preprocessor is automatically invoked if
441the file extension is @file{.fpp}, @file{.FPP},  @file{.F}, @file{.FOR},
442@file{.FTN}, @file{.F90}, @file{.F95}, @file{.F03} or @file{.F08}. Use
443this option to manually enable preprocessing of any kind of Fortran file.
444
445To disable preprocessing of files with any of the above listed extensions,
446use the negative form: @option{-nocpp}.
447
448The preprocessor is run in traditional mode. Any restrictions of the
449file-format, especially the limits on line length, apply for
450preprocessed output as well, so it might be advisable to use the
451@option{-ffree-line-length-none} or @option{-ffixed-line-length-none}
452options.
453
454@item -dM
455@opindex @code{dM}
456@cindex preprocessor, debugging
457@cindex debugging, preprocessor
458Instead of the normal output, generate a list of @code{'#define'}
459directives for all the macros defined during the execution of the
460preprocessor, including predefined macros. This gives you a way
461of finding out what is predefined in your version of the preprocessor.
462Assuming you have no file @file{foo.f90}, the command
463@smallexample
464  touch foo.f90; gfortran -cpp -E -dM foo.f90
465@end smallexample
466will show all the predefined macros.
467
468@item -dD
469@opindex @code{dD}
470@cindex preprocessor, debugging
471@cindex debugging, preprocessor
472Like @option{-dM} except in two respects: it does not include the
473predefined macros, and it outputs both the @code{#define} directives
474and the result of preprocessing. Both kinds of output go to the
475standard output file.
476
477@item -dN
478@opindex @code{dN}
479@cindex preprocessor, debugging
480@cindex debugging, preprocessor
481Like @option{-dD}, but emit only the macro names, not their expansions.
482
483@item -dU
484@opindex @code{dU}
485@cindex preprocessor, debugging
486@cindex debugging, preprocessor
487Like @option{dD} except that only macros that are expanded, or whose
488definedness is tested in preprocessor directives, are output; the 
489output is delayed until the use or test of the macro; and @code{'#undef'}
490directives are also output for macros tested but undefined at the time.
491
492@item -dI
493@opindex @code{dI}
494@cindex preprocessor, debugging
495@cindex debugging, preprocessor
496Output @code{'#include'} directives in addition to the result
497of preprocessing.
498
499@item -fworking-directory
500@opindex @code{fworking-directory}
501@cindex preprocessor, working directory
502Enable generation of linemarkers in the preprocessor output that will
503let the compiler know the current working directory at the time of
504preprocessing. When this option is enabled, the preprocessor will emit,
505after the initial linemarker, a second linemarker with the current
506working directory followed by two slashes. GCC will use this directory,
507when it is present in the preprocessed input, as the directory emitted
508as the current working directory in some debugging information formats.
509This option is implicitly enabled if debugging information is enabled,
510but this can be inhibited with the negated form
511@option{-fno-working-directory}. If the @option{-P} flag is present
512in the command line, this option has no effect, since no @code{#line}
513directives are emitted whatsoever.
514
515@item -idirafter @var{dir}
516@opindex @code{idirafter @var{dir}}
517@cindex preprocessing, include path
518Search @var{dir} for include files, but do it after all directories
519specified with @option{-I} and the standard system directories have
520been exhausted. @var{dir} is treated as a system include directory.
521If dir begins with @code{=}, then the @code{=} will be replaced by
522the sysroot prefix; see @option{--sysroot} and @option{-isysroot}.
523
524@item -imultilib @var{dir}
525@opindex @code{imultilib @var{dir}}
526@cindex preprocessing, include path
527Use @var{dir} as a subdirectory of the directory containing target-specific
528C++ headers.
529
530@item -iprefix @var{prefix}
531@opindex @code{iprefix @var{prefix}}
532@cindex preprocessing, include path
533Specify @var{prefix} as the prefix for subsequent @option{-iwithprefix}
534options. If the @var{prefix} represents a directory, you should include
535the final @code{'/'}.
536
537@item -isysroot @var{dir}
538@opindex @code{isysroot @var{dir}}
539@cindex preprocessing, include path
540This option is like the @option{--sysroot} option, but applies only to
541header files. See the @option{--sysroot} option for more information.
542
543@item -iquote @var{dir}
544@opindex @code{iquote @var{dir}}
545@cindex preprocessing, include path
546Search @var{dir} only for header files requested with @code{#include "file"};
547they are not searched for @code{#include <file>}, before all directories
548specified by @option{-I} and before the standard system directories. If
549@var{dir} begins with @code{=}, then the @code{=} will be replaced by the
550sysroot prefix; see @option{--sysroot} and @option{-isysroot}.
551
552@item -isystem @var{dir}
553@opindex @code{isystem @var{dir}}
554@cindex preprocessing, include path
555Search @var{dir} for header files, after all directories specified by
556@option{-I} but before the standard system directories. Mark it as a
557system directory, so that it gets the same special treatment as is
558applied to the standard system directories. If @var{dir} begins with
559@code{=}, then the @code{=} will be replaced by the sysroot prefix;
560see @option{--sysroot} and @option{-isysroot}.
561
562@item -nostdinc
563@opindex @code{nostdinc}
564Do not search the standard system directories for header files. Only
565the directories you have specified with @option{-I} options (and the
566directory of the current file, if appropriate) are searched.
567
568@item -undef
569@opindex @code{undef}
570Do not predefine any system-specific or GCC-specific macros.
571The standard predefined macros remain defined.
572
573@item -A@var{predicate}=@var{answer}
574@opindex @code{A@var{predicate}=@var{answer}}
575@cindex preprocessing, assertion
576Make an assertion with the predicate @var{predicate} and answer @var{answer}.
577This form is preferred to the older form -A predicate(answer), which is still
578supported, because it does not use shell special characters.
579
580@item -A-@var{predicate}=@var{answer}
581@opindex @code{A-@var{predicate}=@var{answer}}
582@cindex preprocessing, assertion
583Cancel an assertion with the predicate @var{predicate} and answer @var{answer}.
584
585@item -C
586@opindex @code{C}
587@cindex preprocessing, keep comments
588Do not discard comments. All comments are passed through to the output
589file, except for comments in processed directives, which are deleted
590along with the directive.
591
592You should be prepared for side effects when using @option{-C}; it causes
593the preprocessor to treat comments as tokens in their own right. For example,
594comments appearing at the start of what would be a directive line have the
595effect of turning that line into an ordinary source line, since the first
596token on the line is no longer a @code{'#'}.
597
598Warning: this currently handles C-Style comments only. The preprocessor
599does not yet recognize Fortran-style comments.
600
601@item -CC
602@opindex @code{CC}
603@cindex preprocessing, keep comments
604Do not discard comments, including during macro expansion. This is like
605@option{-C}, except that comments contained within macros are also passed
606through to the output file where the macro is expanded.
607
608In addition to the side-effects of the @option{-C} option, the @option{-CC}
609option causes all C++-style comments inside a macro to be converted to C-style
610comments. This is to prevent later use of that macro from inadvertently
611commenting out the remainder of the source line. The @option{-CC} option
612is generally used to support lint comments.
613
614Warning: this currently handles C- and C++-Style comments only. The
615preprocessor does not yet recognize Fortran-style comments.
616
617@item -D@var{name}
618@opindex @code{D@var{name}}
619@cindex preprocessing, define macros
620Predefine name as a macro, with definition @code{1}.
621
622@item -D@var{name}=@var{definition}
623@opindex @code{D@var{name}=@var{definition}}
624@cindex preprocessing, define macros
625The contents of @var{definition} are tokenized and processed as if they
626appeared during translation phase three in a @code{'#define'} directive.
627In particular, the definition will be truncated by embedded newline
628characters.
629
630If you are invoking the preprocessor from a shell or shell-like program
631you may need to use the shell's quoting syntax to protect characters such
632as spaces that have a meaning in the shell syntax.
633
634If you wish to define a function-like macro on the command line, write
635its argument list with surrounding parentheses before the equals sign
636(if any). Parentheses are meaningful to most shells, so you will need
637to quote the option. With sh and csh, @code{-D'name(args...)=definition'}
638works.
639
640@option{-D} and @option{-U} options are processed in the order they are
641given on the command line. All -imacros file and -include file options
642are processed after all -D and -U options.
643
644@item -H
645@opindex @code{H}
646Print the name of each header file used, in addition to other normal
647activities. Each name is indented to show how deep in the @code{'#include'}
648stack it is.
649
650@item -P
651@opindex @code{P}
652@cindex preprocessing, no linemarkers
653Inhibit generation of linemarkers in the output from the preprocessor.
654This might be useful when running the preprocessor on something that
655is not C code, and will be sent to a program which might be confused
656by the linemarkers.
657
658@item -U@var{name}
659@opindex @code{U@var{name}}
660@cindex preprocessing, undefine macros
661Cancel any previous definition of @var{name}, either built in or provided
662with a @option{-D} option.
663@end table
664
665
666@node Error and Warning Options
667@section Options to request or suppress errors and warnings
668@cindex options, warnings
669@cindex options, errors
670@cindex warnings, suppressing
671@cindex messages, error
672@cindex messages, warning
673@cindex suppressing warnings
674
675Errors are diagnostic messages that report that the GNU Fortran compiler
676cannot compile the relevant piece of source code.  The compiler will
677continue to process the program in an attempt to report further errors
678to aid in debugging, but will not produce any compiled output.  
679
680Warnings are diagnostic messages that report constructions which
681are not inherently erroneous but which are risky or suggest there is
682likely to be a bug in the program.  Unless @option{-Werror} is specified,
683they do not prevent compilation of the program.
684
685You can request many specific warnings with options beginning @option{-W},
686for example @option{-Wimplicit} to request warnings on implicit
687declarations.  Each of these specific warning options also has a
688negative form beginning @option{-Wno-} to turn off warnings;
689for example, @option{-Wno-implicit}.  This manual lists only one of the
690two forms, whichever is not the default.
691
692These options control the amount and kinds of errors and warnings produced
693by GNU Fortran:
694
695@table @gcctabopt
696@item -fmax-errors=@var{n}
697@opindex @code{fmax-errors=}@var{n}
698@cindex errors, limiting
699Limits the maximum number of error messages to @var{n}, at which point
700GNU Fortran bails out rather than attempting to continue processing the
701source code.  If @var{n} is 0, there is no limit on the number of error
702messages produced.
703
704@item -fsyntax-only
705@opindex @code{fsyntax-only}
706@cindex syntax checking
707Check the code for syntax errors, but do not actually compile it.  This
708will generate module files for each module present in the code, but no
709other output file.
710
711@item -pedantic
712@opindex @code{pedantic}
713Issue warnings for uses of extensions to Fortran 95.
714@option{-pedantic} also applies to C-language constructs where they
715occur in GNU Fortran source files, such as use of @samp{\e} in a
716character constant within a directive like @code{#include}.
717
718Valid Fortran 95 programs should compile properly with or without
719this option.
720However, without this option, certain GNU extensions and traditional
721Fortran features are supported as well.
722With this option, many of them are rejected.
723
724Some users try to use @option{-pedantic} to check programs for conformance.
725They soon find that it does not do quite what they want---it finds some
726nonstandard practices, but not all.
727However, improvements to GNU Fortran in this area are welcome.
728
729This should be used in conjunction with @option{-std=f95},
730@option{-std=f2003} or @option{-std=f2008}.
731
732@item -pedantic-errors
733@opindex @code{pedantic-errors}
734Like @option{-pedantic}, except that errors are produced rather than
735warnings.
736
737@item -Wall
738@opindex @code{Wall}
739@cindex all warnings
740@cindex warnings, all
741Enables commonly used warning options pertaining to usage that
742we recommend avoiding and that we believe are easy to avoid.
743This currently includes @option{-Waliasing}, @option{-Wampersand},
744@option{-Wconversion}, @option{-Wsurprising}, @option{-Wc-binding-type},
745@option{-Wintrinsics-std}, @option{-Wtabs}, @option{-Wintrinsic-shadow},
746@option{-Wline-truncation}, @option{-Wtarget-lifetime},
747@option{-Wreal-q-constant} and @option{-Wunused}.
748
749@item -Waliasing
750@opindex @code{Waliasing}
751@cindex aliasing
752@cindex warnings, aliasing
753Warn about possible aliasing of dummy arguments. Specifically, it warns
754if the same actual argument is associated with a dummy argument with
755@code{INTENT(IN)} and a dummy argument with @code{INTENT(OUT)} in a call
756with an explicit interface.
757
758The following example will trigger the warning.
759@smallexample
760  interface
761    subroutine bar(a,b)
762      integer, intent(in) :: a
763      integer, intent(out) :: b
764    end subroutine
765  end interface
766  integer :: a
767
768  call bar(a,a)
769@end smallexample
770
771@item -Wampersand
772@opindex @code{Wampersand}
773@cindex warnings, ampersand
774@cindex @code{&}
775Warn about missing ampersand in continued character constants. The warning is
776given with @option{-Wampersand}, @option{-pedantic}, @option{-std=f95},
777@option{-std=f2003} and @option{-std=f2008}. Note: With no ampersand
778given in a continued character constant, GNU Fortran assumes continuation
779at the first non-comment, non-whitespace character after the ampersand
780that initiated the continuation.
781
782@item -Warray-temporaries
783@opindex @code{Warray-temporaries}
784@cindex warnings, array temporaries
785Warn about array temporaries generated by the compiler.  The information
786generated by this warning is sometimes useful in optimization, in order to
787avoid such temporaries.
788
789@item -Wc-binding-type
790@opindex @code{Wc-binding-type}
791@cindex warning, C binding type
792Warn if the a variable might not be C interoperable.  In particular, warn if 
793the variable has been declared using an intrinsic type with default kind
794instead of using a kind parameter defined for C interoperability in the
795intrinsic @code{ISO_C_Binding} module.  This option is implied by
796@option{-Wall}.
797
798@item -Wcharacter-truncation
799@opindex @code{Wcharacter-truncation}
800@cindex warnings, character truncation
801Warn when a character assignment will truncate the assigned string.
802
803@item -Wline-truncation
804@opindex @code{Wline-truncation}
805@cindex warnings, line truncation
806Warn when a source code line will be truncated.  This option is
807implied by @option{-Wall}.  For free-form source code, the default is
808@option{-Werror=line-truncation} such that truncations are reported as
809error.
810
811@item -Wconversion
812@opindex @code{Wconversion}
813@cindex warnings, conversion
814@cindex conversion
815Warn about implicit conversions that are likely to change the value of 
816the expression after conversion. Implied by @option{-Wall}.
817
818@item -Wconversion-extra
819@opindex @code{Wconversion-extra}
820@cindex warnings, conversion
821@cindex conversion
822Warn about implicit conversions between different types and kinds. This
823option does @emph{not} imply @option{-Wconversion}.
824
825@item -Wextra
826@opindex @code{Wextra}
827@cindex extra warnings
828@cindex warnings, extra
829Enables some warning options for usages of language features which
830may be problematic. This currently includes @option{-Wcompare-reals}
831and @option{-Wunused-parameter}.
832
833@item -Wimplicit-interface
834@opindex @code{Wimplicit-interface}
835@cindex warnings, implicit interface
836Warn if a procedure is called without an explicit interface.
837Note this only checks that an explicit interface is present.  It does not
838check that the declared interfaces are consistent across program units.
839
840@item -Wimplicit-procedure
841@opindex @code{Wimplicit-procedure}
842@cindex warnings, implicit procedure
843Warn if a procedure is called that has neither an explicit interface
844nor has been declared as @code{EXTERNAL}.
845
846@item -Wintrinsics-std
847@opindex @code{Wintrinsics-std}
848@cindex warnings, non-standard intrinsics
849@cindex warnings, intrinsics of other standards
850Warn if @command{gfortran} finds a procedure named like an intrinsic not
851available in the currently selected standard (with @option{-std}) and treats
852it as @code{EXTERNAL} procedure because of this.  @option{-fall-intrinsics} can
853be used to never trigger this behavior and always link to the intrinsic
854regardless of the selected standard.
855
856@item -Wreal-q-constant
857@opindex @code{Wreal-q-constant}
858@cindex warnings, @code{q} exponent-letter
859Produce a warning if a real-literal-constant contains a @code{q}
860exponent-letter.
861
862@item -Wsurprising
863@opindex @code{Wsurprising}
864@cindex warnings, suspicious code
865Produce a warning when ``suspicious'' code constructs are encountered.
866While technically legal these usually indicate that an error has been made.
867
868This currently produces a warning under the following circumstances:
869
870@itemize @bullet
871@item
872An INTEGER SELECT construct has a CASE that can never be matched as its
873lower value is greater than its upper value.
874
875@item
876A LOGICAL SELECT construct has three CASE statements.
877
878@item
879A TRANSFER specifies a source that is shorter than the destination.
880
881@item
882The type of a function result is declared more than once with the same type.  If
883@option{-pedantic} or standard-conforming mode is enabled, this is an error.
884
885@item
886A @code{CHARACTER} variable is declared with negative length.
887@end itemize
888
889@item -Wtabs
890@opindex @code{Wtabs}
891@cindex warnings, tabs
892@cindex tabulators
893By default, tabs are accepted as whitespace, but tabs are not members
894of the Fortran Character Set.  For continuation lines, a tab followed
895by a digit between 1 and 9 is supported.  @option{-Wtabs} will cause
896a warning to be issued if a tab is encountered. Note, @option{-Wtabs}
897is active for @option{-pedantic}, @option{-std=f95}, @option{-std=f2003},
898@option{-std=f2008}, @option{-std=f2008ts} and @option{-Wall}.
899
900@item -Wunderflow
901@opindex @code{Wunderflow}
902@cindex warnings, underflow
903@cindex underflow
904Produce a warning when numerical constant expressions are
905encountered, which yield an UNDERFLOW during compilation. Enabled by default.
906
907@item -Wintrinsic-shadow
908@opindex @code{Wintrinsic-shadow}
909@cindex warnings, intrinsic
910@cindex intrinsic
911Warn if a user-defined procedure or module procedure has the same name as an
912intrinsic; in this case, an explicit interface or @code{EXTERNAL} or
913@code{INTRINSIC} declaration might be needed to get calls later resolved to
914the desired intrinsic/procedure.  This option is implied by @option{-Wall}.
915
916@item -Wuse-without-only
917@opindex @code{Wuse-without-only}
918@cindex warnings, use statements
919@cindex intrinsic
920Warn if a @code{USE} statement has no @code{ONLY} qualifier and 
921thus implicitly imports all public entities of the used module.
922
923@item -Wunused-dummy-argument
924@opindex @code{Wunused-dummy-argument}
925@cindex warnings, unused dummy argument
926@cindex unused dummy argument
927@cindex dummy argument, unused
928Warn about unused dummy arguments. This option is implied by @option{-Wall}.
929
930@item -Wunused-parameter
931@opindex @code{Wunused-parameter}
932@cindex warnings, unused parameter
933@cindex unused parameter
934Contrary to @command{gcc}'s meaning of @option{-Wunused-parameter},
935@command{gfortran}'s implementation of this option does not warn
936about unused dummy arguments (see @option{-Wunused-dummy-argument}),
937but about unused @code{PARAMETER} values. @option{-Wunused-parameter}
938is implied by @option{-Wextra} if also @option{-Wunused} or
939@option{-Wall} is used.
940
941@item -Walign-commons
942@opindex @code{Walign-commons}
943@cindex warnings, alignment of @code{COMMON} blocks
944@cindex alignment of @code{COMMON} blocks
945By default, @command{gfortran} warns about any occasion of variables being
946padded for proper alignment inside a @code{COMMON} block. This warning can be turned
947off via @option{-Wno-align-commons}. See also @option{-falign-commons}.
948
949@item -Wfunction-elimination
950@opindex @code{Wfunction-elimination}
951@cindex function elimination
952@cindex warnings, function elimination
953Warn if any calls to functions are eliminated by the optimizations
954enabled by the @option{-ffrontend-optimize} option.
955
956@item -Wrealloc-lhs
957@opindex @code{Wrealloc-lhs}
958@cindex Reallocate the LHS in assignments, notification
959Warn when the compiler might insert code to for allocation or reallocation of
960an allocatable array variable of intrinsic type in intrinsic assignments.  In
961hot loops, the Fortran 2003 reallocation feature may reduce the performance.
962If the array is already allocated with the correct shape, consider using a
963whole-array array-spec (e.g. @code{(:,:,:)}) for the variable on the left-hand
964side to prevent the reallocation check. Note that in some cases the warning
965is shown, even if the compiler will optimize reallocation checks away.  For
966instance, when the right-hand side contains the same variable multiplied by
967a scalar.  See also @option{-frealloc-lhs}.
968
969@item -Wrealloc-lhs-all
970@opindex @code{Wrealloc-lhs-all}
971Warn when the compiler inserts code to for allocation or reallocation of an
972allocatable variable; this includes scalars and derived types.
973
974@item -Wcompare-reals
975@opindex @code{Wcompare-reals}
976Warn when comparing real or complex types for equality or inequality.
977This option is implied by @option{-Wextra}.
978
979@item -Wtarget-lifetime
980@opindex @code{Wtargt-lifetime}
981Warn if the pointer in a pointer assignment might be longer than the its
982target. This option is implied by @option{-Wall}.
983
984@item -Wzerotrip
985@opindex @code{Wzerotrip}
986Warn if a @code{DO} loop is known to execute zero times at compile
987time.  This option is implied by @option{-Wall}.
988
989@item -Werror
990@opindex @code{Werror}
991@cindex warnings, to errors
992Turns all warnings into errors.
993@end table
994
995@xref{Warning Options,,Options to Request or Suppress Errors and
996Warnings, gcc,Using the GNU Compiler Collection (GCC)}, for information on
997more options offered by the GBE shared by @command{gfortran}, @command{gcc}
998and other GNU compilers.
999
1000Some of these have no effect when compiling programs written in Fortran.
1001
1002@node Debugging Options
1003@section Options for debugging your program or GNU Fortran
1004@cindex options, debugging
1005@cindex debugging information options
1006
1007GNU Fortran has various special options that are used for debugging
1008either your program or the GNU Fortran compiler.
1009
1010@table @gcctabopt
1011@item -fdump-fortran-original
1012@opindex @code{fdump-fortran-original}
1013Output the internal parse tree after translating the source program
1014into internal representation.  Only really useful for debugging the
1015GNU Fortran compiler itself.
1016
1017@item -fdump-fortran-optimized
1018@opindex @code{fdump-fortran-optimized}
1019Output the parse tree after front-end optimization.  Only really
1020useful for debugging the GNU Fortran compiler itself.
1021
1022@item -fdump-parse-tree
1023@opindex @code{fdump-parse-tree}
1024Output the internal parse tree after translating the source program
1025into internal representation.  Only really useful for debugging the
1026GNU Fortran compiler itself.  This option is deprecated; use
1027@code{-fdump-fortran-original} instead.
1028
1029@item -ffpe-trap=@var{list}
1030@opindex @code{ffpe-trap=}@var{list}
1031Specify a list of floating point exception traps to enable.  On most
1032systems, if a floating point exception occurs and the trap for that
1033exception is enabled, a SIGFPE signal will be sent and the program
1034being aborted, producing a core file useful for debugging.  @var{list}
1035is a (possibly empty) comma-separated list of the following
1036exceptions: @samp{invalid} (invalid floating point operation, such as
1037@code{SQRT(-1.0)}), @samp{zero} (division by zero), @samp{overflow}
1038(overflow in a floating point operation), @samp{underflow} (underflow
1039in a floating point operation), @samp{inexact} (loss of precision
1040during operation), and @samp{denormal} (operation performed on a
1041denormal value).  The first five exceptions correspond to the five
1042IEEE 754 exceptions, whereas the last one (@samp{denormal}) is not
1043part of the IEEE 754 standard but is available on some common
1044architectures such as x86.
1045
1046The first three exceptions (@samp{invalid}, @samp{zero}, and
1047@samp{overflow}) often indicate serious errors, and unless the program
1048has provisions for dealing with these exceptions, enabling traps for
1049these three exceptions is probably a good idea.
1050
1051Many, if not most, floating point operations incur loss of precision
1052due to rounding, and hence the @code{ffpe-trap=inexact} is likely to
1053be uninteresting in practice.
1054
1055By default no exception traps are enabled.
1056
1057@item -ffpe-summary=@var{list}
1058@opindex @code{ffpe-summary=}@var{list}
1059Specify a list of floating-point exceptions, whose flag status is printed
1060to @code{ERROR_UNIT} when invoking @code{STOP} and @code{ERROR STOP}.
1061@var{list} can be either @samp{none}, @samp{all} or a comma-separated list
1062of the following exceptions: @samp{invalid}, @samp{zero}, @samp{overflow},
1063@samp{underflow}, @samp{inexact} and @samp{denormal}. (See
1064@option{-ffpe-trap} for a description of the exceptions.)
1065
1066By default, a summary for all exceptions but @samp{inexact} is shown.
1067
1068@item -fno-backtrace
1069@opindex @code{fno-backtrace}
1070@cindex backtrace
1071@cindex trace
1072When a serious runtime error is encountered or a deadly signal is
1073emitted (segmentation fault, illegal instruction, bus error,
1074floating-point exception, and the other POSIX signals that have the
1075action @samp{core}), the Fortran runtime library tries to output a
1076backtrace of the error. @code{-fno-backtrace} disables the backtrace
1077generation. This option only has influence for compilation of the
1078Fortran main program.
1079
1080@end table
1081
1082@xref{Debugging Options,,Options for Debugging Your Program or GCC,
1083gcc,Using the GNU Compiler Collection (GCC)}, for more information on
1084debugging options.
1085
1086@node Directory Options
1087@section Options for directory search
1088@cindex directory, options
1089@cindex options, directory search
1090@cindex search path
1091@cindex @code{INCLUDE} directive
1092@cindex directive, @code{INCLUDE}
1093These options affect how GNU Fortran searches
1094for files specified by the @code{INCLUDE} directive and where it searches
1095for previously compiled modules.
1096
1097It also affects the search paths used by @command{cpp} when used to preprocess
1098Fortran source.
1099
1100@table @gcctabopt
1101@item -I@var{dir}
1102@opindex @code{I}@var{dir}
1103@cindex directory, search paths for inclusion
1104@cindex inclusion, directory search paths for
1105@cindex search paths, for included files
1106@cindex paths, search
1107@cindex module search path
1108These affect interpretation of the @code{INCLUDE} directive
1109(as well as of the @code{#include} directive of the @command{cpp}
1110preprocessor).
1111
1112Also note that the general behavior of @option{-I} and
1113@code{INCLUDE} is pretty much the same as of @option{-I} with
1114@code{#include} in the @command{cpp} preprocessor, with regard to
1115looking for @file{header.gcc} files and other such things.
1116
1117This path is also used to search for @file{.mod} files when previously
1118compiled modules are required by a @code{USE} statement.
1119
1120@xref{Directory Options,,Options for Directory Search,
1121gcc,Using the GNU Compiler Collection (GCC)}, for information on the
1122@option{-I} option.
1123
1124@item -J@var{dir}
1125@opindex @code{J}@var{dir}
1126@opindex @code{M}@var{dir}
1127@cindex paths, search
1128@cindex module search path
1129This option specifies where to put @file{.mod} files for compiled modules.
1130It is also added to the list of directories to searched by an @code{USE}
1131statement.
1132
1133The default is the current directory.
1134
1135@item -fintrinsic-modules-path @var{dir}
1136@opindex @code{fintrinsic-modules-path} @var{dir}
1137@cindex paths, search
1138@cindex module search path
1139This option specifies the location of pre-compiled intrinsic modules, if
1140they are not in the default location expected by the compiler.
1141@end table
1142
1143@node Link Options
1144@section Influencing the linking step
1145@cindex options, linking
1146@cindex linking, static
1147
1148These options come into play when the compiler links object files into an 
1149executable output file. They are meaningless if the compiler is not doing 
1150a link step.
1151
1152@table @gcctabopt
1153@item -static-libgfortran
1154@opindex @code{static-libgfortran}
1155On systems that provide @file{libgfortran} as a shared and a static
1156library, this option forces the use of the static version. If no
1157shared version of @file{libgfortran} was built when the compiler was
1158configured, this option has no effect.
1159@end table
1160
1161
1162@node Runtime Options
1163@section Influencing runtime behavior
1164@cindex options, runtime
1165
1166These options affect the runtime behavior of programs compiled with GNU Fortran.
1167
1168@table @gcctabopt
1169@item -fconvert=@var{conversion}
1170@opindex @code{fconvert=}@var{conversion}
1171Specify the representation of data for unformatted files.  Valid
1172values for conversion are: @samp{native}, the default; @samp{swap},
1173swap between big- and little-endian; @samp{big-endian}, use big-endian
1174representation for unformatted files; @samp{little-endian}, use little-endian
1175representation for unformatted files.
1176
1177@emph{This option has an effect only when used in the main program.
1178The @code{CONVERT} specifier and the GFORTRAN_CONVERT_UNIT environment
1179variable override the default specified by @option{-fconvert}.}
1180
1181@item -frecord-marker=@var{length}
1182@opindex @code{frecord-marker=}@var{length}
1183Specify the length of record markers for unformatted files.
1184Valid values for @var{length} are 4 and 8.  Default is 4.
1185@emph{This is different from previous versions of @command{gfortran}},
1186which specified a default record marker length of 8 on most
1187systems.  If you want to read or write files compatible
1188with earlier versions of @command{gfortran}, use @option{-frecord-marker=8}.
1189
1190@item -fmax-subrecord-length=@var{length}
1191@opindex @code{fmax-subrecord-length=}@var{length}
1192Specify the maximum length for a subrecord.  The maximum permitted
1193value for length is 2147483639, which is also the default.  Only
1194really useful for use by the gfortran testsuite.
1195
1196@item -fsign-zero
1197@opindex @code{fsign-zero}
1198When enabled, floating point numbers of value zero with the sign bit set
1199are written as negative number in formatted output and treated as
1200negative in the @code{SIGN} intrinsic.  @option{-fno-sign-zero} does not
1201print the negative sign of zero values (or values rounded to zero for I/O)
1202and regards zero as positive number in the @code{SIGN} intrinsic for
1203compatibility with Fortran 77. The default is @option{-fsign-zero}.
1204@end table
1205
1206@node Code Gen Options
1207@section Options for code generation conventions
1208@cindex code generation, conventions
1209@cindex options, code generation
1210@cindex options, run-time
1211
1212These machine-independent options control the interface conventions
1213used in code generation.
1214
1215Most of them have both positive and negative forms; the negative form
1216of @option{-ffoo} would be @option{-fno-foo}.  In the table below, only
1217one of the forms is listed---the one which is not the default.  You
1218can figure out the other form by either removing @option{no-} or adding
1219it.
1220
1221@table @gcctabopt
1222@item -fno-automatic
1223@opindex @code{fno-automatic}
1224@cindex @code{SAVE} statement
1225@cindex statement, @code{SAVE}
1226Treat each program unit (except those marked as RECURSIVE) as if the
1227@code{SAVE} statement were specified for every local variable and array
1228referenced in it. Does not affect common blocks. (Some Fortran compilers
1229provide this option under the name @option{-static} or @option{-save}.)
1230The default, which is @option{-fautomatic}, uses the stack for local
1231variables smaller than the value given by @option{-fmax-stack-var-size}.
1232Use the option @option{-frecursive} to use no static memory. 
1233
1234@item -ff2c
1235@opindex ff2c
1236@cindex calling convention
1237@cindex @command{f2c} calling convention
1238@cindex @command{g77} calling convention
1239@cindex libf2c calling convention
1240Generate code designed to be compatible with code generated
1241by @command{g77} and @command{f2c}.
1242
1243The calling conventions used by @command{g77} (originally implemented
1244in @command{f2c}) require functions that return type
1245default @code{REAL} to actually return the C type @code{double}, and
1246functions that return type @code{COMPLEX} to return the values via an
1247extra argument in the calling sequence that points to where to
1248store the return value.  Under the default GNU calling conventions, such
1249functions simply return their results as they would in GNU
1250C---default @code{REAL} functions return the C type @code{float}, and
1251@code{COMPLEX} functions return the GNU C type @code{complex}.
1252Additionally, this option implies the @option{-fsecond-underscore}
1253option, unless @option{-fno-second-underscore} is explicitly requested.
1254
1255This does not affect the generation of code that interfaces with
1256the @command{libgfortran} library.
1257
1258@emph{Caution:} It is not a good idea to mix Fortran code compiled with
1259@option{-ff2c} with code compiled with the default @option{-fno-f2c}
1260calling conventions as, calling @code{COMPLEX} or default @code{REAL}
1261functions between program parts which were compiled with different
1262calling conventions will break at execution time.
1263
1264@emph{Caution:} This will break code which passes intrinsic functions
1265of type default @code{REAL} or @code{COMPLEX} as actual arguments, as
1266the library implementations use the @option{-fno-f2c} calling conventions.
1267
1268@item -fno-underscoring
1269@opindex @code{fno-underscoring}
1270@cindex underscore
1271@cindex symbol names, underscores
1272@cindex transforming symbol names
1273@cindex symbol names, transforming
1274Do not transform names of entities specified in the Fortran
1275source file by appending underscores to them.
1276
1277With @option{-funderscoring} in effect, GNU Fortran appends one
1278underscore to external names with no underscores.  This is done to ensure
1279compatibility with code produced by many UNIX Fortran compilers.
1280
1281@emph{Caution}: The default behavior of GNU Fortran is
1282incompatible with @command{f2c} and @command{g77}, please use the
1283@option{-ff2c} option if you want object files compiled with
1284GNU Fortran to be compatible with object code created with these
1285tools.
1286
1287Use of @option{-fno-underscoring} is not recommended unless you are
1288experimenting with issues such as integration of GNU Fortran into
1289existing system environments (vis-@`{a}-vis existing libraries, tools,
1290and so on).
1291
1292For example, with @option{-funderscoring}, and assuming that @code{j()} and
1293@code{max_count()} are external functions while @code{my_var} and
1294@code{lvar} are local variables, a statement like
1295@smallexample
1296I = J() + MAX_COUNT (MY_VAR, LVAR)
1297@end smallexample
1298@noindent
1299is implemented as something akin to:
1300@smallexample
1301i = j_() + max_count__(&my_var__, &lvar);
1302@end smallexample
1303
1304With @option{-fno-underscoring}, the same statement is implemented as:
1305
1306@smallexample
1307i = j() + max_count(&my_var, &lvar);
1308@end smallexample
1309
1310Use of @option{-fno-underscoring} allows direct specification of
1311user-defined names while debugging and when interfacing GNU Fortran
1312code with other languages.
1313
1314Note that just because the names match does @emph{not} mean that the
1315interface implemented by GNU Fortran for an external name matches the
1316interface implemented by some other language for that same name.
1317That is, getting code produced by GNU Fortran to link to code produced
1318by some other compiler using this or any other method can be only a
1319small part of the overall solution---getting the code generated by
1320both compilers to agree on issues other than naming can require
1321significant effort, and, unlike naming disagreements, linkers normally
1322cannot detect disagreements in these other areas.
1323
1324Also, note that with @option{-fno-underscoring}, the lack of appended
1325underscores introduces the very real possibility that a user-defined
1326external name will conflict with a name in a system library, which
1327could make finding unresolved-reference bugs quite difficult in some
1328cases---they might occur at program run time, and show up only as
1329buggy behavior at run time.
1330
1331In future versions of GNU Fortran we hope to improve naming and linking
1332issues so that debugging always involves using the names as they appear
1333in the source, even if the names as seen by the linker are mangled to
1334prevent accidental linking between procedures with incompatible
1335interfaces.
1336
1337@item -fsecond-underscore
1338@opindex @code{fsecond-underscore}
1339@cindex underscore
1340@cindex symbol names, underscores
1341@cindex transforming symbol names
1342@cindex symbol names, transforming
1343@cindex @command{f2c} calling convention
1344@cindex @command{g77} calling convention
1345@cindex libf2c calling convention
1346By default, GNU Fortran appends an underscore to external
1347names.  If this option is used GNU Fortran appends two
1348underscores to names with underscores and one underscore to external names
1349with no underscores.  GNU Fortran also appends two underscores to
1350internal names with underscores to avoid naming collisions with external
1351names.
1352
1353This option has no effect if @option{-fno-underscoring} is
1354in effect.  It is implied by the @option{-ff2c} option.
1355
1356Otherwise, with this option, an external name such as @code{MAX_COUNT}
1357is implemented as a reference to the link-time external symbol
1358@code{max_count__}, instead of @code{max_count_}.  This is required
1359for compatibility with @command{g77} and @command{f2c}, and is implied
1360by use of the @option{-ff2c} option.
1361
1362@item -fcoarray=@var{<keyword>}
1363@opindex @code{fcoarray}
1364@cindex coarrays
1365
1366@table @asis
1367@item @samp{none}
1368Disable coarray support; using coarray declarations and image-control
1369statements will produce a compile-time error. (Default)
1370
1371@item @samp{single}
1372Single-image mode, i.e. @code{num_images()} is always one.
1373
1374@item @samp{lib}
1375Library-based coarray parallelization; a suitable GNU Fortran coarray
1376library needs to be linked.
1377@end table
1378
1379
1380@item -fcheck=@var{<keyword>}
1381@opindex @code{fcheck}
1382@cindex array, bounds checking
1383@cindex bounds checking
1384@cindex pointer checking
1385@cindex memory checking
1386@cindex range checking
1387@cindex subscript checking
1388@cindex checking subscripts
1389@cindex run-time checking
1390@cindex checking array temporaries
1391
1392Enable the generation of run-time checks; the argument shall be
1393a comma-delimited list of the following keywords.
1394
1395@table @asis
1396@item @samp{all}
1397Enable all run-time test of @option{-fcheck}.
1398
1399@item @samp{array-temps}
1400Warns at run time when for passing an actual argument a temporary array
1401had to be generated. The information generated by this warning is
1402sometimes useful in optimization, in order to avoid such temporaries.
1403
1404Note: The warning is only printed once per location.
1405
1406@item @samp{bounds}
1407Enable generation of run-time checks for array subscripts
1408and against the declared minimum and maximum values.  It also
1409checks array indices for assumed and deferred
1410shape arrays against the actual allocated bounds and ensures that all string
1411lengths are equal for character array constructors without an explicit
1412typespec.
1413
1414Some checks require that @option{-fcheck=bounds} is set for
1415the compilation of the main program.
1416
1417Note: In the future this may also include other forms of checking, e.g.,
1418checking substring references.
1419
1420@item @samp{do}
1421Enable generation of run-time checks for invalid modification of loop
1422iteration variables.
1423
1424@item @samp{mem}
1425Enable generation of run-time checks for memory allocation.
1426Note: This option does not affect explicit allocations using the
1427@code{ALLOCATE} statement, which will be always checked.
1428
1429@item @samp{pointer}
1430Enable generation of run-time checks for pointers and allocatables.
1431
1432@item @samp{recursion}
1433Enable generation of run-time checks for recursively called subroutines and
1434functions which are not marked as recursive. See also @option{-frecursive}.
1435Note: This check does not work for OpenMP programs and is disabled if used
1436together with @option{-frecursive} and @option{-fopenmp}.
1437@end table
1438
1439
1440@item -fbounds-check
1441@opindex @code{fbounds-check}
1442@c Note: This option is also referred in gcc's manpage
1443Deprecated alias for @option{-fcheck=bounds}.
1444
1445@item -fcheck-array-temporaries
1446@opindex @code{fcheck-array-temporaries}
1447Deprecated alias for @option{-fcheck=array-temps}.
1448
1449@item -fmax-array-constructor=@var{n}
1450@opindex @code{fmax-array-constructor}
1451This option can be used to increase the upper limit permitted in 
1452array constructors.  The code below requires this option to expand
1453the array at compile time.
1454
1455@smallexample
1456program test
1457implicit none
1458integer j
1459integer, parameter :: n = 100000
1460integer, parameter :: i(n) = (/ (2*j, j = 1, n) /)
1461print '(10(I0,1X))', i
1462end program test
1463@end smallexample
1464
1465@emph{Caution:  This option can lead to long compile times and excessively
1466large object files.}
1467
1468The default value for @var{n} is 65535.
1469
1470
1471@item -fmax-stack-var-size=@var{n}
1472@opindex @code{fmax-stack-var-size}
1473This option specifies the size in bytes of the largest array that will be put
1474on the stack; if the size is exceeded static memory is used (except in
1475procedures marked as RECURSIVE). Use the option @option{-frecursive} to
1476allow for recursive procedures which do not have a RECURSIVE attribute or
1477for parallel programs. Use @option{-fno-automatic} to never use the stack.
1478
1479This option currently only affects local arrays declared with constant
1480bounds, and may not apply to all character variables.
1481Future versions of GNU Fortran may improve this behavior.
1482
1483The default value for @var{n} is 32768.
1484
1485@item -fstack-arrays
1486@opindex @code{fstack-arrays}
1487Adding this option will make the Fortran compiler put all local arrays,
1488even those of unknown size onto stack memory.  If your program uses very
1489large local arrays it is possible that you will have to extend your runtime
1490limits for stack memory on some operating systems. This flag is enabled
1491by default at optimization level @option{-Ofast}.
1492
1493
1494@item -fpack-derived
1495@opindex @code{fpack-derived}
1496@cindex structure packing
1497This option tells GNU Fortran to pack derived type members as closely as
1498possible.  Code compiled with this option is likely to be incompatible
1499with code compiled without this option, and may execute slower.
1500
1501@item -frepack-arrays
1502@opindex @code{frepack-arrays}
1503@cindex repacking arrays
1504In some circumstances GNU Fortran may pass assumed shape array
1505sections via a descriptor describing a noncontiguous area of memory.
1506This option adds code to the function prologue to repack the data into
1507a contiguous block at runtime.
1508
1509This should result in faster accesses to the array.  However it can introduce
1510significant overhead to the function call, especially  when the passed data
1511is noncontiguous.
1512
1513@item -fshort-enums
1514@opindex @code{fshort-enums}
1515This option is provided for interoperability with C code that was
1516compiled with the @option{-fshort-enums} option.  It will make
1517GNU Fortran choose the smallest @code{INTEGER} kind a given
1518enumerator set will fit in, and give all its enumerators this kind.
1519
1520@item -fexternal-blas
1521@opindex @code{fexternal-blas}
1522This option will make @command{gfortran} generate calls to BLAS functions
1523for some matrix operations like @code{MATMUL}, instead of using our own
1524algorithms, if the size of the matrices involved is larger than a given
1525limit (see @option{-fblas-matmul-limit}).  This may be profitable if an
1526optimized vendor BLAS library is available.  The BLAS library will have
1527to be specified at link time.
1528
1529@item -fblas-matmul-limit=@var{n}
1530@opindex @code{fblas-matmul-limit}
1531Only significant when @option{-fexternal-blas} is in effect.
1532Matrix multiplication of matrices with size larger than (or equal to) @var{n}
1533will be performed by calls to BLAS functions, while others will be
1534handled by @command{gfortran} internal algorithms. If the matrices
1535involved are not square, the size comparison is performed using the
1536geometric mean of the dimensions of the argument and result matrices.
1537
1538The default value for @var{n} is 30.
1539
1540@item -frecursive
1541@opindex @code{frecursive}
1542Allow indirect recursion by forcing all local arrays to be allocated
1543on the stack. This flag cannot be used together with
1544@option{-fmax-stack-var-size=} or @option{-fno-automatic}.
1545
1546@item -finit-local-zero
1547@itemx -finit-integer=@var{n}
1548@itemx -finit-real=@var{<zero|inf|-inf|nan|snan>}
1549@itemx -finit-logical=@var{<true|false>}
1550@itemx -finit-character=@var{n}
1551@opindex @code{finit-local-zero}
1552@opindex @code{finit-integer}
1553@opindex @code{finit-real}
1554@opindex @code{finit-logical}
1555@opindex @code{finit-character}
1556The @option{-finit-local-zero} option instructs the compiler to
1557initialize local @code{INTEGER}, @code{REAL}, and @code{COMPLEX}
1558variables to zero, @code{LOGICAL} variables to false, and
1559@code{CHARACTER} variables to a string of null bytes.  Finer-grained
1560initialization options are provided by the
1561@option{-finit-integer=@var{n}},
1562@option{-finit-real=@var{<zero|inf|-inf|nan|snan>}} (which also initializes
1563the real and imaginary parts of local @code{COMPLEX} variables),
1564@option{-finit-logical=@var{<true|false>}}, and
1565@option{-finit-character=@var{n}} (where @var{n} is an ASCII character
1566value) options.  These options do not initialize
1567@itemize @bullet
1568@item
1569allocatable arrays
1570@item
1571components of derived type variables
1572@item
1573variables that appear in an @code{EQUIVALENCE} statement.
1574@end itemize
1575(These limitations may be removed in future releases).
1576
1577Note that the @option{-finit-real=nan} option initializes @code{REAL}
1578and @code{COMPLEX} variables with a quiet NaN. For a signalling NaN
1579use @option{-finit-real=snan}; note, however, that compile-time
1580optimizations may convert them into quiet NaN and that trapping
1581needs to be enabled (e.g. via @option{-ffpe-trap}).
1582
1583Finally, note that enabling any of the @option{-finit-*} options will
1584silence warnings that would have been emitted by @option{-Wuninitialized}
1585for the affected local variables.
1586
1587@item -falign-commons
1588@opindex @code{falign-commons}
1589@cindex alignment of @code{COMMON} blocks
1590By default, @command{gfortran} enforces proper alignment of all variables in a
1591@code{COMMON} block by padding them as needed. On certain platforms this is mandatory,
1592on others it increases performance. If a @code{COMMON} block is not declared with
1593consistent data types everywhere, this padding can cause trouble, and
1594@option{-fno-align-commons} can be used to disable automatic alignment. The
1595same form of this option should be used for all files that share a @code{COMMON} block.
1596To avoid potential alignment issues in @code{COMMON} blocks, it is recommended to order
1597objects from largest to smallest.
1598
1599@item -fno-protect-parens
1600@opindex @code{fno-protect-parens}
1601@cindex re-association of parenthesized expressions
1602By default the parentheses in expression are honored for all optimization
1603levels such that the compiler does not do any re-association. Using
1604@option{-fno-protect-parens} allows the compiler to reorder @code{REAL} and
1605@code{COMPLEX} expressions to produce faster code. Note that for the re-association
1606optimization @option{-fno-signed-zeros} and @option{-fno-trapping-math}
1607need to be in effect. The parentheses protection is enabled by default, unless
1608@option{-Ofast} is given.
1609
1610@item -frealloc-lhs
1611@opindex @code{frealloc-lhs}
1612@cindex Reallocate the LHS in assignments
1613An allocatable left-hand side of an intrinsic assignment is automatically
1614(re)allocated if it is either unallocated or has a different shape. The
1615option is enabled by default except when @option{-std=f95} is given. See
1616also @option{-Wrealloc-lhs}.
1617
1618@item -faggressive-function-elimination
1619@opindex @code{faggressive-function-elimination}
1620@cindex Elimination of functions with identical argument lists
1621Functions with identical argument lists are eliminated within
1622statements, regardless of whether these functions are marked
1623@code{PURE} or not. For example, in
1624@smallexample
1625  a = f(b,c) + f(b,c)
1626@end smallexample
1627there will only be a single call to @code{f}.  This option only works
1628if @option{-ffrontend-optimize} is in effect.
1629
1630@item -ffrontend-optimize
1631@opindex @code{frontend-optimize}
1632@cindex Front-end optimization
1633This option performs front-end optimization, based on manipulating
1634parts the Fortran parse tree.  Enabled by default by any @option{-O}
1635option.  Optimizations enabled by this option include elimination of
1636identical function calls within expressions, removing unnecessary
1637calls to @code{TRIM} in comparisons and assignments and replacing
1638@code{TRIM(a)} with @code{a(1:LEN_TRIM(a))}. 
1639It can be deselected by specifying @option{-fno-frontend-optimize}.
1640@end table
1641
1642@xref{Code Gen Options,,Options for Code Generation Conventions,
1643gcc,Using the GNU Compiler Collection (GCC)}, for information on more options
1644offered by the GBE
1645shared by @command{gfortran}, @command{gcc}, and other GNU compilers.
1646
1647@c man end
1648
1649@node Environment Variables
1650@section Environment variables affecting @command{gfortran}
1651@cindex environment variable
1652
1653@c man begin ENVIRONMENT
1654
1655The @command{gfortran} compiler currently does not make use of any environment
1656variables to control its operation above and beyond those
1657that affect the operation of @command{gcc}.
1658
1659@xref{Environment Variables,,Environment Variables Affecting GCC,
1660gcc,Using the GNU Compiler Collection (GCC)}, for information on environment
1661variables.
1662
1663@xref{Runtime}, for environment variables that affect the
1664run-time behavior of programs compiled with GNU Fortran.
1665@c man end
1666