1G77(1)                                GNU                               G77(1)
2
3
4

NAME

6       g77 - GNU project Fortran 77 compiler
7

SYNOPSIS

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

DESCRIPTION

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

OPTIONS

33       Here is a summary of all the options specific to GNU Fortran, grouped
34       by type.  Explanations are in the following sections.
35
36       Overall Options
37           -fversion  -fset-g77-defaults  -fno-silent
38
39       Shorthand Options
40           -ff66  -fno-f66  -ff77  -fno-f77  -fno-ugly
41
42       Fortran Language Options
43           -ffree-form  -fno-fixed-form  -ff90 -fvxt  -fdollar-ok  -fno-back‐
44           slash -fno-ugly-args  -fno-ugly-assign  -fno-ugly-assumed
45           -fugly-comma  -fugly-complex  -fugly-init  -fugly-logint -fonetrip
46           -ftypeless-boz -fintrin-case-initcap  -fintrin-case-upper -fin‐
47           trin-case-lower  -fintrin-case-any -fmatch-case-initcap
48           -fmatch-case-upper -fmatch-case-lower  -fmatch-case-any
49           -fsource-case-upper  -fsource-case-lower -fsource-case-preserve
50           -fsymbol-case-initcap  -fsymbol-case-upper -fsymbol-case-lower
51           -fsymbol-case-any -fcase-strict-upper  -fcase-strict-lower
52           -fcase-initcap  -fcase-upper  -fcase-lower  -fcase-preserve
53           -ff2c-intrinsics-delete  -ff2c-intrinsics-hide -ff2c-intrin‐
54           sics-disable  -ff2c-intrinsics-enable -fbadu77-intrinsics-delete
55           -fbadu77-intrinsics-hide -fbadu77-intrinsics-disable
56           -fbadu77-intrinsics-enable -ff90-intrinsics-delete  -ff90-intrin‐
57           sics-hide -ff90-intrinsics-disable  -ff90-intrinsics-enable
58           -fgnu-intrinsics-delete  -fgnu-intrinsics-hide -fgnu-intrin‐
59           sics-disable  -fgnu-intrinsics-enable -fmil-intrinsics-delete
60           -fmil-intrinsics-hide -fmil-intrinsics-disable  -fmil-intrin‐
61           sics-enable -funix-intrinsics-delete  -funix-intrinsics-hide
62           -funix-intrinsics-disable  -funix-intrinsics-enable -fvxt-intrin‐
63           sics-delete  -fvxt-intrinsics-hide -fvxt-intrinsics-disable
64           -fvxt-intrinsics-enable -ffixed-line-length-n
65           -ffixed-line-length-none
66
67       Warning Options
68           -fsyntax-only  -pedantic  -pedantic-errors  -fpedantic -w
69           -Wno-globals  -Wimplicit  -Wunused  -Wuninitialized -Wall  -Wsur‐
70           prising -Werror  -W
71
72       Debugging Options
73           -g
74
75       Optimization Options
76           -malign-double -ffloat-store  -fforce-mem  -fforce-addr
77           -fno-inline -ffast-math  -fstrength-reduce  -frerun-cse-after-loop
78           -funsafe-math-optimizations -ffinite-math-only -fno-trapping-math
79           -fexpensive-optimizations  -fdelayed-branch -fschedule-insns
80           -fschedule-insn2  -fcaller-saves -funroll-loops  -funroll-all-loops
81           -fno-move-all-movables  -fno-reduce-all-givs -fno-rerun-loop-opt
82
83       Directory Options
84           -Idir  -I-
85
86       Code Generation Options
87           -fno-automatic  -finit-local-zero  -fno-f2c -ff2c-library
88           -fno-underscoring  -fno-ident -fpcc-struct-return
89           -freg-struct-return -fshort-double  -fno-common  -fpack-struct
90           -fzeros  -fno-second-underscore -femulate-complex -falias-check
91           -fargument-alias -fargument-noalias  -fno-argument-noalias-global
92           -fno-globals  -fflatten-arrays -fbounds-check  -ffor‐
93           tran-bounds-check
94
95       Compilation can involve as many as four stages: preprocessing, code
96       generation (often what is really meant by the term ``compilation''),
97       assembly, and linking, always in that order.  The first three stages
98       apply to an individual source file, and end by producing an object
99       file; linking combines all the object files (those newly compiled, and
100       those specified as input) into an executable file.
101
102       For any given input file, the file name suffix determines what kind of
103       program is contained in the file---that is, the language in which the
104       program is written is generally indicated by the suffix.  Suffixes spe‐
105       cific to GNU Fortran are listed below.
106
107       file.f
108       file.for
109       file.FOR
110           Fortran source code that should not be preprocessed.
111
112           Such source code cannot contain any preprocessor directives, such
113           as "#include", "#define", "#if", and so on.
114
115           You can force .f files to be preprocessed by cpp by using -x
116           f77-cpp-input.
117
118       file.F
119       file.fpp
120       file.FPP
121           Fortran source code that must be preprocessed (by the C preproces‐
122           sor cpp, which is part of GCC).
123
124           Note that preprocessing is not extended to the contents of files
125           included by the "INCLUDE" directive---the "#include" preprocessor
126           directive must be used instead.
127
128       file.r
129           Ratfor source code, which must be preprocessed by the ratfor com‐
130           mand, which is available separately (as it is not yet part of the
131           GNU Fortran distribution).  A public domain version in C is at
132           <http://sepwww.stanford.edu/sep/prof/ratfor.shar.2>.
133
134       UNIX users typically use the file.f and file.F nomenclature.  Users of
135       other operating systems, especially those that cannot distinguish
136       upper-case letters from lower-case letters in their file names, typi‐
137       cally use the file.for and file.fpp nomenclature.
138
139       Use of the preprocessor cpp allows use of C-like constructs such as
140       "#define" and "#include", but can lead to unexpected, even mistaken,
141       results due to Fortran's source file format.  It is recommended that
142       use of the C preprocessor be limited to "#include" and, in conjunction
143       with "#define", only "#if" and related directives, thus avoiding in-
144       line macro expansion entirely.  This recommendation applies especially
145       when using the traditional fixed source form.  With free source form,
146       fewer unexpected transformations are likely to happen, but use of con‐
147       structs such as Hollerith and character constants can nevertheless
148       present problems, especially when these are continued across multiple
149       source lines.  These problems result, primarily, from differences
150       between the way such constants are interpreted by the C preprocessor
151       and by a Fortran compiler.
152
153       Another example of a problem that results from using the C preprocessor
154       is that a Fortran comment line that happens to contain any characters
155       ``interesting'' to the C preprocessor, such as a backslash at the end
156       of the line, is not recognized by the preprocessor as a comment line,
157       so instead of being passed through ``raw'', the line is edited accord‐
158       ing to the rules for the preprocessor.  For example, the backslash at
159       the end of the line is removed, along with the subsequent newline,
160       resulting in the next line being effectively commented out---unfortu‐
161       nate if that line is a non-comment line of important code!
162
163       Note: The -traditional and -undef flags are supplied to cpp by default,
164       to help avoid unpleasant surprises.
165
166       This means that ANSI C preprocessor features (such as the # operator)
167       aren't available, and only variables in the C reserved namespace (gen‐
168       erally, names with a leading underscore) are liable to substitution by
169       C predefines.  Thus, if you want to do system-specific tests, use, for
170       example, #ifdef __linux__ rather than #ifdef linux.  Use the -v option
171       to see exactly how the preprocessor is invoked.
172
173       Unfortunately, the -traditional flag will not avoid an error from any‐
174       thing that cpp sees as an unterminated C comment, such as:
175
176               C Some Fortran compilers accept /* as starting
177               C an inline comment.
178
179       The following options that affect overall processing are recognized by
180       the g77 and gcc commands in a GNU Fortran installation:
181
182       -fversion
183           Ensure that the g77 version of the compiler phase is reported, if
184           run, and, starting in "egcs" version 1.1, that internal consistency
185           checks in the f771 program are run.
186
187           This option is supplied automatically when -v or --verbose is spec‐
188           ified as a command-line option for g77 or gcc and when the result‐
189           ing commands compile Fortran source files.
190
191           In GCC 3.1, this is changed back to the behavior gcc displays for
192           .c files.
193
194       -fset-g77-defaults
195           Version info: This option was obsolete as of "egcs" version 1.1.
196           The effect is instead achieved by the "lang_init_options" routine
197           in gcc/gcc/f/com.c.
198
199           Set up whatever gcc options are to apply to Fortran compilations,
200           and avoid running internal consistency checks that might take some
201           time.
202
203           This option is supplied automatically when compiling Fortran code
204           via the g77 or gcc command.  The description of this option is pro‐
205           vided so that users seeing it in the output of, say, g77 -v under‐
206           stand why it is there.
207
208           Also, developers who run "f771" directly might want to specify it
209           by hand to get the same defaults as they would running "f771" via
210           g77 or gcc However, such developers should, after linking a new
211           "f771" executable, invoke it without this option once, e.g. via
212           "./f771 -quiet < /dev/null", to ensure that they have not intro‐
213           duced any internal inconsistencies (such as in the table of intrin‐
214           sics) before proceeding---g77 will crash with a diagnostic if it
215           detects an inconsistency.
216
217       -fno-silent
218           Print (to "stderr") the names of the program units as they are com‐
219           piled, in a form similar to that used by popular UNIX f77 implemen‐
220           tations and f2c
221
222       Shorthand Options
223
224       The following options serve as ``shorthand'' for other options accepted
225       by the compiler:
226
227       -fugly
228           Note: This option is no longer supported.  The information, below,
229           is provided to aid in the conversion of old scripts.
230
231           Specify that certain ``ugly'' constructs are to be quietly
232           accepted.  Same as:
233
234                   -fugly-args -fugly-assign -fugly-assumed
235                   -fugly-comma -fugly-complex -fugly-init
236                   -fugly-logint
237
238           These constructs are considered inappropriate to use in new or
239           well-maintained portable Fortran code, but widely used in old code.
240
241       -fno-ugly
242           Specify that all ``ugly'' constructs are to be noisily rejected.
243           Same as:
244
245                   -fno-ugly-args -fno-ugly-assign -fno-ugly-assumed
246                   -fno-ugly-comma -fno-ugly-complex -fno-ugly-init
247                   -fno-ugly-logint
248
249       -ff66
250           Specify that the program is written in idiomatic FORTRAN 66.  Same
251           as -fonetrip -fugly-assumed.
252
253           The -fno-f66 option is the inverse of -ff66.  As such, it is the
254           same as -fno-onetrip -fno-ugly-assumed.
255
256           The meaning of this option is likely to be refined as future ver‐
257           sions of g77 provide more compatibility with other existing and
258           obsolete Fortran implementations.
259
260       -ff77
261           Specify that the program is written in idiomatic UNIX FORTRAN 77
262           and/or the dialect accepted by the f2c product.  Same as -fback‐
263           slash -fno-typeless-boz.
264
265           The meaning of this option is likely to be refined as future ver‐
266           sions of g77 provide more compatibility with other existing and
267           obsolete Fortran implementations.
268
269       -fno-f77
270           The -fno-f77 option is not the inverse of -ff77.  It specifies that
271           the program is not written in idiomatic UNIX FORTRAN 77 or f2c but
272           in a more widely portable dialect.  -fno-f77 is the same as
273           -fno-backslash.
274
275           The meaning of this option is likely to be refined as future ver‐
276           sions of g77 provide more compatibility with other existing and
277           obsolete Fortran implementations.
278
279       Options Controlling Fortran Dialect
280
281       The following options control the dialect of Fortran that the compiler
282       accepts:
283
284       -ffree-form
285       -fno-fixed-form
286           Specify that the source file is written in free form (introduced in
287           Fortran 90) instead of the more-traditional fixed form.
288
289       -ff90
290           Allow certain Fortran-90 constructs.
291
292           This option controls whether certain Fortran 90 constructs are rec‐
293           ognized.  (Other Fortran 90 constructs might or might not be recog‐
294           nized depending on other options such as -fvxt, -ff90-intrin‐
295           sics-enable, and the current level of support for Fortran 90.)
296
297       -fvxt
298           Specify the treatment of certain constructs that have different
299           meanings depending on whether the code is written in GNU Fortran
300           (based on FORTRAN 77 and akin to Fortran 90) or VXT Fortran (more
301           like VAX FORTRAN).
302
303           The default is -fno-vxt.  -fvxt specifies that the VXT Fortran
304           interpretations for those constructs are to be chosen.
305
306       -fdollar-ok
307           Allow $ as a valid character in a symbol name.
308
309       -fno-backslash
310           Specify that \ is not to be specially interpreted in character and
311           Hollerith constants a la C and many UNIX Fortran compilers.
312
313           For example, with -fbackslash in effect, A\nB specifies three char‐
314           acters, with the second one being newline.  With -fno-backslash, it
315           specifies four characters, A, \, n, and B.
316
317           Note that g77 implements a fairly general form of backslash pro‐
318           cessing that is incompatible with the narrower forms supported by
319           some other compilers.  For example, 'A\003B' is a three-character
320           string in g77 whereas other compilers that support backslash might
321           not support the three-octal-digit form, and thus treat that string
322           as longer than three characters.
323
324       -fno-ugly-args
325           Disallow passing Hollerith and typeless constants as actual argu‐
326           ments (for example, CALL FOO(4HABCD)).
327
328       -fugly-assign
329           Use the same storage for a given variable regardless of whether it
330           is used to hold an assigned-statement label (as in ASSIGN 10 TO I)
331           or used to hold numeric data (as in I = 3).
332
333       -fugly-assumed
334           Assume any dummy array with a final dimension specified as 1 is
335           really an assumed-size array, as if * had been specified for the
336           final dimension instead of 1.
337
338           For example, DIMENSION X(1) is treated as if it had read DIMENSION
339           X(*).
340
341       -fugly-comma
342           In an external-procedure invocation, treat a trailing comma in the
343           argument list as specification of a trailing null argument, and
344           treat an empty argument list as specification of a single null
345           argument.
346
347           For example, CALL FOO(,) is treated as CALL FOO(%VAL(0), %VAL(0)).
348           That is, two null arguments are specified by the procedure call
349           when -fugly-comma is in force.  And F = FUNC() is treated as F =
350           FUNC(%VAL(0)).
351
352           The default behavior, -fno-ugly-comma, is to ignore a single trail‐
353           ing comma in an argument list.  So, by default, CALL FOO(X,) is
354           treated exactly the same as CALL FOO(X).
355
356       -fugly-complex
357           Do not complain about REAL(expr) or AIMAG(expr) when expr is a
358           "COMPLEX" type other than "COMPLEX(KIND=1)"---usually this is used
359           to permit "COMPLEX(KIND=2)" ("DOUBLE COMPLEX") operands.
360
361           The -ff90 option controls the interpretation of this construct.
362
363       -fno-ugly-init
364           Disallow use of Hollerith and typeless constants as initial values
365           (in "PARAMETER" and "DATA" statements), and use of character con‐
366           stants to initialize numeric types and vice versa.
367
368           For example, DATA I/'F'/, CHRVAR/65/, J/4HABCD/ is disallowed by
369           -fno-ugly-init.
370
371       -fugly-logint
372           Treat "INTEGER" and "LOGICAL" variables and expressions as poten‐
373           tial stand-ins for each other.
374
375           For example, automatic conversion between "INTEGER" and "LOGICAL"
376           is enabled, for many contexts, via this option.
377
378       -fonetrip
379           Executable iterative "DO" loops are to be executed at least once
380           each time they are reached.
381
382           ANSI FORTRAN 77 and more recent versions of the Fortran standard
383           specify that the body of an iterative "DO" loop is not executed if
384           the number of iterations calculated from the parameters of the loop
385           is less than 1.  (For example, DO 10 I = 1, 0.)  Such a loop is
386           called a zero-trip loop.
387
388           Prior to ANSI FORTRAN 77, many compilers implemented "DO" loops
389           such that the body of a loop would be executed at least once, even
390           if the iteration count was zero.  Fortran code written assuming
391           this behavior is said to require one-trip loops.  For example, some
392           code written to the FORTRAN 66 standard expects this behavior from
393           its "DO" loops, although that standard did not specify this behav‐
394           ior.
395
396           The -fonetrip option specifies that the source file(s) being com‐
397           piled require one-trip loops.
398
399           This option affects only those loops specified by the (iterative)
400           "DO" statement and by implied-"DO" lists in I/O statements.  Loops
401           specified by implied-"DO" lists in "DATA" and specification
402           (non-executable) statements are not affected.
403
404       -ftypeless-boz
405           Specifies that prefix-radix non-decimal constants, such as Z'ABCD',
406           are typeless instead of "INTEGER(KIND=1)".
407
408           You can test for yourself whether a particular compiler treats the
409           prefix form as "INTEGER(KIND=1)" or typeless by running the follow‐
410           ing program:
411
412                   EQUIVALENCE (I, R)
413                   R = Z'ABCD1234'
414                   J = Z'ABCD1234'
415                   IF (J .EQ. I) PRINT *, 'Prefix form is TYPELESS'
416                   IF (J .NE. I) PRINT *, 'Prefix form is INTEGER'
417                   END
418
419           Reports indicate that many compilers process this form as "INTE‐
420           GER(KIND=1)", though a few as typeless, and at least one based on a
421           command-line option specifying some kind of compatibility.
422
423       -fintrin-case-initcap
424       -fintrin-case-upper
425       -fintrin-case-lower
426       -fintrin-case-any
427           Specify expected case for intrinsic names.  -fintrin-case-lower is
428           the default.
429
430       -fmatch-case-initcap
431       -fmatch-case-upper
432       -fmatch-case-lower
433       -fmatch-case-any
434           Specify expected case for keywords.  -fmatch-case-lower is the
435           default.
436
437       -fsource-case-upper
438       -fsource-case-lower
439       -fsource-case-preserve
440           Specify whether source text other than character and Hollerith con‐
441           stants is to be translated to uppercase, to lowercase, or preserved
442           as is.  -fsource-case-lower is the default.
443
444       -fsymbol-case-initcap
445       -fsymbol-case-upper
446       -fsymbol-case-lower
447       -fsymbol-case-any
448           Specify valid cases for user-defined symbol names.  -fsym‐
449           bol-case-any is the default.
450
451       -fcase-strict-upper
452           Same as -fintrin-case-upper -fmatch-case-upper -fsource-case-pre‐
453           serve -fsymbol-case-upper.  (Requires all pertinent source to be in
454           uppercase.)
455
456       -fcase-strict-lower
457           Same as -fintrin-case-lower -fmatch-case-lower -fsource-case-pre‐
458           serve -fsymbol-case-lower.  (Requires all pertinent source to be in
459           lowercase.)
460
461       -fcase-initcap
462           Same as -fintrin-case-initcap -fmatch-case-initcap
463           -fsource-case-preserve -fsymbol-case-initcap.  (Requires all perti‐
464           nent source to be in initial capitals, as in Print *,SqRt(Value).)
465
466       -fcase-upper
467           Same as -fintrin-case-any -fmatch-case-any -fsource-case-upper
468           -fsymbol-case-any.  (Maps all pertinent source to uppercase.)
469
470       -fcase-lower
471           Same as -fintrin-case-any -fmatch-case-any -fsource-case-lower
472           -fsymbol-case-any.  (Maps all pertinent source to lowercase.)
473
474       -fcase-preserve
475           Same as -fintrin-case-any -fmatch-case-any -fsource-case-preserve
476           -fsymbol-case-any.  (Preserves all case in user-defined symbols,
477           while allowing any-case matching of intrinsics and keywords.  For
478           example, call Foo(i,I) would pass two different variables named i
479           and I to a procedure named Foo.)
480
481       -fbadu77-intrinsics-delete
482       -fbadu77-intrinsics-hide
483       -fbadu77-intrinsics-disable
484       -fbadu77-intrinsics-enable
485           Specify status of UNIX intrinsics having inappropriate forms.
486           -fbadu77-intrinsics-enable is the default.
487
488       -ff2c-intrinsics-delete
489       -ff2c-intrinsics-hide
490       -ff2c-intrinsics-disable
491       -ff2c-intrinsics-enable
492           Specify status of f2c-specific intrinsics.  -ff2c-intrinsics-enable
493           is the default.
494
495       -ff90-intrinsics-delete
496       -ff90-intrinsics-hide
497       -ff90-intrinsics-disable
498       -ff90-intrinsics-enable
499           Specify status of F90-specific intrinsics.  -ff90-intrinsics-enable
500           is the default.
501
502       -fgnu-intrinsics-delete
503       -fgnu-intrinsics-hide
504       -fgnu-intrinsics-disable
505       -fgnu-intrinsics-enable
506           Specify status of Digital's COMPLEX-related intrinsics.
507           -fgnu-intrinsics-enable is the default.
508
509       -fmil-intrinsics-delete
510       -fmil-intrinsics-hide
511       -fmil-intrinsics-disable
512       -fmil-intrinsics-enable
513           Specify status of MIL-STD-1753-specific intrinsics.  -fmil-intrin‐
514           sics-enable is the default.
515
516       -funix-intrinsics-delete
517       -funix-intrinsics-hide
518       -funix-intrinsics-disable
519       -funix-intrinsics-enable
520           Specify status of UNIX intrinsics.  -funix-intrinsics-enable is the
521           default.
522
523       -fvxt-intrinsics-delete
524       -fvxt-intrinsics-hide
525       -fvxt-intrinsics-disable
526       -fvxt-intrinsics-enable
527           Specify status of VXT intrinsics.  -fvxt-intrinsics-enable is the
528           default.
529
530       -ffixed-line-length-n
531           Set column after which characters are ignored in typical fixed-form
532           lines in the source file, and through which spaces are assumed (as
533           if padded to that length) after the ends of short fixed-form lines.
534
535           Popular values for n include 72 (the standard and the default), 80
536           (card image), and 132 (corresponds to ``extended-source'' options
537           in some popular compilers).  n may be none, meaning that the entire
538           line is meaningful and that continued character constants never
539           have implicit spaces appended to them to fill out the line.
540           -ffixed-line-length-0 means the same thing as
541           -ffixed-line-length-none.
542
543       Options to Request or Suppress Warnings
544
545       Warnings are diagnostic messages that report constructions which are
546       not inherently erroneous but which are risky or suggest there might
547       have been an error.
548
549       You can request many specific warnings with options beginning -W, for
550       example -Wimplicit to request warnings on implicit declarations.  Each
551       of these specific warning options also has a negative form beginning
552       -Wno- to turn off warnings; for example, -Wno-implicit.  This manual
553       lists only one of the two forms, whichever is not the default.
554
555       These options control the amount and kinds of warnings produced by GNU
556       Fortran:
557
558       -fsyntax-only
559           Check the code for syntax errors, but don't do anything beyond
560           that.
561
562       -pedantic
563           Issue warnings for uses of extensions to ANSI FORTRAN 77.  -pedan‐
564           tic also applies to C-language constructs where they occur in GNU
565           Fortran source files, such as use of \e in a character constant
566           within a directive like #include.
567
568           Valid ANSI FORTRAN 77 programs should compile properly with or
569           without this option.  However, without this option, certain GNU
570           extensions and traditional Fortran features are supported as well.
571           With this option, many of them are rejected.
572
573           Some users try to use -pedantic to check programs for strict ANSI
574           conformance.  They soon find that it does not do quite what they
575           want---it finds some non-ANSI practices, but not all.  However,
576           improvements to g77 in this area are welcome.
577
578       -pedantic-errors
579           Like -pedantic, except that errors are produced rather than warn‐
580           ings.
581
582       -fpedantic
583           Like -pedantic, but applies only to Fortran constructs.
584
585       -w  Inhibit all warning messages.
586
587       -Wno-globals
588           Inhibit warnings about use of a name as both a global name (a sub‐
589           routine, function, or block data program unit, or a common block)
590           and implicitly as the name of an intrinsic in a source file.
591
592           Also inhibit warnings about inconsistent invocations and/or defini‐
593           tions of global procedures (function and subroutines).  Such incon‐
594           sistencies include different numbers of arguments and different
595           types of arguments.
596
597       -Wimplicit
598           Warn whenever a variable, array, or function is implicitly
599           declared.  Has an effect similar to using the "IMPLICIT NONE"
600           statement in every program unit.  (Some Fortran compilers provide
601           this feature by an option named -u or /WARNINGS=DECLARATIONS.)
602
603       -Wunused
604           Warn whenever a variable is unused aside from its declaration.
605
606       -Wuninitialized
607           Warn whenever an automatic variable is used without first being
608           initialized.
609
610           These warnings are possible only in optimizing compilation, because
611           they require data-flow information that is computed only when opti‐
612           mizing.  If you don't specify -O, you simply won't get these warn‐
613           ings.
614
615           These warnings occur only for variables that are candidates for
616           register allocation.  Therefore, they do not occur for a variable
617           whose address is taken, or whose size is other than 1, 2, 4 or 8
618           bytes.  Also, they do not occur for arrays, even when they are in
619           registers.
620
621           Note that there might be no warning about a variable that is used
622           only to compute a value that itself is never used, because such
623           computations may be deleted by data-flow analysis before the warn‐
624           ings are printed.
625
626           These warnings are made optional because GNU Fortran is not smart
627           enough to see all the reasons why the code might be correct despite
628           appearing to have an error.  Here is one example of how this can
629           happen:
630
631                   SUBROUTINE DISPAT(J)
632                   IF (J.EQ.1) I=1
633                   IF (J.EQ.2) I=4
634                   IF (J.EQ.3) I=5
635                   CALL FOO(I)
636                   END
637
638           If the value of "J" is always 1, 2 or 3, then "I" is always ini‐
639           tialized, but GNU Fortran doesn't know this.  Here is another com‐
640           mon case:
641
642                   SUBROUTINE MAYBE(FLAG)
643                   LOGICAL FLAG
644                   IF (FLAG) VALUE = 9.4
645                   ...
646                   IF (FLAG) PRINT *, VALUE
647                   END
648
649           This has no bug because "VALUE" is used only if it is set.
650
651       -Wall
652           The -Wunused and -Wuninitialized options combined.  These are all
653           the options which pertain to usage that we recommend avoiding and
654           that we believe is easy to avoid.  (As more warnings are added to
655           g77 some might be added to the list enabled by -Wall.)
656
657       The remaining -W... options are not implied by -Wall because they warn
658       about constructions that we consider reasonable to use, on occasion, in
659       clean programs.
660
661       -Wsurprising
662           Warn about ``suspicious'' constructs that are interpreted by the
663           compiler in a way that might well be surprising to someone reading
664           the code.  These differences can result in subtle, compiler-depen‐
665           dent (even machine-dependent) behavioral differences.  The con‐
666           structs warned about include:
667
668           *   Expressions having two arithmetic operators in a row, such as
669               X*-Y.  Such a construct is nonstandard, and can produce unex‐
670               pected results in more complicated situations such as X**-Y*Z.
671               g77 along with many other compilers, interprets this example
672               differently than many programmers, and a few other compilers.
673               Specifically, g77 interprets X**-Y*Z as (X**(-Y))*Z, while oth‐
674               ers might think it should be interpreted as X**(-(Y*Z)).
675
676               A revealing example is the constant expression 2**-2*1., which
677               g77 evaluates to .25, while others might evaluate it to 0., the
678               difference resulting from the way precedence affects type pro‐
679               motion.
680
681               (The -fpedantic option also warns about expressions having two
682               arithmetic operators in a row.)
683
684           *   Expressions with a unary minus followed by an operand and then
685               a binary operator other than plus or minus.  For example, -2**2
686               produces a warning, because the precedence is -(2**2), yielding
687               -4, not (-2)**2, which yields 4, and which might represent what
688               a programmer expects.
689
690               An example of an expression producing different results in a
691               surprising way is -I*S, where I holds the value -2147483648 and
692               S holds 0.5.  On many systems, negating I results in the same
693               value, not a positive number, because it is already the lower
694               bound of what an "INTEGER(KIND=1)" variable can hold.  So, the
695               expression evaluates to a positive number, while the
696               ``expected'' interpretation, (-I)*S, would evaluate to a nega‐
697               tive number.
698
699               Even cases such as -I*J produce warnings, even though, in most
700               configurations and situations, there is no computational dif‐
701               ference between the results of the two interpretations---the
702               purpose of this warning is to warn about differing interpreta‐
703               tions and encourage a better style of coding, not to identify
704               only those places where bugs might exist in the user's code.
705
706           *   "DO" loops with "DO" variables that are not of integral
707               type---that is, using "REAL" variables as loop control vari‐
708               ables.  Although such loops can be written to work in the
709               ``obvious'' way, the way g77 is required by the Fortran stan‐
710               dard to interpret such code is likely to be quite different
711               from the way many programmers expect.  (This is true of all
712               "DO" loops, but the differences are pronounced for non-integral
713               loop control variables.)
714
715       -Werror
716           Make all warnings into errors.
717
718       -W  Turns on ``extra warnings'' and, if optimization is specified via
719           -O, the -Wuninitialized option.  (This might change in future ver‐
720           sions of g77
721
722           ``Extra warnings'' are issued for:
723
724           *   Unused parameters to a procedure (when -Wunused also is speci‐
725               fied).
726
727           *   Overflows involving floating-point constants (not available for
728               certain configurations).
729
730       Some of these have no effect when compiling programs written in For‐
731       tran:
732
733       -Wcomment
734       -Wformat
735       -Wparentheses
736       -Wswitch
737       -Wswitch-default
738       -Wswitch-enum
739       -Wtraditional
740       -Wshadow
741       -Wid-clash-len
742       -Wlarger-than-len
743       -Wconversion
744       -Waggregate-return
745       -Wredundant-decls
746           These options all could have some relevant meaning for GNU Fortran
747           programs, but are not yet supported.
748
749       Options for Debugging Your Program or GNU Fortran
750
751       GNU Fortran has various special options that are used for debugging
752       either your program or g77
753
754       -g  Produce debugging information in the operating system's native for‐
755           mat (stabs, COFF, XCOFF, or DWARF).  GDB can work with this debug‐
756           ging information.
757
758           A sample debugging session looks like this (note the use of the
759           breakpoint):
760
761                   $ cat gdb.f
762                         PROGRAM PROG
763                         DIMENSION A(10)
764                         DATA A /1.,2.,3.,4.,5.,6.,7.,8.,9.,10./
765                         A(5) = 4.
766                         PRINT*,A
767                         END
768                   $ g77 -g -O gdb.f
769                   $ gdb a.out
770                   ...
771                   (gdb) break MAIN__
772                   Breakpoint 1 at 0x8048e96: file gdb.f, line 4.
773                   (gdb) run
774                   Starting program: /home/toon/g77-bugs/./a.out
775                   Breakpoint 1, MAIN__ () at gdb.f:4
776                   4             A(5) = 4.
777                   Current language:  auto; currently fortran
778                   (gdb) print a(5)
779                   $1 = 5
780                   (gdb) step
781                   5             PRINT*,A
782                   (gdb) print a(5)
783                   $2 = 4
784                   ...
785
786           One could also add the setting of the breakpoint and the first run
787           command to the file .gdbinit in the current directory, to simplify
788           the debugging session.
789
790       Options That Control Optimization
791
792       Most Fortran users will want to use no optimization when developing and
793       testing programs, and use -O or -O2 when compiling programs for late-
794       cycle testing and for production use.  However, note that certain diag‐
795       nostics---such as for uninitialized variables---depend on the flow
796       analysis done by -O, i.e. you must use -O or -O2 to get such diagnos‐
797       tics.
798
799       The following flags have particular applicability when compiling For‐
800       tran programs:
801
802       -malign-double
803           (Intel x86 architecture only.)
804
805           Noticeably improves performance of g77 programs making heavy use of
806           "REAL(KIND=2)" ("DOUBLE PRECISION") data on some systems.  In par‐
807           ticular, systems using Pentium, Pentium Pro, 586, and 686 implemen‐
808           tations of the i386 architecture execute programs faster when
809           "REAL(KIND=2)" ("DOUBLE PRECISION") data are aligned on 64-bit
810           boundaries in memory.
811
812           This option can, at least, make benchmark results more consistent
813           across various system configurations, versions of the program, and
814           data sets.
815
816           Note: The warning in the gcc documentation about this option does
817           not apply, generally speaking, to Fortran code compiled by g77
818
819           Also also note: The negative form of -malign-double is
820           -mno-align-double, not -benign-double.
821
822       -ffloat-store
823           Might help a Fortran program that depends on exact IEEE conformance
824           on some machines, but might slow down a program that doesn't.
825
826           This option is effective when the floating-point unit is set to
827           work in IEEE 854 `extended precision'---as it typically is on x86
828           and m68k GNU systems---rather than IEEE 754 double precision.
829           -ffloat-store tries to remove the extra precision by spilling data
830           from floating-point registers into memory and this typically
831           involves a big performance hit.  However, it doesn't affect inter‐
832           mediate results, so that it is only partially effective.  `Excess
833           precision' is avoided in code like:
834
835                   a = b + c
836                   d = a * e
837
838           but not in code like:
839
840                         d = (b + c) * e
841
842           For another, potentially better, way of controlling the precision,
843           see Floating-point precision.
844
845       -fforce-mem
846       -fforce-addr
847           Might improve optimization of loops.
848
849       -fno-inline
850           Don't compile statement functions inline.  Might reduce the size of
851           a program unit---which might be at expense of some speed (though it
852           should compile faster).  Note that if you are not optimizing, no
853           functions can be expanded inline.
854
855       -ffast-math
856           Might allow some programs designed to not be too dependent on IEEE
857           behavior for floating-point to run faster, or die trying.  Sets
858           -funsafe-math-optimizations, -ffinite-math-only, and -fno-trap‐
859           ping-math.
860
861       -funsafe-math-optimizations
862           Allow optimizations that may be give incorrect results for certain
863           IEEE inputs.
864
865       -ffinite-math-only
866           Allow optimizations for floating-point arithmetic that assume that
867           arguments and results are not NaNs or +-Infs.
868
869           This option should never be turned on by any -O option since it can
870           result in incorrect output for programs which depend on an exact
871           implementation of IEEE or ISO rules/specifications.
872
873           The default is -fno-finite-math-only.
874
875       -fno-trapping-math
876           Allow the compiler to assume that floating-point arithmetic will
877           not generate traps on any inputs.  This is useful, for example,
878           when running a program using IEEE "non-stop" floating-point arith‐
879           metic.
880
881       -fstrength-reduce
882           Might make some loops run faster.
883
884       -frerun-cse-after-loop
885       -fexpensive-optimizations
886       -fdelayed-branch
887       -fschedule-insns
888       -fschedule-insns2
889       -fcaller-saves
890           Might improve performance on some code.
891
892       -funroll-loops
893           Typically improves performance on code using iterative "DO" loops
894           by unrolling them and is probably generally appropriate for For‐
895           tran, though it is not turned on at any optimization level.  Note
896           that outer loop unrolling isn't done specifically; decisions about
897           whether to unroll a loop are made on the basis of its instruction
898           count.
899
900           Also, no `loop discovery'[1] is done, so only loops written with
901           "DO" benefit from loop optimizations, including---but not limited
902           to---unrolling.  Loops written with "IF" and "GOTO" are not cur‐
903           rently recognized as such.  This option unrolls only iterative "DO"
904           loops, not "DO WHILE" loops.
905
906       -funroll-all-loops
907           Probably improves performance on code using "DO WHILE" loops by
908           unrolling them in addition to iterative "DO" loops.  In the absence
909           of "DO WHILE", this option is equivalent to -funroll-loops but pos‐
910           sibly slower.
911
912       -fno-move-all-movables
913       -fno-reduce-all-givs
914       -fno-rerun-loop-opt
915           In general, the optimizations enabled with these options will lead
916           to faster code being generated by GNU Fortran; hence they are
917           enabled by default when issuing the g77 command.
918
919           -fmove-all-movables and -freduce-all-givs will enable loop opti‐
920           mization to move all loop-invariant index computations in nested
921           loops over multi-rank array dummy arguments out of these loops.
922
923           -frerun-loop-opt will move offset calculations resulting from the
924           fact that Fortran arrays by default have a lower bound of 1 out of
925           the loops.
926
927           These three options are intended to be removed someday, once loop
928           optimization is sufficiently advanced to perform all those trans‐
929           formations without help from these options.
930
931       Options Controlling the Preprocessor
932
933       These options control the C preprocessor, which is run on each C source
934       file before actual compilation.
935
936       Some of these options also affect how g77 processes the "INCLUDE"
937       directive.  Since this directive is processed even when preprocessing
938       is not requested, it is not described in this section.
939
940       However, the "INCLUDE" directive does not apply preprocessing to the
941       contents of the included file itself.
942
943       Therefore, any file that contains preprocessor directives (such as
944       "#include", "#define", and "#if") must be included via the "#include"
945       directive, not via the "INCLUDE" directive.  Therefore, any file con‐
946       taining preprocessor directives, if included, is necessarily included
947       by a file that itself contains preprocessor directives.
948
949       Options for Directory Search
950
951       These options affect how the cpp preprocessor searches for files speci‐
952       fied via the "#include" directive.  Therefore, when compiling Fortran
953       programs, they are meaningful when the preprocessor is used.
954
955       Some of these options also affect how g77 searches for files specified
956       via the "INCLUDE" directive, although files included by that directive
957       are not, themselves, preprocessed.  These options are:
958
959       -I-
960       -Idir
961           These affect interpretation of the "INCLUDE" directive (as well as
962           of the "#include" directive of the cpp preprocessor).
963
964           Note that -Idir must be specified without any spaces between -I and
965           the directory name---that is, -Ifoo/bar is valid, but -I foo/bar is
966           rejected by the g77 compiler (though the preprocessor supports the
967           latter form).  Also note that the general behavior of -I and
968           "INCLUDE" is pretty much the same as of -I with "#include" in the
969           cpp preprocessor, with regard to looking for header.gcc files and
970           other such things.
971
972       Options for Code Generation Conventions
973
974       These machine-independent options control the interface conventions
975       used in code generation.
976
977       Most of them have both positive and negative forms; the negative form
978       of -ffoo would be -fno-foo.  In the table below, only one of the forms
979       is listed---the one which is not the default.  You can figure out the
980       other form by either removing no- or adding it.
981
982       -fno-automatic
983           Treat each program unit as if the "SAVE" statement was specified
984           for every local variable and array referenced in it.  Does not
985           affect common blocks.  (Some Fortran compilers provide this option
986           under the name -static.)
987
988       -finit-local-zero
989           Specify that variables and arrays that are local to a program unit
990           (not in a common block and not passed as an argument) are to be
991           initialized to binary zeros.
992
993           Since there is a run-time penalty for initialization of variables
994           that are not given the "SAVE" attribute, it might be a good idea to
995           also use -fno-automatic with -finit-local-zero.
996
997       -fno-f2c
998           Do not generate code designed to be compatible with code generated
999           by f2c use the GNU calling conventions instead.
1000
1001           The f2c calling conventions require functions that return type
1002           "REAL(KIND=1)" to actually return the C type "double", and func‐
1003           tions that return type "COMPLEX" to return the values via an extra
1004           argument in the calling sequence that points to where to store the
1005           return value.  Under the GNU calling conventions, such functions
1006           simply return their results as they would in GNU C---"REAL(KIND=1)"
1007           functions return the C type "float", and "COMPLEX" functions return
1008           the GNU C type "complex" (or its "struct" equivalent).
1009
1010           This does not affect the generation of code that interfaces with
1011           the "libg2c" library.
1012
1013           However, because the "libg2c" library uses f2c calling conventions,
1014           g77 rejects attempts to pass intrinsics implemented by routines in
1015           this library as actual arguments when -fno-f2c is used, to avoid
1016           bugs when they are actually called by code expecting the GNU call‐
1017           ing conventions to work.
1018
1019           For example, INTRINSIC ABS;CALL FOO(ABS) is rejected when -fno-f2c
1020           is in force.  (Future versions of the g77 run-time library might
1021           offer routines that provide GNU-callable versions of the routines
1022           that implement the f2c intrinsics that may be passed as actual
1023           arguments, so that valid programs need not be rejected when
1024           -fno-f2c is used.)
1025
1026           Caution: If -fno-f2c is used when compiling any source file used in
1027           a program, it must be used when compiling all Fortran source files
1028           used in that program.
1029
1030       -ff2c-library
1031           Specify that use of "libg2c" (or the original "libf2c") is
1032           required.  This is the default for the current version of g77
1033
1034           Currently it is not valid to specify -fno-f2c-library.  This option
1035           is provided so users can specify it in shell scripts that build
1036           programs and libraries that require the "libf2c" library, even when
1037           being compiled by future versions of g77 that might otherwise
1038           default to generating code for an incompatible library.
1039
1040       -fno-underscoring
1041           Do not transform names of entities specified in the Fortran source
1042           file by appending underscores to them.
1043
1044           With -funderscoring in effect, g77 appends two underscores to names
1045           with underscores and one underscore to external names with no
1046           underscores.  (g77 also appends two underscores to internal names
1047           with underscores to avoid naming collisions with external names.
1048           The -fno-second-underscore option disables appending of the second
1049           underscore in all cases.)
1050
1051           This is done to ensure compatibility with code produced by many
1052           UNIX Fortran compilers, including f2c which perform the same trans‐
1053           formations.
1054
1055           Use of -fno-underscoring is not recommended unless you are experi‐
1056           menting with issues such as integration of (GNU) Fortran into
1057           existing system environments (vis-a-vis existing libraries, tools,
1058           and so on).
1059
1060           For example, with -funderscoring, and assuming other defaults like
1061           -fcase-lower and that j() and max_count() are external functions
1062           while my_var and lvar are local variables, a statement like
1063
1064                   I = J() + MAX_COUNT (MY_VAR, LVAR)
1065
1066           is implemented as something akin to:
1067
1068                   i = j_() + max_count__(&my_var__, &lvar);
1069
1070           With -fno-underscoring, the same statement is implemented as:
1071
1072                   i = j() + max_count(&my_var, &lvar);
1073
1074           Use of -fno-underscoring allows direct specification of user-
1075           defined names while debugging and when interfacing g77 code with
1076           other languages.
1077
1078           Note that just because the names match does not mean that the
1079           interface implemented by g77 for an external name matches the
1080           interface implemented by some other language for that same name.
1081           That is, getting code produced by g77 to link to code produced by
1082           some other compiler using this or any other method can be only a
1083           small part of the overall solution---getting the code generated by
1084           both compilers to agree on issues other than naming can require
1085           significant effort, and, unlike naming disagreements, linkers nor‐
1086           mally cannot detect disagreements in these other areas.
1087
1088           Also, note that with -fno-underscoring, the lack of appended under‐
1089           scores introduces the very real possibility that a user-defined
1090           external name will conflict with a name in a system library, which
1091           could make finding unresolved-reference bugs quite difficult in
1092           some cases---they might occur at program run time, and show up only
1093           as buggy behavior at run time.
1094
1095           In future versions of g77 we hope to improve naming and linking
1096           issues so that debugging always involves using the names as they
1097           appear in the source, even if the names as seen by the linker are
1098           mangled to prevent accidental linking between procedures with
1099           incompatible interfaces.
1100
1101       -fno-second-underscore
1102           Do not append a second underscore to names of entities specified in
1103           the Fortran source file.
1104
1105           This option has no effect if -fno-underscoring is in effect.
1106
1107           Otherwise, with this option, an external name such as MAX_COUNT is
1108           implemented as a reference to the link-time external symbol
1109           max_count_, instead of max_count__.
1110
1111       -fno-ident
1112           Ignore the #ident directive.
1113
1114       -fzeros
1115           Treat initial values of zero as if they were any other value.
1116
1117           As of version 0.5.18, g77 normally treats "DATA" and other state‐
1118           ments that are used to specify initial values of zero for variables
1119           and arrays as if no values were actually specified, in the sense
1120           that no diagnostics regarding multiple initializations are pro‐
1121           duced.
1122
1123           This is done to speed up compiling of programs that initialize
1124           large arrays to zeros.
1125
1126           Use -fzeros to revert to the simpler, slower behavior that can
1127           catch multiple initializations by keeping track of all initializa‐
1128           tions, zero or otherwise.
1129
1130           Caution: Future versions of g77 might disregard this option (and
1131           its negative form, the default) or interpret it somewhat differ‐
1132           ently.  The interpretation changes will affect only non-standard
1133           programs; standard-conforming programs should not be affected.
1134
1135       -femulate-complex
1136           Implement "COMPLEX" arithmetic via emulation, instead of using the
1137           facilities of the gcc back end that provide direct support of "com‐
1138           plex" arithmetic.
1139
1140           (gcc had some bugs in its back-end support for "complex" arith‐
1141           metic, due primarily to the support not being completed as of ver‐
1142           sion 2.8.1 and "egcs" 1.1.2.)
1143
1144           Use -femulate-complex if you suspect code-generation bugs, or expe‐
1145           rience compiler crashes, that might result from g77 using the "COM‐
1146           PLEX" support in the gcc back end.  If using that option fixes the
1147           bugs or crashes you are seeing, that indicates a likely g77 bugs
1148           (though, all compiler crashes are considered bugs), so, please
1149           report it.  (Note that the known bugs, now believed fixed, produced
1150           compiler crashes rather than causing the generation of incorrect
1151           code.)
1152
1153           Use of this option should not affect how Fortran code compiled by
1154           g77 works in terms of its interfaces to other code, e.g. that com‐
1155           piled by f2c
1156
1157           As of GCC version 3.0, this option is not necessary anymore.
1158
1159           Caution: Future versions of g77 might ignore both forms of this
1160           option.
1161
1162       -falias-check
1163       -fargument-alias
1164       -fargument-noalias
1165       -fno-argument-noalias-global
1166           Version info: These options are not supported by versions of g77
1167           based on gcc version 2.8.
1168
1169           These options specify to what degree aliasing (overlap) is permit‐
1170           ted between arguments (passed as pointers) and "COMMON" (external,
1171           or public) storage.
1172
1173           The default for Fortran code, as mandated by the FORTRAN 77 and
1174           Fortran 90 standards, is -fargument-noalias-global.  The default
1175           for code written in the C language family is -fargument-alias.
1176
1177           Note that, on some systems, compiling with -fforce-addr in effect
1178           can produce more optimal code when the default aliasing options are
1179           in effect (and when optimization is enabled).
1180
1181       -fno-globals
1182           Disable diagnostics about inter-procedural analysis problems, such
1183           as disagreements about the type of a function or a procedure's
1184           argument, that might cause a compiler crash when attempting to
1185           inline a reference to a procedure within a program unit.  (The
1186           diagnostics themselves are still produced, but as warnings, unless
1187           -Wno-globals is specified, in which case no relevant diagnostics
1188           are produced.)
1189
1190           Further, this option disables such inlining, to avoid compiler
1191           crashes resulting from incorrect code that would otherwise be diag‐
1192           nosed.
1193
1194           As such, this option might be quite useful when compiling existing,
1195           ``working'' code that happens to have a few bugs that do not gener‐
1196           ally show themselves, but which g77 diagnoses.
1197
1198           Use of this option therefore has the effect of instructing g77 to
1199           behave more like it did up through version 0.5.19.1, when it paid
1200           little or no attention to disagreements between program units about
1201           a procedure's type and argument information, and when it performed
1202           no inlining of procedures (except statement functions).
1203
1204           Without this option, g77 defaults to performing the potentially
1205           inlining procedures as it started doing in version 0.5.20, but as
1206           of version 0.5.21, it also diagnoses disagreements that might cause
1207           such inlining to crash the compiler as (fatal) errors, and warns
1208           about similar disagreements that are currently believed to not
1209           likely to result in the compiler later crashing or producing incor‐
1210           rect code.
1211
1212       -fflatten-arrays
1213           Use back end's C-like constructs (pointer plus offset) instead of
1214           its "ARRAY_REF" construct to handle all array references.
1215
1216           Note: This option is not supported.  It is intended for use only by
1217           g77 developers, to evaluate code-generation issues.  It might be
1218           removed at any time.
1219
1220       -fbounds-check
1221       -ffortran-bounds-check
1222           Enable generation of run-time checks for array subscripts and sub‐
1223           string start and end points against the (locally) declared minimum
1224           and maximum values.
1225
1226           The current implementation uses the "libf2c" library routine
1227           "s_rnge" to print the diagnostic.
1228
1229           However, whereas f2c generates a single check per reference for a
1230           multi-dimensional array, of the computed offset against the valid
1231           offset range (0 through the size of the array), g77 generates a
1232           single check per subscript expression.  This catches some cases of
1233           potential bugs that f2c does not, such as references to below the
1234           beginning of an assumed-size array.
1235
1236           g77 also generates checks for "CHARACTER" substring references,
1237           something f2c currently does not do.
1238
1239           Use the new -ffortran-bounds-check option to specify bounds-check‐
1240           ing for only the Fortran code you are compiling, not necessarily
1241           for code written in other languages.
1242
1243           Note: To provide more detailed information on the offending sub‐
1244           script, g77 provides the "libg2c" run-time library routine "s_rnge"
1245           with somewhat differently-formatted information.  Here's a sample
1246           diagnostic:
1247
1248                   Subscript out of range on file line 4, procedure rnge.f/bf.
1249                   Attempt to access the -6-th element of variable b[subscript-2-of-2].
1250                   Aborted
1251
1252           The above message indicates that the offending source line is line
1253           4 of the file rnge.f, within the program unit (or statement func‐
1254           tion) named bf.  The offended array is named b.  The offended array
1255           dimension is the second for a two-dimensional array, and the
1256           offending, computed subscript expression was -6.
1257
1258           For a "CHARACTER" substring reference, the second line has this
1259           appearance:
1260
1261                   Attempt to access the 11-th element of variable a[start-substring].
1262
1263           This indicates that the offended "CHARACTER" variable or array is
1264           named a, the offended substring position is the starting (leftmost)
1265           position, and the offending substring expression is 11.
1266
1267           (Though the verbage of "s_rnge" is not ideal for the purpose of the
1268           g77 compiler, the above information should provide adequate diag‐
1269           nostic abilities to it users.)
1270
1271       Some of these do not work when compiling programs written in Fortran:
1272
1273       -fpcc-struct-return
1274       -freg-struct-return
1275           You should not use these except strictly the same way as you used
1276           them to build the version of "libg2c" with which you will be link‐
1277           ing all code compiled by g77 with the same option.
1278
1279       -fshort-double
1280           This probably either has no effect on Fortran programs, or makes
1281           them act loopy.
1282
1283       -fno-common
1284           Do not use this when compiling Fortran programs, or there will be
1285           Trouble.
1286
1287       -fpack-struct
1288           This probably will break any calls to the "libg2c" library, at the
1289           very least, even if it is built with the same option.
1290

ENVIRONMENT

1292       GNU Fortran currently does not make use of any environment variables to
1293       control its operation above and beyond those that affect the operation
1294       of gcc.
1295

BUGS

1297       For instructions on reporting bugs, see <http://gcc.gnu.org/bugs.html>.
1298       Use of the gccbug script to report bugs is recommended.
1299

FOOTNOTES

1301       1.  loop discovery refers to the process by which a compiler, or indeed
1302           any reader of a program, determines which portions of the program
1303           are more likely to be executed repeatedly as it is being run.  Such
1304           discovery typically is done early when compiling using optimization
1305           techniques, so the ``discovered'' loops get more attention---and
1306           more run-time resources, such as registers---from the compiler.  It
1307           is easy to ``discover'' loops that are constructed out of looping
1308           constructs in the language (such as Fortran's "DO").  For some pro‐
1309           grams, ``discovering'' loops constructed out of lower-level con‐
1310           structs (such as "IF" and "GOTO") can lead to generation of more
1311           optimal code than otherwise.
1312

SEE ALSO

1314       gpl(7), gfdl(7), fsf-funding(7), cpp(1), gcov(1), gcc(1), as(1), ld(1),
1315       gdb(1), adb(1), dbx(1), sdb(1) and the Info entries for gcc, cpp, g77,
1316       as, ld, binutils and gdb.
1317

AUTHOR

1319       See the Info entry for g77 for contributors to GCC and G77.
1320
1322       Copyright (c) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2004 Free Soft‐
1323       ware Foundation, Inc.
1324
1325       Permission is granted to copy, distribute and/or modify this document
1326       under the terms of the GNU Free Documentation License, Version 1.2 or
1327       any later version published by the Free Software Foundation; with the
1328       Invariant Sections being ``GNU General Public License'' and ``Funding
1329       Free Software'', the Front-Cover texts being (a) (see below), and with
1330       the Back-Cover Texts being (b) (see below).  A copy of the license is
1331       included in the gfdl(7) man page.
1332
1333       (a) The FSF's Front-Cover Text is:
1334
1335            A GNU Manual
1336
1337       (b) The FSF's Back-Cover Text is:
1338
1339            You have freedom to copy and modify this GNU Manual, like GNU
1340            software.  Copies published by the Free Software Foundation raise
1341            funds for GNU development.
1342
1343
1344
1345gcc-3.4.6                         2007-03-03                            G77(1)
Impressum