1GFORTRAN(1)                           GNU                          GFORTRAN(1)
2
3
4

NAME

6       gfortran - GNU Fortran compiler
7

SYNOPSIS

9       gfortran [-c|-S|-E]
10                [-g] [-pg] [-Olevel]
11                [-Wwarn...] [-pedantic]
12                [-Idir...] [-Ldir...]
13                [-Dmacro[=defn]...] [-Umacro]
14                [-foption...]
15                [-mmachine-option...]
16                [-o outfile] infile...
17
18       Only the most useful options are listed here; see below for the
19       remainder.
20

DESCRIPTION

22       The gfortran command supports all the options supported by the gcc
23       command.  Only options specific to GNU Fortran are documented here.
24
25       All GCC and GNU Fortran options are accepted both by gfortran and by
26       gcc (as well as any other drivers built at the same time, such as g++),
27       since adding GNU Fortran to the GCC distribution enables acceptance of
28       GNU Fortran options by all of the relevant drivers.
29
30       In some cases, options have positive and negative forms; the negative
31       form of -ffoo would be -fno-foo.  This manual documents only one of
32       these two forms, whichever one is not the default.
33

OPTIONS

35       Here is a summary of all the options specific to GNU Fortran, grouped
36       by type.  Explanations are in the following sections.
37
38       Fortran Language Options
39           -fall-intrinsics -fbackslash -fcray-pointer -fd-lines-as-code
40           -fd-lines-as-comments -fdefault-double-8 -fdefault-integer-8
41           -fdefault-real-8 -fdollar-ok -ffixed-line-length-n
42           -ffixed-line-length-none -ffree-form -ffree-line-length-n
43           -ffree-line-length-none -fimplicit-none -finteger-4-integer-8
44           -fmax-identifier-length -fmodule-private -fno-fixed-form
45           -fno-range-check -fopenmp -freal-4-real-10 -freal-4-real-16
46           -freal-4-real-8 -freal-8-real-10 -freal-8-real-16 -freal-8-real-4
47           -std=std
48
49       Preprocessing Options
50           -A-question[=answer] -Aquestion=answer -C -CC -Dmacro[=defn] -H -P
51           -Umacro -cpp -dD -dI -dM -dN -dU -fworking-directory -imultilib dir
52           -iprefix file -iquote -isysroot dir -isystem dir -nocpp -nostdinc
53           -undef
54
55       Error and Warning Options
56           -Waliasing -Wall -Wampersand -Warray-bounds -Wc-binding-type
57           -Wcharacter-truncation -Wconversion -Wfunction-elimination
58           -Wimplicit-interface -Wimplicit-procedure -Wintrinsic-shadow
59           -Wintrinsics-std -Wline-truncation -Wno-align-commons -Wno-tabs
60           -Wreal-q-constant -Wsurprising -Wunderflow -Wunused-parameter
61           -Wrealloc-lhs Wrealloc-lhs-all -Wtarget-lifetime -fmax-errors=n
62           -fsyntax-only -pedantic -pedantic-errors
63
64       Debugging Options
65           -fbacktrace -fdump-fortran-optimized -fdump-fortran-original
66           -fdump-parse-tree -ffpe-trap=list
67
68       Directory Options
69           -Idir  -Jdir -fintrinsic-modules-path dir
70
71       Link Options
72           -static-libgfortran
73
74       Runtime Options
75           -fconvert=conversion -fmax-subrecord-length=length
76           -frecord-marker=length -fsign-zero
77
78       Code Generation Options
79           -faggressive-function-elimination -fblas-matmul-limit=n
80           -fbounds-check -fcheck-array-temporaries
81           -fcheck=<all|array-temps|bounds|do|mem|pointer|recursion>
82           -fcoarray=<none|single|lib> -fexternal-blas -ff2c
83           -ffrontend-optimize -finit-character=n -finit-integer=n
84           -finit-local-zero -finit-logical=<true|false>
85           -finit-real=<zero|inf|-inf|nan|snan> -fmax-array-constructor=n
86           -fmax-stack-var-size=n -fno-align-commons -fno-automatic
87           -fno-protect-parens -fno-underscoring -fno-whole-file
88           -fsecond-underscore -fpack-derived -frealloc-lhs -frecursive
89           -frepack-arrays -fshort-enums -fstack-arrays
90
91   Options controlling Fortran dialect
92       The following options control the details of the Fortran dialect
93       accepted by the compiler:
94
95       -ffree-form
96       -ffixed-form
97           Specify the layout used by the source file.  The free form layout
98           was introduced in Fortran 90.  Fixed form was traditionally used in
99           older Fortran programs.  When neither option is specified, the
100           source form is determined by the file extension.
101
102       -fall-intrinsics
103           This option causes all intrinsic procedures (including the GNU-
104           specific extensions) to be accepted.  This can be useful with
105           -std=f95 to force standard-compliance but get access to the full
106           range of intrinsics available with gfortran.  As a consequence,
107           -Wintrinsics-std will be ignored and no user-defined procedure with
108           the same name as any intrinsic will be called except when it is
109           explicitly declared "EXTERNAL".
110
111       -fd-lines-as-code
112       -fd-lines-as-comments
113           Enable special treatment for lines beginning with "d" or "D" in
114           fixed form sources.  If the -fd-lines-as-code option is given they
115           are treated as if the first column contained a blank.  If the
116           -fd-lines-as-comments option is given, they are treated as comment
117           lines.
118
119       -fdefault-double-8
120           Set the "DOUBLE PRECISION" type to an 8 byte wide type.  If
121           -fdefault-real-8 is given, "DOUBLE PRECISION" would instead be
122           promoted to 16 bytes if possible, and -fdefault-double-8 can be
123           used to prevent this.  The kind of real constants like "1.d0" will
124           not be changed by -fdefault-real-8 though, so also
125           -fdefault-double-8 does not affect it.
126
127       -fdefault-integer-8
128           Set the default integer and logical types to an 8 byte wide type.
129           Do nothing if this is already the default.  This option also
130           affects the kind of integer constants like 42.
131
132       -fdefault-real-8
133           Set the default real type to an 8 byte wide type.  Do nothing if
134           this is already the default.  This option also affects the kind of
135           non-double real constants like 1.0, and does promote the default
136           width of "DOUBLE PRECISION" to 16 bytes if possible, unless
137           "-fdefault-double-8" is given, too.
138
139       -fdollar-ok
140           Allow $ as a valid non-first character in a symbol name. Symbols
141           that start with $ are rejected since it is unclear which rules to
142           apply to implicit typing as different vendors implement different
143           rules.  Using $ in "IMPLICIT" statements is also rejected.
144
145       -fbackslash
146           Change the interpretation of backslashes in string literals from a
147           single backslash character to "C-style" escape characters. The
148           following combinations are expanded "\a", "\b", "\f", "\n", "\r",
149           "\t", "\v", "\\", and "\0" to the ASCII characters alert,
150           backspace, form feed, newline, carriage return, horizontal tab,
151           vertical tab, backslash, and NUL, respectively.  Additionally,
152           "\x"nn, "\u"nnnn and "\U"nnnnnnnn (where each n is a hexadecimal
153           digit) are translated into the Unicode characters corresponding to
154           the specified code points. All other combinations of a character
155           preceded by \ are unexpanded.
156
157       -fmodule-private
158           Set the default accessibility of module entities to "PRIVATE".
159           Use-associated entities will not be accessible unless they are
160           explicitly declared as "PUBLIC".
161
162       -ffixed-line-length-n
163           Set column after which characters are ignored in typical fixed-form
164           lines in the source file, and through which spaces are assumed (as
165           if padded to that length) after the ends of short fixed-form lines.
166
167           Popular values for n include 72 (the standard and the default), 80
168           (card image), and 132 (corresponding to "extended-source" options
169           in some popular compilers).  n may also be none, meaning that the
170           entire line is meaningful and that continued character constants
171           never have implicit spaces appended to them to fill out the line.
172           -ffixed-line-length-0 means the same thing as
173           -ffixed-line-length-none.
174
175       -ffree-line-length-n
176           Set column after which characters are ignored in typical free-form
177           lines in the source file. The default value is 132.  n may be none,
178           meaning that the entire line is meaningful.  -ffree-line-length-0
179           means the same thing as -ffree-line-length-none.
180
181       -fmax-identifier-length=n
182           Specify the maximum allowed identifier length. Typical values are
183           31 (Fortran 95) and 63 (Fortran 2003 and Fortran 2008).
184
185       -fimplicit-none
186           Specify that no implicit typing is allowed, unless overridden by
187           explicit "IMPLICIT" statements.  This is the equivalent of adding
188           "implicit none" to the start of every procedure.
189
190       -finteger-4-integer-8
191           Promote all "INTEGER(KIND=4)" entities to an "INTEGER(KIND=8)"
192           entities.  If "KIND=8" is unavailable, then an error will be
193           issued.  This option should be used with care and may not be
194           suitable for your codes.  Areas of possible concern include calls
195           to external procedures, alignment in "EQUIVALENCE" and/or "COMMON",
196           generic interfaces, BOZ literal constant conversion, and I/O.
197           Inspection of the intermediate representation of the translated
198           Fortran code, produced by -fdump-tree-original, is suggested.
199
200       -fcray-pointer
201           Enable the Cray pointer extension, which provides C-like pointer
202           functionality.
203
204       -fopenmp
205           Enable the OpenMP extensions.  This includes OpenMP "!$omp"
206           directives in free form and "c$omp", *$omp and "!$omp" directives
207           in fixed form, "!$" conditional compilation sentinels in free form
208           and "c$", "*$" and "!$" sentinels in fixed form, and when linking
209           arranges for the OpenMP runtime library to be linked in.  The
210           option -fopenmp implies -frecursive.
211
212       -fno-range-check
213           Disable range checking on results of simplification of constant
214           expressions during compilation.  For example, GNU Fortran will give
215           an error at compile time when simplifying "a = 1. / 0".  With this
216           option, no error will be given and "a" will be assigned the value
217           "+Infinity".  If an expression evaluates to a value outside of the
218           relevant range of ["-HUGE()":"HUGE()"], then the expression will be
219           replaced by "-Inf" or "+Inf" as appropriate.  Similarly, "DATA
220           i/Z'FFFFFFFF'/" will result in an integer overflow on most systems,
221           but with -fno-range-check the value will "wrap around" and "i" will
222           be initialized to -1 instead.
223
224       -freal-4-real-8
225       -freal-4-real-10
226       -freal-8-real-4
227       -freal-8-real-10
228       -freal-8-real-16
229           Promote all "REAL(KIND=M)" entities to "REAL(KIND=N)" entities.  If
230           "REAL(KIND=N)" is unavailable, then an error will be issued.  All
231           other real kind types are unaffected by this option.  These options
232           should be used with care and may not be suitable for your codes.
233           Areas of possible concern include calls to external procedures,
234           alignment in "EQUIVALENCE" and/or "COMMON", generic interfaces, BOZ
235           literal constant conversion, and I/O.  Inspection of the
236           intermediate representation of the translated Fortran code,
237           produced by -fdump-tree-original, is suggested.
238
239       -std=std
240           Specify the standard to which the program is expected to conform,
241           which may be one of f95, f2003, f2008, gnu, or legacy.  The default
242           value for std is gnu, which specifies a superset of the Fortran 95
243           standard that includes all of the extensions supported by GNU
244           Fortran, although warnings will be given for obsolete extensions
245           not recommended for use in new code.  The legacy value is
246           equivalent but without the warnings for obsolete extensions, and
247           may be useful for old non-standard programs.  The f95, f2003 and
248           f2008 values specify strict conformance to the Fortran 95, Fortran
249           2003 and Fortran 2008 standards, respectively; errors are given for
250           all extensions beyond the relevant language standard, and warnings
251           are given for the Fortran 77 features that are permitted but
252           obsolescent in later standards. -std=f2008ts allows the Fortran
253           2008 standard including the additions of the Technical
254           Specification (TS) 29113 on Further Interoperability of Fortran
255           with C.
256
257   Enable and customize preprocessing
258       Preprocessor related options. See section Preprocessing and conditional
259       compilation for more detailed information on preprocessing in gfortran.
260
261       -cpp
262       -nocpp
263           Enable preprocessing. The preprocessor is automatically invoked if
264           the file extension is .fpp, .FPP,  .F, .FOR, .FTN, .F90, .F95, .F03
265           or .F08. Use this option to manually enable preprocessing of any
266           kind of Fortran file.
267
268           To disable preprocessing of files with any of the above listed
269           extensions, use the negative form: -nocpp.
270
271           The preprocessor is run in traditional mode. Any restrictions of
272           the file-format, especially the limits on line length, apply for
273           preprocessed output as well, so it might be advisable to use the
274           -ffree-line-length-none or -ffixed-line-length-none options.
275
276       -dM Instead of the normal output, generate a list of '#define'
277           directives for all the macros defined during the execution of the
278           preprocessor, including predefined macros. This gives you a way of
279           finding out what is predefined in your version of the preprocessor.
280           Assuming you have no file foo.f90, the command
281
282                     touch foo.f90; gfortran -cpp -E -dM foo.f90
283
284           will show all the predefined macros.
285
286       -dD Like -dM except in two respects: it does not include the predefined
287           macros, and it outputs both the "#define" directives and the result
288           of preprocessing. Both kinds of output go to the standard output
289           file.
290
291       -dN Like -dD, but emit only the macro names, not their expansions.
292
293       -dU Like dD except that only macros that are expanded, or whose
294           definedness is tested in preprocessor directives, are output; the
295           output is delayed until the use or test of the macro; and '#undef'
296           directives are also output for macros tested but undefined at the
297           time.
298
299       -dI Output '#include' directives in addition to the result of
300           preprocessing.
301
302       -fworking-directory
303           Enable generation of linemarkers in the preprocessor output that
304           will let the compiler know the current working directory at the
305           time of preprocessing. When this option is enabled, the
306           preprocessor will emit, after the initial linemarker, a second
307           linemarker with the current working directory followed by two
308           slashes. GCC will use this directory, when it is present in the
309           preprocessed input, as the directory emitted as the current working
310           directory in some debugging information formats.  This option is
311           implicitly enabled if debugging information is enabled, but this
312           can be inhibited with the negated form -fno-working-directory. If
313           the -P flag is present in the command line, this option has no
314           effect, since no "#line" directives are emitted whatsoever.
315
316       -idirafter dir
317           Search dir for include files, but do it after all directories
318           specified with -I and the standard system directories have been
319           exhausted. dir is treated as a system include directory.  If dir
320           begins with "=", then the "=" will be replaced by the sysroot
321           prefix; see --sysroot and -isysroot.
322
323       -imultilib dir
324           Use dir as a subdirectory of the directory containing target-
325           specific C++ headers.
326
327       -iprefix prefix
328           Specify prefix as the prefix for subsequent -iwithprefix options.
329           If the prefix represents a directory, you should include the final
330           '/'.
331
332       -isysroot dir
333           This option is like the --sysroot option, but applies only to
334           header files. See the --sysroot option for more information.
335
336       -iquote dir
337           Search dir only for header files requested with "#include "file"";
338           they are not searched for "#include <file>", before all directories
339           specified by -I and before the standard system directories. If dir
340           begins with "=", then the "=" will be replaced by the sysroot
341           prefix; see --sysroot and -isysroot.
342
343       -isystem dir
344           Search dir for header files, after all directories specified by -I
345           but before the standard system directories. Mark it as a system
346           directory, so that it gets the same special treatment as is applied
347           to the standard system directories. If dir begins with "=", then
348           the "=" will be replaced by the sysroot prefix; see --sysroot and
349           -isysroot.
350
351       -nostdinc
352           Do not search the standard system directories for header files.
353           Only the directories you have specified with -I options (and the
354           directory of the current file, if appropriate) are searched.
355
356       -undef
357           Do not predefine any system-specific or GCC-specific macros.  The
358           standard predefined macros remain defined.
359
360       -Apredicate=answer
361           Make an assertion with the predicate predicate and answer answer.
362           This form is preferred to the older form -A predicate(answer),
363           which is still supported, because it does not use shell special
364           characters.
365
366       -A-predicate=answer
367           Cancel an assertion with the predicate predicate and answer answer.
368
369       -C  Do not discard comments. All comments are passed through to the
370           output file, except for comments in processed directives, which are
371           deleted along with the directive.
372
373           You should be prepared for side effects when using -C; it causes
374           the preprocessor to treat comments as tokens in their own right.
375           For example, comments appearing at the start of what would be a
376           directive line have the effect of turning that line into an
377           ordinary source line, since the first token on the line is no
378           longer a '#'.
379
380           Warning: this currently handles C-Style comments only. The
381           preprocessor does not yet recognize Fortran-style comments.
382
383       -CC Do not discard comments, including during macro expansion. This is
384           like -C, except that comments contained within macros are also
385           passed through to the output file where the macro is expanded.
386
387           In addition to the side-effects of the -C option, the -CC option
388           causes all C++-style comments inside a macro to be converted to
389           C-style comments. This is to prevent later use of that macro from
390           inadvertently commenting out the remainder of the source line. The
391           -CC option is generally used to support lint comments.
392
393           Warning: this currently handles C- and C++-Style comments only. The
394           preprocessor does not yet recognize Fortran-style comments.
395
396       -Dname
397           Predefine name as a macro, with definition 1.
398
399       -Dname=definition
400           The contents of definition are tokenized and processed as if they
401           appeared during translation phase three in a '#define' directive.
402           In particular, the definition will be truncated by embedded newline
403           characters.
404
405           If you are invoking the preprocessor from a shell or shell-like
406           program you may need to use the shell's quoting syntax to protect
407           characters such as spaces that have a meaning in the shell syntax.
408
409           If you wish to define a function-like macro on the command line,
410           write its argument list with surrounding parentheses before the
411           equals sign (if any). Parentheses are meaningful to most shells, so
412           you will need to quote the option. With sh and csh,
413           "-D'name(args...)=definition'" works.
414
415           -D and -U options are processed in the order they are given on the
416           command line. All -imacros file and -include file options are
417           processed after all -D and -U options.
418
419       -H  Print the name of each header file used, in addition to other
420           normal activities. Each name is indented to show how deep in the
421           '#include' stack it is.
422
423       -P  Inhibit generation of linemarkers in the output from the
424           preprocessor.  This might be useful when running the preprocessor
425           on something that is not C code, and will be sent to a program
426           which might be confused by the linemarkers.
427
428       -Uname
429           Cancel any previous definition of name, either built in or provided
430           with a -D option.
431
432   Options to request or suppress errors and warnings
433       Errors are diagnostic messages that report that the GNU Fortran
434       compiler cannot compile the relevant piece of source code.  The
435       compiler will continue to process the program in an attempt to report
436       further errors to aid in debugging, but will not produce any compiled
437       output.
438
439       Warnings are diagnostic messages that report constructions which are
440       not inherently erroneous but which are risky or suggest there is likely
441       to be a bug in the program.  Unless -Werror is specified, they do not
442       prevent compilation of the program.
443
444       You can request many specific warnings with options beginning -W, for
445       example -Wimplicit to request warnings on implicit declarations.  Each
446       of these specific warning options also has a negative form beginning
447       -Wno- to turn off warnings; for example, -Wno-implicit.  This manual
448       lists only one of the two forms, whichever is not the default.
449
450       These options control the amount and kinds of errors and warnings
451       produced by GNU Fortran:
452
453       -fmax-errors=n
454           Limits the maximum number of error messages to n, at which point
455           GNU Fortran bails out rather than attempting to continue processing
456           the source code.  If n is 0, there is no limit on the number of
457           error messages produced.
458
459       -fsyntax-only
460           Check the code for syntax errors, but do not actually compile it.
461           This will generate module files for each module present in the
462           code, but no other output file.
463
464       -pedantic
465           Issue warnings for uses of extensions to Fortran 95.  -pedantic
466           also applies to C-language constructs where they occur in GNU
467           Fortran source files, such as use of \e in a character constant
468           within a directive like "#include".
469
470           Valid Fortran 95 programs should compile properly with or without
471           this option.  However, without this option, certain GNU extensions
472           and traditional Fortran features are supported as well.  With this
473           option, many of them are rejected.
474
475           Some users try to use -pedantic to check programs for conformance.
476           They soon find that it does not do quite what they want---it finds
477           some nonstandard practices, but not all.  However, improvements to
478           GNU Fortran in this area are welcome.
479
480           This should be used in conjunction with -std=f95, -std=f2003 or
481           -std=f2008.
482
483       -pedantic-errors
484           Like -pedantic, except that errors are produced rather than
485           warnings.
486
487       -Wall
488           Enables commonly used warning options pertaining to usage that we
489           recommend avoiding and that we believe are easy to avoid.  This
490           currently includes -Waliasing, -Wampersand, -Wconversion,
491           -Wsurprising, -Wc-binding-type, -Wintrinsics-std, -Wno-tabs,
492           -Wintrinsic-shadow, -Wline-truncation, -Wtarget-lifetime,
493           -Wreal-q-constant and -Wunused.
494
495       -Waliasing
496           Warn about possible aliasing of dummy arguments. Specifically, it
497           warns if the same actual argument is associated with a dummy
498           argument with "INTENT(IN)" and a dummy argument with "INTENT(OUT)"
499           in a call with an explicit interface.
500
501           The following example will trigger the warning.
502
503                     interface
504                       subroutine bar(a,b)
505                         integer, intent(in) :: a
506                         integer, intent(out) :: b
507                       end subroutine
508                     end interface
509                     integer :: a
510
511                     call bar(a,a)
512
513       -Wampersand
514           Warn about missing ampersand in continued character constants. The
515           warning is given with -Wampersand, -pedantic, -std=f95, -std=f2003
516           and -std=f2008. Note: With no ampersand given in a continued
517           character constant, GNU Fortran assumes continuation at the first
518           non-comment, non-whitespace character after the ampersand that
519           initiated the continuation.
520
521       -Warray-temporaries
522           Warn about array temporaries generated by the compiler.  The
523           information generated by this warning is sometimes useful in
524           optimization, in order to avoid such temporaries.
525
526       -Wc-binding-type
527           Warn if the a variable might not be C interoperable.  In
528           particular, warn if the variable has been declared using an
529           intrinsic type with default kind instead of using a kind parameter
530           defined for C interoperability in the intrinsic "ISO_C_Binding"
531           module.  This option is implied by -Wall.
532
533       -Wcharacter-truncation
534           Warn when a character assignment will truncate the assigned string.
535
536       -Wline-truncation
537           Warn when a source code line will be truncated.  This option is
538           implied by -Wall.
539
540       -Wconversion
541           Warn about implicit conversions that are likely to change the value
542           of the expression after conversion. Implied by -Wall.
543
544       -Wconversion-extra
545           Warn about implicit conversions between different types and kinds.
546
547       -Wextra
548           Enables some warning options for usages of language features which
549           may be problematic. This currently includes -Wcompare-reals and
550           -Wunused-parameter.
551
552       -Wimplicit-interface
553           Warn if a procedure is called without an explicit interface.  Note
554           this only checks that an explicit interface is present.  It does
555           not check that the declared interfaces are consistent across
556           program units.
557
558       -Wimplicit-procedure
559           Warn if a procedure is called that has neither an explicit
560           interface nor has been declared as "EXTERNAL".
561
562       -Wintrinsics-std
563           Warn if gfortran finds a procedure named like an intrinsic not
564           available in the currently selected standard (with -std) and treats
565           it as "EXTERNAL" procedure because of this.  -fall-intrinsics can
566           be used to never trigger this behavior and always link to the
567           intrinsic regardless of the selected standard.
568
569       -Wreal-q-constant
570           Produce a warning if a real-literal-constant contains a "q"
571           exponent-letter.
572
573       -Wsurprising
574           Produce a warning when "suspicious" code constructs are
575           encountered.  While technically legal these usually indicate that
576           an error has been made.
577
578           This currently produces a warning under the following
579           circumstances:
580
581           ·   An INTEGER SELECT construct has a CASE that can never be
582               matched as its lower value is greater than its upper value.
583
584           ·   A LOGICAL SELECT construct has three CASE statements.
585
586           ·   A TRANSFER specifies a source that is shorter than the
587               destination.
588
589           ·   The type of a function result is declared more than once with
590               the same type.  If -pedantic or standard-conforming mode is
591               enabled, this is an error.
592
593           ·   A "CHARACTER" variable is declared with negative length.
594
595       -Wtabs
596           By default, tabs are accepted as whitespace, but tabs are not
597           members of the Fortran Character Set.  For continuation lines, a
598           tab followed by a digit between 1 and 9 is supported.  -Wno-tabs
599           will cause a warning to be issued if a tab is encountered. Note,
600           -Wno-tabs is active for -pedantic, -std=f95, -std=f2003, -std=f2008
601           and -Wall.
602
603       -Wunderflow
604           Produce a warning when numerical constant expressions are
605           encountered, which yield an UNDERFLOW during compilation.
606
607       -Wintrinsic-shadow
608           Warn if a user-defined procedure or module procedure has the same
609           name as an intrinsic; in this case, an explicit interface or
610           "EXTERNAL" or "INTRINSIC" declaration might be needed to get calls
611           later resolved to the desired intrinsic/procedure.  This option is
612           implied by -Wall.
613
614       -Wunused-dummy-argument
615           Warn about unused dummy arguments. This option is implied by -Wall.
616
617       -Wunused-parameter
618           Contrary to gcc's meaning of -Wunused-parameter, gfortran's
619           implementation of this option does not warn about unused dummy
620           arguments (see -Wunused-dummy-argument), but about unused
621           "PARAMETER" values. -Wunused-parameter is not included in -Wall but
622           is implied by -Wall -Wextra.
623
624       -Walign-commons
625           By default, gfortran warns about any occasion of variables being
626           padded for proper alignment inside a "COMMON" block. This warning
627           can be turned off via -Wno-align-commons. See also -falign-commons.
628
629       -Wfunction-elimination
630           Warn if any calls to functions are eliminated by the optimizations
631           enabled by the -ffrontend-optimize option.
632
633       -Wrealloc-lhs
634           Warn when the compiler might insert code to for allocation or
635           reallocation of an allocatable array variable of intrinsic type in
636           intrinsic assignments.  In hot loops, the Fortran 2003 reallocation
637           feature may reduce the performance.  If the array is already
638           allocated with the correct shape, consider using a whole-array
639           array-spec (e.g. "(:,:,:)") for the variable on the left-hand side
640           to prevent the reallocation check. Note that in some cases the
641           warning is shown, even if the compiler will optimize reallocation
642           checks away.  For instance, when the right-hand side contains the
643           same variable multiplied by a scalar.  See also -frealloc-lhs.
644
645       -Wrealloc-lhs-all
646           Warn when the compiler inserts code to for allocation or
647           reallocation of an allocatable variable; this includes scalars and
648           derived types.
649
650       -Wcompare-reals
651           Warn when comparing real or complex types for equality or
652           inequality.  This option is implied by -Wextra.
653
654       -Wtarget-lifetime
655           Warn if the pointer in a pointer assignment might be longer than
656           the its target. This option is implied by -Wall.
657
658       -Werror
659           Turns all warnings into errors.
660
661       Some of these have no effect when compiling programs written in
662       Fortran.
663
664   Options for debugging your program or GNU Fortran
665       GNU Fortran has various special options that are used for debugging
666       either your program or the GNU Fortran compiler.
667
668       -fdump-fortran-original
669           Output the internal parse tree after translating the source program
670           into internal representation.  Only really useful for debugging the
671           GNU Fortran compiler itself.
672
673       -fdump-fortran-optimized
674           Output the parse tree after front-end optimization.  Only really
675           useful for debugging the GNU Fortran compiler itself.
676
677       -fdump-parse-tree
678           Output the internal parse tree after translating the source program
679           into internal representation.  Only really useful for debugging the
680           GNU Fortran compiler itself.  This option is deprecated; use
681           "-fdump-fortran-original" instead.
682
683       -ffpe-trap=list
684           Specify a list of floating point exception traps to enable.  On
685           most systems, if a floating point exception occurs and the trap for
686           that exception is enabled, a SIGFPE signal will be sent and the
687           program being aborted, producing a core file useful for debugging.
688           list is a (possibly empty) comma-separated list of the following
689           exceptions: invalid (invalid floating point operation, such as
690           "SQRT(-1.0)"), zero (division by zero), overflow (overflow in a
691           floating point operation), underflow (underflow in a floating point
692           operation), inexact (loss of precision during operation), and
693           denormal (operation performed on a denormal value).  The first five
694           exceptions correspond to the five IEEE 754 exceptions, whereas the
695           last one (denormal) is not part of the IEEE 754 standard but is
696           available on some common architectures such as x86.
697
698           The first three exceptions (invalid, zero, and overflow) often
699           indicate serious errors, and unless the program has provisions for
700           dealing with these exceptions, enabling traps for these three
701           exceptions is probably a good idea.
702
703           Many, if not most, floating point operations incur loss of
704           precision due to rounding, and hence the "ffpe-trap=inexact" is
705           likely to be uninteresting in practice.
706
707           By default no exception traps are enabled.
708
709       -fno-backtrace
710           When a serious runtime error is encountered or a deadly signal is
711           emitted (segmentation fault, illegal instruction, bus error,
712           floating-point exception, and the other POSIX signals that have the
713           action core), the Fortran runtime library tries to output a
714           backtrace of the error. "-fno-backtrace" disables the backtrace
715           generation. This option only has influence for compilation of the
716           Fortran main program.
717
718   Options for directory search
719       These options affect how GNU Fortran searches for files specified by
720       the "INCLUDE" directive and where it searches for previously compiled
721       modules.
722
723       It also affects the search paths used by cpp when used to preprocess
724       Fortran source.
725
726       -Idir
727           These affect interpretation of the "INCLUDE" directive (as well as
728           of the "#include" directive of the cpp preprocessor).
729
730           Also note that the general behavior of -I and "INCLUDE" is pretty
731           much the same as of -I with "#include" in the cpp preprocessor,
732           with regard to looking for header.gcc files and other such things.
733
734           This path is also used to search for .mod files when previously
735           compiled modules are required by a "USE" statement.
736
737       -Jdir
738           This option specifies where to put .mod files for compiled modules.
739           It is also added to the list of directories to searched by an "USE"
740           statement.
741
742           The default is the current directory.
743
744       -fintrinsic-modules-path dir
745           This option specifies the location of pre-compiled intrinsic
746           modules, if they are not in the default location expected by the
747           compiler.
748
749   Influencing the linking step
750       These options come into play when the compiler links object files into
751       an executable output file. They are meaningless if the compiler is not
752       doing a link step.
753
754       -static-libgfortran
755           On systems that provide libgfortran as a shared and a static
756           library, this option forces the use of the static version. If no
757           shared version of libgfortran was built when the compiler was
758           configured, this option has no effect.
759
760   Influencing runtime behavior
761       These options affect the runtime behavior of programs compiled with GNU
762       Fortran.
763
764       -fconvert=conversion
765           Specify the representation of data for unformatted files.  Valid
766           values for conversion are: native, the default; swap, swap between
767           big- and little-endian; big-endian, use big-endian representation
768           for unformatted files; little-endian, use little-endian
769           representation for unformatted files.
770
771           This option has an effect only when used in the main program.  The
772           "CONVERT" specifier and the GFORTRAN_CONVERT_UNIT environment
773           variable override the default specified by -fconvert.
774
775       -frecord-marker=length
776           Specify the length of record markers for unformatted files.  Valid
777           values for length are 4 and 8.  Default is 4.  This is different
778           from previous versions of gfortran, which specified a default
779           record marker length of 8 on most systems.  If you want to read or
780           write files compatible with earlier versions of gfortran, use
781           -frecord-marker=8.
782
783       -fmax-subrecord-length=length
784           Specify the maximum length for a subrecord.  The maximum permitted
785           value for length is 2147483639, which is also the default.  Only
786           really useful for use by the gfortran testsuite.
787
788       -fsign-zero
789           When enabled, floating point numbers of value zero with the sign
790           bit set are written as negative number in formatted output and
791           treated as negative in the "SIGN" intrinsic.  -fno-sign-zero does
792           not print the negative sign of zero values (or values rounded to
793           zero for I/O) and regards zero as positive number in the "SIGN"
794           intrinsic for compatibility with Fortran 77. The default is
795           -fsign-zero.
796
797   Options for code generation conventions
798       These machine-independent options control the interface conventions
799       used in code generation.
800
801       Most of them have both positive and negative forms; the negative form
802       of -ffoo would be -fno-foo.  In the table below, only one of the forms
803       is listed---the one which is not the default.  You can figure out the
804       other form by either removing no- or adding it.
805
806       -fno-automatic
807           Treat each program unit (except those marked as RECURSIVE) as if
808           the "SAVE" statement were specified for every local variable and
809           array referenced in it. Does not affect common blocks. (Some
810           Fortran compilers provide this option under the name -static or
811           -save.)  The default, which is -fautomatic, uses the stack for
812           local variables smaller than the value given by
813           -fmax-stack-var-size.  Use the option -frecursive to use no static
814           memory.
815
816       -ff2c
817           Generate code designed to be compatible with code generated by g77
818           and f2c.
819
820           The calling conventions used by g77 (originally implemented in f2c)
821           require functions that return type default "REAL" to actually
822           return the C type "double", and functions that return type
823           "COMPLEX" to return the values via an extra argument in the calling
824           sequence that points to where to store the return value.  Under the
825           default GNU calling conventions, such functions simply return their
826           results as they would in GNU C---default "REAL" functions return
827           the C type "float", and "COMPLEX" functions return the GNU C type
828           "complex".  Additionally, this option implies the
829           -fsecond-underscore option, unless -fno-second-underscore is
830           explicitly requested.
831
832           This does not affect the generation of code that interfaces with
833           the libgfortran library.
834
835           Caution: It is not a good idea to mix Fortran code compiled with
836           -ff2c with code compiled with the default -fno-f2c calling
837           conventions as, calling "COMPLEX" or default "REAL" functions
838           between program parts which were compiled with different calling
839           conventions will break at execution time.
840
841           Caution: This will break code which passes intrinsic functions of
842           type default "REAL" or "COMPLEX" as actual arguments, as the
843           library implementations use the -fno-f2c calling conventions.
844
845       -fno-underscoring
846           Do not transform names of entities specified in the Fortran source
847           file by appending underscores to them.
848
849           With -funderscoring in effect, GNU Fortran appends one underscore
850           to external names with no underscores.  This is done to ensure
851           compatibility with code produced by many UNIX Fortran compilers.
852
853           Caution: The default behavior of GNU Fortran is incompatible with
854           f2c and g77, please use the -ff2c option if you want object files
855           compiled with GNU Fortran to be compatible with object code created
856           with these tools.
857
858           Use of -fno-underscoring is not recommended unless you are
859           experimenting with issues such as integration of GNU Fortran into
860           existing system environments (vis-a-vis existing libraries, tools,
861           and so on).
862
863           For example, with -funderscoring, and assuming other defaults like
864           -fcase-lower and that "j()" and "max_count()" are external
865           functions while "my_var" and "lvar" are local variables, a
866           statement like
867
868                   I = J() + MAX_COUNT (MY_VAR, LVAR)
869
870           is implemented as something akin to:
871
872                   i = j_() + max_count__(&my_var__, &lvar);
873
874           With -fno-underscoring, the same statement is implemented as:
875
876                   i = j() + max_count(&my_var, &lvar);
877
878           Use of -fno-underscoring allows direct specification of user-
879           defined names while debugging and when interfacing GNU Fortran code
880           with other languages.
881
882           Note that just because the names match does not mean that the
883           interface implemented by GNU Fortran for an external name matches
884           the interface implemented by some other language for that same
885           name.  That is, getting code produced by GNU Fortran to link to
886           code produced by some other compiler using this or any other method
887           can be only a small part of the overall solution---getting the code
888           generated by both compilers to agree on issues other than naming
889           can require significant effort, and, unlike naming disagreements,
890           linkers normally cannot detect disagreements in these other areas.
891
892           Also, note that with -fno-underscoring, the lack of appended
893           underscores introduces the very real possibility that a user-
894           defined external name will conflict with a name in a system
895           library, which could make finding unresolved-reference bugs quite
896           difficult in some cases---they might occur at program run time, and
897           show up only as buggy behavior at run time.
898
899           In future versions of GNU Fortran we hope to improve naming and
900           linking issues so that debugging always involves using the names as
901           they appear in the source, even if the names as seen by the linker
902           are mangled to prevent accidental linking between procedures with
903           incompatible interfaces.
904
905       -fno-whole-file
906           This flag causes the compiler to resolve and translate each
907           procedure in a file separately.
908
909           By default, the whole file is parsed and placed in a single front-
910           end tree.  During resolution, in addition to all the usual checks
911           and fixups, references to external procedures that are in the same
912           file effect resolution of that procedure, if not already done, and
913           a check of the interfaces.  The dependences are resolved by
914           changing the order in which the file is translated into the backend
915           tree.  Thus, a procedure that is referenced is translated before
916           the reference and the duplication of backend tree declarations
917           eliminated.
918
919           The -fno-whole-file option is deprecated and may lead to wrong
920           code.
921
922       -fsecond-underscore
923           By default, GNU Fortran appends an underscore to external names.
924           If this option is used GNU Fortran appends two underscores to names
925           with underscores and one underscore to external names with no
926           underscores.  GNU Fortran also appends two underscores to internal
927           names with underscores to avoid naming collisions with external
928           names.
929
930           This option has no effect if -fno-underscoring is in effect.  It is
931           implied by the -ff2c option.
932
933           Otherwise, with this option, an external name such as "MAX_COUNT"
934           is implemented as a reference to the link-time external symbol
935           "max_count__", instead of "max_count_".  This is required for
936           compatibility with g77 and f2c, and is implied by use of the -ff2c
937           option.
938
939       -fcoarray=<keyword>
940           none
941               Disable coarray support; using coarray declarations and image-
942               control statements will produce a compile-time error. (Default)
943
944           single
945               Single-image mode, i.e. "num_images()" is always one.
946
947           lib Library-based coarray parallelization; a suitable GNU Fortran
948               coarray library needs to be linked.
949
950       -fcheck=<keyword>
951           Enable the generation of run-time checks; the argument shall be a
952           comma-delimited list of the following keywords.
953
954           all Enable all run-time test of -fcheck.
955
956           array-temps
957               Warns at run time when for passing an actual argument a
958               temporary array had to be generated. The information generated
959               by this warning is sometimes useful in optimization, in order
960               to avoid such temporaries.
961
962               Note: The warning is only printed once per location.
963
964           bounds
965               Enable generation of run-time checks for array subscripts and
966               against the declared minimum and maximum values.  It also
967               checks array indices for assumed and deferred shape arrays
968               against the actual allocated bounds and ensures that all string
969               lengths are equal for character array constructors without an
970               explicit typespec.
971
972               Some checks require that -fcheck=bounds is set for the
973               compilation of the main program.
974
975               Note: In the future this may also include other forms of
976               checking, e.g., checking substring references.
977
978           do  Enable generation of run-time checks for invalid modification
979               of loop iteration variables.
980
981           mem Enable generation of run-time checks for memory allocation.
982               Note: This option does not affect explicit allocations using
983               the "ALLOCATE" statement, which will be always checked.
984
985           pointer
986               Enable generation of run-time checks for pointers and
987               allocatables.
988
989           recursion
990               Enable generation of run-time checks for recursively called
991               subroutines and functions which are not marked as recursive.
992               See also -frecursive.  Note: This check does not work for
993               OpenMP programs and is disabled if used together with
994               -frecursive and -fopenmp.
995
996       -fbounds-check
997           Deprecated alias for -fcheck=bounds.
998
999       -fcheck-array-temporaries
1000           Deprecated alias for -fcheck=array-temps.
1001
1002       -fmax-array-constructor=n
1003           This option can be used to increase the upper limit permitted in
1004           array constructors.  The code below requires this option to expand
1005           the array at compile time.
1006
1007                   program test
1008                   implicit none
1009                   integer j
1010                   integer, parameter :: n = 100000
1011                   integer, parameter :: i(n) = (/ (2*j, j = 1, n) /)
1012                   print '(10(I0,1X))', i
1013                   end program test
1014
1015           Caution:  This option can lead to long compile times and
1016           excessively large object files.
1017
1018           The default value for n is 65535.
1019
1020       -fmax-stack-var-size=n
1021           This option specifies the size in bytes of the largest array that
1022           will be put on the stack; if the size is exceeded static memory is
1023           used (except in procedures marked as RECURSIVE). Use the option
1024           -frecursive to allow for recursive procedures which do not have a
1025           RECURSIVE attribute or for parallel programs. Use -fno-automatic to
1026           never use the stack.
1027
1028           This option currently only affects local arrays declared with
1029           constant bounds, and may not apply to all character variables.
1030           Future versions of GNU Fortran may improve this behavior.
1031
1032           The default value for n is 32768.
1033
1034       -fstack-arrays
1035           Adding this option will make the Fortran compiler put all local
1036           arrays, even those of unknown size onto stack memory.  If your
1037           program uses very large local arrays it is possible that you will
1038           have to extend your runtime limits for stack memory on some
1039           operating systems. This flag is enabled by default at optimization
1040           level -Ofast.
1041
1042       -fpack-derived
1043           This option tells GNU Fortran to pack derived type members as
1044           closely as possible.  Code compiled with this option is likely to
1045           be incompatible with code compiled without this option, and may
1046           execute slower.
1047
1048       -frepack-arrays
1049           In some circumstances GNU Fortran may pass assumed shape array
1050           sections via a descriptor describing a noncontiguous area of
1051           memory.  This option adds code to the function prologue to repack
1052           the data into a contiguous block at runtime.
1053
1054           This should result in faster accesses to the array.  However it can
1055           introduce significant overhead to the function call, especially
1056           when the passed data is noncontiguous.
1057
1058       -fshort-enums
1059           This option is provided for interoperability with C code that was
1060           compiled with the -fshort-enums option.  It will make GNU Fortran
1061           choose the smallest "INTEGER" kind a given enumerator set will fit
1062           in, and give all its enumerators this kind.
1063
1064       -fexternal-blas
1065           This option will make gfortran generate calls to BLAS functions for
1066           some matrix operations like "MATMUL", instead of using our own
1067           algorithms, if the size of the matrices involved is larger than a
1068           given limit (see -fblas-matmul-limit).  This may be profitable if
1069           an optimized vendor BLAS library is available.  The BLAS library
1070           will have to be specified at link time.
1071
1072       -fblas-matmul-limit=n
1073           Only significant when -fexternal-blas is in effect.  Matrix
1074           multiplication of matrices with size larger than (or equal to) n
1075           will be performed by calls to BLAS functions, while others will be
1076           handled by gfortran internal algorithms. If the matrices involved
1077           are not square, the size comparison is performed using the
1078           geometric mean of the dimensions of the argument and result
1079           matrices.
1080
1081           The default value for n is 30.
1082
1083       -frecursive
1084           Allow indirect recursion by forcing all local arrays to be
1085           allocated on the stack. This flag cannot be used together with
1086           -fmax-stack-var-size= or -fno-automatic.
1087
1088       -finit-local-zero
1089       -finit-integer=n
1090       -finit-real=<zero|inf|-inf|nan|snan>
1091       -finit-logical=<true|false>
1092       -finit-character=n
1093           The -finit-local-zero option instructs the compiler to initialize
1094           local "INTEGER", "REAL", and "COMPLEX" variables to zero, "LOGICAL"
1095           variables to false, and "CHARACTER" variables to a string of null
1096           bytes.  Finer-grained initialization options are provided by the
1097           -finit-integer=n, -finit-real=<zero|inf|-inf|nan|snan> (which also
1098           initializes the real and imaginary parts of local "COMPLEX"
1099           variables), -finit-logical=<true|false>, and -finit-character=n
1100           (where n is an ASCII character value) options.  These options do
1101           not initialize
1102
1103           ·   allocatable arrays
1104
1105           ·   components of derived type variables
1106
1107           ·   variables that appear in an "EQUIVALENCE" statement.
1108
1109           (These limitations may be removed in future releases).
1110
1111           Note that the -finit-real=nan option initializes "REAL" and
1112           "COMPLEX" variables with a quiet NaN. For a signalling NaN use
1113           -finit-real=snan; note, however, that compile-time optimizations
1114           may convert them into quiet NaN and that trapping needs to be
1115           enabled (e.g. via -ffpe-trap).
1116
1117           Finally, note that enabling any of the -finit-* options will
1118           silence warnings that would have been emitted by -Wuninitialized
1119           for the affected local variables.
1120
1121       -falign-commons
1122           By default, gfortran enforces proper alignment of all variables in
1123           a "COMMON" block by padding them as needed. On certain platforms
1124           this is mandatory, on others it increases performance. If a
1125           "COMMON" block is not declared with consistent data types
1126           everywhere, this padding can cause trouble, and -fno-align-commons
1127           can be used to disable automatic alignment. The same form of this
1128           option should be used for all files that share a "COMMON" block.
1129           To avoid potential alignment issues in "COMMON" blocks, it is
1130           recommended to order objects from largest to smallest.
1131
1132       -fno-protect-parens
1133           By default the parentheses in expression are honored for all
1134           optimization levels such that the compiler does not do any re-
1135           association. Using -fno-protect-parens allows the compiler to
1136           reorder "REAL" and "COMPLEX" expressions to produce faster code.
1137           Note that for the re-association optimization -fno-signed-zeros and
1138           -fno-trapping-math need to be in effect. The parentheses protection
1139           is enabled by default, unless -Ofast is given.
1140
1141       -frealloc-lhs
1142           An allocatable left-hand side of an intrinsic assignment is
1143           automatically (re)allocated if it is either unallocated or has a
1144           different shape. The option is enabled by default except when
1145           -std=f95 is given. See also -Wrealloc-lhs.
1146
1147       -faggressive-function-elimination
1148           Functions with identical argument lists are eliminated within
1149           statements, regardless of whether these functions are marked "PURE"
1150           or not. For example, in
1151
1152                     a = f(b,c) + f(b,c)
1153
1154           there will only be a single call to "f".  This option only works if
1155           -ffrontend-optimize is in effect.
1156
1157       -ffrontend-optimize
1158           This option performs front-end optimization, based on manipulating
1159           parts the Fortran parse tree.  Enabled by default by any -O option.
1160           Optimizations enabled by this option include elimination of
1161           identical function calls within expressions, removing unnecessary
1162           calls to "TRIM" in comparisons and assignments and replacing
1163           TRIM(a) with "a(1:LEN_TRIM(a))".  It can be deselected by
1164           specifying -fno-frontend-optimize.
1165

ENVIRONMENT

1167       The gfortran compiler currently does not make use of any environment
1168       variables to control its operation above and beyond those that affect
1169       the operation of gcc.
1170

BUGS

1172       For instructions on reporting bugs, see
1173       <http://bugzilla.redhat.com/bugzilla>.
1174

SEE ALSO

1176       gpl(7), gfdl(7), fsf-funding(7), cpp(1), gcov(1), gcc(1), as(1), ld(1),
1177       gdb(1), adb(1), dbx(1), sdb(1) and the Info entries for gcc, cpp,
1178       gfortran, as, ld, binutils and gdb.
1179

AUTHOR

1181       See the Info entry for gfortran for contributors to GCC and GNU
1182       Fortran.
1183
1185       Copyright (c) 2004-2013 Free Software Foundation, Inc.
1186
1187       Permission is granted to copy, distribute and/or modify this document
1188       under the terms of the GNU Free Documentation License, Version 1.3 or
1189       any later version published by the Free Software Foundation; with the
1190       Invariant Sections being "Funding Free Software", the Front-Cover Texts
1191       being (a) (see below), and with the Back-Cover Texts being (b) (see
1192       below).  A copy of the license is included in the gfdl(7) man page.
1193
1194       (a) The FSF's Front-Cover Text is:
1195
1196            A GNU Manual
1197
1198       (b) The FSF's Back-Cover Text is:
1199
1200            You have freedom to copy and modify this GNU Manual, like GNU
1201            software.  Copies published by the Free Software Foundation raise
1202            funds for GNU development.
1203
1204
1205
1206gcc-4.8.5                         2015-06-23                       GFORTRAN(1)
Impressum